| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
PlutusCore.Builtin.KnownType
Synopsis
- data BuiltinError
- class GEqL f a where
- geqL ∷ f (Esc a) → f (Esc b) → EvaluationResult (a :~: b)
- newtype LoopBreaker uni a = LoopBreaker (uni a)
- type KnownBuiltinTypeIn uni val a = (HasConstantIn uni val, PrettyParens (SomeTypeIn uni), GEqL uni a, uni `HasTermLevel` a)
- type KnownBuiltinType val a = KnownBuiltinTypeIn (UniOf val) val a
- data BuiltinResult a
- type ReadKnownM = Either BuiltinError
- data Spine a
- data HeadSpine a b
- headSpine ∷ a → [b] → HeadSpine a b
- type MonoHeadSpine a = HeadSpine a a
- class uni ~ UniOf val ⇒ MakeKnownIn uni val a where
- makeKnown ∷ a → BuiltinResult val
- readKnownConstant ∷ ∀ val a. KnownBuiltinType val a ⇒ val → ReadKnownM a
- type MakeKnown val = MakeKnownIn (UniOf val) val
- class uni ~ UniOf val ⇒ ReadKnownIn uni val a where
- readKnown ∷ val → ReadKnownM a
- type ReadKnown val = ReadKnownIn (UniOf val) val
- makeKnownOrFail ∷ MakeKnownIn uni val a ⇒ a → EvaluationResult val
- readKnownSelf ∷ (ReadKnown val a, BuiltinErrorToEvaluationError structural operational) ⇒ val → Either (ErrorWithCause (EvaluationError structural operational) val) a
Documentation
data BuiltinError Source #
The type of errors that readKnown and makeKnown can return.
Instances
| Show BuiltinError Source # | |
Defined in PlutusCore.Builtin.Result | |
| Eq BuiltinError Source # | |
Defined in PlutusCore.Builtin.Result Methods (==) ∷ BuiltinError → BuiltinError → Bool Source # (/=) ∷ BuiltinError → BuiltinError → Bool Source # | |
| Pretty BuiltinError Source # | |
Defined in PlutusCore.Builtin.Result | |
| MonadError BuiltinError BuiltinResult Source # |
|
Defined in PlutusCore.Builtin.Result Methods throwError ∷ BuiltinError → BuiltinResult a Source # catchError ∷ BuiltinResult a → (BuiltinError → BuiltinResult a) → BuiltinResult a Source # | |
A version of GEq that fixes a in place, which allows us to create an inlinable recursive
implementation of geqL.
The way it works is that whenever there's recursion, we look up the recursive case in the current
context (i.e. the dictionary) instead of actually calling geqL recursively (even though it's
gonna look like we do exactly that, because there's no way to distinguish between a recursive
call and a dictionary lookup as the two share the same name, although to help GHC choose a lookup
we sprinkle the perhaps unreliable LoopBreaker in the DefaultUni instance of this class).
Alligning things this way allows us to inline arbitrarily deep recursion for as long as types keep being monomorphic.
For example, the MapData builtin accepts a [(Data, Data)] and with geqL matching on all of
DefaultUniProtoList, DefaultUniProtoPair and DefaultUniData gets inlined in the denotation
of the builtin. For the Constr builtin that resulted in a 4.3% speedup at the time this comment
was written.
Instances
| AllBuiltinArgs DefaultUni (GEqL DefaultUni) a ⇒ GEqL DefaultUni a Source # | |
Defined in PlutusCore.Default.Universe Methods geqL ∷ DefaultUni (Esc a) → DefaultUni (Esc b) → EvaluationResult (a :~: b) Source # | |
| GEqL uni a ⇒ GEqL (LoopBreaker uni) a Source # | |
Defined in PlutusCore.Builtin.KnownType Methods geqL ∷ LoopBreaker uni (Esc a) → LoopBreaker uni (Esc b) → EvaluationResult (a :~: b) Source # | |
newtype LoopBreaker uni a Source #
In f = ... f ... where f is a class method, how do you know if f is going to be a
recursive call or a type class method call? If both type check, then you don't really know how
GHC is going to play it. So we add this data type to make sure that the RHS f will have to
become a type class method call.
Can GHC turn that method call into a recursive one once type classes are resolved? Dunno, but at least we've introduced an obstacle preventing GHC from immediately creating a non-inlinable recursive definition.
Constructors
| LoopBreaker (uni a) |
Instances
| GEqL uni a ⇒ GEqL (LoopBreaker uni) a Source # | |
Defined in PlutusCore.Builtin.KnownType Methods geqL ∷ LoopBreaker uni (Esc a) → LoopBreaker uni (Esc b) → EvaluationResult (a :~: b) Source # | |
type KnownBuiltinTypeIn uni val a = (HasConstantIn uni val, PrettyParens (SomeTypeIn uni), GEqL uni a, 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:
- everything is strict
- has the
BuiltinSuccessconstructor 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.
Constructors
| BuiltinSuccess a | |
| BuiltinSuccessWithLogs (DList Text) a | |
| BuiltinFailure (DList Text) BuiltinError |
Instances
type ReadKnownM = Either BuiltinError Source #
The monad that readKnown runs in.
A non-empty spine. Isomorphic to NonEmpty, except is strict and is defined as a single
recursive data type.
Instances
The head-spine form of an iterated application. Provides O(1) access to the head of the
application. NonEmpty a ~ HeadSpine a a, except is strict and the no-spine case is made a separate
constructor for performance reasons (it only takes a single pattern match to access the head when
there's no spine this way, while otherwise we'd also need to match on the spine to ensure that
it's empty -- and the no-spine case is by far the most common one, hence we want to optimize it).
Used in built-in functions returning function applications such as CaseList.
Instances
| Bifunctor HeadSpine Source # | |
| (PrettyBy config a, PrettyBy config b) ⇒ DefaultPrettyBy config (HeadSpine a b) Source # | |
Defined in PlutusCore.Builtin.KnownType Methods defaultPrettyBy ∷ config → HeadSpine a b → Doc ann Source # defaultPrettyListBy ∷ config → [HeadSpine a b] → Doc ann Source # | |
| PrettyDefaultBy config (HeadSpine a b) ⇒ PrettyBy config (HeadSpine a b) Source # | |
| Functor (HeadSpine a) Source # | |
| (Show a, Show b) ⇒ Show (HeadSpine a b) Source # | |
| (Eq a, Eq b) ⇒ Eq (HeadSpine a b) Source # | |
| (Pretty a, Pretty b) ⇒ Pretty (HeadSpine a b) Source # |
|
type MonoHeadSpine a = HeadSpine a a Source #
HeadSpine but the type of head and spine is same
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 makeKnown ∷ KnownBuiltinType val a ⇒ a → BuiltinResult val Source #
Instances
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 readKnown ∷ KnownBuiltinType val a ⇒ val → ReadKnownM a Source #
Instances
type ReadKnown val = ReadKnownIn (UniOf val) val Source #
makeKnownOrFail ∷ MakeKnownIn 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, BuiltinErrorToEvaluationError structural operational) ⇒ val → Either (ErrorWithCause (EvaluationError structural operational) val) a Source #
Same as readKnown, but the cause of a potential failure is the provided term itself.