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

PlutusCore.Evaluation.ErrorWithCause

Synopsis

Documentation

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 #

AsEvaluationFailure err ⇒ AsEvaluationFailure (ErrorWithCause err cause) Source # 
Instance details

Defined in PlutusCore.Evaluation.ErrorWithCause

Methods

_EvaluationFailure ∷ Prism' (ErrorWithCause err cause) () 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.34.1.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))))

throwingWithCause ∷ ∀ exc e t term m x. (exc ~ ErrorWithCause e term, MonadError exc m) ⇒ AReview e t → t → Maybe term → m x Source #

Prismatically throw an error and its (optional) cause.

throwingWithCause_ ∷ ∀ exc e term m x. (exc ~ ErrorWithCause e term, MonadError exc m) ⇒ AReview e () → Maybe term → m x Source #

Prismatically throw a contentless error and its (optional) cause. throwingWithCause_ is to throwingWithCause as throwing_ is to throwing.

throwBuiltinErrorWithCause ∷ (MonadError (ErrorWithCause err cause) m, AsUnliftingEvaluationError err, AsEvaluationFailure err) ⇒ 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.