plutus-core-1.31.0.0: Language library for Plutus Core
Safe HaskellSafe-Inferred
LanguageHaskell2010

PlutusCore.Builtin.Result

Synopsis

Documentation

data EvaluationError operational structural Source #

The type of errors that can occur during evaluation. There are two kinds of errors:

  1. Operational ones -- these are errors that are indicative of the _logic_ of the program being wrong. For example, error was executed, tailList was applied to an empty list or evaluation ran out of gas.
  2. Structural ones -- these are errors that are indicative of the _structure_ of the program being wrong. For example, a free variable was encountered during evaluation, a non-function was applied to an argument or tailList was applied to a non-list.

On the chain both of these are just regular failures and we don't distinguish between them there: if a script fails, it fails, it doesn't matter what the reason was. However in the tests it does matter why the failure occurred: a structural error may indicate that the test was written incorrectly while an operational error may be entirely expected.

In other words, operational errors are regular runtime errors and structural errors are "runtime type errors". Which means that evaluating an (erased) well-typed program should never produce a structural error, only an operational one. This creates a sort of "runtime type system" for UPLC and it would be great to stick to it and enforce in tests etc, but we currently don't. For example, a built-in function expecting a list but getting something else should throw a structural error, but currently it'll throw an operational one. This is something that we plan to improve upon in future.

Constructors

OperationalEvaluationError !operational 
StructuralEvaluationError !structural 

Instances

Instances details
Bifoldable EvaluationError Source # 
Instance details

Defined in PlutusCore.Evaluation.Error

Methods

bifoldMonoid m ⇒ EvaluationError m m → m Source #

bifoldMapMonoid m ⇒ (a → m) → (b → m) → EvaluationError a b → m Source #

bifoldr ∷ (a → c → c) → (b → c → c) → c → EvaluationError a b → c Source #

bifoldl ∷ (c → a → c) → (c → b → c) → c → EvaluationError a b → c Source #

Bifunctor EvaluationError Source # 
Instance details

Defined in PlutusCore.Evaluation.Error

Methods

bimap ∷ (a → b) → (c → d) → EvaluationError a c → EvaluationError b d Source #

first ∷ (a → b) → EvaluationError a c → EvaluationError b c Source #

second ∷ (b → c) → EvaluationError a b → EvaluationError a c Source #

Bitraversable EvaluationError Source # 
Instance details

Defined in PlutusCore.Evaluation.Error

Methods

bitraverseApplicative f ⇒ (a → f c) → (b → f d) → EvaluationError a b → f (EvaluationError c d) Source #

