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

PlutusLedgerApi.V1

Description

The interface to Plutus V1 for the ledger.

Synopsis

Scripts

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 ScriptForEvaluationTypeType Source #

Show ScriptForEvaluation Source # 
Instance details

Defined in PlutusLedgerApi.Common.SerialisedScript

NFData ScriptForEvaluation Source # 
Instance details

Defined in PlutusLedgerApi.Common.SerialisedScript

Methods

rnfScriptForEvaluation → () Source #

Eq ScriptForEvaluation Source # 
Instance details

Defined in PlutusLedgerApi.Common.SerialisedScript

NoThunks ScriptForEvaluation Source # 
Instance details

Defined in PlutusLedgerApi.Common.SerialisedScript

type Rep ScriptForEvaluation Source # 
Instance details

Defined in PlutusLedgerApi.Common.SerialisedScript

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

serialiseCompiledCode ∷ ∀ 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.

serialiseUPLCProgram 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

∷ ∀ m. MonadError ScriptDecodeError m 
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).

uncheckedDeserialiseUPLCSerialisedScriptProgram DeBruijn DefaultUni DefaultFun () Source #

Deserialises a SerialisedScript back into an AST. Does *not* do ledger-language-version-specific checks like for allowable builtins.

Running scripts

evaluateScriptRestricting Source #

Arguments

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.

evaluateScriptCounting Source #

Arguments

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.

Protocol version

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 MajorProtocolVersionTypeType 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

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.36.0.0-inplace" 'True) (C1 ('MetaCons "MajorProtocolVersion" 'PrefixI 'True) (S1 ('MetaSel ('Just "getMajorProtocolVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

Verbose mode and log output

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.

Costing-related types

data ExBudget Source #

Constructors

ExBudget 

Instances

Instances details
FromJSON ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

parseJSON ∷ Value → Parser ExBudget

parseJSONList ∷ Value → Parser [ExBudget]

omittedFieldMaybe ExBudget

ToJSON ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

toJSONExBudget → Value

toEncodingExBudget → Encoding

toJSONList ∷ [ExBudget] → Value

toEncodingList ∷ [ExBudget] → Encoding

omitFieldExBudgetBool

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 ExBudgetTypeType Source #

Show ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

NFData ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

rnfExBudget → () Source #

Eq ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

NoThunks ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Pretty ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

prettyExBudgetDoc ann Source #

prettyList ∷ [ExBudget] → Doc ann Source #

Serialise ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

PrettyBy config ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

prettyBy ∷ config → ExBudgetDoc ann Source #

prettyListBy ∷ config → [ExBudget] → Doc ann Source #

Lift ExBudget 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Methods

liftQuote m ⇒ ExBudget → m Exp Source #

liftTyped ∷ ∀ (m ∷ TypeType). Quote m ⇒ ExBudgetCode 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.36.0.0-inplace" 'False) (C1 ('MetaCons "ExBudget" 'PrefixI 'True) (S1 ('MetaSel ('Just "exBudgetCPU") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedUnpack) (Rec0 ExCPU) :*: S1 ('MetaSel ('Just "exBudgetMemory") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedUnpack) (Rec0 ExMemory)))

newtype ExCPU Source #

Counts CPU units in picoseconds: maximum value for SatInt is 2^63 ps, or appproximately 106 days.

Constructors

ExCPU CostingInteger 

Instances

Instances details
FromJSON ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

parseJSON ∷ Value → Parser ExCPU

parseJSONList ∷ Value → Parser [ExCPU]

omittedFieldMaybe ExCPU

ToJSON ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

toJSONExCPU → Value

toEncodingExCPU → Encoding

toJSONList ∷ [ExCPU] → Value

toEncodingList ∷ [ExCPU] → Encoding

omitFieldExCPUBool

Monoid ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Semigroup ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

(<>)ExCPUExCPUExCPU Source #

sconcatNonEmpty ExCPUExCPU Source #

stimesIntegral b ⇒ b → ExCPUExCPU Source #

Bounded ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Generic ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Associated Types

type Rep ExCPUTypeType Source #

Methods

fromExCPURep ExCPU x Source #

toRep ExCPU x → ExCPU Source #

Num ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Read ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Show ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

NFData ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

rnfExCPU → () Source #

Eq ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

(==)ExCPUExCPUBool Source #

(/=)ExCPUExCPUBool Source #

Ord ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

compareExCPUExCPUOrdering Source #

(<)ExCPUExCPUBool Source #

(<=)ExCPUExCPUBool Source #

(>)ExCPUExCPUBool Source #

(>=)ExCPUExCPUBool Source #

maxExCPUExCPUExCPU Source #

minExCPUExCPUExCPU Source #

NoThunks ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Pretty ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

prettyExCPUDoc ann Source #

prettyList ∷ [ExCPU] → Doc ann Source #

Serialise ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

PrettyBy config ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

prettyBy ∷ config → ExCPUDoc ann Source #

prettyListBy ∷ config → [ExCPU] → Doc ann Source #

Lift ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

liftQuote m ⇒ ExCPU → m Exp Source #

liftTyped ∷ ∀ (m ∷ TypeType). Quote m ⇒ ExCPUCode m ExCPU Source #

type Rep ExCPU 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

