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

PlutusCore.Builtin.KnownType

Synopsis

Documentation

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

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.

type KnownBuiltinTypeIn uni val a = (HasConstantIn uni val, PrettyParens (SomeTypeIn uni), GEq uni, uni `HasTermLevel` a) Source #

A constraint for "a is a ReadKnownIn and MakeKnownIn by means of being included in uni".

type KnownBuiltinType val a = KnownBuiltinTypeIn (UniOf val) val a Source #

A constraint for "a is a ReadKnownIn and MakeKnownIn by means of being included in UniOf term".

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]

type ReadKnownM = Either BuiltinError Source #

The monad that readKnown runs in.

class uni ~ UniOf val ⇒ MakeKnownIn uni val a where Source #

Minimal complete definition

Nothing

Methods

makeKnown ∷ a → BuiltinResult val Source #

Convert a Haskell value to the corresponding PLC value. The inverse of readKnown.

default makeKnownKnownBuiltinType val a ⇒ a → BuiltinResult val Source #

Instances

Instances details
UniOf term ~ DefaultUniMakeKnownIn DefaultUni term Void Source # 
Instance details

Defined in PlutusCore.Examples.Builtins

Methods

makeKnownVoidBuiltinResult term Source #

KnownBuiltinTypeIn DefaultUni term IntegerMakeKnownIn DefaultUni term Int16 Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnownInt16BuiltinResult term Source #

KnownBuiltinTypeIn DefaultUni term IntegerMakeKnownIn DefaultUni term Int32 Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnownInt32BuiltinResult term Source #

KnownBuiltinTypeIn DefaultUni term IntegerMakeKnownIn DefaultUni term Int64 Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnownInt64BuiltinResult term Source #

KnownBuiltinTypeIn DefaultUni term IntegerMakeKnownIn DefaultUni term Int8 Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnownInt8BuiltinResult term Source #

KnownBuiltinTypeIn DefaultUni term IntegerMakeKnownIn DefaultUni term Word16 Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnownWord16BuiltinResult term Source #

KnownBuiltinTypeIn DefaultUni term IntegerMakeKnownIn DefaultUni term Word32 Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnownWord32BuiltinResult term Source #

KnownBuiltinTypeIn DefaultUni term IntegerMakeKnownIn DefaultUni term Word64 Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnownWord64BuiltinResult term Source #

KnownBuiltinTypeIn DefaultUni term IntegerMakeKnownIn DefaultUni term Word8 Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnownWord8BuiltinResult term Source #

KnownBuiltinTypeIn DefaultUni term ByteStringMakeKnownIn DefaultUni term ByteString Source # 
Instance details

Defined in PlutusCore.Default.Universe

KnownBuiltinTypeIn DefaultUni term ElementMakeKnownIn DefaultUni term Element Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnownElementBuiltinResult term Source #

KnownBuiltinTypeIn DefaultUni term ElementMakeKnownIn DefaultUni term Element Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnownElementBuiltinResult term Source #

KnownBuiltinTypeIn DefaultUni term MlResultMakeKnownIn DefaultUni term MlResult Source # 
Instance details

Defined in PlutusCore.Default.Universe

KnownBuiltinTypeIn DefaultUni term DataMakeKnownIn DefaultUni term Data Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnownDataBuiltinResult term Source #

KnownBuiltinTypeIn DefaultUni term IntegerMakeKnownIn DefaultUni term IntegerCostedLiterally Source # 
Instance details

Defined in PlutusCore.Default.Universe

KnownBuiltinTypeIn DefaultUni term IntegerMakeKnownIn DefaultUni term NumBytesCostedAsNumWords Source # 
Instance details

Defined in PlutusCore.Default.Universe

KnownBuiltinTypeIn DefaultUni term TextMakeKnownIn DefaultUni term Text Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnownTextBuiltinResult term Source #

KnownBuiltinTypeIn DefaultUni term IntegerMakeKnownIn DefaultUni term Integer Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnownIntegerBuiltinResult term Source #

KnownBuiltinTypeIn DefaultUni term IntegerMakeKnownIn DefaultUni term Natural Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnownNaturalBuiltinResult term Source #

KnownBuiltinTypeIn DefaultUni term () ⇒ MakeKnownIn DefaultUni term () Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnown ∷ () → BuiltinResult term Source #

KnownBuiltinTypeIn DefaultUni term BoolMakeKnownIn DefaultUni term Bool Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnownBoolBuiltinResult term Source #

KnownBuiltinTypeIn DefaultUni term IntegerMakeKnownIn DefaultUni term Int Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnownIntBuiltinResult term Source #

KnownBuiltinTypeIn DefaultUni term IntegerMakeKnownIn DefaultUni term Word Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnownWordBuiltinResult term Source #

KnownBuiltinTypeIn DefaultUni term [a] ⇒ MakeKnownIn DefaultUni term (ListCostedByLength a) Source # 
Instance details

Defined in PlutusCore.Default.Universe

KnownBuiltinTypeIn DefaultUni term [a] ⇒ MakeKnownIn DefaultUni term [a] Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnown ∷ [a] → BuiltinResult term Source #

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

Defined in PlutusCore.Builtin.KnownType

(TypeError ('Text "Use \8216BuiltinResult\8217 instead of \8216EvaluationResult\8217") ∷ Constraint, uni ~ UniOf val) ⇒ MakeKnownIn uni val (EvaluationResult a) Source # 
Instance details

Defined in PlutusCore.Builtin.KnownType

KnownBuiltinTypeIn DefaultUni term (a, b) ⇒ MakeKnownIn DefaultUni term (a, b) Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnown ∷ (a, b) → BuiltinResult term Source #

uni ~ UniOf val ⇒ MakeKnownIn uni val (Opaque val rep) Source # 
Instance details

Defined in PlutusCore.Builtin.KnownType

Methods

makeKnownOpaque val rep → BuiltinResult val Source #

HasConstantIn uni val ⇒ MakeKnownIn uni val (SomeConstant uni rep) Source # 
Instance details

Defined in PlutusCore.Builtin.KnownType

Methods

makeKnownSomeConstant uni rep → BuiltinResult val Source #

MakeKnownIn DefaultUni term a ⇒ MakeKnownIn DefaultUni term (MetaForall name a) Source # 
Instance details

Defined in PlutusCore.Examples.Builtins

Methods

makeKnownMetaForall name a → BuiltinResult term Source #

readKnownConstant ∷ ∀ val a. KnownBuiltinType val a ⇒ val → ReadKnownM a Source #

Convert a constant embedded into a PLC term to the corresponding Haskell value.

type MakeKnown val = MakeKnownIn (UniOf val) val Source #

class uni ~ UniOf val ⇒ ReadKnownIn uni val a where Source #

Minimal complete definition

Nothing

Methods

readKnown ∷ val → ReadKnownM a Source #

Convert a PLC value to the corresponding Haskell value. The inverse of makeKnown.

default readKnownKnownBuiltinType val a ⇒ val → ReadKnownM a Source #

Instances

Instances details
UniOf term ~ DefaultUniReadKnownIn DefaultUni term Void Source # 
Instance details

Defined in PlutusCore.Examples.Builtins

Methods

readKnown ∷ term → ReadKnownM Void Source #

KnownBuiltinTypeIn DefaultUni term IntegerReadKnownIn DefaultUni term Int16 Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM Int16 Source #

KnownBuiltinTypeIn DefaultUni term IntegerReadKnownIn DefaultUni term Int32 Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM Int32 Source #

KnownBuiltinTypeIn DefaultUni term IntegerReadKnownIn DefaultUni term Int64 Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM Int64 Source #

KnownBuiltinTypeIn DefaultUni term IntegerReadKnownIn DefaultUni term Int8 Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM Int8 Source #

KnownBuiltinTypeIn DefaultUni term IntegerReadKnownIn DefaultUni term Word16 Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM Word16 Source #

KnownBuiltinTypeIn DefaultUni term IntegerReadKnownIn DefaultUni term Word32 Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM Word32 Source #

KnownBuiltinTypeIn DefaultUni term IntegerReadKnownIn DefaultUni term Word64 Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM Word64 Source #

KnownBuiltinTypeIn DefaultUni term IntegerReadKnownIn DefaultUni term Word8 Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM Word8 Source #

KnownBuiltinTypeIn DefaultUni term ByteStringReadKnownIn DefaultUni term ByteString Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM ByteString Source #

KnownBuiltinTypeIn DefaultUni term ElementReadKnownIn DefaultUni term Element Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM Element Source #

KnownBuiltinTypeIn DefaultUni term ElementReadKnownIn DefaultUni term Element Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM Element Source #

KnownBuiltinTypeIn DefaultUni term MlResultReadKnownIn DefaultUni term MlResult Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM MlResult Source #

KnownBuiltinTypeIn DefaultUni term DataReadKnownIn DefaultUni term Data Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM Data Source #

KnownBuiltinTypeIn DefaultUni term IntegerReadKnownIn DefaultUni term IntegerCostedLiterally Source # 
Instance details

Defined in PlutusCore.Default.Universe

KnownBuiltinTypeIn DefaultUni term IntegerReadKnownIn DefaultUni term NumBytesCostedAsNumWords Source # 
Instance details

Defined in PlutusCore.Default.Universe

KnownBuiltinTypeIn DefaultUni term TextReadKnownIn DefaultUni term Text Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM Text Source #

KnownBuiltinTypeIn DefaultUni term IntegerReadKnownIn DefaultUni term Integer Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM Integer Source #

KnownBuiltinTypeIn DefaultUni term IntegerReadKnownIn DefaultUni term Natural Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM Natural Source #

KnownBuiltinTypeIn DefaultUni term () ⇒ ReadKnownIn DefaultUni term () Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM () Source #

KnownBuiltinTypeIn DefaultUni term BoolReadKnownIn DefaultUni term Bool Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM Bool Source #

KnownBuiltinTypeIn DefaultUni term IntegerReadKnownIn DefaultUni term Int Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM Int Source #

KnownBuiltinTypeIn DefaultUni term IntegerReadKnownIn DefaultUni term Word Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM Word Source #

KnownBuiltinTypeIn DefaultUni term [a] ⇒ ReadKnownIn DefaultUni term (ListCostedByLength a) Source # 
Instance details

Defined in PlutusCore.Default.Universe

KnownBuiltinTypeIn DefaultUni term [a] ⇒ ReadKnownIn DefaultUni term [a] Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM [a] Source #

(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 #

(TypeError ('Text "Use \8216BuiltinResult\8217 instead of \8216EvaluationResult\8217") ∷ Constraint, uni ~ UniOf val) ⇒ ReadKnownIn uni val (EvaluationResult a) Source # 
Instance details

Defined in PlutusCore.Builtin.KnownType

KnownBuiltinTypeIn DefaultUni term (a, b) ⇒ ReadKnownIn DefaultUni term (a, b) Source # 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM (a, b) Source #

uni ~ UniOf val ⇒ ReadKnownIn uni val (Opaque val rep) Source # 
Instance details

Defined in PlutusCore.Builtin.KnownType

Methods

readKnown ∷ val → ReadKnownM (Opaque val rep) Source #

HasConstantIn uni val ⇒ ReadKnownIn uni val (SomeConstant uni rep) Source # 
Instance details

Defined in PlutusCore.Builtin.KnownType

Methods

readKnown ∷ val → ReadKnownM (SomeConstant uni rep) Source #

type ReadKnown val = ReadKnownIn (UniOf val) val Source #

makeKnownOrFailMakeKnownIn uni val a ⇒ a → EvaluationResult val Source #

Same as makeKnown, but allows for neither emitting nor storing the cause of a failure.

readKnownSelf ∷ (ReadKnown val a, AsUnliftingEvaluationError err, AsEvaluationFailure err) ⇒ val → Either (ErrorWithCause err val) a Source #

Same as readKnown, but the cause of a potential failure is the provided term itself.