(HasPrettyDefaults config ~ 'True, Pretty operational, PrettyBy config structural) ⇒ PrettyBy config (EvaluationError operational structural) Source # 
Instance details

Defined in PlutusCore.Evaluation.Error

Methods

prettyBy ∷ config → EvaluationError operational structural → Doc ann Source #

prettyListBy ∷ config → [EvaluationError operational structural] → Doc ann Source #

Functor (EvaluationError operational) Source # 
Instance details

Defined in PlutusCore.Evaluation.Error

Methods

fmap ∷ (a → b) → EvaluationError operational a → EvaluationError operational b Source #

(<$) ∷ a → EvaluationError operational b → EvaluationError operational a Source #

Generic (EvaluationError operational structural) Source # 
Instance details

Defined in PlutusCore.Evaluation.Error

Associated Types

type Rep (EvaluationError operational structural) ∷ TypeType Source #

Methods

fromEvaluationError operational structural → Rep (EvaluationError operational structural) x Source #

toRep (EvaluationError operational structural) x → EvaluationError operational structural Source #

(Show operational, Show structural) ⇒ Show (EvaluationError operational structural) Source # 
Instance details

Defined in PlutusCore.Evaluation.Error

Methods

showsPrecIntEvaluationError operational structural → ShowS Source #

showEvaluationError operational structural → String Source #

showList ∷ [EvaluationError operational structural] → ShowS Source #

(NFData operational, NFData structural) ⇒ NFData (EvaluationError operational structural) Source # 
Instance details

Defined in PlutusCore.Evaluation.Error

Methods

rnfEvaluationError operational structural → () Source #

(Eq operational, Eq structural) ⇒ Eq (EvaluationError operational structural) Source # 
Instance details

Defined in PlutusCore.Evaluation.Error

Methods

(==)EvaluationError operational structural → EvaluationError operational structural → Bool Source #

(/=)EvaluationError operational structural → EvaluationError operational structural → Bool Source #

(AsUnliftingError operational, AsUnliftingError structural) ⇒ AsUnliftingEvaluationError (EvaluationError operational structural) Source #

An UnliftingEvaluationError is an EvaluationError, hence for this instance we only require both operational and structural to have _UnliftingError prisms, so that we can handle both the cases pointwisely.

Instance details

Defined in PlutusCore.Builtin.Result

AsEvaluationFailure operational ⇒ AsEvaluationFailure (EvaluationError operational structural) Source #

A raw evaluation failure is always an operational error.

Instance details

Defined in PlutusCore.Evaluation.Error

Methods

_EvaluationFailure ∷ Prism' (EvaluationError operational structural) () Source #

(Pretty operational, Pretty structural) ⇒ Pretty (EvaluationError operational structural) Source # 
Instance details

Defined in PlutusCore.Evaluation.Error

Methods

prettyEvaluationError operational structural → Doc ann Source #

prettyList ∷ [EvaluationError operational structural] → Doc ann Source #

structural ~ MachineError fun ⇒ AsMachineError (EvaluationError operational structural) fun Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Methods

_MachineError ∷ Prism' (EvaluationError operational structural) (MachineError fun) Source #

_NonPolymorphicInstantiationMachineError ∷ Prism' (EvaluationError operational structural) () Source #

_NonWrapUnwrappedMachineError ∷ Prism' (EvaluationError operational structural) () Source #

_NonFunctionalApplicationMachineError ∷ Prism' (EvaluationError operational structural) () Source #

_OpenTermEvaluatedMachineError ∷ Prism' (EvaluationError operational structural) () Source #

_UnliftingMachineError ∷ Prism' (EvaluationError operational structural) UnliftingError Source #

_BuiltinTermArgumentExpectedMachineError ∷ Prism' (EvaluationError operational structural) () Source #

_UnexpectedBuiltinTermArgumentMachineError ∷ Prism' (EvaluationError operational structural) () Source #

_NonConstrScrutinized ∷ Prism' (EvaluationError operational structural) () Source #

_MissingCaseBranch ∷ Prism' (EvaluationError operational structural) Word64 Source #

AsEvaluationError (EvaluationError operational structural) operational structural Source # 
Instance details

Defined in PlutusCore.Evaluation.Error

Methods

_EvaluationError ∷ Prism' (EvaluationError operational structural) (EvaluationError operational structural) Source #

_OperationalEvaluationError ∷ Prism' (EvaluationError operational structural) operational Source #

_StructuralEvaluationError ∷ Prism' (EvaluationError operational structural) structural Source #

ThrowableBuiltins uni fun ⇒ MonadError (CekEvaluationException NamedDeBruijn uni fun) (CekM uni fun s) Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Methods

throwErrorCekEvaluationException NamedDeBruijn uni fun → CekM uni fun s a Source #

catchErrorCekM uni fun s a → (CekEvaluationException NamedDeBruijn uni fun → CekM uni fun s a) → CekM uni fun s a Source #

type Rep (EvaluationError operational structural) Source # 
Instance details

Defined in PlutusCore.Evaluation.Error

type Rep (EvaluationError operational structural) = D1 ('MetaData "EvaluationError" "PlutusCore.Evaluation.Error" "plutus-core-1.31.0.0-inplace" 'False) (C1 ('MetaCons "OperationalEvaluationError" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 operational)) :+: C1 ('MetaCons "StructuralEvaluationError" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 structural)))

class AsEvaluationError r operational structural | r → operational structural where Source #

Minimal complete definition

_EvaluationError

Methods

_EvaluationError ∷ Prism' r (EvaluationError operational structural) Source #

_OperationalEvaluationError ∷ Prism' r operational Source #

_StructuralEvaluationError ∷ Prism' r structural Source #

Instances

Instances details
AsEvaluationError UnliftingEvaluationError UnliftingError UnliftingError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

AsEvaluationError (EvaluationError operational structural) operational structural Source # 
Instance details

Defined in PlutusCore.Evaluation.Error

Methods

_EvaluationError ∷ Prism' (EvaluationError operational structural) (EvaluationError operational structural) Source #

_OperationalEvaluationError ∷ Prism' (EvaluationError operational structural) operational Source #

