Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
The interface to Plutus V3 for the ledger.
Synopsis
- type SerialisedScript = ShortByteString
- serialiseCompiledCode :: forall a. CompiledCode a -> SerialisedScript
- serialiseUPLC :: Program DeBruijn DefaultUni DefaultFun () -> SerialisedScript
- deserialiseUPLC :: SerialisedScript -> Program DeBruijn DefaultUni DefaultFun ()
- assertScriptWellFormed :: MonadError ScriptDecodeError m => ProtocolVersion -> SerialisedScript -> m ()
- evaluateScriptRestricting :: ProtocolVersion -> VerboseMode -> EvaluationContext -> ExBudget -> SerialisedScript -> [Data] -> (LogOutput, Either EvaluationError ExBudget)
- evaluateScriptCounting :: ProtocolVersion -> VerboseMode -> EvaluationContext -> SerialisedScript -> [Data] -> (LogOutput, Either EvaluationError ExBudget)
- data ProtocolVersion = ProtocolVersion {}
- data VerboseMode
- type LogOutput = [Text]
- data ExBudget = ExBudget {}
- newtype ExCPU = ExCPU CostingInteger
- newtype ExMemory = ExMemory CostingInteger
- data SatInt
- data EvaluationContext
- mkEvaluationContext :: (MonadError CostModelApplyError m, MonadWriter [CostModelApplyWarn] m) => [Integer] -> m EvaluationContext
- data ParamName
- = 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
- | SerialiseData'cpu'arguments'intercept
- | SerialiseData'cpu'arguments'slope
- | SerialiseData'memory'arguments'intercept
- | SerialiseData'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
- | VerifyEcdsaSecp256k1Signature'cpu'arguments
- | VerifyEcdsaSecp256k1Signature'memory'arguments
- | VerifyEd25519Signature'cpu'arguments'intercept
- | VerifyEd25519Signature'cpu'arguments'slope
- | VerifyEd25519Signature'memory'arguments
- | VerifySchnorrSecp256k1Signature'cpu'arguments'intercept
- | VerifySchnorrSecp256k1Signature'cpu'arguments'slope
- | VerifySchnorrSecp256k1Signature'memory'arguments
- data CostModelApplyError
- type CostModelParams = Map Text Integer
- assertWellFormedCostModelParams :: MonadError CostModelApplyError m => CostModelParams -> m ()
- data ScriptContext = ScriptContext {}
- data ScriptPurpose
- data BuiltinByteString
- toBuiltin :: ToBuiltin a arep => a -> arep
- fromBuiltin :: FromBuiltin arep a => arep -> a
- newtype LedgerBytes = LedgerBytes {}
- fromBytes :: ByteString -> LedgerBytes
- data DCert
- data StakingCredential
- data Credential
- newtype Value = Value {}
- newtype CurrencySymbol = CurrencySymbol {}
- newtype TokenName = TokenName {}
- singleton :: CurrencySymbol -> TokenName -> Integer -> Value
- unionWith :: (Integer -> Integer -> Integer) -> Value -> Value -> Value
- adaSymbol :: CurrencySymbol
- adaToken :: TokenName
- newtype POSIXTime = POSIXTime {}
- type POSIXTimeRange = Interval POSIXTime
- data Address = Address {}
- newtype PubKeyHash = PubKeyHash {}
- newtype TxId = TxId {}
- data TxInfo = TxInfo {
- txInfoInputs :: [TxInInfo]
- txInfoReferenceInputs :: [TxInInfo]
- txInfoOutputs :: [TxOut]
- txInfoFee :: Value
- txInfoMint :: Value
- txInfoDCert :: [DCert]
- txInfoWdrl :: Map StakingCredential Integer
- txInfoValidRange :: POSIXTimeRange
- txInfoSignatories :: [PubKeyHash]
- txInfoRedeemers :: Map ScriptPurpose Redeemer
- txInfoData :: Map DatumHash Datum
- txInfoId :: TxId
- data TxOut = TxOut {}
- data TxOutRef = TxOutRef {
- txOutRefId :: TxId
- txOutRefIdx :: Integer
- data TxInInfo = TxInInfo {}
- data OutputDatum
- data Interval a = Interval {
- ivFrom :: LowerBound a
- ivTo :: UpperBound a
- data Extended a
- type Closure = Bool
- data UpperBound a = UpperBound (Extended a) Closure
- data LowerBound a = LowerBound (Extended a) Closure
- always :: Interval a
- from :: a -> Interval a
- to :: a -> Interval a
- lowerBound :: a -> LowerBound a
- upperBound :: a -> UpperBound a
- strictLowerBound :: a -> LowerBound a
- strictUpperBound :: a -> UpperBound a
- data Map k v
- fromList :: [(k, v)] -> Map k v
- newtype ScriptHash = ScriptHash {}
- newtype Redeemer = Redeemer {}
- newtype RedeemerHash = RedeemerHash BuiltinByteString
- newtype Datum = Datum {}
- newtype DatumHash = DatumHash BuiltinByteString
- data Data
- data BuiltinData = BuiltinData Data
- class ToData a where
- toBuiltinData :: a -> BuiltinData
- class FromData a where
- fromBuiltinData :: BuiltinData -> Maybe a
- class UnsafeFromData a where
- unsafeFromBuiltinData :: BuiltinData -> a
- toData :: ToData a => a -> Data
- fromData :: FromData a => Data -> Maybe a
- dataToBuiltinData :: Data -> BuiltinData
- builtinDataToData :: BuiltinData -> Data
- data EvaluationError
- data ScriptDecodeError
Scripts
type SerialisedScript = ShortByteString Source #
Scripts to the ledger are serialised bytestrings.
serialiseCompiledCode :: forall a. CompiledCode a -> SerialisedScript Source #
serialiseUPLC :: Program DeBruijn DefaultUni DefaultFun () -> SerialisedScript Source #
Note [Using Flat for serialising/deserialising Script] `plutus-ledger` uses CBOR for data serialisation and `plutus-core` uses Flat. The choice to use Flat was made to have a more efficient (most wins are in uncompressed size) data serialisation format and use less space on-chain.
To make `plutus-ledger` work with scripts serialised with Flat, and keep the CBOR
format otherwise, we have defined the serialiseUPLC
and deserialiseUPLC
functions.
Because Flat is not self-describing and it gets used in the encoding of Programs, data structures that include scripts (for example, transactions) no-longer benefit for CBOR's ability to self-describe it's format.
Validating scripts
assertScriptWellFormed :: MonadError ScriptDecodeError m => ProtocolVersion -> SerialisedScript -> m () Source #
Check if a Script
is "valid" according to a protocol version. At the moment this means "deserialises correctly", which in particular
implies that it is (almost certainly) an encoded script and the script does not mention any builtins unavailable in the given protocol version.
Running scripts
evaluateScriptRestricting Source #
:: ProtocolVersion | |
-> VerboseMode | Whether to produce log output |
-> EvaluationContext | The cost model that should already be synced to the most recent cost-model-params coming from the current protocol |
-> ExBudget | The resource budget which must not be exceeded during evaluation |
-> SerialisedScript | 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 #
:: ProtocolVersion | |
-> VerboseMode | Whether to produce log output |
-> EvaluationContext | The cost model that should already be synced to the most recent cost-model-params coming from the current protocol |
-> SerialisedScript | 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
data ProtocolVersion Source #
This represents the Cardano protocol version, with its major and minor components. This relies on careful understanding between us and the ledger as to what this means.
Instances
Verbose mode and log output
data VerboseMode Source #
A simple toggle indicating whether or not we should produce logs.
Instances
Eq VerboseMode Source # | |
Defined in PlutusLedgerApi.Common.Eval (==) :: VerboseMode -> VerboseMode -> Bool Source # (/=) :: VerboseMode -> VerboseMode -> Bool Source # |
Costing-related types
Instances
FromJSON ExBudget | |
ToJSON ExBudget | |
Monoid ExBudget | |
Semigroup ExBudget | |
Generic ExBudget | |
Show ExBudget | |
NFData ExBudget | |
Defined in PlutusCore.Evaluation.Machine.ExBudget | |
Eq ExBudget | |
NoThunks ExBudget | |
Pretty ExBudget | |
Serialise ExBudget | |
ab ~ ExBudget => OnMemoryUsages ExBudget ab | |
Defined in PlutusCore.Evaluation.Machine.CostingFun.Core onMemoryUsages :: ExBudget -> ab | |
PrettyBy config ExBudget | |
Lift ExBudget | |
type Rep ExBudget | |
Defined in PlutusCore.Evaluation.Machine.ExBudget type Rep ExBudget = D1 ('MetaData "ExBudget" "PlutusCore.Evaluation.Machine.ExBudget" "plutus-core-1.0.0.0.0.0.0.0.1-4IL9F87IOMGE1LK9JtuHT8" 'False) (C1 ('MetaCons "ExBudget" 'PrefixI 'True) (S1 ('MetaSel ('Just "exBudgetCPU") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedUnpack) (Rec0 ExCPU) :*: S1 ('MetaSel ('Just "exBudgetMemory") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedUnpack) (Rec0 ExMemory))) |
Counts CPU units in picoseconds: maximum value for SatInt is 2^63 ps, or appproximately 106 days.
Instances
FromJSON ExCPU | |
ToJSON ExCPU | |
Monoid ExCPU | |
Semigroup ExCPU | |
Generic ExCPU | |
Num ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory | |
Show ExCPU | |
NFData ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory | |
Eq ExCPU | |
Ord ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory | |
NoThunks ExCPU | |
Pretty ExCPU | |
Serialise ExCPU | |
PrettyBy config ExCPU | |
Lift ExCPU | |
type Rep ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory type Rep ExCPU = D1 ('MetaData "ExCPU" "PlutusCore.Evaluation.Machine.ExMemory" "plutus-core-1.0.0.0.0.0.0.0.1-4IL9F87IOMGE1LK9JtuHT8" 'True) (C1 ('MetaCons "ExCPU" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CostingInteger))) |
Counts size in machine words.
Instances
Instances
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 recomputed on every evaluation.
There are two sets of parameters: one is with immediate unlifting and the other one is with deferred unlifting. We have to keep both of them, because depending on the language version either one has to be used or the other. We also compile them separately due to all the inlining and optimization that need to happen for things to be efficient.
Instances
Generic EvaluationContext Source # | |
Defined in PlutusLedgerApi.Common.Eval from :: EvaluationContext -> Rep EvaluationContext x Source # to :: Rep EvaluationContext x -> EvaluationContext Source # | |
NFData EvaluationContext Source # | |
Defined in PlutusLedgerApi.Common.Eval rnf :: EvaluationContext -> () Source # | |
NoThunks EvaluationContext Source # | |
Defined in PlutusLedgerApi.Common.Eval | |
type Rep EvaluationContext Source # | |
Defined in PlutusLedgerApi.Common.Eval type Rep EvaluationContext = D1 ('MetaData "EvaluationContext" "PlutusLedgerApi.Common.Eval" "plutus-ledger-api-1.0.0.0.0.0.0.0.1-62zX2BmwjkDFan4zfGhQ4n" 'False) (C1 ('MetaCons "EvaluationContext" 'PrefixI 'True) (S1 ('MetaSel ('Just "machineParametersImmediate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 DefaultMachineParameters) :*: S1 ('MetaSel ('Just "machineParametersDeferred") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 DefaultMachineParameters))) |
mkEvaluationContext :: (MonadError CostModelApplyError m, MonadWriter [CostModelApplyWarn] m) => [Integer] -> m EvaluationContext Source #
Build the EvaluationContext
.
The input is a list of integer values passed from the ledger and are expected to appear in correct order.
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]
Instances
Bounded ParamName Source # | |
Enum ParamName Source # | |
Defined in PlutusLedgerApi.V3.ParamName succ :: ParamName -> ParamName Source # pred :: ParamName -> ParamName Source # toEnum :: Int -> ParamName Source # fromEnum :: ParamName -> Int Source # enumFrom :: ParamName -> [ParamName] Source # enumFromThen :: ParamName -> ParamName -> [ParamName] Source # enumFromTo :: ParamName -> ParamName -> [ParamName] Source # enumFromThenTo :: ParamName -> ParamName -> ParamName -> [ParamName] Source # | |
Generic ParamName Source # | |
Ix ParamName Source # | |
Defined in PlutusLedgerApi.V3.ParamName | |
Eq ParamName Source # | |
Ord ParamName Source # | |
Defined in PlutusLedgerApi.V3.ParamName | |
IsParamName ParamName Source # | |
Defined in PlutusLedgerApi.V3.ParamName showParamName :: ParamName -> String Source # | |
type Rep ParamName Source # | |
Defined in PlutusLedgerApi.V3.ParamName type Rep ParamName = D1 ('MetaData "ParamName" "PlutusLedgerApi.V3.ParamName" "plutus-ledger-api-1.0.0.0.0.0.0.0.1-62zX2BmwjkDFan4zfGhQ4n" 'False) (((((((C1 ('MetaCons "AddInteger'cpu'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AddInteger'cpu'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AddInteger'memory'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AddInteger'memory'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AppendByteString'cpu'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "AppendByteString'cpu'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AppendByteString'memory'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AppendByteString'memory'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AppendString'cpu'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AppendString'cpu'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "AppendString'memory'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AppendString'memory'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BData'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BData'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Blake2b_256'cpu'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Blake2b_256'cpu'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Blake2b_256'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CekApplyCost'exBudgetCPU" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "CekApplyCost'exBudgetMemory" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CekBuiltinCost'exBudgetCPU" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CekBuiltinCost'exBudgetMemory" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "CekConstCost'exBudgetCPU" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CekConstCost'exBudgetMemory" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CekDelayCost'exBudgetCPU" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CekDelayCost'exBudgetMemory" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CekForceCost'exBudgetCPU" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "CekForceCost'exBudgetMemory" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CekLamCost'exBudgetCPU" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CekLamCost'exBudgetMemory" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "CekStartupCost'exBudgetCPU" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CekStartupCost'exBudgetMemory" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CekVarCost'exBudgetCPU" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "CekVarCost'exBudgetMemory" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ChooseData'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ChooseData'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ChooseList'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ChooseList'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ChooseUnit'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ChooseUnit'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ConsByteString'cpu'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ConsByteString'cpu'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ConsByteString'memory'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ConsByteString'memory'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "ConstrData'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ConstrData'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "DecodeUtf8'cpu'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DecodeUtf8'cpu'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DecodeUtf8'memory'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "DecodeUtf8'memory'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DivideInteger'cpu'arguments'constant" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DivideInteger'cpu'arguments'model'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "DivideInteger'cpu'arguments'model'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "DivideInteger'memory'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DivideInteger'memory'arguments'minimum" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "DivideInteger'memory'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EncodeUtf8'cpu'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EncodeUtf8'cpu'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EncodeUtf8'memory'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EncodeUtf8'memory'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "EqualsByteString'cpu'arguments'constant" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EqualsByteString'cpu'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EqualsByteString'cpu'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "EqualsByteString'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EqualsData'cpu'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EqualsData'cpu'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "EqualsData'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EqualsInteger'cpu'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "EqualsInteger'cpu'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EqualsInteger'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EqualsString'cpu'arguments'constant" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "EqualsString'cpu'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EqualsString'cpu'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EqualsString'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "FstPair'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "FstPair'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "HeadList'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "HeadList'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IData'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "IData'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "IfThenElse'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IfThenElse'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "IndexByteString'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "IndexByteString'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LengthOfByteString'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "LengthOfByteString'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LessThanByteString'cpu'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LessThanByteString'cpu'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type)))))))) :+: ((((((C1 ('MetaCons "LessThanByteString'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LessThanEqualsByteString'cpu'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LessThanEqualsByteString'cpu'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LessThanEqualsByteString'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LessThanEqualsInteger'cpu'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "LessThanEqualsInteger'cpu'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LessThanEqualsInteger'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LessThanInteger'cpu'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "LessThanInteger'cpu'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LessThanInteger'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ListData'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "ListData'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MapData'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MapData'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MkCons'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MkCons'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "MkNilData'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MkNilData'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MkNilPairData'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "MkNilPairData'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MkPairData'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MkPairData'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "ModInteger'cpu'arguments'constant" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ModInteger'cpu'arguments'model'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ModInteger'cpu'arguments'model'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ModInteger'memory'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ModInteger'memory'arguments'minimum" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "ModInteger'memory'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MultiplyInteger'cpu'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MultiplyInteger'cpu'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "MultiplyInteger'memory'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "MultiplyInteger'memory'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NullList'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "NullList'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QuotientInteger'cpu'arguments'constant" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "QuotientInteger'cpu'arguments'model'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "QuotientInteger'cpu'arguments'model'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QuotientInteger'memory'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "QuotientInteger'memory'arguments'minimum" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "QuotientInteger'memory'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RemainderInteger'cpu'arguments'constant" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "RemainderInteger'cpu'arguments'model'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RemainderInteger'cpu'arguments'model'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RemainderInteger'memory'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "RemainderInteger'memory'arguments'minimum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RemainderInteger'memory'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SerialiseData'cpu'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SerialiseData'cpu'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SerialiseData'memory'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "SerialiseData'memory'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Sha2_256'cpu'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Sha2_256'cpu'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Sha2_256'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Sha3_256'cpu'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Sha3_256'cpu'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Sha3_256'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SliceByteString'cpu'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SliceByteString'cpu'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SliceByteString'memory'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SliceByteString'memory'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "SndPair'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SndPair'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SubtractInteger'cpu'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "SubtractInteger'cpu'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SubtractInteger'memory'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SubtractInteger'memory'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "TailList'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TailList'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Trace'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Trace'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnBData'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "UnBData'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UnConstrData'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnConstrData'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "UnIData'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "UnIData'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnListData'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "UnListData'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UnMapData'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UnMapData'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "VerifyEcdsaSecp256k1Signature'cpu'arguments" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "VerifyEcdsaSecp256k1Signature'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "VerifyEd25519Signature'cpu'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "VerifyEd25519Signature'cpu'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "VerifyEd25519Signature'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "VerifySchnorrSecp256k1Signature'cpu'arguments'intercept" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "VerifySchnorrSecp256k1Signature'cpu'arguments'slope" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "VerifySchnorrSecp256k1Signature'memory'arguments" 'PrefixI 'False) (U1 :: Type -> Type))))))))) |
data CostModelApplyError Source #
The type of errors that applyParams
can throw.
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) |
CMTooFewParamsError | See Note [Cost model parameters from the ledger's point of view] |
|
Instances
assertWellFormedCostModelParams :: MonadError CostModelApplyError m => CostModelParams -> m () Source #
Comparably expensive to mkEvaluationContext
, so it should only be used sparingly.
Context types
data ScriptContext Source #
Instances
data ScriptPurpose Source #
Purpose of the script that is currently running
Instances
Supporting types used in the context types
ByteStrings
data BuiltinByteString Source #
An opaque type representing Plutus Core ByteStrings.
Instances
fromBuiltin :: FromBuiltin arep a => arep -> a Source #
Bytes
newtype LedgerBytes Source #
Instances
fromBytes :: ByteString -> LedgerBytes Source #
Certificates
A representation of the ledger DCert. Some information is digested, and not included
DCertDelegRegKey StakingCredential | |
DCertDelegDeRegKey StakingCredential | |
DCertDelegDelegate | |
| |
DCertPoolRegister | A digest of the PoolParams |
| |
DCertPoolRetire PubKeyHash Integer | The retiremant certificate and the Epoch N |
DCertGenesis | A really terse Digest |
DCertMir | Another really terse Digest |
Instances
Credentials
data StakingCredential Source #
Staking credential used to assign rewards.
StakingHash Credential | The staking hash is the |
StakingPtr | The certificate pointer, constructed by the given
slot number, transaction and certificate indices.
NB: The fields should really be all |
Instances
data Credential Source #
Credentials required to unlock a transaction output.
PubKeyCredential PubKeyHash | The transaction that spends this output must be signed by the private key.
See |
ScriptCredential ScriptHash | The transaction that spends this output must include the validator script and
be accepted by the validator. See |
Instances
Value
The Value
type represents a collection of amounts of different currencies.
We can think of Value
as a vector space whose dimensions are currencies.
To create a value of Value
, we need to specify a currency. This can be done
using adaValueOf
. To get the ada dimension of Value
we use
fromValue
. Plutus contract authors will be able to define modules
similar to Ada
for their own 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 Value
s 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.
Instances
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
ByteString of a name of a token.
Shown as UTF-8 string when possible.
Should be no longer than 32 bytes, empty for Ada.
Forms an AssetClass
along with a CurrencySymbol
.
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
singleton :: CurrencySymbol -> TokenName -> Integer -> Value Source #
Make a Value
containing only the given quantity of the given currency.
adaSymbol :: CurrencySymbol Source #
The CurrencySymbol
of the Ada
currency.
Time
POSIX time is measured as the number of milliseconds since 1970-01-01T00:00:00Z.
This is not the same as Haskell's POSIXTime
Instances
Types for representing transactions
Address with two kinds of credentials, normal and staking.
Instances
newtype PubKeyHash Source #
The hash of a public key. This is frequently used to identify the public key, rather than the key itself. Hashed with BLAKE2b-224. 28 bytes.
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
A transaction ID, i.e. the hash of a transaction. Hashed with BLAKE2b-256. 32 byte.
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
A pending transaction. This is the view as seen by validator scripts, so some details are stripped out.
TxInfo | |
|
Instances
A transaction output, consisting of a target address, a value, optionally a datum/datum hash, and optionally a reference script.
Instances
A reference to a transaction output. This is a
pair of a transaction ID (TxId
), and an index indicating which of the outputs
of that transaction we are referring to.
TxOutRef | |
|
Instances
An input of a pending transaction.
Instances
data OutputDatum Source #
The datum attached to an output: either nothing; a datum hash; or the datum itself (an "inline datum").
Instances
Intervals
An interval of a
s.
The interval may be either closed or open at either end, meaning that the endpoints may or may not be included in the interval.
The interval can also be unbounded on either side.
Interval | |
|
Instances
A set extended with a positive and negative infinity.
Instances
data UpperBound a Source #
The upper bound of an interval.
Instances
data LowerBound a Source #
The lower bound of an interval.
Instances
from :: a -> Interval a Source #
from a
is an Interval
that includes all values that are
greater than or equal to a
.
to :: a -> Interval a Source #
to a
is an Interval
that includes all values that are
smaller than or equal to a
.
lowerBound :: a -> LowerBound a Source #
upperBound :: a -> UpperBound a Source #
strictLowerBound :: a -> LowerBound a Source #
strictUpperBound :: a -> UpperBound a Source #
Association maps
A Map
of key-value pairs.
Instances
Lift DefaultUni [(k, v)] => Lift DefaultUni (Map k v) | |
Defined in PlutusTx.AssocMap lift :: Map k v -> RTCompile DefaultUni fun (Term TyName Name DefaultUni fun ()) Source # | |
Foldable (Map k) | |
Functor (Map k) | |
Traversable (Map k) | |
Defined in PlutusTx.AssocMap | |
(Data k, Data v) => Data (Map k v) | |
Defined in PlutusTx.AssocMap gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Map k v -> c (Map k v) Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Map k v) Source # toConstr :: Map k v -> Constr Source # dataTypeOf :: Map k v -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Map k v)) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Map k v)) Source # gmapT :: (forall b. Data b => b -> b) -> Map k v -> Map k v Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Map k v -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Map k v -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Map k v -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Map k v -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Map k v -> m (Map k v) Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k v -> m (Map k v) Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k v -> m (Map k v) Source # | |
Generic (Map k v) | |
(Show k, Show v) => Show (Map k v) | |
(NFData k, NFData v) => NFData (Map k v) | |
Defined in PlutusTx.AssocMap | |
(Eq k, Eq v) => Eq (Map k v) | |
(Eq k, Eq v) => Eq (Map k v) | |
(FromData k, FromData v) => FromData (Map k v) | |
Defined in PlutusTx.AssocMap fromBuiltinData :: BuiltinData -> Maybe (Map k v) Source # | |
(ToData k, ToData v) => ToData (Map k v) | |
Defined in PlutusTx.AssocMap toBuiltinData :: Map k v -> BuiltinData Source # | |
(UnsafeFromData k, UnsafeFromData v) => UnsafeFromData (Map k v) | |
Defined in PlutusTx.AssocMap unsafeFromBuiltinData :: BuiltinData -> Map k v Source # | |
(Eq k, Semigroup v) => Monoid (Map k v) | |
Defined in PlutusTx.AssocMap | |
(Ord k, Ord v) => Ord (Map k v) | |
(Eq k, Semigroup v) => Semigroup (Map k v) | |
(Pretty k, Pretty v) => Pretty (Map k v) | |
Typeable DefaultUni Map | |
Defined in PlutusTx.AssocMap typeRep :: Proxy Map -> RTCompile DefaultUni fun (Type TyName DefaultUni ()) Source # | |
type Rep (Map k v) | |
Defined in PlutusTx.AssocMap |
Newtypes and hash types
newtype ScriptHash Source #
Script runtime representation of a Digest SHA256
.
Instances
Redeemer
is a wrapper around Data
values that are used as redeemers in transaction inputs.
Instances
newtype RedeemerHash Source #
Type representing the BLAKE2b-256 hash of a redeemer. 32 bytes.
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
Datum
is a wrapper around Data
values which are used as data in transaction outputs.
Instances
Script runtime representation of a Digest SHA256
.
Instances
Data
A generic "data" type.
The main constructor Constr
represents a datatype value in sum-of-products
form: Constr i args
represents a use of the i
th constructor along with its arguments.
The other constructors are various primitives.
Instances
data BuiltinData Source #
A type corresponding to the Plutus Core builtin equivalent of Data
.
The point of this type is to be an opaque equivalent of Data
, so as to
ensure that it is only used in ways that the compiler can handle.
As such, you should use this type in your on-chain code, and in any data structures that you want to be representable on-chain.
For off-chain usage, there are conversion functions builtinDataToData
and
dataToBuiltinData
, but note that these will not work on-chain.
Instances
A typeclass for types that can be converted to and from BuiltinData
.
toBuiltinData :: a -> BuiltinData Source #
Convert a value to BuiltinData
.
Instances
class FromData a where Source #
fromBuiltinData :: BuiltinData -> Maybe a Source #
Convert a value from BuiltinData
, returning Nothing
if this fails.
Instances
class UnsafeFromData a where Source #
unsafeFromBuiltinData :: BuiltinData -> a Source #
Convert a value from BuiltinData
, calling error
if this fails.
This is typically much faster than fromBuiltinData
.
When implementing this function, make sure to call unsafeFromBuiltinData
rather than fromBuiltinData
when converting substructures!
This is a simple type without any validation, use with caution.
Instances
dataToBuiltinData :: Data -> BuiltinData Source #
Convert a Data
into a BuiltinData
. Only works off-chain.
builtinDataToData :: BuiltinData -> Data Source #
Convert a BuiltinData
into a Data
. Only works off-chain.
Errors
data EvaluationError Source #
Errors that can be thrown when evaluating a Plutus script.
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 |
IncompatibleVersionError (Version ()) | An error indicating a version tag that we don't support TODO: make this error more informative when we have more information about what went wrong |
CostModelParameterMismatch | An error indicating that the cost model parameters didn't match what we expected |
Instances
Show EvaluationError Source # | |
Defined in PlutusLedgerApi.Common.Eval | |
Eq EvaluationError Source # | |
Defined in PlutusLedgerApi.Common.Eval (==) :: EvaluationError -> EvaluationError -> Bool Source # (/=) :: EvaluationError -> EvaluationError -> Bool Source # | |
Pretty EvaluationError Source # | |
Defined in PlutusLedgerApi.Common.Eval pretty :: EvaluationError -> Doc ann Source # prettyList :: [EvaluationError] -> Doc ann Source # |
data ScriptDecodeError Source #