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

PlutusLedgerApi.Common

Description

The types and functions that are common among all ledger Plutus versions.

Synopsis

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

Instances details
Generic ScriptForEvaluation Source # 
Instance details

Defined in PlutusLedgerApi.Common.SerialisedScript

Associated Types

type Rep ScriptForEvaluation :: Type -> Type Source #

Show ScriptForEvaluation Source # 
Instance details

Defined in PlutusLedgerApi.Common.SerialisedScript

NFData ScriptForEvaluation Source # 
Instance details

Defined in PlutusLedgerApi.Common.SerialisedScript

Eq ScriptForEvaluation Source # 
Instance details

Defined in PlutusLedgerApi.Common.SerialisedScript

NoThunks ScriptForEvaluation Source # 
Instance details

Defined in PlutusLedgerApi.Common.SerialisedScript

Methods

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

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

showTypeOf :: Proxy ScriptForEvaluation -> String

type Rep ScriptForEvaluation Source # 
Instance details

Defined in PlutusLedgerApi.Common.SerialisedScript

type Rep ScriptForEvaluation = D1 ('MetaData "ScriptForEvaluation" "PlutusLedgerApi.Common.SerialisedScript" "plutus-ledger-api-1.18.0.0-Arniy3OL4wy69RH7u4QMZP" 'False) (C1 ('MetaCons "UnsafeScriptForEvaluation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SerialisedScript) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ScriptNamedDeBruijn)))

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.

deserialiseScript Source #

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

newtype ScriptNamedDeBruijn Source #

A script with named de-bruijn indices.

Constructors

ScriptNamedDeBruijn (Program NamedDeBruijn DefaultUni DefaultFun ()) 

Instances

Instances details
Generic ScriptNamedDeBruijn Source # 
Instance details

Defined in PlutusLedgerApi.Common.SerialisedScript

Associated Types

type Rep ScriptNamedDeBruijn :: Type -> Type Source #

Show ScriptNamedDeBruijn Source # 
Instance details

Defined in PlutusLedgerApi.Common.SerialisedScript

NFData ScriptNamedDeBruijn Source # 
Instance details

Defined in PlutusLedgerApi.Common.SerialisedScript

Eq ScriptNamedDeBruijn Source # 
Instance details

Defined in PlutusLedgerApi.Common.SerialisedScript

type Rep ScriptNamedDeBruijn Source # 
Instance details

Defined in PlutusLedgerApi.Common.SerialisedScript

type Rep ScriptNamedDeBruijn = D1 ('MetaData "ScriptNamedDeBruijn" "PlutusLedgerApi.Common.SerialisedScript" "plutus-ledger-api-1.18.0.0-Arniy3OL4wy69RH7u4QMZP" 'True) (C1 ('MetaCons "ScriptNamedDeBruijn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Program NamedDeBruijn DefaultUni DefaultFun ()))))

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.

Constructors

Verbose

accumulate all traces

Quiet

don't accumulate anything

Instances

Instances details
Eq VerboseMode Source # 
Instance details

Defined in PlutusLedgerApi.Common.Eval

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

data Data #

Constructors

Constr Integer [Data] 
Map [(Data, Data)] 
List [Data] 
I Integer 
B ByteString 

Instances

Instances details
Data Data 
Instance details

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 
Instance details

Defined in PlutusCore.Data

Associated Types

type Rep Data :: Type -> Type Source #

Methods

from :: Data -> Rep Data x Source #

to :: Rep Data x -> Data Source #

Show Data 
Instance details

Defined in PlutusCore.Data

NFData Data 
Instance details

Defined in PlutusCore.Data

Methods

rnf :: Data -> () Source #

Eq Data 
Instance details

Defined in PlutusCore.Data

Methods

(==) :: Data -> Data -> Bool Source #

(/=) :: Data -> Data -> Bool Source #

Ord Data 
Instance details

Defined in PlutusCore.Data

Hashable Data 
Instance details

Defined in PlutusCore.Data

Methods

hashWithSalt :: Int -> Data -> Int

hash :: Data -> Int

NoThunks Data 
Instance details

Defined in PlutusCore.Data

Methods

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

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

showTypeOf :: Proxy Data -> String

Pretty Data 
Instance details

Defined in PlutusCore.Data

Methods

pretty :: Data -> Doc ann

prettyList :: [Data] -> Doc ann

Serialise Data 
Instance details

Defined in PlutusCore.Data

Methods

encode :: Data -> Encoding

decode :: Decoder s Data

encodeList :: [Data] -> Encoding

decodeList :: Decoder s [Data]

PrettyBy ConstConfig Data 
Instance details

Defined in PlutusCore.Pretty.PrettyConst

Methods

prettyBy :: ConstConfig -> Data -> Doc ann

prettyListBy :: ConstConfig -> [Data] -> Doc ann

KnownBuiltinTypeIn DefaultUni term Data => MakeKnownIn DefaultUni term Data 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnown :: Data -> MakeKnownM term

KnownBuiltinTypeIn DefaultUni term Data => ReadKnownIn DefaultUni term Data 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown :: term -> ReadKnownM Data

Contains DefaultUni Data 
Instance details

Defined in PlutusCore.Default.Universe

Methods

knownUni :: DefaultUni (Esc Data)

KnownBuiltinTypeAst tyname DefaultUni Data => KnownTypeAst tyname DefaultUni Data 
Instance details

Defined in PlutusCore.Default.Universe

Associated Types

type IsBuiltin DefaultUni Data :: Bool

type ToHoles DefaultUni Data :: [Hole]

type ToBinds DefaultUni acc Data :: [Some TyNameRep]

Methods

toTypeAst :: proxy Data -> Type tyname DefaultUni ()

type Rep Data 
Instance details

Defined in PlutusCore.Data

type IsBuiltin DefaultUni Data 
Instance details

Defined in PlutusCore.Default.Universe

type IsBuiltin DefaultUni Data = IsBuiltin DefaultUni (ElaborateBuiltin DefaultUni Data)
type ToHoles DefaultUni Data 
Instance details

Defined in PlutusCore.Default.Universe

type ToHoles DefaultUni Data = ToHoles DefaultUni (ElaborateBuiltin DefaultUni Data)
type ToBinds DefaultUni acc Data 
Instance details

Defined in PlutusCore.Default.Universe

type ToBinds DefaultUni acc Data = ToBinds DefaultUni acc (ElaborateBuiltin DefaultUni Data)

data ExBudget #

Constructors

ExBudget 

Instances

Instances details
FromJSON ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

parseJSON :: Value -> Parser ExBudget

parseJSONList :: Value -> Parser [ExBudget]

omittedField :: Maybe ExBudget

ToJSON ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

toJSON :: ExBudget -> Value

toEncoding :: ExBudget -> Encoding

toJSONList :: [ExBudget] -> Value

toEncodingList :: [ExBudget] -> Encoding

omitField :: ExBudget -> Bool

Monoid ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Semigroup ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Generic ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Associated Types

type Rep ExBudget :: Type -> Type Source #

Show ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

NFData ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

rnf :: ExBudget -> () Source #

Eq ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

NoThunks ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

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

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

showTypeOf :: Proxy ExBudget -> String

Pretty ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

pretty :: ExBudget -> Doc ann

prettyList :: [ExBudget] -> Doc ann

Serialise ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

encode :: ExBudget -> Encoding

decode :: Decoder s ExBudget

encodeList :: [ExBudget] -> Encoding

decodeList :: Decoder s [ExBudget]

PrettyBy config ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

prettyBy :: config -> ExBudget -> Doc ann

prettyListBy :: config -> [ExBudget] -> Doc ann

Lift ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

lift :: Quote m => ExBudget -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => ExBudget -> Code m ExBudget Source #

type Rep ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

type Rep ExBudget = D1 ('MetaData "ExBudget" "PlutusCore.Evaluation.Machine.ExBudget" "plutus-core-1.18.0.0-Bo1HApUitrK8tVw3GuwnrY" 'False) (C1 ('MetaCons "ExBudget" 'PrefixI 'True) (S1 ('MetaSel ('Just "exBudgetCPU") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedUnpack) (Rec0 ExCPU) :*: S1 ('MetaSel ('Just "exBudgetMemory") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedUnpack) (Rec0 ExMemory)))

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.

Instances

Instances details
Generic MajorProtocolVersion Source # 
Instance details

Defined in PlutusLedgerApi.Common.ProtocolVersions

Associated Types

type Rep MajorProtocolVersion :: Type -> Type Source #

Show MajorProtocolVersion Source # 
Instance details

Defined in PlutusLedgerApi.Common.ProtocolVersions

Eq MajorProtocolVersion Source # 
Instance details

Defined in PlutusLedgerApi.Common.ProtocolVersions

Ord MajorProtocolVersion Source # 
Instance details

Defined in PlutusLedgerApi.Common.ProtocolVersions

Pretty MajorProtocolVersion Source # 
Instance details

Defined in PlutusLedgerApi.Common.ProtocolVersions

Methods

pretty :: MajorProtocolVersion -> Doc ann

prettyList :: [MajorProtocolVersion] -> Doc ann

Serialise MajorProtocolVersion Source # 
Instance details

Defined in PlutusLedgerApi.Common.ProtocolVersions

type Rep MajorProtocolVersion Source # 
Instance details

Defined in PlutusLedgerApi.Common.ProtocolVersions

type Rep MajorProtocolVersion = D1 ('MetaData "MajorProtocolVersion" "PlutusLedgerApi.Common.ProtocolVersions" "plutus-ledger-api-1.18.0.0-Arniy3OL4wy69RH7u4QMZP" 'True) (C1 ('MetaCons "MajorProtocolVersion" 'PrefixI 'True) (S1 ('MetaSel ('Just "getMajorProtocolVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

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

Constructors

PlutusV1

introduced in shelley era

PlutusV2

introduced in vasil era

PlutusV3

not yet enabled

Instances

Instances details
Bounded PlutusLedgerLanguage Source # 
Instance details

Defined in PlutusLedgerApi.Common.Versions

Enum PlutusLedgerLanguage Source # 
Instance details

Defined in PlutusLedgerApi.Common.Versions

Generic PlutusLedgerLanguage Source # 
Instance details

Defined in PlutusLedgerApi.Common.Versions

Associated Types

type Rep PlutusLedgerLanguage :: Type -> Type Source #

Show PlutusLedgerLanguage Source # 
Instance details

Defined in PlutusLedgerApi.Common.Versions

Eq PlutusLedgerLanguage Source # 
Instance details

Defined in PlutusLedgerApi.Common.Versions

Ord PlutusLedgerLanguage Source # 
Instance details

Defined in PlutusLedgerApi.Common.Versions

Pretty PlutusLedgerLanguage Source # 
Instance details

Defined in PlutusLedgerApi.Common.Versions

Methods

pretty :: PlutusLedgerLanguage -> Doc ann

prettyList :: [PlutusLedgerLanguage] -> Doc ann

type Rep PlutusLedgerLanguage Source # 
Instance details

Defined in PlutusLedgerApi.Common.Versions

type Rep PlutusLedgerLanguage = D1 ('MetaData "PlutusLedgerLanguage" "PlutusLedgerApi.Common.Versions" "plutus-ledger-api-1.18.0.0-Arniy3OL4wy69RH7u4QMZP" 'False) (C1 ('MetaCons "PlutusV1" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PlutusV2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PlutusV3" 'PrefixI 'False) (U1 :: Type -> Type)))

data Version #

Instances

Instances details
Generic Version 
Instance details

Defined in PlutusCore.Version

Associated Types

type Rep Version :: Type -> Type Source #

Show Version 
Instance details

Defined in PlutusCore.Version

NFData Version 
Instance details

Defined in PlutusCore.Version

Methods

rnf :: Version -> () Source #

Eq Version 
Instance details

Defined in PlutusCore.Version

Ord Version 
Instance details

Defined in PlutusCore.Version

Hashable Version 
Instance details

Defined in PlutusCore.Version

Methods

hashWithSalt :: Int -> Version -> Int

hash :: Version -> Int

Pretty Version 
Instance details

Defined in PlutusCore.Version

Methods

pretty :: Version -> Doc ann

prettyList :: [Version] -> Doc ann

type Rep Version 
Instance details

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

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

showParamName

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)

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.18.0.0-Bo1HApUitrK8tVw3GuwnrY" '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)) :+: C1 ('MetaCons "CMTooFewParamsError" 'PrefixI 'True) (S1 ('MetaSel ('Just "cmTooFewExpected") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int) :*: S1 ('MetaSel ('Just "cmTooFewActual") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int))))

data CostModelApplyWarn #

Instances

Instances details
Pretty CostModelApplyWarn 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

Methods

pretty :: CostModelApplyWarn -> Doc ann

prettyList :: [CostModelApplyWarn] -> Doc ann

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

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

mkTermToEvaluate 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