_StructuralEvaluationError ∷ Prism' (EvaluationError operational structural) structural Source #

newtype UnliftingError Source #

The error message part of an UnliftingEvaluationError.

Constructors

MkUnliftingError 

Instances

Instances details
IsString UnliftingError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

Monoid UnliftingError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

Semigroup UnliftingError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

Show UnliftingError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

NFData UnliftingError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

Methods

rnfUnliftingError → () Source #

Eq UnliftingError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

AsUnliftingError UnliftingError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

Pretty UnliftingError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

AsEvaluationError UnliftingEvaluationError UnliftingError UnliftingError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

newtype UnliftingEvaluationError Source #

When unlifting of a PLC term into a Haskell value fails, this error is thrown.

Instances

Instances details
Show UnliftingEvaluationError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

NFData UnliftingEvaluationError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

Eq UnliftingEvaluationError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

AsUnliftingEvaluationError UnliftingEvaluationError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

Pretty UnliftingEvaluationError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

AsEvaluationError UnliftingEvaluationError UnliftingError UnliftingError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

data BuiltinError Source #

The type of errors that readKnown and makeKnown can return.

Instances

Instances details
Show BuiltinError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

Eq BuiltinError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

AsBuiltinError BuiltinError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

AsUnliftingEvaluationError BuiltinError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

AsEvaluationFailure BuiltinError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

Pretty BuiltinError Source # 
Instance details

Defined in PlutusCore.Builtin.Result

Methods

prettyBuiltinErrorDoc ann Source #

prettyList ∷ [BuiltinError] → Doc ann Source #

MonadError BuiltinError BuiltinResult Source #