type Rep ExCPU = D1 ('MetaData "ExCPU" "PlutusCore.Evaluation.Machine.ExMemory" "plutus-core-1.36.0.0-inplace" 'True) (C1 ('MetaCons "ExCPU" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CostingInteger)))

newtype ExMemory Source #

Counts size in machine words.

Constructors

ExMemory CostingInteger 

Instances

Instances details
FromJSON ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

parseJSON ∷ Value → Parser ExMemory

parseJSONList ∷ Value → Parser [ExMemory]

omittedFieldMaybe ExMemory

ToJSON ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

toJSONExMemory → Value

toEncodingExMemory → Encoding

toJSONList ∷ [ExMemory] → Value

toEncodingList ∷ [ExMemory] → Encoding

omitFieldExMemoryBool

Monoid ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Semigroup ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Bounded ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Generic ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Associated Types

type Rep ExMemoryTypeType Source #

Num ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Read ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Show ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

NFData ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

rnfExMemory → () Source #

Eq ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Ord ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

NoThunks ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Pretty ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

prettyExMemoryDoc ann Source #

prettyList ∷ [ExMemory] → Doc ann Source #

Serialise ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

PrettyBy config ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

prettyBy ∷ config → ExMemoryDoc ann Source #

prettyListBy ∷ config → [ExMemory] → Doc ann Source #

Lift ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

liftQuote m ⇒ ExMemory → m Exp Source #

liftTyped ∷ ∀ (m ∷ TypeType). Quote m ⇒ ExMemoryCode m ExMemory Source #

type Rep ExMemory 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

type Rep ExMemory = D1 ('MetaData "ExMemory" "PlutusCore.Evaluation.Machine.ExMemory" "plutus-core-1.36.0.0-inplace" 'True) (C1 ('MetaCons "ExMemory" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CostingInteger)))

data SatInt Source #

Instances

Instances details
FromJSON SatInt 
Instance details

Defined in Data.SatInt

Methods

parseJSON ∷ Value → Parser SatInt

parseJSONList ∷ Value → Parser [SatInt]

omittedFieldMaybe SatInt

ToJSON SatInt 
Instance details

Defined in Data.SatInt

Methods

toJSONSatInt → Value

toEncodingSatInt → Encoding

toJSONList ∷ [SatInt] → Value

toEncodingList ∷ [SatInt] → Encoding

omitFieldSatIntBool

Bits SatInt 
Instance details

Defined in Data.SatInt

FiniteBits SatInt 
Instance details

Defined in Data.SatInt

Bounded SatInt 
Instance details

Defined in Data.SatInt

Generic SatInt 
Instance details

Defined in Data.SatInt

Associated Types

type Rep SatIntTypeType Source #

Methods

fromSatIntRep SatInt x Source #

toRep SatInt x → SatInt Source #

Num SatInt

In the Num instance, we plug in our own addition, multiplication and subtraction function that perform overflow-checking.

Instance details

Defined in Data.SatInt

Read SatInt 
Instance details

Defined in Data.SatInt

Show SatInt 
Instance details

Defined in Data.SatInt

FromField SatInt 
Instance details

Defined in Data.SatInt

Methods

parseField ∷ Field → Parser SatInt

NFData SatInt 
Instance details

Defined in Data.SatInt

Methods

rnfSatInt → () Source #

Eq SatInt 
Instance details

Defined in Data.SatInt

Methods

(==)SatIntSatIntBool Source #

(/=)SatIntSatIntBool Source #

Ord SatInt 
Instance details

Defined in Data.SatInt

NoThunks SatInt 
Instance details

Defined in Data.SatInt

Prim SatInt 
Instance details

Defined in Data.SatInt

Serialise SatInt 
Instance details

Defined in Data.SatInt

Lift SatInt 
Instance details

Defined in Data.SatInt

Methods

liftQuote m ⇒ SatInt → m Exp Source #

liftTyped ∷ ∀ (m ∷ TypeType). Quote m ⇒ SatIntCode m SatInt Source #

type Rep SatInt 
Instance details

Defined in Data.SatInt

type Rep SatInt = D1 ('MetaData "SatInt" "Data.SatInt" "plutus-core-1.36.0.0-inplace-satint" 'True) (C1 ('MetaCons "SI" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSatInt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

fromSatIntNum a ⇒ SatInt → a Source #

An optimized version of fromIntegral . unSatInt.

Cost model

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 EvaluationContextTypeType Source #

NFData EvaluationContext Source # 
Instance details

Defined in PlutusLedgerApi.Common.Eval

Methods

rnfEvaluationContext → () Source #

NoThunks EvaluationContext Source # 
Instance details

Defined in PlutusLedgerApi.Common.Eval

type Rep EvaluationContext Source # 
Instance details

Defined in PlutusLedgerApi.Common.Eval

type Rep EvaluationContext = D1 ('MetaData "EvaluationContext" "PlutusLedgerApi.Common.Eval" "plutus-ledger-api-1.36.0.0-inplace" 'False) (C1 ('MetaCons "EvaluationContext" 'PrefixI 'True) (S1 ('MetaSel ('Just "_evalCtxLedgerLang") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 PlutusLedgerLanguage) :*: (S1 ('MetaSel ('Just "_evalCtxToSemVar") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (MajorProtocolVersionBuiltinSemanticsVariant 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.

data ParamName Source #

The enumeration of all possible cost model parameter names for this language version.

IMPORTANT: The order of appearance of the data constructors here matters. DO NOT REORDER. See Note [Quotation marks in cost model parameter constructors] See Note [Cost model parameters from the ledger's point of view]

Constructors

AddInteger'cpu'arguments'intercept 
AddInteger'cpu'arguments'slope 
AddInteger'memory'arguments'intercept 
AddInteger'memory'arguments'slope 
AppendByteString'cpu'arguments'intercept 
AppendByteString'cpu'arguments'slope 
AppendByteString'memory'arguments'intercept 
AppendByteString'memory'arguments'slope 
AppendString'cpu'arguments'intercept 
AppendString'cpu'arguments'slope 
AppendString'memory'arguments'intercept 
AppendString'memory'arguments'slope 
BData'cpu'arguments 
BData'memory'arguments 
Blake2b_256'cpu'arguments'intercept 
Blake2b_256'cpu'arguments'slope 
Blake2b_256'memory'arguments 
CekApplyCost'exBudgetCPU 
CekApplyCost'exBudgetMemory 
CekBuiltinCost'exBudgetCPU 
CekBuiltinCost'exBudgetMemory 
CekConstCost'exBudgetCPU 
CekConstCost'exBudgetMemory 
CekDelayCost'exBudgetCPU 
CekDelayCost'exBudgetMemory 
CekForceCost'exBudgetCPU 
CekForceCost'exBudgetMemory 
CekLamCost'exBudgetCPU 
CekLamCost'exBudgetMemory 
CekStartupCost'exBudgetCPU 
CekStartupCost'exBudgetMemory 
CekVarCost'exBudgetCPU 
CekVarCost'exBudgetMemory 
ChooseData'cpu'arguments 
ChooseData'memory'arguments 
ChooseList'cpu'arguments 
ChooseList'memory'arguments 
ChooseUnit'cpu'arguments 
ChooseUnit'memory'arguments 
ConsByteString'cpu'arguments'intercept 
ConsByteString'cpu'arguments'slope 
ConsByteString'memory'arguments'intercept 
ConsByteString'memory'arguments'slope 
ConstrData'cpu'arguments 
ConstrData'memory'arguments 
DecodeUtf8'cpu'arguments'intercept 
DecodeUtf8'cpu'arguments'slope 
DecodeUtf8'memory'arguments'intercept 
DecodeUtf8'memory'arguments'slope 
DivideInteger'cpu'arguments'constant 
DivideInteger'cpu'arguments'model'arguments'intercept 
DivideInteger'cpu'arguments'model'arguments'slope 
DivideInteger'memory'arguments'intercept 
DivideInteger'memory'arguments'minimum 
DivideInteger'memory'arguments'slope 
EncodeUtf8'cpu'arguments'intercept 
EncodeUtf8'cpu'arguments'slope 
EncodeUtf8'memory'arguments'intercept 
EncodeUtf8'memory'arguments'slope 
EqualsByteString'cpu'arguments'constant 
EqualsByteString'cpu'arguments'intercept 
EqualsByteString'cpu'arguments'slope 
EqualsByteString'memory'arguments 
EqualsData'cpu'arguments'intercept 
EqualsData'cpu'arguments'slope 
EqualsData'memory'arguments 
EqualsInteger'cpu'arguments'intercept 
EqualsInteger'cpu'arguments'slope 
EqualsInteger'memory'arguments 
EqualsString'cpu'arguments'constant 
EqualsString'cpu'arguments'intercept 
EqualsString'cpu'arguments'slope 
EqualsString'memory'arguments 
FstPair'cpu'arguments 
FstPair'memory'arguments 
HeadList'cpu'arguments 
HeadList'memory'arguments 
IData'cpu'arguments 
IData'memory'arguments 
IfThenElse'cpu'arguments 
IfThenElse'memory'arguments 
IndexByteString'cpu'arguments 
IndexByteString'memory'arguments 
LengthOfByteString'cpu'arguments 
LengthOfByteString'memory'arguments 
LessThanByteString'cpu'arguments'intercept 
LessThanByteString'cpu'arguments'slope 
LessThanByteString'memory'arguments 
LessThanEqualsByteString'cpu'arguments'intercept 
LessThanEqualsByteString'cpu'arguments'slope 
LessThanEqualsByteString'memory'arguments 
LessThanEqualsInteger'cpu'arguments'intercept 
LessThanEqualsInteger'cpu'arguments'slope 
LessThanEqualsInteger'memory'arguments 
LessThanInteger'cpu'arguments'intercept 
LessThanInteger'cpu'arguments'slope 
LessThanInteger'memory'arguments 
ListData'cpu'arguments 
ListData'memory'arguments 
MapData'cpu'arguments 
MapData'memory'arguments 
MkCons'cpu'arguments 
MkCons'memory'arguments 
MkNilData'cpu'arguments 
MkNilData'memory'arguments 
MkNilPairData'cpu'arguments 
MkNilPairData'memory'arguments 
MkPairData'cpu'arguments 
MkPairData'memory'arguments 
ModInteger'cpu'arguments'constant 
ModInteger'cpu'arguments'model'arguments'intercept 
ModInteger'cpu'arguments'model'arguments'slope 
ModInteger'memory'arguments'intercept 
ModInteger'memory'arguments'minimum 
ModInteger'memory'arguments'slope 
MultiplyInteger'cpu'arguments'intercept 
MultiplyInteger'cpu'arguments'slope 
MultiplyInteger'memory'arguments'intercept 
MultiplyInteger'memory'arguments'slope 
NullList'cpu'arguments 
NullList'memory'arguments 
QuotientInteger'cpu'arguments'constant 
QuotientInteger'cpu'arguments'model'arguments'intercept 
QuotientInteger'cpu'arguments'model'arguments'slope 
QuotientInteger'memory'arguments'intercept 
QuotientInteger'memory'arguments'minimum 
QuotientInteger'memory'arguments'slope 
RemainderInteger'cpu'arguments'constant 
RemainderInteger'cpu'arguments'model'arguments'intercept 
RemainderInteger'cpu'arguments'model'arguments'slope 
RemainderInteger'memory'arguments'intercept 
RemainderInteger'memory'arguments'minimum 
RemainderInteger'memory'arguments'slope 
Sha2_256'cpu'arguments'intercept 
Sha2_256'cpu'arguments'slope 
Sha2_256'memory'arguments 
Sha3_256'cpu'arguments'intercept 
Sha3_256'cpu'arguments'slope 
Sha3_256'memory'arguments 
SliceByteString'cpu'arguments'intercept 
SliceByteString'cpu'arguments'slope 
SliceByteString'memory'arguments'intercept 
SliceByteString'memory'arguments'slope 
SndPair'cpu'arguments 
SndPair'memory'arguments 
SubtractInteger'cpu'arguments'intercept 
SubtractInteger'cpu'arguments'slope 
SubtractInteger'memory'arguments'intercept 
SubtractInteger'memory'arguments'slope 
TailList'cpu'arguments 
TailList'memory'arguments 
Trace'cpu'arguments 
Trace'memory'arguments 
UnBData'cpu'arguments 
UnBData'memory'arguments 
UnConstrData'cpu'arguments 
UnConstrData'memory'arguments 
UnIData'cpu'arguments 
UnIData'memory'arguments 
UnListData'cpu'arguments 
UnListData'memory'arguments 
UnMapData'cpu'arguments 
UnMapData'memory'arguments 
VerifyEd25519Signature'cpu'arguments'intercept 
VerifyEd25519Signature'cpu'arguments'slope 
VerifyEd25519Signature'memory'arguments 

Instances

Instances details
Bounded ParamName Source # 
Instance details

Defined in PlutusLedgerApi.V1.ParamName

Enum ParamName Source # 
Instance details

Defined in PlutusLedgerApi.V1.ParamName

Generic ParamName Source # 
Instance details

Defined in PlutusLedgerApi.V1.ParamName

Associated Types

type Rep ParamNameTypeType Source #

Ix ParamName Source # 
Instance details

Defined in PlutusLedgerApi.V1.ParamName

Eq ParamName Source # 
Instance details

Defined in PlutusLedgerApi.V1.ParamName

Ord ParamName Source # 
Instance details

Defined in PlutusLedgerApi.V1.ParamName

IsParamName ParamName Source # 
Instance details

Defined in PlutusLedgerApi.V1.ParamName

type Rep ParamName Source # 
Instance details

Defined in PlutusLedgerApi.V1.ParamName

type Rep ParamName = D1 ('MetaData "ParamName" "PlutusLedgerApi.V1.ParamName" "plutus-ledger-api-1.36.0.0-inplace" 'False) (((((((C1 ('MetaCons "AddInteger'cpu'arguments'intercept" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "AddInteger'cpu'arguments'slope" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "AddInteger'memory'arguments'intercept" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "AddInteger'memory'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "AppendByteString'cpu'arguments'intercept" 'PrefixI 'False) (U1TypeType)))) :+: ((C1 ('MetaCons "AppendByteString'cpu'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "AppendByteString'memory'arguments'intercept" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "AppendByteString'memory'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "AppendString'cpu'arguments'intercept" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "AppendString'cpu'arguments'slope" 'PrefixI 'False) (U1TypeType))))) :+: (((C1 ('MetaCons "AppendString'memory'arguments'intercept" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "AppendString'memory'arguments'slope" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "BData'cpu'arguments" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "BData'memory'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "Blake2b_256'cpu'arguments'intercept" 'PrefixI 'False) (U1TypeType)))) :+: ((C1 ('MetaCons "Blake2b_256'cpu'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "Blake2b_256'memory'arguments" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "CekApplyCost'exBudgetCPU" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "CekApplyCost'exBudgetMemory" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "CekBuiltinCost'exBudgetCPU" 'PrefixI 'False) (U1TypeType)))))) :+: ((((C1 ('MetaCons "CekBuiltinCost'exBudgetMemory" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "CekConstCost'exBudgetCPU" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "CekConstCost'exBudgetMemory" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "CekDelayCost'exBudgetCPU" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "CekDelayCost'exBudgetMemory" 'PrefixI 'False) (U1TypeType)))) :+: ((C1 ('MetaCons "CekForceCost'exBudgetCPU" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "CekForceCost'exBudgetMemory" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "CekLamCost'exBudgetCPU" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "CekLamCost'exBudgetMemory" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "CekStartupCost'exBudgetCPU" 'PrefixI 'False) (U1TypeType))))) :+: (((C1 ('MetaCons "CekStartupCost'exBudgetMemory" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "CekVarCost'exBudgetCPU" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "CekVarCost'exBudgetMemory" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "ChooseData'cpu'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "ChooseData'memory'arguments" 'PrefixI 'False) (U1TypeType)))) :+: ((C1 ('MetaCons "ChooseList'cpu'arguments" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "ChooseList'memory'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "ChooseUnit'cpu'arguments" 'PrefixI 'False) (U1TypeType))) :+: (C1 ('MetaCons "ChooseUnit'memory'arguments" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "ConsByteString'cpu'arguments'intercept" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "ConsByteString'cpu'arguments'slope" 'PrefixI 'False) (U1TypeType))))))) :+: (((((C1 ('MetaCons "ConsByteString'memory'arguments'intercept" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "ConsByteString'memory'arguments'slope" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "ConstrData'cpu'arguments" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "ConstrData'memory'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "DecodeUtf8'cpu'arguments'intercept" 'PrefixI 'False) (U1TypeType)))) :+: ((C1 ('MetaCons "DecodeUtf8'cpu'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "DecodeUtf8'memory'arguments'intercept" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "DecodeUtf8'memory'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "DivideInteger'cpu'arguments'constant" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "DivideInteger'cpu'arguments'model'arguments'intercept" 'PrefixI 'False) (U1TypeType))))) :+: (((C1 ('MetaCons "DivideInteger'cpu'arguments'model'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "DivideInteger'memory'arguments'intercept" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "DivideInteger'memory'arguments'minimum" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "DivideInteger'memory'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "EncodeUtf8'cpu'arguments'intercept" 'PrefixI 'False) (U1TypeType)))) :+: ((C1 ('MetaCons "EncodeUtf8'cpu'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "EncodeUtf8'memory'arguments'intercept" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "EncodeUtf8'memory'arguments'slope" 'PrefixI 'False) (U1TypeType))) :+: (C1 ('MetaCons "EqualsByteString'cpu'arguments'constant" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "EqualsByteString'cpu'arguments'intercept" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "EqualsByteString'cpu'arguments'slope" 'PrefixI 'False) (U1TypeType)))))) :+: ((((C1 ('MetaCons "EqualsByteString'memory'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "EqualsData'cpu'arguments'intercept" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "EqualsData'cpu'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "EqualsData'memory'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "EqualsInteger'cpu'arguments'intercept" 'PrefixI 'False) (U1TypeType)))) :+: ((C1 ('MetaCons "EqualsInteger'cpu'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "EqualsInteger'memory'arguments" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "EqualsString'cpu'arguments'constant" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "EqualsString'cpu'arguments'intercept" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "EqualsString'cpu'arguments'slope" 'PrefixI 'False) (U1TypeType))))) :+: (((C1 ('MetaCons "EqualsString'memory'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "FstPair'cpu'arguments" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "FstPair'memory'arguments" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "HeadList'cpu'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "HeadList'memory'arguments" 'PrefixI 'False) (U1TypeType)))) :+: ((C1 ('MetaCons "IData'cpu'arguments" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "IData'memory'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "IfThenElse'cpu'arguments" 'PrefixI 'False) (U1TypeType))) :+: (C1 ('MetaCons "IfThenElse'memory'arguments" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "IndexByteString'cpu'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "IndexByteString'memory'arguments" 'PrefixI 'False) (U1TypeType)))))))) :+: ((((((C1 ('MetaCons "LengthOfByteString'cpu'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "LengthOfByteString'memory'arguments" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "LessThanByteString'cpu'arguments'intercept" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "LessThanByteString'cpu'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "LessThanByteString'memory'arguments" 'PrefixI 'False) (U1TypeType)))) :+: ((C1 ('MetaCons "LessThanEqualsByteString'cpu'arguments'intercept" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "LessThanEqualsByteString'cpu'arguments'slope" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "LessThanEqualsByteString'memory'arguments" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "LessThanEqualsInteger'cpu'arguments'intercept" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "LessThanEqualsInteger'cpu'arguments'slope" 'PrefixI 'False) (U1TypeType))))) :+: (((C1 ('MetaCons "LessThanEqualsInteger'memory'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "LessThanInteger'cpu'arguments'intercept" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "LessThanInteger'cpu'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "LessThanInteger'memory'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "ListData'cpu'arguments" 'PrefixI 'False) (U1TypeType)))) :+: ((C1 ('MetaCons "ListData'memory'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "MapData'cpu'arguments" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "MapData'memory'arguments" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "MkCons'cpu'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "MkCons'memory'arguments" 'PrefixI 'False) (U1TypeType)))))) :+: ((((C1 ('MetaCons "MkNilData'cpu'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "MkNilData'memory'arguments" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "MkNilPairData'cpu'arguments" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "MkNilPairData'memory'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "MkPairData'cpu'arguments" 'PrefixI 'False) (U1TypeType)))) :+: ((C1 ('MetaCons "MkPairData'memory'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "ModInteger'cpu'arguments'constant" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "ModInteger'cpu'arguments'model'arguments'intercept" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "ModInteger'cpu'arguments'model'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "ModInteger'memory'arguments'intercept" 'PrefixI 'False) (U1TypeType))))) :+: (((C1 ('MetaCons "ModInteger'memory'arguments'minimum" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "ModInteger'memory'arguments'slope" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "MultiplyInteger'cpu'arguments'intercept" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "MultiplyInteger'cpu'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "MultiplyInteger'memory'arguments'intercept" 'PrefixI 'False) (U1TypeType)))) :+: ((C1 ('MetaCons "MultiplyInteger'memory'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "NullList'cpu'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "NullList'memory'arguments" 'PrefixI 'False) (U1TypeType))) :+: (C1 ('MetaCons "QuotientInteger'cpu'arguments'constant" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "QuotientInteger'cpu'arguments'model'arguments'intercept" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "QuotientInteger'cpu'arguments'model'arguments'slope" 'PrefixI 'False) (U1TypeType))))))) :+: (((((C1 ('MetaCons "QuotientInteger'memory'arguments'intercept" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "QuotientInteger'memory'arguments'minimum" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "QuotientInteger'memory'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "RemainderInteger'cpu'arguments'constant" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "RemainderInteger'cpu'arguments'model'arguments'intercept" 'PrefixI 'False) (U1TypeType)))) :+: ((C1 ('MetaCons "RemainderInteger'cpu'arguments'model'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "RemainderInteger'memory'arguments'intercept" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "RemainderInteger'memory'arguments'minimum" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "RemainderInteger'memory'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "Sha2_256'cpu'arguments'intercept" 'PrefixI 'False) (U1TypeType))))) :+: (((C1 ('MetaCons "Sha2_256'cpu'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "Sha2_256'memory'arguments" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "Sha3_256'cpu'arguments'intercept" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "Sha3_256'cpu'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "Sha3_256'memory'arguments" 'PrefixI 'False) (U1TypeType)))) :+: ((C1 ('MetaCons "SliceByteString'cpu'arguments'intercept" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "SliceByteString'cpu'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "SliceByteString'memory'arguments'intercept" 'PrefixI 'False) (U1TypeType))) :+: (C1 ('MetaCons "SliceByteString'memory'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "SndPair'cpu'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "SndPair'memory'arguments" 'PrefixI 'False) (U1TypeType)))))) :+: ((((C1 ('MetaCons "SubtractInteger'cpu'arguments'intercept" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "SubtractInteger'cpu'arguments'slope" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "SubtractInteger'memory'arguments'intercept" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "SubtractInteger'memory'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "TailList'cpu'arguments" 'PrefixI 'False) (U1TypeType)))) :+: ((C1 ('MetaCons "TailList'memory'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "Trace'cpu'arguments" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "Trace'memory'arguments" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "UnBData'cpu'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "UnBData'memory'arguments" 'PrefixI 'False) (U1TypeType))))) :+: (((C1 ('MetaCons "UnConstrData'cpu'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "UnConstrData'memory'arguments" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "UnIData'cpu'arguments" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "UnIData'memory'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "UnListData'cpu'arguments" 'PrefixI 'False) (U1TypeType)))) :+: ((C1 ('MetaCons "UnListData'memory'arguments" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "UnMapData'cpu'arguments" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "UnMapData'memory'arguments" 'PrefixI 'False) (U1TypeType))) :+: (C1 ('MetaCons "VerifyEd25519Signature'cpu'arguments'intercept" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "VerifyEd25519Signature'cpu'arguments'slope" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "VerifyEd25519Signature'memory'arguments" 'PrefixI 'False) (U1TypeType)))))))))

