Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
The types and functions that are common among all ledger Plutus versions.
Synopsis
- type SerialisedScript = ShortByteString
- data ScriptForEvaluation
- serialisedScript :: ScriptForEvaluation -> SerialisedScript
- deserialisedScript :: ScriptForEvaluation -> ScriptNamedDeBruijn
- serialiseCompiledCode :: forall a. CompiledCode a -> SerialisedScript
- serialiseUPLC :: Program DeBruijn DefaultUni DefaultFun () -> SerialisedScript
- deserialiseScript :: forall m. MonadError ScriptDecodeError m => PlutusLedgerLanguage -> MajorProtocolVersion -> SerialisedScript -> m ScriptForEvaluation
- uncheckedDeserialiseUPLC :: SerialisedScript -> Program DeBruijn DefaultUni DefaultFun ()
- data ScriptDecodeError
- = CBORDeserialiseError !DeserialiseFailureInfo
- | RemainderError !ByteString
- | LedgerLanguageNotAvailableError { }
- | PlutusCoreLanguageNotAvailableError { }
- newtype ScriptNamedDeBruijn = ScriptNamedDeBruijn (Program NamedDeBruijn DefaultUni DefaultFun ())
- evaluateScriptCounting :: PlutusLedgerLanguage -> MajorProtocolVersion -> VerboseMode -> EvaluationContext -> ScriptForEvaluation -> [Data] -> (LogOutput, Either EvaluationError ExBudget)
- evaluateScriptRestricting :: PlutusLedgerLanguage -> MajorProtocolVersion -> VerboseMode -> EvaluationContext -> ExBudget -> ScriptForEvaluation -> [Data] -> (LogOutput, Either EvaluationError ExBudget)
- evaluateTerm :: ExBudgetMode cost DefaultUni DefaultFun -> MajorProtocolVersion -> VerboseMode -> EvaluationContext -> Term NamedDeBruijn DefaultUni DefaultFun () -> (Either (CekEvaluationException NamedDeBruijn DefaultUni DefaultFun) (Term NamedDeBruijn DefaultUni DefaultFun ()), cost, [Text])
- data VerboseMode
- type LogOutput = [Text]
- data EvaluationError
- = CekError !(CekEvaluationException NamedDeBruijn DefaultUni DefaultFun)
- | DeBruijnError !FreeVariableError
- | CodecError !ScriptDecodeError
- | CostModelParameterMismatch
- | InvalidReturnValue
- newtype MajorProtocolVersion = MajorProtocolVersion {}
- data PlutusLedgerLanguage
- data Version = Version {}
- builtinsIntroducedIn :: Map (PlutusLedgerLanguage, MajorProtocolVersion) (Set DefaultFun)
- builtinsAvailableIn :: PlutusLedgerLanguage -> MajorProtocolVersion -> Set DefaultFun
- ledgerLanguageIntroducedIn :: PlutusLedgerLanguage -> MajorProtocolVersion
- ledgerLanguagesAvailableIn :: MajorProtocolVersion -> Set PlutusLedgerLanguage
- data ExBudget = ExBudget {}
- newtype ExCPU = ExCPU CostingInteger
- newtype ExMemory = ExMemory CostingInteger
- data SatInt
- fromSatInt :: Num a => SatInt -> a
- type CostModelParams = Map Text Int64
- toCostModelParams :: IsParamName p => [(p, Int64)] -> CostModelParams
- assertWellFormedCostModelParams :: MonadError CostModelApplyError m => CostModelParams -> m ()
- class (Enum a, Bounded a) => IsParamName a where
- showParamName :: a -> Text
- readParamName :: Text -> Maybe a
- data GenericParamName a
- data CostModelApplyError
- data CostModelApplyWarn
- = CMTooManyParamsWarn {
- cmExpected :: !Int
- cmActual :: !Int
- | CMTooFewParamsWarn {
- cmExpected :: !Int
- cmActual :: !Int
- = CMTooManyParamsWarn {
- data EvaluationContext = EvaluationContext {
- _evalCtxLedgerLang :: PlutusLedgerLanguage
- _evalCtxToSemVar :: MajorProtocolVersion -> BuiltinSemanticsVariant DefaultFun
- _evalCtxMachParsCache :: [(BuiltinSemanticsVariant DefaultFun, DefaultMachineParameters)]
- mkDynEvaluationContext :: MonadError CostModelApplyError m => PlutusLedgerLanguage -> [BuiltinSemanticsVariant DefaultFun] -> (MajorProtocolVersion -> BuiltinSemanticsVariant DefaultFun) -> CostModelParams -> m EvaluationContext
- toMachineParameters :: MajorProtocolVersion -> EvaluationContext -> DefaultMachineParameters
- mkTermToEvaluate :: MonadError EvaluationError m => PlutusLedgerLanguage -> MajorProtocolVersion -> ScriptForEvaluation -> [Data] -> m (Term NamedDeBruijn DefaultUni DefaultFun ())
- data BuiltinByteString
- toBuiltin :: HasToBuiltin a => a -> ToBuiltin a
- fromBuiltin :: HasFromBuiltin arep => arep -> FromBuiltin arep
- toOpaque :: HasToOpaque a arep => a -> arep
- fromOpaque :: HasFromOpaque arep a => arep -> a
- 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
- unsafeFromData :: UnsafeFromData a => Data -> a
- dataToBuiltinData :: Data -> BuiltinData
- builtinDataToData :: BuiltinData -> Data
- class Monad m => MonadError e (m :: Type -> Type) | m -> e
Script (de)serialization
type SerialisedScript = ShortByteString Source #
Scripts to the ledger are serialised bytestrings.
data ScriptForEvaluation Source #
A Plutus script ready to be evaluated on-chain, via evaluateScriptRestricting
.
Instances
serialisedScript :: ScriptForEvaluation -> SerialisedScript Source #
Get a SerialisedScript
from a ScriptForEvaluation
. O(1).
deserialisedScript :: ScriptForEvaluation -> ScriptNamedDeBruijn Source #
Get a ScriptNamedDeBruijn
from a ScriptForEvaluation
. O(1).
serialiseCompiledCode :: forall a. CompiledCode a -> SerialisedScript Source #
Turns a program which was compiled using the 'PlutusTx' toolchain into a binary format that is understood by the network and can be stored on-chain.
serialiseUPLC :: Program DeBruijn DefaultUni DefaultFun () -> SerialisedScript Source #
Turns a program's AST (most likely manually constructed) into a binary format that is understood by the network and can be stored on-chain.
:: forall m. MonadError ScriptDecodeError m | |
=> PlutusLedgerLanguage | the Plutus ledger language of the script. |
-> MajorProtocolVersion | which major protocol version the script was submitted in. |
-> SerialisedScript | the script to deserialise. |
-> m ScriptForEvaluation |
The deserialization from a serialised script into a ScriptForEvaluation
,
ready to be evaluated on-chain.
Called inside phase-1 validation (i.e., deserialisation error is a phase-1 error).
uncheckedDeserialiseUPLC :: SerialisedScript -> Program DeBruijn DefaultUni DefaultFun () Source #
Deserialises a SerialisedScript
back into an AST. Does *not* do
ledger-language-version-specific checks like for allowable builtins.
data ScriptDecodeError Source #
An error that occurred during script deserialization.
CBORDeserialiseError !DeserialiseFailureInfo | an error from the underlying CBOR/serialise library |
RemainderError !ByteString | Script was successfully parsed, but more (runaway) bytes encountered after script's position |
LedgerLanguageNotAvailableError | the plutus version of the given script is not enabled yet |
| |
PlutusCoreLanguageNotAvailableError | |
|
Instances
Exception ScriptDecodeError Source # | |
Show ScriptDecodeError Source # | |
Defined in PlutusLedgerApi.Common.SerialisedScript | |
Eq ScriptDecodeError Source # | |
Defined in PlutusLedgerApi.Common.SerialisedScript (==) :: ScriptDecodeError -> ScriptDecodeError -> Bool Source # (/=) :: ScriptDecodeError -> ScriptDecodeError -> Bool Source # | |
Pretty ScriptDecodeError Source # | |
Defined in PlutusLedgerApi.Common.SerialisedScript pretty :: ScriptDecodeError -> Doc ann prettyList :: [ScriptDecodeError] -> Doc ann |
newtype ScriptNamedDeBruijn Source #
A script with named de-bruijn indices.
ScriptNamedDeBruijn (Program NamedDeBruijn DefaultUni DefaultFun ()) |
Instances
Script evaluation
evaluateScriptCounting Source #
:: PlutusLedgerLanguage | The Plutus ledger language of the script under execution. |
-> MajorProtocolVersion | Which major protocol version to run the operation in |
-> VerboseMode | Whether to produce log output |
-> EvaluationContext | Includes the cost model to use for tallying up the execution costs |
-> ScriptForEvaluation | The script to evaluate |
-> [Data] | The arguments to the script |
-> (LogOutput, Either EvaluationError ExBudget) |
Evaluates a script, returning the minimum budget that the script would need
to evaluate successfully. This will take as long as the script takes, if you need to
limit the execution time of the script also, you can use evaluateScriptRestricting
, which
also returns the used budget.
Note: Parameterized over the ledger-plutus-version since the builtins allowed (during decoding) differs.
evaluateScriptRestricting Source #
:: PlutusLedgerLanguage | The Plutus ledger language of the script under execution. |
-> MajorProtocolVersion | Which major protocol version to run the operation in |
-> VerboseMode | Whether to produce log output |
-> EvaluationContext | Includes the cost model to use for tallying up the execution costs |
-> ExBudget | The resource budget which must not be exceeded during evaluation |
-> ScriptForEvaluation | The script to evaluate |
-> [Data] | The arguments to the script |
-> (LogOutput, Either EvaluationError ExBudget) |
Evaluates a script, with a cost model and a budget that restricts how many resources it can use according to the cost model. Also returns the budget that was actually used.
Can be used to calculate budgets for scripts, but even in this case you must give a limit to guard against scripts that run for a long time or loop.
Note: Parameterized over the LedgerPlutusVersion
since
1. The builtins allowed (during decoding) differ, and
2. The Plutus language versions allowed differ.
evaluateTerm :: ExBudgetMode cost DefaultUni DefaultFun -> MajorProtocolVersion -> VerboseMode -> EvaluationContext -> Term NamedDeBruijn DefaultUni DefaultFun () -> (Either (CekEvaluationException NamedDeBruijn DefaultUni DefaultFun) (Term NamedDeBruijn DefaultUni DefaultFun ()), cost, [Text]) Source #
Evaluate a fully-applied term using the CEK machine. Useful for mimicking the behaviour of the on-chain evaluator.
data VerboseMode Source #
A simple toggle indicating whether or not we should accumulate logs during script execution.
Instances
Eq VerboseMode Source # | |
Defined in PlutusLedgerApi.Common.Eval (==) :: VerboseMode -> VerboseMode -> Bool Source # (/=) :: VerboseMode -> VerboseMode -> Bool Source # |
type LogOutput = [Text] Source #
The type of the executed script's accumulated log output: a list of Text
.
It will be an empty list if the VerboseMode
is set to Quiet
.
data EvaluationError Source #
Errors that can be thrown when evaluating a Plutus script.
CekError !(CekEvaluationException NamedDeBruijn DefaultUni DefaultFun) | An error from the evaluator itself |
DeBruijnError !FreeVariableError | An error in the pre-evaluation step of converting from de-Bruijn indices |
CodecError !ScriptDecodeError | A deserialisation error TODO: make this error more informative when we have more information about what went wrong |
CostModelParameterMismatch | An error indicating that the cost model parameters didn't match what we expected |
InvalidReturnValue | The script evaluated to a value that is not a valid return value. |
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 prettyList :: [EvaluationError] -> Doc ann |
Network's versioning
The network's behaviour (and plutus's by extension) can change via hard forks, which directly correspond to major-number protocol version bumps.
newtype MajorProtocolVersion Source #
This represents the major component of the Cardano protocol version. The ledger can only supply the major component of the protocol version, not the minor component, and Plutus should only need to care about the major component anyway. This relies on careful understanding between us and the ledger as to what this means.
Instances
data PlutusLedgerLanguage Source #
The Plutus ledger language. These are entirely different script languages from the ledger's perspective, which on our side are interpreted in very similar ways.
It is a simple enumerated datatype (there is no major and minor components as in protocol version) and the ordering of constructors is essential for deriving Enum,Ord,Bounded.
IMPORTANT: this is different from the Plutus Core language version, Version
Instances
Instances
Generic Version | |
Show Version | |
NFData Version | |
Defined in PlutusCore.Version | |
Eq Version | |
Ord Version | |
Hashable Version | |
Defined in PlutusCore.Version | |
Pretty Version | |
Defined in PlutusCore.Version prettyList :: [Version] -> Doc ann | |
type Rep Version | |
Defined in PlutusCore.Version type Rep Version = D1 ('MetaData "Version" "PlutusCore.Version" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'False) (C1 ('MetaCons "Version" 'PrefixI 'True) (S1 ('MetaSel ('Just "_versionMajor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural) :*: (S1 ('MetaSel ('Just "_versionMinor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural) :*: S1 ('MetaSel ('Just "_versionPatch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural)))) |
builtinsIntroducedIn :: Map (PlutusLedgerLanguage, MajorProtocolVersion) (Set DefaultFun) Source #
A map indicating which builtin functions were introduced in which MajorProtocolVersion
.
This must be updated when new builtins are added. See Note [New builtins/language versions and protocol versions]
builtinsAvailableIn :: PlutusLedgerLanguage -> MajorProtocolVersion -> Set DefaultFun Source #
Which builtin functions are available in the given given PlutusLedgerLanguage
and MajorProtocolVersion
?
See Note [New builtins/language versions and protocol versions]
ledgerLanguageIntroducedIn :: PlutusLedgerLanguage -> MajorProtocolVersion Source #
Query the protocol version that a specific Plutus ledger language was first introduced in.
ledgerLanguagesAvailableIn :: MajorProtocolVersion -> Set PlutusLedgerLanguage Source #
Which Plutus language versions are available in the given MajorProtocolVersion
?
See Note [New builtins/language versions and protocol versions]
Costing-related types
Instances
ExCPU CostingInteger |
Instances
FromJSON ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory parseJSON :: Value -> Parser ExCPU parseJSONList :: Value -> Parser [ExCPU] | |
ToJSON ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory | |
Monoid ExCPU | |
Semigroup ExCPU | |
Bounded ExCPU | |
Generic ExCPU | |
Num ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory | |
Read ExCPU | |
Show ExCPU | |
NFData ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory | |
Eq ExCPU | |
Ord ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory | |
NoThunks ExCPU | |
Pretty ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory prettyList :: [ExCPU] -> Doc ann | |
Serialise ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory encodeList :: [ExCPU] -> Encoding decodeList :: Decoder s [ExCPU] | |
PrettyBy config ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory prettyBy :: config -> ExCPU -> Doc ann prettyListBy :: config -> [ExCPU] -> Doc ann | |
Lift ExCPU | |
type Rep ExCPU | |
Defined in PlutusCore.Evaluation.Machine.ExMemory |
ExMemory CostingInteger |
Instances
Instances
fromSatInt :: Num a => SatInt -> a #
Network's costing parameters
A less drastic approach (that does not rely on a HF) to affect the network's (and plutus's by extension) behaviour is by tweaking the values of the cost model parameters.
The network does not associate names to cost model parameters; Plutus attaches names to the network's cost model parameters (values) either in a raw textual form or typed by a specific plutus version.
See Note [Cost model parameters]
type CostModelParams = Map Text Int64 #
toCostModelParams :: IsParamName p => [(p, Int64)] -> CostModelParams Source #
Untags the plutus version from the typed cost model parameters and returns their raw textual form (internally used by CostModelInterface).
assertWellFormedCostModelParams :: MonadError CostModelApplyError m => CostModelParams -> m () Source #
class (Enum a, Bounded a) => IsParamName a where Source #
A parameter name for different plutus versions.
Each Plutus version should expose such an enumeration as an ADT and create
an instance of ParamName
out of it.
A valid parameter name has to be enumeration, bounded, ordered, and prettyprintable to a "lower-Kebab" string.
showParamName :: a -> Text Source #
Produce the raw textual form for a given typed-by-plutus-version cost model parameter
Any implementation *must be* an injective function.
The GIsParamName
generic implementation guarantees injectivity.
readParamName :: Text -> Maybe a Source #
default implementation that inverts the showParamName operation (not very efficient)
Instances
IsParamName ParamName Source # | |
Defined in PlutusLedgerApi.V1.ParamName | |
IsParamName ParamName Source # | |
Defined in PlutusLedgerApi.V2.ParamName | |
IsParamName ParamName Source # | |
Defined in PlutusLedgerApi.V3.ParamName | |
(Enum (GenericParamName a), Bounded (GenericParamName a), Generic a, GIsParamName (Rep a)) => IsParamName (GenericParamName a) Source # | |
Defined in PlutusLedgerApi.Common.ParamName showParamName :: GenericParamName a -> Text Source # readParamName :: Text -> Maybe (GenericParamName a) Source # |
data GenericParamName a Source #
A Generic wrapper for use with deriving via
Instances
data CostModelApplyError #
Instances
data CostModelApplyWarn #
CMTooManyParamsWarn | |
| |
CMTooFewParamsWarn | |
|
Instances
Pretty CostModelApplyWarn | |
Defined in PlutusCore.Evaluation.Machine.CostModelInterface pretty :: CostModelApplyWarn -> Doc ann prettyList :: [CostModelApplyWarn] -> Doc ann |
Evaluation context
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
- 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
- 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
EvaluationContext | |
|
Instances
mkDynEvaluationContext :: MonadError CostModelApplyError m => PlutusLedgerLanguage -> [BuiltinSemanticsVariant DefaultFun] -> (MajorProtocolVersion -> BuiltinSemanticsVariant DefaultFun) -> CostModelParams -> m EvaluationContext Source #
Create an EvaluationContext
given all builtin semantics variants supported by the provided
language version.
The input is a Map
of Text
s to cost integer values (aka CostModelParams
, CostModel
)
See Note [Inlining meanings of builtins].
IMPORTANT: the toSemVar
argument computes the semantics variant for each MajorProtocolVersion
and it must only return semantics variants from the semVars
list, as well as cover ANY
MajorProtocolVersion
, including those that do not exist yet (i.e. toSemVar
must never fail).
IMPORTANT: The evaluation context of every Plutus version must be recreated upon a protocol update with the updated cost model parameters.
toMachineParameters :: MajorProtocolVersion -> EvaluationContext -> DefaultMachineParameters Source #
:: MonadError EvaluationError m | |
=> PlutusLedgerLanguage | the Plutus ledger language of the script under execution. |
-> MajorProtocolVersion | which major protocol version to run the operation in |
-> ScriptForEvaluation | the script to evaluate |
-> [Data] | the arguments that the script's underlying term will be applied to |
-> m (Term NamedDeBruijn DefaultUni DefaultFun ()) |
Shared helper for the evaluation functions: evaluateScriptCounting
and evaluateScriptRestricting
,
Given a ScriptForEvaluation
:
1) applies the term to a list of Data
arguments (e.g. Datum, Redeemer, ScriptContext
)
2) checks that the applied-term is well-scoped
3) returns the applied-term
Supporting types used in the context types
Builtins
data BuiltinByteString #
Instances
fromBuiltin :: HasFromBuiltin arep => arep -> FromBuiltin arep #
fromOpaque :: HasFromOpaque arep a => arep -> a #
Data
Instances
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 # | |
Generic Data | |
Read Data | |
Show Data | |
NFData Data | |
Defined in PlutusCore.Data | |
Eq Data | |
Ord Data | |
Hashable Data | |
Defined in PlutusCore.Data | |
NoThunks Data | |
HasToBuiltin Data | |
Pretty Data | |
Defined in PlutusCore.Data prettyList :: [Data] -> Doc ann | |
Serialise Data | |
Defined in PlutusCore.Data encodeList :: [Data] -> Encoding decodeList :: Decoder s [Data] | |
PrettyBy ConstConfig Data | |
Defined in PlutusCore.Pretty.PrettyConst prettyBy :: ConstConfig -> Data -> Doc ann prettyListBy :: ConstConfig -> [Data] -> Doc ann | |
KnownBuiltinTypeIn DefaultUni term Data => MakeKnownIn DefaultUni term Data | |
Defined in PlutusCore.Default.Universe | |
KnownBuiltinTypeIn DefaultUni term Data => ReadKnownIn DefaultUni term Data | |
Defined in PlutusCore.Default.Universe | |
Contains DefaultUni Data | |
Defined in PlutusCore.Default.Universe | |
KnownBuiltinTypeAst tyname DefaultUni Data => KnownTypeAst tyname DefaultUni Data | |
type Rep Data | |
Defined in PlutusCore.Data type Rep Data = D1 ('MetaData "Data" "PlutusCore.Data" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" '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 ToBuiltin Data | |
Defined in PlutusTx.Builtins.HasBuiltin | |
type IsBuiltin DefaultUni Data | |
Defined in PlutusCore.Default.Universe | |
type ToHoles DefaultUni Data | |
Defined in PlutusCore.Default.Universe | |
type ToBinds DefaultUni acc 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
unsafeFromData :: UnsafeFromData a => Data -> a #
dataToBuiltinData :: Data -> BuiltinData #
builtinDataToData :: BuiltinData -> Data #
Misc
class Monad m => MonadError e (m :: Type -> Type) | m -> e Source #
The strategy of combining computations that can throw exceptions by bypassing bound functions from the point an exception is thrown to the point that it is handled.
Is parameterized over the type of error information and
the monad type constructor.
It is common to use
as the monad type constructor
for an error monad in which error descriptions take the form of strings.
In that case and many other common cases the resulting monad is already defined
as an instance of the Either
StringMonadError
class.
You can also define your own error type and/or use a monad type constructor
other than
or Either
String
.
In these cases you will have to explicitly define instances of the Either
IOError
MonadError
class.
(If you are using the deprecated Control.Monad.Error or
Control.Monad.Trans.Error, you may also have to define an Error
instance.)
Instances
MonadError IOException IO | |
Defined in Control.Monad.Error.Class throwError :: IOException -> IO a Source # catchError :: IO a -> (IOException -> IO a) -> IO a Source # | |
MonadError BuiltinError BuiltinResult | |
Defined in PlutusCore.Builtin.Result throwError :: BuiltinError -> BuiltinResult a Source # catchError :: BuiltinResult a -> (BuiltinError -> BuiltinResult a) -> BuiltinResult a Source # | |
MonadError () EvaluationResult | |
Defined in PlutusCore.Evaluation.Result throwError :: () -> EvaluationResult a Source # catchError :: EvaluationResult a -> (() -> EvaluationResult a) -> EvaluationResult a Source # | |
MonadError () Maybe | Since: mtl-2.2.2 |
Defined in Control.Monad.Error.Class throwError :: () -> Maybe a Source # catchError :: Maybe a -> (() -> Maybe a) -> Maybe a Source # | |
MonadError e (Either e) | |
Defined in Control.Monad.Error.Class throwError :: e -> Either e a Source # catchError :: Either e a -> (e -> Either e a) -> Either e a Source # | |
MonadError e m => MonadError e (Free m) | |
Defined in Control.Monad.Free throwError :: e -> Free m a Source # catchError :: Free m a -> (e -> Free m a) -> Free m a Source # | |
MonadError e m => MonadError e (GenT m) | |
Defined in Hedgehog.Internal.Gen throwError :: e -> GenT m a Source # catchError :: GenT m a -> (e -> GenT m a) -> GenT m a Source # | |
MonadError e m => MonadError e (PropertyT m) | |
Defined in Hedgehog.Internal.Property throwError :: e -> PropertyT m a Source # catchError :: PropertyT m a -> (e -> PropertyT m a) -> PropertyT m a Source # | |
MonadError e m => MonadError e (TestT m) | |
Defined in Hedgehog.Internal.Property throwError :: e -> TestT m a Source # catchError :: TestT m a -> (e -> TestT m a) -> TestT m a Source # | |
MonadError e m => MonadError e (TreeT m) | |
Defined in Hedgehog.Internal.Tree throwError :: e -> TreeT m a Source # catchError :: TreeT m a -> (e -> TreeT m a) -> TreeT m a Source # | |
MonadError e m => MonadError e (ListT m) | |
Defined in ListT throwError :: e -> ListT m a Source # catchError :: ListT m a -> (e -> ListT m a) -> ListT m a Source # | |
MonadError e m => MonadError e (QuoteT m) | |
Defined in PlutusCore.Quote throwError :: e -> QuoteT m a Source # catchError :: QuoteT m a -> (e -> QuoteT m a) -> QuoteT m a Source # | |
MonadError e m => MonadError e (ResourceT m) | |
Defined in Control.Monad.Trans.Resource.Internal throwError :: e -> ResourceT m a Source # catchError :: ResourceT m a -> (e -> ResourceT m a) -> ResourceT m a Source # | |
MonadError e m => MonadError e (MaybeT m) | |
Defined in Control.Monad.Error.Class throwError :: e -> MaybeT m a Source # catchError :: MaybeT m a -> (e -> MaybeT m a) -> MaybeT m a Source # | |
(Functor f, MonadError e m) => MonadError e (FreeT f m) | |
Defined in Control.Monad.Trans.Free throwError :: e -> FreeT f m a Source # catchError :: FreeT f m a -> (e -> FreeT f m a) -> FreeT f m a Source # | |
(Monoid w, MonadError e m) => MonadError e (AccumT w m) | Since: mtl-2.3 |
Defined in Control.Monad.Error.Class throwError :: e -> AccumT w m a Source # catchError :: AccumT w m a -> (e -> AccumT w m a) -> AccumT w m a Source # | |
Monad m => MonadError e (ExceptT e m) | Since: mtl-2.2 |
Defined in Control.Monad.Error.Class throwError :: e -> ExceptT e m a Source # catchError :: ExceptT e m a -> (e -> ExceptT e m a) -> ExceptT e m a Source # | |
MonadError e m => MonadError e (IdentityT m) | |
Defined in Control.Monad.Error.Class throwError :: e -> IdentityT m a Source # catchError :: IdentityT m a -> (e -> IdentityT m a) -> IdentityT m a Source # | |
MonadError e m => MonadError e (ReaderT r m) | |
Defined in Control.Monad.Error.Class throwError :: e -> ReaderT r m a Source # catchError :: ReaderT r m a -> (e -> ReaderT r m a) -> ReaderT r m a Source # | |
MonadError e m => MonadError e (StateT s m) | |
Defined in Control.Monad.Error.Class throwError :: e -> StateT s m a Source # catchError :: StateT s m a -> (e -> StateT s m a) -> StateT s m a Source # | |
MonadError e m => MonadError e (StateT s m) | |
Defined in Control.Monad.Error.Class throwError :: e -> StateT s m a Source # catchError :: StateT s m a -> (e -> StateT s m a) -> StateT s m a Source # | |
(Monoid w, MonadError e m) => MonadError e (WriterT w m) | Since: mtl-2.3 |
Defined in Control.Monad.Error.Class throwError :: e -> WriterT w m a Source # catchError :: WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a Source # | |
(Monoid w, MonadError e m) => MonadError e (WriterT w m) | |
Defined in Control.Monad.Error.Class throwError :: e -> WriterT w m a Source # catchError :: WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a Source # | |
(Monoid w, MonadError e m) => MonadError e (WriterT w m) | |
Defined in Control.Monad.Error.Class throwError :: e -> WriterT w m a Source # catchError :: WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a Source # | |
(Monoid w, MonadError e m) => MonadError e (RWST r w s m) | Since: mtl-2.3 |
Defined in Control.Monad.Error.Class throwError :: e -> RWST r w s m a Source # catchError :: RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s m a Source # | |
(Monoid w, MonadError e m) => MonadError e (RWST r w s m) | |
Defined in Control.Monad.Error.Class throwError :: e -> RWST r w s m a Source # catchError :: RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s m a Source # | |
(Monoid w, MonadError e m) => MonadError e (RWST r w s m) | |
Defined in Control.Monad.Error.Class throwError :: e -> RWST r w s m a Source # catchError :: RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s m a Source # | |
MonadError e m => MonadError e (DefT key uni fun ann m) | |
Defined in PlutusIR.Compiler.Definitions throwError :: e -> DefT key uni fun ann m a Source # catchError :: DefT key uni fun ann m a -> (e -> DefT key uni fun ann m a) -> DefT key uni fun ann m a Source # | |
ThrowableBuiltins uni fun => MonadError (CekEvaluationException NamedDeBruijn uni fun) (CekM uni fun s) | |
Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal throwError :: CekEvaluationException NamedDeBruijn uni fun -> CekM uni fun s a Source # catchError :: CekM uni fun s a -> (CekEvaluationException NamedDeBruijn uni fun -> CekM uni fun s a) -> CekM uni fun s a Source # |