Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
PlutusLedgerApi.Common
Description
The types and functions that are common among all ledger Plutus versions.
Synopsis
- type SerialisedScript = ShortByteString
- data ScriptForEvaluation
- serialisedScript :: ScriptForEvaluation -> SerialisedScript
- deserialisedScript :: ScriptForEvaluation -> ScriptNamedDeBruijn
- serialiseCompiledCode :: forall a. CompiledCode a -> SerialisedScript
- serialiseUPLC :: Program DeBruijn DefaultUni DefaultFun () -> SerialisedScript
- deserialiseScript :: forall m. MonadError ScriptDecodeError m => PlutusLedgerLanguage -> MajorProtocolVersion -> SerialisedScript -> m ScriptForEvaluation
- uncheckedDeserialiseUPLC :: SerialisedScript -> Program DeBruijn DefaultUni DefaultFun ()
- data ScriptDecodeError
- newtype ScriptNamedDeBruijn = ScriptNamedDeBruijn (Program NamedDeBruijn DefaultUni DefaultFun ())
- evaluateScriptCounting :: PlutusLedgerLanguage -> MajorProtocolVersion -> VerboseMode -> EvaluationContext -> ScriptForEvaluation -> [Data] -> (LogOutput, Either EvaluationError ExBudget)
- evaluateScriptRestricting :: PlutusLedgerLanguage -> MajorProtocolVersion -> VerboseMode -> EvaluationContext -> ExBudget -> ScriptForEvaluation -> [Data] -> (LogOutput, Either EvaluationError ExBudget)
- evaluateTerm :: ExBudgetMode cost DefaultUni DefaultFun -> MajorProtocolVersion -> VerboseMode -> EvaluationContext -> Term NamedDeBruijn DefaultUni DefaultFun () -> (Either (CekEvaluationException NamedDeBruijn DefaultUni DefaultFun) (Term NamedDeBruijn DefaultUni DefaultFun ()), cost, [Text])
- data VerboseMode
- type LogOutput = [Text]
- data EvaluationError
- = CekError !(CekEvaluationException NamedDeBruijn DefaultUni DefaultFun)
- | DeBruijnError !FreeVariableError
- | CodecError !ScriptDecodeError
- | CostModelParameterMismatch
- data Data
- data ExBudget = ExBudget {}
- newtype MajorProtocolVersion = MajorProtocolVersion {}
- data PlutusLedgerLanguage
- data Version = Version {}
- builtinsIntroducedIn :: Map (PlutusLedgerLanguage, MajorProtocolVersion) (Set DefaultFun)
- builtinsAvailableIn :: PlutusLedgerLanguage -> MajorProtocolVersion -> Set DefaultFun
- ledgerLanguageIntroducedIn :: PlutusLedgerLanguage -> MajorProtocolVersion
- ledgerLanguagesAvailableIn :: MajorProtocolVersion -> Set PlutusLedgerLanguage
- type CostModelParams = Map Text Integer
- toCostModelParams :: IsParamName p => [(p, Integer)] -> CostModelParams
- assertWellFormedCostModelParams :: MonadError CostModelApplyError m => CostModelParams -> m ()
- class (Enum a, Bounded a) => IsParamName a where
- showParamName :: a -> Text
- readParamName :: Text -> Maybe a
- data GenericParamName a
- data CostModelApplyError
- = CMUnknownParamError !Text
- | CMInternalReadError
- | CMInternalWriteError !String
- | CMTooFewParamsError {
- cmTooFewExpected :: !Int
- cmTooFewActual :: !Int
- data CostModelApplyWarn = CMTooManyParamsWarn {
- cmTooManyExpected :: !Int
- cmTooManyActual :: !Int
- newtype EvaluationContext = EvaluationContext {
- machineParameters :: DefaultMachineParameters
- mkDynEvaluationContext :: MonadError CostModelApplyError m => BuiltinSemanticsVariant DefaultFun -> CostModelParams -> m EvaluationContext
- toMachineParameters :: MajorProtocolVersion -> EvaluationContext -> DefaultMachineParameters
- mkTermToEvaluate :: MonadError EvaluationError m => PlutusLedgerLanguage -> MajorProtocolVersion -> ScriptForEvaluation -> [Data] -> m (Term NamedDeBruijn DefaultUni DefaultFun ())
Script (de)serialization
type SerialisedScript = ShortByteString Source #
Scripts to the ledger are serialised bytestrings.
data ScriptForEvaluation Source #
A Plutus script ready to be evaluated on-chain, via evaluateScriptRestricting
.
Instances
serialisedScript :: ScriptForEvaluation -> SerialisedScript Source #
Get a SerialisedScript
from a ScriptForEvaluation
. O(1).
deserialisedScript :: ScriptForEvaluation -> ScriptNamedDeBruijn Source #
Get a ScriptNamedDeBruijn
from a ScriptForEvaluation
. O(1).
serialiseCompiledCode :: forall a. CompiledCode a -> SerialisedScript Source #
Turns a program which was compiled using the 'PlutusTx' toolchain into a binary format that is understood by the network and can be stored on-chain.
serialiseUPLC :: Program DeBruijn DefaultUni DefaultFun () -> SerialisedScript Source #
Turns a program's AST (most likely manually constructed) into a binary format that is understood by the network and can be stored on-chain.
Arguments
:: forall m. MonadError ScriptDecodeError m | |
=> PlutusLedgerLanguage | the Plutus ledger language of the script. |
-> MajorProtocolVersion | which major protocol version the script was submitted in. |
-> SerialisedScript | the script to deserialise. |
-> m ScriptForEvaluation |
The deserialization from a serialised script into a ScriptForEvaluation
,
ready to be evaluated on-chain.
Called inside phase-1 validation (i.e., deserialisation error is a phase-1 error).
uncheckedDeserialiseUPLC :: SerialisedScript -> Program DeBruijn DefaultUni DefaultFun () Source #
Deserialises a SerialisedScript
back into an AST. Does *not* do
ledger-language-version-specific checks like for allowable builtins.
data ScriptDecodeError Source #
An error that occurred during script deserialization.
Constructors
CBORDeserialiseError !DeserialiseFailureInfo | an error from the underlying CBOR/serialise library |
RemainderError !ByteString | Script was successfully parsed, but more (runaway) bytes encountered after script's position |
LedgerLanguageNotAvailableError | the plutus version of the given script is not enabled yet |
Fields
| |
PlutusCoreLanguageNotAvailableError | |
Fields
|
Instances
Exception ScriptDecodeError Source # | |
Defined in PlutusLedgerApi.Common.SerialisedScript Methods toException :: ScriptDecodeError -> SomeException Source # fromException :: SomeException -> Maybe ScriptDecodeError Source # | |
Show ScriptDecodeError Source # | |
Defined in PlutusLedgerApi.Common.SerialisedScript | |
Eq ScriptDecodeError Source # | |
Defined in PlutusLedgerApi.Common.SerialisedScript Methods (==) :: ScriptDecodeError -> ScriptDecodeError -> Bool Source # (/=) :: ScriptDecodeError -> ScriptDecodeError -> Bool Source # |
newtype ScriptNamedDeBruijn Source #
A script with named de-bruijn indices.
Constructors
ScriptNamedDeBruijn (Program NamedDeBruijn DefaultUni DefaultFun ()) |
Instances
Script evaluation
evaluateScriptCounting Source #
Arguments
:: PlutusLedgerLanguage | The Plutus ledger language of the script under execution. |
-> MajorProtocolVersion | Which major 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 |
-> ScriptForEvaluation | The script to evaluate |
-> [Data] | The arguments to the script |
-> (LogOutput, Either EvaluationError ExBudget) |
Evaluates a script, returning the minimum budget that the script would need
to evaluate successfully. This will take as long as the script takes, if you need to
limit the execution time of the script also, you can use evaluateScriptRestricting
, which
also returns the used budget.
Note: Parameterized over the ledger-plutus-version since the builtins allowed (during decoding) differs.
evaluateScriptRestricting Source #
Arguments
:: PlutusLedgerLanguage | The Plutus ledger language of the script under execution. |
-> MajorProtocolVersion | Which major 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 |
-> ScriptForEvaluation | The script to evaluate |
-> [Data] | The arguments to the script |
-> (LogOutput, Either EvaluationError ExBudget) |
Evaluates a script, with a cost model and a budget that restricts how many resources it can use according to the cost model. Also returns the budget that was actually used.
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.
Note: Parameterized over the LedgerPlutusVersion
since
1. The builtins allowed (during decoding) differ, and
2. The Plutus language versions allowed differ.
evaluateTerm :: ExBudgetMode cost DefaultUni DefaultFun -> MajorProtocolVersion -> VerboseMode -> EvaluationContext -> Term NamedDeBruijn DefaultUni DefaultFun () -> (Either (CekEvaluationException NamedDeBruijn DefaultUni DefaultFun) (Term NamedDeBruijn DefaultUni DefaultFun ()), cost, [Text]) Source #
Evaluate a fully-applied term using the CEK machine. Useful for mimicking the behaviour of the on-chain evaluator.
data VerboseMode Source #
A simple toggle indicating whether or not we should accumulate logs during script execution.
Instances
Eq VerboseMode Source # | |
Defined in PlutusLedgerApi.Common.Eval Methods (==) :: VerboseMode -> VerboseMode -> Bool Source # (/=) :: VerboseMode -> VerboseMode -> Bool Source # |
type LogOutput = [Text] Source #
The type of the executed script's accumulated log output: a list of Text
.
It will be an empty list if the VerboseMode
is set to Quiet
.
data EvaluationError Source #
Errors that can be thrown when evaluating a Plutus script.
Constructors
CekError !(CekEvaluationException NamedDeBruijn DefaultUni DefaultFun) | An error from the evaluator itself |
DeBruijnError !FreeVariableError | An error in the pre-evaluation step of converting from de-Bruijn indices |
CodecError !ScriptDecodeError | A deserialisation error TODO: make this error more informative when we have more information about what went wrong |
CostModelParameterMismatch | An error indicating that the cost model parameters didn't match what we expected |
Instances
Show EvaluationError Source # | |
Defined in PlutusLedgerApi.Common.Eval | |
Eq EvaluationError Source # | |
Defined in PlutusLedgerApi.Common.Eval Methods (==) :: EvaluationError -> EvaluationError -> Bool Source # (/=) :: EvaluationError -> EvaluationError -> Bool Source # | |
Pretty EvaluationError Source # | |
Defined in PlutusLedgerApi.Common.Eval |
Instances
Data Data | |
Defined in PlutusCore.Data Methods gfoldl :: (forall d b. Data0 d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Data -> c Data Source # gunfold :: (forall b r. Data0 b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Data Source # toConstr :: Data -> Constr Source # dataTypeOf :: Data -> DataType Source # dataCast1 :: Typeable t => (forall d. Data0 d => c (t d)) -> Maybe (c Data) Source # dataCast2 :: Typeable t => (forall d e. (Data0 d, Data0 e) => c (t d e)) -> Maybe (c Data) Source # gmapT :: (forall b. Data0 b => b -> b) -> Data -> Data Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data0 d => d -> r') -> Data -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data0 d => d -> r') -> Data -> r Source # gmapQ :: (forall d. Data0 d => d -> u) -> Data -> [u] Source # gmapQi :: Int -> (forall d. Data0 d => d -> u) -> Data -> u Source # gmapM :: Monad m => (forall d. Data0 d => d -> m d) -> Data -> m Data Source # gmapMp :: MonadPlus m => (forall d. Data0 d => d -> m d) -> Data -> m Data Source # gmapMo :: MonadPlus m => (forall d. Data0 d => d -> m d) -> Data -> m Data Source # | |
Generic Data | |
Show Data | |
NFData Data | |
Defined in PlutusCore.Data | |
Eq Data | |
Ord Data | |
Hashable Data | |
Defined in PlutusCore.Data | |
NoThunks Data | |
Pretty Data | |
Defined in PlutusCore.Data | |
Serialise Data | |
Defined in PlutusCore.Data | |
PrettyBy ConstConfig Data | |
Defined in PlutusCore.Pretty.PrettyConst | |
KnownBuiltinTypeIn DefaultUni term Data => MakeKnownIn DefaultUni term Data | |
Defined in PlutusCore.Default.Universe | |
KnownBuiltinTypeIn DefaultUni term Data => ReadKnownIn DefaultUni term Data | |
Defined in PlutusCore.Default.Universe | |
Contains DefaultUni Data | |
Defined in PlutusCore.Default.Universe | |
KnownBuiltinTypeAst tyname DefaultUni Data => KnownTypeAst tyname DefaultUni Data | |
type Rep Data | |
Defined in PlutusCore.Data type Rep Data = D1 ('MetaData "Data" "PlutusCore.Data" "plutus-core-1.18.0.0-Bo1HApUitrK8tVw3GuwnrY" 'False) ((C1 ('MetaCons "Constr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Data])) :+: C1 ('MetaCons "Map" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Data, Data)]))) :+: (C1 ('MetaCons "List" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Data])) :+: (C1 ('MetaCons "I" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)) :+: C1 ('MetaCons "B" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))))) | |
type IsBuiltin DefaultUni Data | |
Defined in PlutusCore.Default.Universe | |
type ToHoles DefaultUni Data | |
Defined in PlutusCore.Default.Universe | |
type ToBinds DefaultUni acc Data | |
Defined in PlutusCore.Default.Universe |
Constructors
ExBudget | |
Fields |
Instances
Network's versioning
The network's behaviour (and plutus's by extension) can change via hard forks, which directly correspond to major-number protocol version bumps.
newtype MajorProtocolVersion Source #
This represents the major component of the Cardano protocol version. The ledger can only supply the major component of the protocol version, not the minor component, and Plutus should only need to care about the major component anyway. This relies on careful understanding between us and the ledger as to what this means.
Constructors
MajorProtocolVersion | |
Fields |
Instances
data PlutusLedgerLanguage Source #
The Plutus ledger language. These are entirely different script languages from the ledger's perspective, which on our side are interpreted in very similar ways.
It is a simple enumerated datatype (there is no major and minor components as in protocol version) and the ordering of constructors is essential for deriving Enum,Ord,Bounded.
IMPORTANT: this is different from the Plutus Core language version, Version
Instances
Constructors
Version | |
Fields |
Instances
Generic Version | |
Show Version | |
NFData Version | |
Defined in PlutusCore.Version | |
Eq Version | |
Ord Version | |
Defined in PlutusCore.Version | |
Hashable Version | |
Defined in PlutusCore.Version | |
Pretty Version | |
Defined in PlutusCore.Version | |
type Rep Version | |
Defined in PlutusCore.Version type Rep Version = D1 ('MetaData "Version" "PlutusCore.Version" "plutus-core-1.18.0.0-Bo1HApUitrK8tVw3GuwnrY" 'False) (C1 ('MetaCons "Version" 'PrefixI 'True) (S1 ('MetaSel ('Just "_versionMajor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural) :*: (S1 ('MetaSel ('Just "_versionMinor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural) :*: S1 ('MetaSel ('Just "_versionPatch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural)))) |
builtinsIntroducedIn :: Map (PlutusLedgerLanguage, MajorProtocolVersion) (Set DefaultFun) Source #
A map indicating which builtin functions were introduced in which MajorProtocolVersion
.
Each builtin function should appear at most once.
This must be updated when new builtins are added. See Note [New builtins/language versions and protocol versions]
builtinsAvailableIn :: PlutusLedgerLanguage -> MajorProtocolVersion -> Set DefaultFun Source #
Which builtin functions are available in the given given PlutusLedgerLanguage
and MajorProtocolVersion
?
See Note [New builtins/language versions and protocol versions]
ledgerLanguageIntroducedIn :: PlutusLedgerLanguage -> MajorProtocolVersion Source #
Query the protocol version that a specific Plutus ledger language was first introduced in.
ledgerLanguagesAvailableIn :: MajorProtocolVersion -> Set PlutusLedgerLanguage Source #
Which Plutus language versions are available in the given MajorProtocolVersion
?
See Note [New builtins/language versions and protocol versions]
Network's costing parameters
A less drastic approach (that does not rely on a HF) to affect the network's (and plutus's by extension) behaviour is by tweaking the values of the cost model parameters.
The network does not associate names to cost model parameters; Plutus attaches names to the network's cost model parameters (values) either in a raw textual form or typed by a specific plutus version.
See Note [Cost model parameters]
type CostModelParams = Map Text Integer #
toCostModelParams :: IsParamName p => [(p, Integer)] -> CostModelParams Source #
Untags the plutus version from the typed cost model parameters and returns their raw textual form (internally used by CostModelInterface).
assertWellFormedCostModelParams :: MonadError CostModelApplyError m => CostModelParams -> m () Source #
class (Enum a, Bounded a) => IsParamName a where Source #
A parameter name for different plutus versions.
Each Plutus version should expose such an enumeration as an ADT and create
an instance of ParamName
out of it.
A valid parameter name has to be enumeration, bounded, ordered, and prettyprintable to a "lower-Kebab" string.
Minimal complete definition
Methods
showParamName :: a -> Text Source #
Produce the raw textual form for a given typed-by-plutus-version cost model parameter
Any implementation *must be* an injective function.
The GIsParamName
generic implementation guarantees injectivity.
readParamName :: Text -> Maybe a Source #
default implementation that inverts the showParamName operation (not very efficient)
Instances
IsParamName ParamName Source # | |
Defined in PlutusLedgerApi.V1.ParamName | |
IsParamName ParamName Source # | |
Defined in PlutusLedgerApi.V2.ParamName | |
IsParamName ParamName Source # | |
Defined in PlutusLedgerApi.V3.ParamName | |
(Enum (GenericParamName a), Bounded (GenericParamName a), Generic a, GIsParamName (Rep a)) => IsParamName (GenericParamName a) Source # | |
Defined in PlutusLedgerApi.Common.ParamName Methods showParamName :: GenericParamName a -> Text Source # readParamName :: Text -> Maybe (GenericParamName a) Source # |
data GenericParamName a Source #
A Generic wrapper for use with deriving via
Instances
data CostModelApplyError #
Constructors
CMUnknownParamError !Text | |
CMInternalReadError | |
CMInternalWriteError !String | |
CMTooFewParamsError | |
Fields
|
Instances
data CostModelApplyWarn #
Constructors
CMTooManyParamsWarn | |
Fields
|
Instances
Pretty CostModelApplyWarn | |
Evaluation context
newtype EvaluationContext Source #
An opaque type that contains all the static parameters that the evaluator needs to evaluate a script. This is so that they can be computed once and cached, rather than being recomputed on every evaluation.
Constructors
EvaluationContext | |
Fields
|
Instances
Generic EvaluationContext Source # | |
Defined in PlutusLedgerApi.Common.Eval Methods from :: EvaluationContext -> Rep EvaluationContext x Source # to :: Rep EvaluationContext x -> EvaluationContext Source # | |
NFData EvaluationContext Source # | |
Defined in PlutusLedgerApi.Common.Eval Methods rnf :: EvaluationContext -> () Source # | |
NoThunks EvaluationContext Source # | |
Defined in PlutusLedgerApi.Common.Eval Methods noThunks :: Context -> EvaluationContext -> IO (Maybe ThunkInfo) wNoThunks :: Context -> EvaluationContext -> IO (Maybe ThunkInfo) | |
type Rep EvaluationContext Source # | |
Defined in PlutusLedgerApi.Common.Eval type Rep EvaluationContext = D1 ('MetaData "EvaluationContext" "PlutusLedgerApi.Common.Eval" "plutus-ledger-api-1.18.0.0-Arniy3OL4wy69RH7u4QMZP" 'True) (C1 ('MetaCons "EvaluationContext" 'PrefixI 'True) (S1 ('MetaSel ('Just "machineParameters") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DefaultMachineParameters))) |
mkDynEvaluationContext :: MonadError CostModelApplyError m => BuiltinSemanticsVariant DefaultFun -> CostModelParams -> m EvaluationContext Source #
Create an EvaluationContext
for a given builtin semantics variant.
The input is a Map
of Text
s to cost integer values (aka CostModelParams
, CostModel
)
See Note [Inlining meanings of builtins].
IMPORTANT: The evaluation context of every Plutus version must be recreated upon a protocol update with the updated cost model parameters.
toMachineParameters :: MajorProtocolVersion -> EvaluationContext -> DefaultMachineParameters Source #
Arguments
:: MonadError EvaluationError m | |
=> PlutusLedgerLanguage | the Plutus ledger language of the script under execution. |
-> MajorProtocolVersion | which major protocol version to run the operation in |
-> ScriptForEvaluation | the script to evaluate |
-> [Data] | the arguments that the script's underlying term will be applied to |
-> m (Term NamedDeBruijn DefaultUni DefaultFun ()) |
Shared helper for the evaluation functions: evaluateScriptCounting
and evaluateScriptRestricting
,
Given a ScriptForEvaluation
:
1) applies the term to a list of Data
arguments (e.g. Datum, Redeemer, ScriptContext
)
2) checks that the applied-term is well-scoped
3) returns the applied-term