data CostModelApplyError Source #

A fatal error when trying to create a cost given some plain costmodel parameters.

Constructors

CMUnknownParamError !Text

a costmodel parameter with the give name does not exist in the costmodel to be applied upon

CMInternalReadError

internal error when we are transforming the applyParams' input to json (should not happen)

CMInternalWriteError !String

internal error when we are transforming the applied params from json with given jsonstring error (should not happen)

Instances

Instances details
Data CostModelApplyError 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

Methods

gfoldl ∷ (∀ d b. Data d ⇒ c (d → b) → d → c b) → (∀ g. g → c g) → CostModelApplyError → c CostModelApplyError Source #

gunfold ∷ (∀ b r. Data b ⇒ c (b → r) → c r) → (∀ r. r → c r) → Constr → c CostModelApplyError Source #

toConstrCostModelApplyErrorConstr Source #

dataTypeOfCostModelApplyErrorDataType Source #

dataCast1Typeable t ⇒ (∀ d. Data d ⇒ c (t d)) → Maybe (c CostModelApplyError) Source #

dataCast2Typeable t ⇒ (∀ d e. (Data d, Data e) ⇒ c (t d e)) → Maybe (c CostModelApplyError) Source #

gmapT ∷ (∀ b. Data b ⇒ b → b) → CostModelApplyErrorCostModelApplyError Source #

