Safe Haskell | None |
---|---|
Language | Haskell2010 |
The interface to Plutus V1 for the ledger.
Synopsis
- type SerializedScript = ShortByteString
- data Script
- fromCompiledCode :: CompiledCode a -> Script
- isScriptWellFormed :: ProtocolVersion -> SerializedScript -> Bool
- evaluateScriptRestricting :: ProtocolVersion -> VerboseMode -> EvaluationContext -> ExBudget -> SerializedScript -> [Data] -> (LogOutput, Either EvaluationError ExBudget)
- evaluateScriptCounting :: ProtocolVersion -> VerboseMode -> EvaluationContext -> SerializedScript -> [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 => CostModelParams -> m EvaluationContext
- data CostModelApplyError
- type CostModelParams = Map Text Integer
- assertWellFormedCostModelParams :: MonadError CostModelApplyError m => CostModelParams -> m ()
- costModelParamNames :: Set Text
- 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]
- txInfoOutputs :: [TxOut]
- txInfoFee :: Value
- txInfoMint :: Value
- txInfoDCert :: [DCert]
- txInfoWdrl :: [(StakingCredential, Integer)]
- txInfoValidRange :: POSIXTimeRange
- txInfoSignatories :: [PubKeyHash]
- txInfoData :: [(DatumHash, Datum)]
- txInfoId :: TxId
- data TxOut = TxOut {}
- data TxOutRef = TxOutRef {
- txOutRefId :: TxId
- txOutRefIdx :: Integer
- data TxInInfo = TxInInfo {}
- 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
- newtype Validator = Validator {}
- mkValidatorScript :: CompiledCode (BuiltinData -> BuiltinData -> BuiltinData -> ()) -> Validator
- unValidatorScript :: Validator -> Script
- newtype ValidatorHash = ValidatorHash BuiltinByteString
- newtype MintingPolicy = MintingPolicy {}
- mkMintingPolicyScript :: CompiledCode (BuiltinData -> BuiltinData -> ()) -> MintingPolicy
- unMintingPolicyScript :: MintingPolicy -> Script
- newtype MintingPolicyHash = MintingPolicyHash BuiltinByteString
- newtype StakeValidator = StakeValidator {}
- mkStakeValidatorScript :: CompiledCode (BuiltinData -> BuiltinData -> ()) -> StakeValidator
- unStakeValidatorScript :: StakeValidator -> Script
- newtype StakeValidatorHash = StakeValidatorHash BuiltinByteString
- 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
- = CekError (CekEvaluationException NamedDeBruijn DefaultUni DefaultFun)
- | DeBruijnError FreeVariableError
- | CodecError DeserialiseFailure
- | IncompatibleVersionError (Version ())
- | CostModelParameterMismatch
Scripts
type SerializedScript = ShortByteString Source #
Scripts to the ledger are serialised bytestrings.
A script on the chain. This is an opaque type as far as the chain is concerned.
Instances
Eq Script Source # | Note [Using Flat inside CBOR instance of 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 a Serialise instance for Script, which is a wrapper over Programs serialised with Flat. The instance will see programs as an opaque ByteString, which is the result of encoding programs using Flat. 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. |
Ord Script Source # | |
Defined in Plutus.V1.Ledger.Scripts | |
Show Script Source # | |
Generic Script Source # | |
NFData Script Source # | |
Defined in Plutus.V1.Ledger.Scripts | |
Serialise Script Source # | |
Defined in Plutus.V1.Ledger.Scripts encodeList :: [Script] -> Encoding decodeList :: Decoder s [Script] | |
type Rep Script Source # | |
Defined in Plutus.V1.Ledger.Scripts type Rep Script = D1 ('MetaData "Script" "Plutus.V1.Ledger.Scripts" "plutus-ledger-api-1.0.0.1-6EvbyJiK8IAAVEtnIJDu5Z" 'True) (C1 ('MetaCons "Script" 'PrefixI 'True) (S1 ('MetaSel ('Just "unScript") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Program DeBruijn DefaultUni DefaultFun ())))) |
fromCompiledCode :: CompiledCode a -> Script Source #
Turn a CompiledCode
(usually produced by compile
) into a Script
for use with this package.
Validating scripts
isScriptWellFormed :: ProtocolVersion -> SerializedScript -> Bool 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 |
-> SerializedScript | 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 |
-> SerializedScript | 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
Eq ProtocolVersion Source # | |
Defined in Plutus.ApiCommon (==) :: ProtocolVersion -> ProtocolVersion -> Bool Source # (/=) :: ProtocolVersion -> ProtocolVersion -> Bool Source # | |
Ord ProtocolVersion Source # | |
Defined in Plutus.ApiCommon compare :: ProtocolVersion -> ProtocolVersion -> Ordering Source # (<) :: ProtocolVersion -> ProtocolVersion -> Bool Source # (<=) :: ProtocolVersion -> ProtocolVersion -> Bool Source # (>) :: ProtocolVersion -> ProtocolVersion -> Bool Source # (>=) :: ProtocolVersion -> ProtocolVersion -> Bool Source # max :: ProtocolVersion -> ProtocolVersion -> ProtocolVersion Source # min :: ProtocolVersion -> ProtocolVersion -> ProtocolVersion Source # | |
Show ProtocolVersion Source # | |
Defined in Plutus.ApiCommon | |
Pretty ProtocolVersion Source # | |
Defined in Plutus.ApiCommon pretty :: ProtocolVersion -> Doc ann prettyList :: [ProtocolVersion] -> Doc ann |
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 Plutus.ApiCommon (==) :: VerboseMode -> VerboseMode -> Bool Source # (/=) :: VerboseMode -> VerboseMode -> Bool Source # |
Costing-related types
Instances
ExCPU CostingInteger |
Instances
Eq ExCPU | |
Num ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory | |
Ord ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory | |
Show ExCPU | |
Generic ExCPU | |
Semigroup ExCPU | |
Monoid ExCPU | |
NFData ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory | |
Pretty ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory prettyList :: [ExCPU] -> Doc ann | |
FromJSON ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory parseJSON :: Value -> Parser ExCPU parseJSONList :: Value -> Parser [ExCPU] | |
ToJSON ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory | |
NoThunks ExCPU | |
Lift ExCPU | |
PrettyBy config ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory prettyBy :: config -> ExCPU -> Doc ann prettyListBy :: config -> [ExCPU] -> Doc ann | |
type Rep ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory |
ExMemory CostingInteger |
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
mkEvaluationContext :: MonadError CostModelApplyError m => CostModelParams -> m EvaluationContext Source #
Build the EvaluationContext
.
The input is a Map
of strings to cost integer values (aka CostModelParams
, CostModel
)
See Note [Inlining meanings of builtins].
data CostModelApplyError #
Instances
Show CostModelApplyError | |
Exception CostModelApplyError | |
Pretty CostModelApplyError | |
Defined in PlutusCore.Evaluation.Machine.CostModelInterface pretty :: CostModelApplyError -> Doc ann prettyList :: [CostModelApplyError] -> Doc ann |
type CostModelParams = Map Text Integer #
assertWellFormedCostModelParams :: MonadError CostModelApplyError m => CostModelParams -> m () Source #
Comparably expensive to mkEvaluationContext
, so it should only be used sparingly.
costModelParamNames :: Set Text Source #
The set of valid names that a cost model parameter can take for this language version.
It is used for the deserialization of CostModelParams
.
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 #
Instances
fromBuiltin :: FromBuiltin arep a => arep -> a #
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
Instances
data Credential Source #
Credential required to unlock a transaction output
PubKeyCredential PubKeyHash | The transaction that spends this output must be signed by the private key |
ScriptCredential ValidatorHash | The transaction that spends this output must include the validator script and be accepted by the validator. |
Instances
Value
A cryptocurrency value. This is a map from CurrencySymbol
s to a
quantity of that currency.
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.
See note [Currencies] for more details.
Instances
newtype CurrencySymbol Source #
Instances
ByteString of a name of a token, shown as UTF-8 string when possible
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
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.
Instances
A transaction ID, using a SHA256 hash as the transaction id.
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, and optionally a datum hash.
Instances
A reference to a transaction output. This is a pair of a transaction reference, and an index indicating which of the outputs of that transaction we are referring to.
TxOutRef | |
|
Instances
An input of a pending transaction.
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 #
Newtypes for script/datum types and hash types
Instances
Eq Validator Source # | |
Ord Validator Source # | |
Defined in Plutus.V1.Ledger.Scripts | |
Show Validator Source # | |
Generic Validator Source # | |
NFData Validator Source # | |
Defined in Plutus.V1.Ledger.Scripts | |
Serialise Validator Source # | |
Defined in Plutus.V1.Ledger.Scripts encode :: Validator -> Encoding encodeList :: [Validator] -> Encoding decodeList :: Decoder s [Validator] | |
Pretty Validator Source # | |
Defined in Plutus.V1.Ledger.Scripts pretty :: Validator -> Doc ann prettyList :: [Validator] -> Doc ann | |
type Rep Validator Source # | |
Defined in Plutus.V1.Ledger.Scripts |
mkValidatorScript :: CompiledCode (BuiltinData -> BuiltinData -> BuiltinData -> ()) -> Validator Source #
unValidatorScript :: Validator -> Script Source #
newtype ValidatorHash Source #
Script runtime representation of a Digest SHA256
.
Instances
newtype MintingPolicy Source #
MintingPolicy
is a wrapper around Script
s which are used as validators for minting constraints.
Instances
mkMintingPolicyScript :: CompiledCode (BuiltinData -> BuiltinData -> ()) -> MintingPolicy Source #
newtype MintingPolicyHash Source #
Script runtime representation of a Digest SHA256
.
Instances
newtype StakeValidator Source #
StakeValidator
is a wrapper around Script
s which are used as validators for withdrawals and stake address certificates.
Instances
mkStakeValidatorScript :: CompiledCode (BuiltinData -> BuiltinData -> ()) -> StakeValidator Source #
newtype StakeValidatorHash 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 #
Script runtime representation of a Digest SHA256
.
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
Instances
Eq Data | |
Data Data | |
Defined in PlutusCore.Data gfoldl :: (forall d b. Data0 d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Data -> c Data Source # gunfold :: (forall b r. Data0 b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Data Source # toConstr :: Data -> Constr Source # dataTypeOf :: Data -> DataType Source # dataCast1 :: Typeable t => (forall d. Data0 d => c (t d)) -> Maybe (c Data) Source # dataCast2 :: Typeable t => (forall d e. (Data0 d, Data0 e) => c (t d e)) -> Maybe (c Data) Source # gmapT :: (forall b. Data0 b => b -> b) -> Data -> Data Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data0 d => d -> r') -> Data -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data0 d => d -> r') -> Data -> r Source # gmapQ :: (forall d. Data0 d => d -> u) -> Data -> [u] Source # gmapQi :: Int -> (forall d. Data0 d => d -> u) -> Data -> u Source # gmapM :: Monad m => (forall d. Data0 d => d -> m d) -> Data -> m Data Source # gmapMp :: MonadPlus m => (forall d. Data0 d => d -> m d) -> Data -> m Data Source # gmapMo :: MonadPlus m => (forall d. Data0 d => d -> m d) -> Data -> m Data Source # | |
Ord Data | |
Show Data | |
Generic Data | |
NFData Data | |
Defined in PlutusCore.Data | |
Serialise Data | |
Defined in PlutusCore.Data encodeList :: [Data] -> Encoding decodeList :: Decoder s [Data] | |
Pretty Data | |
Defined in PlutusCore.Data prettyList :: [Data] -> Doc ann | |
ExMemoryUsage Data | |
Defined in PlutusCore.Evaluation.Machine.ExMemory memoryUsage :: Data -> ExMemory | |
PrettyBy ConstConfig Data | |
Defined in PlutusCore.Pretty.PrettyConst prettyBy :: ConstConfig -> Data -> Doc ann prettyListBy :: ConstConfig -> [Data] -> Doc ann | |
HasConstantIn DefaultUni term => MakeKnownIn DefaultUni term Data | |
Defined in PlutusCore.Default.Universe | |
HasConstantIn DefaultUni term => ReadKnownIn DefaultUni term Data | |
Defined in PlutusCore.Default.Universe | |
Contains DefaultUni Data | |
Defined in PlutusCore.Default.Universe | |
KnownBuiltinTypeAst DefaultUni Data => KnownTypeAst DefaultUni Data | |
Defined in PlutusCore.Default.Universe | |
type Rep Data | |
Defined in PlutusCore.Data type Rep Data = D1 ('MetaData "Data" "PlutusCore.Data" "plutus-core-1.0.0.1-6wMiyL0yerXJu56t8zBoKx" 'False) ((C1 ('MetaCons "Constr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Data])) :+: C1 ('MetaCons "Map" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Data, Data)]))) :+: (C1 ('MetaCons "List" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Data])) :+: (C1 ('MetaCons "I" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)) :+: C1 ('MetaCons "B" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))))) | |
type ToBinds Data | |
Defined in PlutusCore.Default.Universe | |
type ToHoles Data | |
Defined in PlutusCore.Default.Universe |
data BuiltinData #
Instances
toBuiltinData :: a -> BuiltinData #
Instances
fromBuiltinData :: BuiltinData -> Maybe a #
Instances
class UnsafeFromData a where #
unsafeFromBuiltinData :: BuiltinData -> a #
Instances
dataToBuiltinData :: Data -> BuiltinData #
builtinDataToData :: BuiltinData -> Data #
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 DeserialiseFailure | A serialisation 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
Eq EvaluationError Source # | |
Defined in Plutus.ApiCommon (==) :: EvaluationError -> EvaluationError -> Bool Source # (/=) :: EvaluationError -> EvaluationError -> Bool Source # | |
Show EvaluationError Source # | |
Defined in Plutus.ApiCommon | |
Pretty EvaluationError Source # | |
Defined in Plutus.ApiCommon pretty :: EvaluationError -> Doc ann prettyList :: [EvaluationError] -> Doc ann |