throwError puts every operational unlifting error into the BuiltinFailure logs. This is to compensate for the historical lack of error message content in operational errors (structural ones don't have this problem) in our evaluators (the CK and CEK machines). It would be better to fix the underlying issue and allow operational evaluation errors to carry some form of content, but for now we just fix the symptom in order for the end user to see the error message that they are supposed to see. The fix even makes some sense: what we do here is we emulate logging when the thrown unlifting error is an operational one, i.e. this is similar to what some builtins do manually (like when a crypto builtin fails and puts info about the failure into the logs).

Instance details

Defined in PlutusCore.Builtin.Result

data BuiltinResult a Source #

The monad that makeKnown runs in. Equivalent to ExceptT BuiltinError (Writer (DList Text)), except optimized in two ways:

  1. everything is strict
  2. has the BuiltinSuccess constructor that is used for returning a value with no logs attached, which is the most common case for us, so it helps a lot not to construct and deconstruct a redundant tuple

Moving from ExceptT BuiltinError (Writer (DList Text)) to this data type gave us a speedup of 8% of total evaluation time.

Logs are represented as a DList, because we don't particularly care about the efficiency of logging, since there's no logging on the chain and builtins don't emit much anyway. Otherwise we'd have to use text-builder or text-builder-linear or something of this sort.

Instances

Instances details
MonadFail BuiltinResult Source # 
Instance details

Defined in PlutusCore.Builtin.Result

Methods

failStringBuiltinResult a Source #

Foldable BuiltinResult Source # 
Instance details

Defined in PlutusCore.Builtin.Result

Methods

foldMonoid m ⇒ BuiltinResult m → m Source #

foldMapMonoid m ⇒ (a → m) → BuiltinResult a → m Source #

foldMap'Monoid m ⇒ (a → m) → BuiltinResult a → m Source #

foldr ∷ (a → b → b) → b → BuiltinResult a → b Source #

foldr' ∷ (a → b → b) → b → BuiltinResult a → b Source #

foldl ∷ (b → a → b) → b → BuiltinResult a → b Source #

foldl' ∷ (b → a → b) → b → BuiltinResult a → b Source #

foldr1 ∷ (a → a → a) → BuiltinResult a → a Source #

foldl1 ∷ (a → a → a) → BuiltinResult a → a Source #

toListBuiltinResult a → [a] Source #

nullBuiltinResult a → Bool Source #

lengthBuiltinResult a → Int Source #

elemEq a ⇒ a → BuiltinResult a → Bool Source #

maximumOrd a ⇒ BuiltinResult a → a Source #

minimumOrd a ⇒ BuiltinResult a → a Source #

sumNum a ⇒ BuiltinResult a → a Source #

productNum a ⇒ BuiltinResult a → a Source #

Applicative BuiltinResult Source # 
Instance details

Defined in PlutusCore.Builtin.Result

Functor BuiltinResult Source # 
Instance details

Defined in PlutusCore.Builtin.Result

Methods

fmap ∷ (a → b) → BuiltinResult a → BuiltinResult b Source #

(<$) ∷ a → BuiltinResult b → BuiltinResult a Source #

Monad BuiltinResult Source # 
Instance details

Defined in PlutusCore.Builtin.Result

MonadError BuiltinError BuiltinResult Source #

throwError puts every operational unlifting error into the BuiltinFailure logs. This is to compensate for the historical lack of error message content in operational errors (structural ones don't have this problem) in our evaluators (the CK and CEK machines). It would be better to fix the underlying issue and allow operational evaluation errors to carry some form of content, but for now we just fix the symptom in order for the end user to see the error message that they are supposed to see. The fix even makes some sense: what we do here is we emulate logging when the thrown unlifting error is an operational one, i.e. this is similar to what some builtins do manually (like when a crypto builtin fails and puts info about the failure into the logs).

Instance details

Defined in PlutusCore.Builtin.Result

KnownTypeAst tyname uni a ⇒ KnownTypeAst tyname uni (BuiltinResult a ∷ Type) Source # 
Instance details

Defined in PlutusCore.Builtin.KnownTypeAst

Associated Types

type IsBuiltin uni (BuiltinResult a) ∷ Bool Source #

type ToHoles uni (BuiltinResult a) ∷ [Hole] Source #

type ToBinds uni acc (BuiltinResult a) ∷ [Some TyNameRep] Source #

Methods

typeAstType0 tyname uni () Source #

MakeKnownIn uni val a ⇒ MakeKnownIn uni val (BuiltinResult a) Source # 
Instance details

Defined in PlutusCore.Builtin.KnownType

(TypeError ('Text "\8216BuiltinResult\8217 cannot appear in the type of an argument") ∷ Constraint, uni ~ UniOf val) ⇒ ReadKnownIn uni val (BuiltinResult a) Source # 
Instance details

Defined in PlutusCore.Builtin.KnownType

Methods

readKnown ∷ val → ReadKnownM (BuiltinResult a) Source #

Show a ⇒ Show (BuiltinResult a) Source # 
Instance details

Defined in PlutusCore.Builtin.Result

AsEvaluationFailure (BuiltinResult a) Source # 
Instance details

Defined in PlutusCore.Builtin.Result

Methods

_EvaluationFailure ∷ Prism' (BuiltinResult a) () Source #

AsBuiltinResult (BuiltinResult a) a Source # 
Instance details

Defined in PlutusCore.Builtin.Result

type ToBinds uni acc (BuiltinResult a ∷ Type) Source # 
Instance details

Defined in PlutusCore.Builtin.KnownTypeAst

type ToBinds uni acc (BuiltinResult a ∷ Type) = ToBinds uni acc a
type IsBuiltin uni (BuiltinResult a ∷ Type) Source # 
Instance details

Defined in PlutusCore.Builtin.KnownTypeAst

type IsBuiltin uni (BuiltinResult a ∷ Type) = 'False
type ToHoles uni (BuiltinResult a ∷ Type) Source # 
Instance details

Defined in PlutusCore.Builtin.KnownTypeAst

type ToHoles uni (BuiltinResult a ∷ Type) = '[TypeHole a ∷ Hole]

class AsUnliftingEvaluationError r where Source #

Minimal complete definition

_UnliftingEvaluationError

class AsBuiltinResult r a | r → a where Source #

Minimal complete definition

_BuiltinResult

_UnliftingErrorViaPretty err ⇒ err → Prism' err UnliftingError Source #

Construct a prism focusing on the *EvaluationFailure part of err by taking that *EvaluationFailure and

  1. pretty-printing and embedding it into an UnliftingError for the setter part of the prism
  2. returning it directly for the opposite direction (there's no other way to convert an UnliftingError to an evaluation failure, since the latter doesn't carry any content)

This is useful for providing AsUnliftingError instances for types such as CkUserError and CekUserError.

emitTextBuiltinResult () Source #

Add a log line to the logs.

withLogsDList TextBuiltinResult a → BuiltinResult a Source #

Prepend logs to a BuiltinResult computation.

throwingMonadError e m ⇒ AReview e t → t → m x #

throwing_MonadError e m ⇒ AReview e () → m x #