gmapQl ∷ (r → r' → r) → r → (∀ d. Data d ⇒ d → r') → CostModelApplyError → r Source #

gmapQr ∷ ∀ r r'. (r' → r → r) → r → (∀ d. Data d ⇒ d → r') → CostModelApplyError → r Source #

gmapQ ∷ (∀ d. Data d ⇒ d → u) → CostModelApplyError → [u] Source #

gmapQiInt → (∀ d. Data d ⇒ d → u) → CostModelApplyError → u Source #

gmapMMonad m ⇒ (∀ d. Data d ⇒ d → m d) → CostModelApplyError → m CostModelApplyError Source #

gmapMpMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → CostModelApplyError → m CostModelApplyError Source #

gmapMoMonadPlus m ⇒ (∀ 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 CostModelApplyErrorTypeType Source #

Show CostModelApplyError 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

NFData CostModelApplyError 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

Methods

rnfCostModelApplyError → () Source #

Eq CostModelApplyError 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

NoThunks CostModelApplyError 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

Pretty CostModelApplyError 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

type Rep CostModelApplyError 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

type Rep CostModelApplyError = D1 ('MetaData "CostModelApplyError" "PlutusCore.Evaluation.Machine.CostModelInterface" "plutus-core-1.36.0.0-inplace" 'False) (C1 ('MetaCons "CMUnknownParamError" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: (C1 ('MetaCons "CMInternalReadError" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "CMInternalWriteError" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String))))

