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

PlutusCore.Evaluation.Machine.Exception

Description

The exceptions that an abstract machine can throw.

Synopsis

Documentation

newtype UnliftingError Source #

The error message part of an UnliftingEvaluationError.

Constructors

MkUnliftingError 

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

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 MachineError fun Source #

Errors which can occur during a run of an abstract machine.

Constructors

NonPolymorphicInstantiationMachineError

An attempt to reduce a not immediately reducible type instantiation.

NonWrapUnwrappedMachineError

An attempt to unwrap a not wrapped term.

NonFunctionalApplicationMachineError

An attempt to reduce a not immediately reducible application.

OpenTermEvaluatedMachineError

An attempt to evaluate an open term.

UnliftingMachineError UnliftingError

An attempt to compute a constant application resulted in UnliftingError.

BuiltinTermArgumentExpectedMachineError

A builtin expected a term argument, but something else was received.

UnexpectedBuiltinTermArgumentMachineError

A builtin received a term argument when something else was expected

NonConstrScrutinizedMachineError

An attempt to scrutinize a non-constr.

MissingCaseBranchMachineError Word64

An attempt to go into a non-existent case branch.

PanicMachineError String

A GHC exception was thrown.

Instances

Instances details
Functor MachineError Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Methods

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

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

(HasPrettyDefaults config ~ 'True, Pretty fun) ⇒ PrettyBy config (MachineError fun) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Methods

prettyBy ∷ config → MachineError fun → Doc ann Source #

prettyListBy ∷ config → [MachineError fun] → Doc ann Source #

Generic (MachineError fun) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Associated Types

type Rep (MachineError fun) ∷ TypeType Source #

Methods

fromMachineError fun → Rep (MachineError fun) x Source #

toRep (MachineError fun) x → MachineError fun Source #

Show (MachineError fun) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

NFData (MachineError fun) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Methods

rnfMachineError fun → () Source #

Eq (MachineError fun) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Methods

(==)MachineError fun → MachineError fun → Bool Source #

(/=)MachineError fun → MachineError fun → Bool Source #

BuiltinErrorToEvaluationError (MachineError fun) CekUserError Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

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 (MachineError fun) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

type Rep (MachineError fun) = D1 ('MetaData "MachineError" "PlutusCore.Evaluation.Machine.Exception" "plutus-core-1.47.0.0-inplace" 'False) (((C1 ('MetaCons "NonPolymorphicInstantiationMachineError" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "NonWrapUnwrappedMachineError" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "NonFunctionalApplicationMachineError" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "OpenTermEvaluatedMachineError" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "UnliftingMachineError" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnliftingError))))) :+: ((C1 ('MetaCons "BuiltinTermArgumentExpectedMachineError" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "UnexpectedBuiltinTermArgumentMachineError" 'PrefixI 'False) (U1TypeType)) :+: (C1 ('MetaCons "NonConstrScrutinizedMachineError" 'PrefixI 'False) (U1TypeType) :+: (C1 ('MetaCons "MissingCaseBranchMachineError" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)) :+: C1 ('MetaCons "PanicMachineError" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))))

data EvaluationError structural operational Source #

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

  1. 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.
  2. 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.

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, structural errors are "runtime type errors" and operational errors are regular runtime 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.

Constructors

StructuralError !structural 
OperationalError !operational 

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, PrettyBy config structural, Pretty operational) ⇒ PrettyBy config (EvaluationError structural operational) Source # 
Instance details

Defined in PlutusCore.Evaluation.Error

Methods

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

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

Functor (EvaluationError structural) Source # 
Instance details

Defined in PlutusCore.Evaluation.Error

Methods

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

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

Generic (EvaluationError structural operational) Source # 
Instance details

Defined in PlutusCore.Evaluation.Error

Associated Types

type Rep (EvaluationError structural operational) ∷ TypeType Source #

Methods

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

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

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

Defined in PlutusCore.Evaluation.Error

Methods

showsPrecIntEvaluationError structural operational → ShowS Source #

showEvaluationError structural operational → String Source #

showList ∷ [EvaluationError structural operational] → ShowS Source #

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

Defined in PlutusCore.Evaluation.Error

Methods

rnfEvaluationError structural operational → () Source #

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

Defined in PlutusCore.Evaluation.Error

Methods

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

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

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

Defined in PlutusCore.Evaluation.Error

Methods

prettyEvaluationError structural operational → Doc ann Source #

prettyList ∷ [EvaluationError structural operational] → Doc ann 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 structural operational) Source # 
Instance details

Defined in PlutusCore.Evaluation.Error

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

data ErrorWithCause err cause Source #

An error and (optionally) what caused it.

Constructors

ErrorWithCause 

Fields

Instances

Instances details
Bifunctor ErrorWithCause Source # 
Instance details

Defined in PlutusCore.Evaluation.ErrorWithCause

Methods

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

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

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

(PrettyBy config cause, PrettyBy config err) ⇒ PrettyBy config (ErrorWithCause err cause) Source # 
Instance details

Defined in PlutusCore.Evaluation.ErrorWithCause

Methods

prettyBy ∷ config → ErrorWithCause err cause → Doc ann Source #

prettyListBy ∷ config → [ErrorWithCause err cause] → Doc ann Source #

Foldable (ErrorWithCause err) Source # 
Instance details

Defined in PlutusCore.Evaluation.ErrorWithCause

Methods

foldMonoid m ⇒ ErrorWithCause err m → m Source #

foldMapMonoid m ⇒ (a → m) → ErrorWithCause err a → m Source #

foldMap'Monoid m ⇒ (a → m) → ErrorWithCause err a → m Source #

foldr ∷ (a → b → b) → b → ErrorWithCause err a → b Source #

foldr' ∷ (a → b → b) → b → ErrorWithCause err a → b Source #

foldl ∷ (b → a → b) → b → ErrorWithCause err a → b Source #

foldl' ∷ (b → a → b) → b → ErrorWithCause err a → b Source #

foldr1 ∷ (a → a → a) → ErrorWithCause err a → a Source #

foldl1 ∷ (a → a → a) → ErrorWithCause err a → a Source #

toListErrorWithCause err a → [a] Source #

nullErrorWithCause err a → Bool Source #

lengthErrorWithCause err a → Int Source #

elemEq a ⇒ a → ErrorWithCause err a → Bool Source #

maximumOrd a ⇒ ErrorWithCause err a → a Source #

minimumOrd a ⇒ ErrorWithCause err a → a Source #

sumNum a ⇒ ErrorWithCause err a → a Source #

productNum a ⇒ ErrorWithCause err a → a Source #

Traversable (ErrorWithCause err) Source # 
Instance details

Defined in PlutusCore.Evaluation.ErrorWithCause

Methods

traverseApplicative f ⇒ (a → f b) → ErrorWithCause err a → f (ErrorWithCause err b) Source #

sequenceAApplicative f ⇒ ErrorWithCause err (f a) → f (ErrorWithCause err a) Source #

mapMMonad m ⇒ (a → m b) → ErrorWithCause err a → m (ErrorWithCause err b) Source #

sequenceMonad m ⇒ ErrorWithCause err (m a) → m (ErrorWithCause err a) Source #

Functor (ErrorWithCause err) Source # 
Instance details

Defined in PlutusCore.Evaluation.ErrorWithCause

Methods

fmap ∷ (a → b) → ErrorWithCause err a → ErrorWithCause err b Source #

(<$) ∷ a → ErrorWithCause err b → ErrorWithCause err a Source #

(PrettyPlc cause, PrettyPlc err, Typeable cause, Typeable err) ⇒ Exception (ErrorWithCause err cause) Source # 
Instance details

Defined in PlutusCore.Evaluation.ErrorWithCause

Generic (ErrorWithCause err cause) Source # 
Instance details

Defined in PlutusCore.Evaluation.ErrorWithCause

Associated Types

type Rep (ErrorWithCause err cause) ∷ TypeType Source #

Methods

fromErrorWithCause err cause → Rep (ErrorWithCause err cause) x Source #

toRep (ErrorWithCause err cause) x → ErrorWithCause err cause Source #

(PrettyPlc cause, PrettyPlc err) ⇒ Show (ErrorWithCause err cause) Source # 
Instance details

Defined in PlutusCore.Evaluation.ErrorWithCause

Methods

showsPrecIntErrorWithCause err cause → ShowS Source #

showErrorWithCause err cause → String Source #

showList ∷ [ErrorWithCause err cause] → ShowS Source #

(NFData err, NFData cause) ⇒ NFData (ErrorWithCause err cause) Source # 
Instance details

Defined in PlutusCore.Evaluation.ErrorWithCause

Methods

rnfErrorWithCause err cause → () Source #

(Eq err, Eq cause) ⇒ Eq (ErrorWithCause err cause) Source # 
Instance details

Defined in PlutusCore.Evaluation.ErrorWithCause

Methods

(==)ErrorWithCause err cause → ErrorWithCause err cause → Bool Source #

(/=)ErrorWithCause err cause → ErrorWithCause err cause → Bool Source #

(Pretty err, Pretty cause) ⇒ Pretty (ErrorWithCause err cause) Source # 
Instance details

Defined in PlutusCore.Evaluation.ErrorWithCause

Methods

prettyErrorWithCause err cause → Doc ann Source #

prettyList ∷ [ErrorWithCause err cause] → Doc ann 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 (ErrorWithCause err cause) Source # 
Instance details

Defined in PlutusCore.Evaluation.ErrorWithCause

type Rep (ErrorWithCause err cause) = D1 ('MetaData "ErrorWithCause" "PlutusCore.Evaluation.ErrorWithCause" "plutus-core-1.47.0.0-inplace" 'False) (C1 ('MetaCons "ErrorWithCause" 'PrefixI 'True) (S1 ('MetaSel ('Just "_ewcError") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 err) :*: S1 ('MetaSel ('Just "_ewcCause") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe cause))))

type EvaluationException structural operational = ErrorWithCause (EvaluationError structural operational) Source #

throwErrorWithCauseMonadError (ErrorWithCause e cause) m ⇒ e → cause → m x Source #

splitStructuralOperationalEither (EvaluationException structural operational term) a → Either (ErrorWithCause structural term) (EvaluationResult a) Source #

Preserve the contents of an StructuralError as a Left and turn an OperationalError into a Right EvaluationFailure (thus erasing the content of the error in the latter case).

unsafeSplitStructuralOperational ∷ (PrettyPlc structural, PrettyPlc term, Typeable structural, Typeable term) ⇒ Either (EvaluationException structural operational term) a → EvaluationResult a Source #

Throw on a StructuralError and turn an OperationalError into an EvaluationFailure (thus erasing the content of the error in the latter case).

builtinErrorToEvaluationErrorBuiltinErrorToEvaluationError structural operational ⇒ BuiltinErrorEvaluationError structural operational Source #

throwBuiltinErrorWithCause ∷ (MonadError (EvaluationException structural operational cause) m, BuiltinErrorToEvaluationError structural operational) ⇒ cause → BuiltinError → m void Source #

Attach a cause to a BuiltinError and throw that. Note that an evaluator might require the cause to be computed lazily for best performance on the happy path, hence this function must not force its first argument. TODO: wrap cause in Lazy once we have it.