plutus-ledger-api-1.28.0.0: Interface to the Plutus ledger for the Cardano ledger.
Safe HaskellSafe-Inferred
LanguageHaskell2010

PlutusLedgerApi.V2.EvaluationContext

Synopsis

Documentation

data 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.

Different protocol versions may require different bundles of machine parameters, which allows us for example to tweak the shape of the costing function of a builtin, so that the builtin costs less. Currently this means that we have to create multiple DefaultMachineParameters per language version, which we put into a cache (represented by an association list) in order to avoid costly recomputation of machine parameters.

In order to get the appropriate DefaultMachineParameters at validation time we look it up in the cache using a semantics variant as a key. We compute the semantics variant from the protocol version using the stored function. Note that the semantics variant depends on the language version too, but the latter is known statically (because each language version has its own evaluation context), hence there's no reason to require it to be provided at runtime.

To say it differently, there's a matrix of semantics variants indexed by (LL, PV) pairs and we cache its particular row corresponding to the statically given LL in an EvaluationContext.

The reason why we associate a DefaultMachineParameters with a semantics variant rather than a protocol version are

  1. generally there are far more protocol versions than semantics variants supported by a specific language version, so we save on pointless duplication of bundles of machine parameters
  2. builtins don't know anything about protocol versions, only semantics variants. It is therefore more semantically precise to associate bundles of machine parameters with semantics variants than with protocol versions

Instances

Instances details
Generic EvaluationContext Source # 
Instance details

Defined in PlutusLedgerApi.Common.Eval

Associated Types

type Rep EvaluationContext :: Type -> Type Source #

NFData EvaluationContext Source # 
Instance details

Defined in PlutusLedgerApi.Common.Eval

Methods

rnf :: EvaluationContext -> () Source #

NoThunks EvaluationContext Source # 
Instance details

Defined in PlutusLedgerApi.Common.Eval

Methods

noThunks :: Context -> EvaluationContext -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> EvaluationContext -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy EvaluationContext -> String

type Rep EvaluationContext Source # 
Instance details

Defined in PlutusLedgerApi.Common.Eval

type Rep EvaluationContext = D1 ('MetaData "EvaluationContext" "PlutusLedgerApi.Common.Eval" "plutus-ledger-api-1.28.0.0-KyoQa0mVRQg8X358A39cIn" 'False) (C1 ('MetaCons "EvaluationContext" 'PrefixI 'True) (S1 ('MetaSel ('Just "_evalCtxLedgerLang") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PlutusLedgerLanguage) :*: (S1 ('MetaSel ('Just "_evalCtxToSemVar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (MajorProtocolVersion -> BuiltinSemanticsVariant DefaultFun)) :*: S1 ('MetaSel ('Just "_evalCtxMachParsCache") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [(BuiltinSemanticsVariant DefaultFun, DefaultMachineParameters)]))))

mkEvaluationContext Source #

Arguments

:: (MonadError CostModelApplyError m, MonadWriter [CostModelApplyWarn] m) 
=> [Int64]

the (updated) cost model parameters of the protocol

-> m EvaluationContext 

Build the EvaluationContext.

The input is a list of cost model parameters (which are integer values) passed from the ledger.

IMPORTANT: the cost model parameters MUST appear in the correct order, matching the names in ParamName. If the parameters are supplied in the wrong order then script cost calculations will be incorrect.

IMPORTANT: The evaluation context of every Plutus version must be recreated upon a protocol update with the updated cost model parameters.

type CostModelParams = Map Text Int64 #

data CostModelApplyError #

Instances

Instances details
Data CostModelApplyError 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CostModelApplyError -> c CostModelApplyError Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CostModelApplyError Source #

toConstr :: CostModelApplyError -> Constr Source #

dataTypeOf :: CostModelApplyError -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CostModelApplyError) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CostModelApplyError) Source #

gmapT :: (forall b. Data b => b -> b) -> CostModelApplyError -> CostModelApplyError Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CostModelApplyError -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CostModelApplyError -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> CostModelApplyError -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CostModelApplyError -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CostModelApplyError -> m CostModelApplyError Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CostModelApplyError -> m CostModelApplyError Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CostModelApplyError -> m CostModelApplyError Source #

Exception CostModelApplyError 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

Generic CostModelApplyError 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

Associated Types

type Rep CostModelApplyError :: Type -> Type Source #

Show CostModelApplyError 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

NFData CostModelApplyError 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

Eq CostModelApplyError 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

NoThunks CostModelApplyError 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

Methods

noThunks :: Context -> CostModelApplyError -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> CostModelApplyError -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy CostModelApplyError -> String

Pretty CostModelApplyError 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

Methods

pretty :: CostModelApplyError -> Doc ann

prettyList :: [CostModelApplyError] -> Doc ann

type Rep CostModelApplyError 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

type Rep CostModelApplyError = D1 ('MetaData "CostModelApplyError" "PlutusCore.Evaluation.Machine.CostModelInterface" "plutus-core-1.28.0.0-3U9ttQ2VSzq19dvt02pvJO" 'False) (C1 ('MetaCons "CMUnknownParamError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: (C1 ('MetaCons "CMInternalReadError" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CMInternalWriteError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String))))