type CostModelParams = Map Text Int64 Source #

A raw representation of the ledger's cost model parameters.

The associated keys/names to the parameter values are arbitrarily set by the plutus team; the ledger does not hold any such names.

See Note [Cost model parameters]

Context types

data ScriptContext Source #

The context that the currently-executing script can access.

Constructors

ScriptContext 

Fields

Instances

Instances details
Generic ScriptContext Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

Associated Types

type Rep ScriptContextTypeType Source #

Show ScriptContext Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

Eq ScriptContext Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

Eq ScriptContext Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

FromData ScriptContext Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

ToData ScriptContext Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

UnsafeFromData ScriptContext Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

Pretty ScriptContext Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

(HasSchemaDefinition TxInfo referencedTypes, HasSchemaDefinition ScriptPurpose referencedTypes) ⇒ HasBlueprintSchema ScriptContext referencedTypes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

Methods

schemaSchema referencedTypes Source #

Lift DefaultUni ScriptContext Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

Typeable DefaultUni ScriptContext Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

type Rep ScriptContext Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

type Rep ScriptContext = D1 ('MetaData "ScriptContext" "PlutusLedgerApi.V1.Contexts" "plutus-ledger-api-1.36.0.0-inplace" 'False) (C1 ('MetaCons "ScriptContext" 'PrefixI 'True) (S1 ('MetaSel ('Just "scriptContextTxInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxInfo) :*: S1 ('MetaSel ('Just "scriptContextPurpose") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ScriptPurpose)))

data ScriptPurpose Source #

Purpose of the script that is currently running

Instances

Instances details
Generic ScriptPurpose Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

Associated Types

type Rep ScriptPurposeTypeType Source #

Show ScriptPurpose Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

Eq ScriptPurpose Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

Ord ScriptPurpose Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

HasBlueprintDefinition ScriptPurpose Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

Associated Types

type Unroll ScriptPurpose ∷ [Type] Source #

Eq ScriptPurpose Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

FromData ScriptPurpose Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

ToData ScriptPurpose Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

UnsafeFromData ScriptPurpose Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

Pretty ScriptPurpose Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

(HasSchemaDefinition CurrencySymbol referencedTypes, HasSchemaDefinition TxOutRef referencedTypes, HasSchemaDefinition StakingCredential referencedTypes, HasSchemaDefinition DCert referencedTypes) ⇒ HasBlueprintSchema ScriptPurpose referencedTypes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

Methods

schemaSchema referencedTypes Source #

Lift DefaultUni ScriptPurpose Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

Typeable DefaultUni ScriptPurpose Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

type Rep ScriptPurpose Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

type Unroll ScriptPurpose Source # 
Instance details

Defined in PlutusLedgerApi.V1.Contexts

Supporting types used in the context types

Builtins

data BuiltinByteString Source #

An opaque type representing Plutus Core ByteStrings.

Instances

Instances details
Data BuiltinByteString 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

gfoldl ∷ (∀ d b. Data d ⇒ c (d → b) → d → c b) → (∀ g. g → c g) → BuiltinByteString → c BuiltinByteString Source #

gunfold ∷ (∀ b r. Data b ⇒ c (b → r) → c r) → (∀ r. r → c r) → Constr → c BuiltinByteString Source #

toConstrBuiltinByteStringConstr Source #

dataTypeOfBuiltinByteStringDataType Source #

dataCast1Typeable t ⇒ (∀ d. Data d ⇒ c (t d)) → Maybe (c BuiltinByteString) Source #

dataCast2Typeable t ⇒ (∀ d e. (Data d, Data e) ⇒ c (t d e)) → Maybe (c BuiltinByteString) Source #

gmapT ∷ (∀ b. Data b ⇒ b → b) → BuiltinByteStringBuiltinByteString Source #

gmapQl ∷ (r → r' → r) → r → (∀ d. Data d ⇒ d → r') → BuiltinByteString → r Source #

gmapQr ∷ ∀ r r'. (r' → r → r) → r → (∀ d. Data d ⇒ d → r') → BuiltinByteString → r Source #

gmapQ ∷ (∀ d. Data d ⇒ d → u) → BuiltinByteString → [u] Source #

gmapQiInt → (∀ d. Data d ⇒ d → u) → BuiltinByteString → u Source #

gmapMMonad m ⇒ (∀ d. Data d ⇒ d → m d) → BuiltinByteString → m BuiltinByteString Source #

gmapMpMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → BuiltinByteString → m BuiltinByteString Source #

gmapMoMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → BuiltinByteString → m BuiltinByteString Source #

Monoid BuiltinByteString 
Instance details

Defined in PlutusTx.Builtins.Internal

Semigroup BuiltinByteString 
Instance details

Defined in PlutusTx.Builtins.Internal

Show BuiltinByteString 
Instance details

Defined in PlutusTx.Builtins.Internal

NFData BuiltinByteString 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

rnfBuiltinByteString → () Source #

Eq BuiltinByteString 
Instance details

Defined in PlutusTx.Builtins.Internal

Ord BuiltinByteString 
Instance details

Defined in PlutusTx.Builtins.Internal

Hashable BuiltinByteString 
Instance details

Defined in PlutusTx.Builtins.Internal

ByteArray BuiltinByteString 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

allocRetInt → (Ptr p → IO a) → IO (a, BuiltinByteString) Source #

ByteArrayAccess BuiltinByteString 
Instance details

Defined in PlutusTx.Builtins.Internal

HasBlueprintDefinition BuiltinByteString 
Instance details

Defined in PlutusTx.Blueprint.Definition.Unroll

Associated Types

type Unroll BuiltinByteString ∷ [Type] Source #

HasFromBuiltin BuiltinByteString 
Instance details

Defined in PlutusTx.Builtins.HasBuiltin

Associated Types

type FromBuiltin BuiltinByteString Source #

Eq BuiltinByteString 
Instance details

Defined in PlutusTx.Eq

FromData BuiltinByteString 
Instance details

Defined in PlutusTx.IsData.Class

ToData BuiltinByteString 
Instance details

Defined in PlutusTx.IsData.Class

UnsafeFromData BuiltinByteString 
Instance details

Defined in PlutusTx.IsData.Class

Monoid BuiltinByteString 
Instance details

Defined in PlutusTx.Monoid

Ord BuiltinByteString 
Instance details

Defined in PlutusTx.Ord

Semigroup BuiltinByteString 
Instance details

Defined in PlutusTx.Semigroup

Pretty BuiltinByteString 
Instance details

Defined in PlutusTx.Builtins.Internal

Serialise BuiltinByteString 
Instance details

Defined in PlutusTx.Builtins.Internal

HasBlueprintSchema BuiltinByteString referencedTypes 
Instance details

Defined in PlutusTx.Blueprint.Class

Methods

schemaSchema referencedTypes Source #

HasFromOpaque BuiltinByteString BuiltinByteString 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

HasToOpaque BuiltinByteString BuiltinByteString 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

HasTermLevel uni ByteStringLift uni BuiltinByteString 
Instance details

Defined in PlutusTx.Lift.Class

Methods

liftBuiltinByteStringRTCompile uni fun (Term TyName Name uni fun ()) Source #

HasTypeLevel uni ByteStringTypeable uni BuiltinByteString 
Instance details

Defined in PlutusTx.Lift.Class

Methods

typeRepProxy BuiltinByteStringRTCompile uni fun (Type TyName uni ()) Source #

type Unroll BuiltinByteString 
Instance details

Defined in PlutusTx.Blueprint.Definition.Unroll

type FromBuiltin BuiltinByteString 
Instance details

Defined in PlutusTx.Builtins.HasBuiltin

fromBuiltinHasFromBuiltin arep ⇒ arep → FromBuiltin arep Source #

toOpaqueHasToOpaque a arep ⇒ a → arep Source #

fromOpaqueHasFromOpaque arep a ⇒ arep → a Source #

Bytes

newtype LedgerBytes Source #

Instances

Instances details
IsString LedgerBytes Source #

Read in arbitrary LedgerBytes as a "string" (of characters).

This is mostly used together with GHC's OverloadedStrings extension to specify at the source code any LedgerBytes constants, by utilizing Haskell's double-quoted string syntax.

IMPORTANT: the LedgerBytes are expected to be already hex-encoded (base16); otherwise, LedgerBytesError will be raised as an Exception.

Instance details

Defined in PlutusLedgerApi.V1.Bytes

Generic LedgerBytes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Bytes

Associated Types

type Rep LedgerBytesTypeType Source #

Show LedgerBytes Source #

The Show instance of LedgerBytes is its Base16/Hex encoded bytestring, decoded with UTF-8, unpacked to String.

Instance details

Defined in PlutusLedgerApi.V1.Bytes

NFData LedgerBytes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Bytes

Methods

rnfLedgerBytes → () Source #

Eq LedgerBytes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Bytes

Ord LedgerBytes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Bytes

HasBlueprintDefinition LedgerBytes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Bytes

Associated Types

type Unroll LedgerBytes ∷ [Type] Source #

Eq LedgerBytes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Bytes

FromData LedgerBytes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Bytes

ToData LedgerBytes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Bytes

UnsafeFromData LedgerBytes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Bytes

Ord LedgerBytes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Bytes

Pretty LedgerBytes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Bytes

Methods

prettyLedgerBytesDoc ann Source #

prettyList ∷ [LedgerBytes] → Doc ann Source #

HasBlueprintSchema LedgerBytes referencedTypes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Bytes

Methods

schemaSchema referencedTypes Source #

Lift DefaultUni LedgerBytes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Bytes

Typeable DefaultUni LedgerBytes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Bytes

type Rep LedgerBytes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Bytes

type Rep LedgerBytes = D1 ('MetaData "LedgerBytes" "PlutusLedgerApi.V1.Bytes" "plutus-ledger-api-1.36.0.0-inplace" 'True) (C1 ('MetaCons "LedgerBytes" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLedgerBytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BuiltinByteString)))
type Unroll LedgerBytes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Bytes

fromBytesByteStringLedgerBytes Source #

Lift a Haskell bytestring to the Plutus abstraction LedgerBytes

Certificates

data DCert Source #

A representation of the ledger DCert. Some information is digested, and not included

Constructors

DCertDelegRegKey StakingCredential 
DCertDelegDeRegKey StakingCredential 
DCertDelegDelegate 

Fields

DCertPoolRegister

A digest of the PoolParams

Fields

DCertPoolRetire PubKeyHash Integer

The retirement certificate and the Epoch in which the retirement will take place

DCertGenesis

A really terse Digest

DCertMir

Another really terse Digest

Instances

Instances details
Generic DCert Source # 
Instance details

Defined in PlutusLedgerApi.V1.DCert

Associated Types

type Rep DCertTypeType Source #

Methods

fromDCertRep DCert x Source #

toRep DCert x → DCert Source #

Show DCert Source # 
Instance details

Defined in PlutusLedgerApi.V1.DCert

NFData DCert Source # 
Instance details

Defined in PlutusLedgerApi.V1.DCert

Methods

rnfDCert → () Source #

Eq DCert Source # 
Instance details

Defined in PlutusLedgerApi.V1.DCert

Methods

(==)DCertDCertBool Source #

(/=)DCertDCertBool Source #

Ord DCert Source # 
Instance details

Defined in PlutusLedgerApi.V1.DCert

Methods

compareDCertDCertOrdering Source #

(<)DCertDCertBool Source #

(<=)DCertDCertBool Source #

(>)DCertDCertBool Source #

(>=)DCertDCertBool Source #

maxDCertDCertDCert Source #

minDCertDCertDCert Source #

HasBlueprintDefinition DCert Source # 
Instance details

Defined in PlutusLedgerApi.V1.DCert

Associated Types

type Unroll DCert ∷ [Type] Source #

Eq DCert Source # 
Instance details

Defined in PlutusLedgerApi.V1.DCert

Methods

(==)DCertDCertBool Source #

FromData DCert Source # 
Instance details

Defined in PlutusLedgerApi.V1.DCert

ToData DCert Source # 
Instance details

Defined in PlutusLedgerApi.V1.DCert

UnsafeFromData DCert Source # 
Instance details

Defined in PlutusLedgerApi.V1.DCert

Pretty DCert Source # 
Instance details

Defined in PlutusLedgerApi.V1.DCert

Methods

prettyDCertDoc ann Source #

prettyList ∷ [DCert] → Doc ann Source #

(HasSchemaDefinition StakingCredential referencedTypes, HasSchemaDefinition PubKeyHash referencedTypes, HasSchemaDefinition Integer referencedTypes) ⇒ HasBlueprintSchema DCert referencedTypes Source # 
Instance details

Defined in PlutusLedgerApi.V1.DCert

Methods

schemaSchema referencedTypes Source #

Lift DefaultUni DCert Source # 
Instance details

Defined in PlutusLedgerApi.V1.DCert

Typeable DefaultUni DCert Source # 
Instance details

Defined in PlutusLedgerApi.V1.DCert

type Rep DCert Source # 
Instance details

Defined in PlutusLedgerApi.V1.DCert

type Unroll DCert Source # 
Instance details

Defined in PlutusLedgerApi.V1.DCert

Credentials

data StakingCredential Source #

Staking credential used to assign rewards.

Constructors

StakingHash Credential

The staking hash is the Credential required to unlock a transaction output. Either a public key credential (PubKeyHash) or a script credential (ScriptHash). Both are hashed with BLAKE2b-244. 28 byte.

StakingPtr

The certificate pointer, constructed by the given slot number, transaction and certificate indices. NB: The fields should really be all Word64, as they are implemented in Word64, but Integer is our only integral type so we need to use it instead.

Fields

  • Integer

    the slot number

  • Integer

    the transaction index (within the block)

  • Integer

    the certificate index (within the transaction)

Instances

Instances details
Generic StakingCredential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

Associated Types

type Rep StakingCredentialTypeType Source #

Show StakingCredential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

NFData StakingCredential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

Methods

rnfStakingCredential → () Source #

Eq StakingCredential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

Ord StakingCredential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

HasBlueprintDefinition StakingCredential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

Associated Types

type Unroll StakingCredential ∷ [Type] Source #

Eq StakingCredential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

FromData StakingCredential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

ToData StakingCredential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

UnsafeFromData StakingCredential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

Pretty StakingCredential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

(HasSchemaDefinition Credential referencedTypes, HasSchemaDefinition Integer referencedTypes) ⇒ HasBlueprintSchema StakingCredential referencedTypes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

Methods

schemaSchema referencedTypes Source #

Lift DefaultUni StakingCredential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

Typeable DefaultUni StakingCredential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

type Rep StakingCredential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

type Unroll StakingCredential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

data Credential Source #

Credentials required to unlock a transaction output.

Constructors

PubKeyCredential PubKeyHash

The transaction that spends this output must be signed by the private key. See PubKeyHash.

ScriptCredential ScriptHash

The transaction that spends this output must include the validator script and be accepted by the validator. See ScriptHash.

Instances

Instances details
Generic Credential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

Associated Types

type Rep CredentialTypeType Source #

Show Credential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

NFData Credential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

Methods

rnfCredential → () Source #

Eq Credential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

Ord Credential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

HasBlueprintDefinition Credential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

Associated Types

type Unroll Credential ∷ [Type] Source #

Eq Credential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

Methods

(==)CredentialCredentialBool Source #

FromData Credential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

ToData Credential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

UnsafeFromData Credential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

Pretty Credential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

Methods

prettyCredentialDoc ann Source #

prettyList ∷ [Credential] → Doc ann Source #

(HasSchemaDefinition PubKeyHash referencedTypes, HasSchemaDefinition ScriptHash referencedTypes) ⇒ HasBlueprintSchema Credential referencedTypes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

Methods

schemaSchema referencedTypes Source #

Lift DefaultUni Credential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

Typeable DefaultUni Credential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

type Rep Credential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

type Rep Credential = D1 ('MetaData "Credential" "PlutusLedgerApi.V1.Credential" "plutus-ledger-api-1.36.0.0-inplace" 'False) (C1 ('MetaCons "PubKeyCredential" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PubKeyHash)) :+: C1 ('MetaCons "ScriptCredential" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ScriptHash)))
type Unroll Credential Source # 
Instance details

Defined in PlutusLedgerApi.V1.Credential

Value

newtype Value Source #

The Value type represents a collection of amounts of different currencies. We can think of Value as a vector space whose dimensions are currencies.

Operations on currencies are usually implemented pointwise. That is, we apply the operation to the quantities for each currency in turn. So when we add two Values the resulting Value has, for each currency, the sum of the quantities of that particular currency in the argument Value. The effect of this is that the currencies in the Value are "independent", and are operated on separately.

Whenever we need to get the quantity of a currency in a Value where there is no explicit quantity of that currency in the Value, then the quantity is taken to be zero.

There is no 'Ord Value' instance since Value is only a partial order, so compare can't do the right thing in some cases.

Constructors

Value 

Instances

Instances details
Data Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

gfoldl ∷ (∀ d b. Data d ⇒ c (d → b) → d → c b) → (∀ g. g → c g) → Value → c Value Source #

gunfold ∷ (∀ b r. Data b ⇒ c (b → r) → c r) → (∀ r. r → c r) → Constr → c Value Source #

toConstrValueConstr Source #

dataTypeOfValueDataType Source #

dataCast1Typeable t ⇒ (∀ d. Data d ⇒ c (t d)) → Maybe (c Value) Source #

dataCast2Typeable t ⇒ (∀ d e. (Data d, Data e) ⇒ c (t d e)) → Maybe (c Value) Source #

gmapT ∷ (∀ b. Data b ⇒ b → b) → ValueValue Source #

gmapQl ∷ (r → r' → r) → r → (∀ d. Data d ⇒ d → r') → Value → r Source #

gmapQr ∷ ∀ r r'. (r' → r → r) → r → (∀ d. Data d ⇒ d → r') → Value → r Source #

gmapQ ∷ (∀ d. Data d ⇒ d → u) → Value → [u] Source #

gmapQiInt → (∀ d. Data d ⇒ d → u) → Value → u Source #

gmapMMonad m ⇒ (∀ d. Data d ⇒ d → m d) → Value → m Value Source #

gmapMpMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → Value → m Value Source #

gmapMoMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → Value → m Value Source #

Monoid Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

Semigroup Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

(<>)ValueValueValue Source #

sconcatNonEmpty ValueValue Source #

stimesIntegral b ⇒ b → ValueValue Source #

Generic Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

Associated Types

type Rep ValueTypeType Source #

Methods

fromValueRep Value x Source #

toRep Value x → Value Source #

Show Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

NFData Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

rnfValue → () Source #

Eq Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

(==)ValueValueBool Source #

(/=)ValueValueBool Source #

HasBlueprintDefinition Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

Associated Types

type Unroll Value ∷ [Type] Source #

Eq Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

(==)ValueValueBool Source #

FromData Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

ToData Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

UnsafeFromData Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

JoinSemiLattice Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

(\/)ValueValueValue Source #

MeetSemiLattice Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

(/\)ValueValueValue Source #

Group Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

invValueValue Source #

Monoid Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

memptyValue Source #

AdditiveGroup Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

(-)ValueValueValue Source #

AdditiveMonoid Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

zeroValue Source #

AdditiveSemigroup Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

(+)ValueValueValue Source #

Semigroup Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

(<>)ValueValueValue Source #

Pretty Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

prettyValueDoc ann Source #

prettyList ∷ [Value] → Doc ann Source #

HasBlueprintSchema Value referencedTypes Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

schemaSchema referencedTypes Source #

Lift DefaultUni Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

Module Integer Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

scaleIntegerValueValue Source #

Typeable DefaultUni Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

type Rep Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

type Rep Value = D1 ('MetaData "Value" "PlutusLedgerApi.V1.Value" "plutus-ledger-api-1.36.0.0-inplace" 'True) (C1 ('MetaCons "Value" 'PrefixI 'True) (S1 ('MetaSel ('Just "getValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map CurrencySymbol (Map TokenName Integer)))))
type Unroll Value Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

newtype CurrencySymbol Source #

ByteString representing the currency, hashed with BLAKE2b-224. It is empty for Ada, 28 bytes for MintingPolicyHash. Forms an AssetClass along with TokenName. A Value is a map from CurrencySymbol's to a map from TokenName to an Integer.

This is a simple type without any validation, use with caution. You may want to add checks for its invariants. See the Shelley ledger specification.

Instances

Instances details
Data CurrencySymbol Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

Methods

gfoldl ∷ (∀ d b. Data d ⇒ c (d → b) → d → c b) → (∀ g. g → c g) → CurrencySymbol → c CurrencySymbol Source #

gunfold ∷ (∀ b r. Data b ⇒ c (b → r) → c r) → (∀ r. r → c r) → Constr → c CurrencySymbol Source #

toConstrCurrencySymbolConstr Source #

dataTypeOfCurrencySymbolDataType Source #

dataCast1Typeable t ⇒ (∀ d. Data d ⇒ c (t d)) → Maybe (c CurrencySymbol) Source #

dataCast2Typeable t ⇒ (∀ d e. (Data d, Data e) ⇒ c (t d e)) → Maybe (c CurrencySymbol) Source #

gmapT ∷ (∀ b. Data b ⇒ b → b) → CurrencySymbolCurrencySymbol Source #

gmapQl ∷ (r → r' → r) → r → (∀ d. Data d ⇒ d → r') → CurrencySymbol → r Source #

gmapQr ∷ ∀ r r'. (r' → r → r) → r → (∀ d. Data d ⇒ d → r') → CurrencySymbol → r Source #

gmapQ ∷ (∀ d. Data d ⇒ d → u) → CurrencySymbol → [u] Source #

gmapQiInt → (∀ d. Data d ⇒ d → u) → CurrencySymbol → u Source #

gmapMMonad m ⇒ (∀ d. Data d ⇒ d → m d) → CurrencySymbol → m CurrencySymbol Source #

gmapMpMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → CurrencySymbol → m CurrencySymbol Source #

gmapMoMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → CurrencySymbol → m CurrencySymbol Source #

IsString CurrencySymbol Source #

from hex encoding

Instance details

Defined in PlutusLedgerApi.V1.Value

Generic CurrencySymbol Source # 
Instance details

Defined in PlutusLedgerApi.V1.Value

Associated Types

type Rep CurrencySymbolTypeType Source #

Show CurrencySymbol Source #

using hex encoding

Instance details

Defined in PlutusLedgerApi.V1.Value