plutus-core-1.0.0.1: Language library for Plutus Core
Safe Haskell None
Language Haskell2010

UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Description

The CEK machine. The CEK machine relies on variables having non-equal Unique s whenever they have non-equal string names. I.e. Unique s are used instead of string names. This is for efficiency reasons. The CEK machines handles name capture by design.

Synopsis

Documentation

data EvaluationResult a Source #

The parameterized type of results various evaluation engines return. On the PLC side this becomes (via makeKnown ) either a call to Error or a value of the PLC counterpart of type a .

Instances

Instances details
Monad EvaluationResult Source #
Instance details

Defined in PlutusCore.Evaluation.Result

Functor EvaluationResult Source #
Instance details

Defined in PlutusCore.Evaluation.Result

MonadFail EvaluationResult Source #
Instance details

Defined in PlutusCore.Evaluation.Result

Applicative EvaluationResult Source #
Instance details

Defined in PlutusCore.Evaluation.Result

Foldable EvaluationResult Source #
Instance details

Defined in PlutusCore.Evaluation.Result

Traversable EvaluationResult Source #
Instance details

Defined in PlutusCore.Evaluation.Result

Alternative EvaluationResult Source #
Instance details

Defined in PlutusCore.Evaluation.Result

MonadError () EvaluationResult Source #
Instance details

Defined in PlutusCore.Evaluation.Result

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

Defined in PlutusCore.Builtin.KnownType

MakeKnownIn uni val a => MakeKnownIn uni val ( EvaluationResult a) Source #
Instance details

Defined in PlutusCore.Builtin.KnownType

PrettyBy config a => PrettyBy config ( EvaluationResult a) Source #
Instance details

Defined in PlutusCore.Evaluation.Result

Eq a => Eq ( EvaluationResult a) Source #
Instance details

Defined in PlutusCore.Evaluation.Result

Show a => Show ( EvaluationResult a) Source #
Instance details

Defined in PlutusCore.Evaluation.Result

Generic ( EvaluationResult a) Source #
Instance details

Defined in PlutusCore.Evaluation.Result

NFData a => NFData ( EvaluationResult a) Source #
Instance details

Defined in PlutusCore.Evaluation.Result

PrettyClassic a => Pretty ( EvaluationResult a) Source #
Instance details

Defined in PlutusCore.Evaluation.Result

KnownTypeAst uni a => KnownTypeAst uni ( EvaluationResult a :: Type ) Source #
Instance details

Defined in PlutusCore.Builtin.KnownTypeAst

type Rep ( EvaluationResult a) Source #
Instance details

Defined in PlutusCore.Evaluation.Result

type Rep ( EvaluationResult a) = D1 (' MetaData "EvaluationResult" "PlutusCore.Evaluation.Result" "plutus-core-1.0.0.1-76bWF9ZEWyb4eDyjHx0kCS" ' False ) ( C1 (' MetaCons "EvaluationSuccess" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 a)) :+: C1 (' MetaCons "EvaluationFailure" ' PrefixI ' False ) ( U1 :: Type -> Type ))
type ToHoles ( EvaluationResult a :: Type ) Source #
Instance details

Defined in PlutusCore.Builtin.KnownTypeAst

type ToBinds ( EvaluationResult a :: Type ) Source #
Instance details

Defined in PlutusCore.Builtin.KnownTypeAst

data CekValue uni fun Source #

Constructors

VCon !( Some ( ValueOf uni))
VDelay ( Term NamedDeBruijn uni fun ()) !(CekValEnv uni fun)
VLamAbs NamedDeBruijn ( Term NamedDeBruijn uni fun ()) !(CekValEnv uni fun)
VBuiltin !fun ( Term NamedDeBruijn uni fun ()) (CekValEnv uni fun) !( BuiltinRuntime ( CekValue uni fun))

Instances

Instances details
( Closed uni, GShow uni, Everywhere uni PrettyConst , Pretty fun) => PrettyBy PrettyConfigPlc ( CekValue uni fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Show ( BuiltinRuntime ( CekValue uni fun)) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

( Everywhere uni Show , GShow uni, Closed uni, Show fun) => Show ( CekValue uni fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

HasConstant ( CekValue uni fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

type UniOf ( CekValue uni fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

type UniOf ( CekValue uni fun) = uni

data CekUserError Source #

Constructors

CekOutOfExError ExRestrictingBudget

The final overspent (i.e. negative) budget.

CekEvaluationFailure

Error has been called or a builtin application has failed

Instances

Instances details
Eq CekUserError Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Show CekUserError Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Generic CekUserError Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

NFData CekUserError Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Pretty CekUserError Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

HasErrorCode CekUserError Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

AsEvaluationFailure CekUserError Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

PrettyUni uni fun => MonadError ( CekEvaluationException NamedDeBruijn uni fun) ( CekM uni fun s) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

type Rep CekUserError Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

type Rep CekUserError = D1 (' MetaData "CekUserError" "UntypedPlutusCore.Evaluation.Machine.Cek.Internal" "plutus-core-1.0.0.1-76bWF9ZEWyb4eDyjHx0kCS" ' False ) ( C1 (' MetaCons "CekOutOfExError" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ExRestrictingBudget )) :+: C1 (' MetaCons "CekEvaluationFailure" ' PrefixI ' False ) ( U1 :: Type -> Type ))

newtype CekBudgetSpender uni fun s Source #

The CEK machine is parameterized over a spendBudget function. This makes the budgeting machinery extensible and allows us to separate budgeting logic from evaluation logic and avoid branching on the union of all possible budgeting state types during evaluation.

data ExBudgetInfo cost uni fun s Source #

Runtime budgeting info.

Constructors

ExBudgetInfo

Fields

newtype ExBudgetMode cost uni fun Source #

A budgeting mode to execute the CEK machine in.

Constructors

ExBudgetMode

Fields

type CekEmitter uni fun s = DList Text -> CekM uni fun s () Source #

The CEK machine is parameterized over an emitter function, similar to CekBudgetSpender .

newtype EmitterMode uni fun Source #

An emitting mode to execute the CEK machine in, similar to ExBudgetMode .

Constructors

EmitterMode

Fields

newtype CekM uni fun s a Source #

The monad the CEK machine runs in.

Constructors

CekM

Fields

Instances

Instances details
Monad ( CekM uni fun s) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Methods

(>>=) :: CekM uni fun s a -> (a -> CekM uni fun s b) -> CekM uni fun s b Source #

(>>) :: CekM uni fun s a -> CekM uni fun s b -> CekM uni fun s b Source #

return :: a -> CekM uni fun s a Source #

Functor ( CekM uni fun s) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Methods

fmap :: (a -> b) -> CekM uni fun s a -> CekM uni fun s b Source #

(<$) :: a -> CekM uni fun s b -> CekM uni fun s a Source #

Applicative ( CekM uni fun s) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Methods

pure :: a -> CekM uni fun s a Source #

(<*>) :: CekM uni fun s (a -> b) -> CekM uni fun s a -> CekM uni fun s b Source #

liftA2 :: (a -> b -> c) -> CekM uni fun s a -> CekM uni fun s b -> CekM uni fun s c Source #

(*>) :: CekM uni fun s a -> CekM uni fun s b -> CekM uni fun s b Source #

(<*) :: CekM uni fun s a -> CekM uni fun s b -> CekM uni fun s a Source #

PrettyUni uni fun => MonadError ( CekEvaluationException NamedDeBruijn uni fun) ( CekM uni fun s) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

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.Machine.Exception

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

Defined in PlutusCore.Evaluation.Machine.Exception

Methods

prettyBy :: config -> ErrorWithCause err cause -> Doc ann Source #

prettyListBy :: config -> [ ErrorWithCause err cause] -> Doc ann Source #

Functor ( ErrorWithCause err) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Foldable ( ErrorWithCause err) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Traversable ( ErrorWithCause err) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

( Eq err, Eq cause) => Eq ( ErrorWithCause err cause) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

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

Defined in PlutusCore.Evaluation.Machine.Exception

Generic ( ErrorWithCause err cause) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Associated Types

type Rep ( ErrorWithCause err cause) :: Type -> Type Source #

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

Defined in PlutusCore.Evaluation.Machine.Exception

( NFData err, NFData cause) => NFData ( ErrorWithCause err cause) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Methods

rnf :: ErrorWithCause err cause -> () Source #

( Pretty err, Pretty cause) => Pretty ( ErrorWithCause err cause) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

HasErrorCode err => HasErrorCode ( ErrorWithCause err t) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

AsEvaluationFailure err => AsEvaluationFailure ( ErrorWithCause err cause) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

PrettyUni uni fun => MonadError ( CekEvaluationException NamedDeBruijn uni fun) ( CekM uni fun s) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

type Rep ( ErrorWithCause err cause) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

type Rep ( ErrorWithCause err cause) = D1 (' MetaData "ErrorWithCause" "PlutusCore.Evaluation.Machine.Exception" "plutus-core-1.0.0.1-76bWF9ZEWyb4eDyjHx0kCS" ' False ) ( C1 (' MetaCons "ErrorWithCause" ' PrefixI ' True ) ( S1 (' MetaSel (' Just "_ewcError") ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 err) :*: S1 (' MetaSel (' Just "_ewcCause") ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Maybe cause))))

data EvaluationError user internal Source #

The type of errors (all of them) which can occur during evaluation (some are used-caused, some are internal).

Constructors

InternalEvaluationError internal

Indicates bugs.

UserEvaluationError user

Indicates user errors.

Instances

Instances details
( HasPrettyDefaults config ~ ' True , PrettyBy config internal, Pretty user) => PrettyBy config ( EvaluationError user internal) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Methods

prettyBy :: config -> EvaluationError user internal -> Doc ann Source #

prettyListBy :: config -> [ EvaluationError user internal] -> Doc ann Source #

Functor ( EvaluationError user) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

( Eq internal, Eq user) => Eq ( EvaluationError user internal) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

( Show internal, Show user) => Show ( EvaluationError user internal) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Generic ( EvaluationError user internal) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Associated Types

type Rep ( EvaluationError user internal) :: Type -> Type Source #

Methods

from :: EvaluationError user internal -> Rep ( EvaluationError user internal) x Source #

to :: Rep ( EvaluationError user internal) x -> EvaluationError user internal Source #

( NFData internal, NFData user) => NFData ( EvaluationError user internal) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Methods

rnf :: EvaluationError user internal -> () Source #

( HasErrorCode user, HasErrorCode internal) => HasErrorCode ( EvaluationError user internal) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

AsEvaluationFailure user => AsEvaluationFailure ( EvaluationError user internal) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

AsUnliftingError internal => AsUnliftingError ( EvaluationError user internal) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

internal ~ MachineError fun => AsMachineError ( EvaluationError user internal) fun Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

AsEvaluationError ( EvaluationError user internal) user internal Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

PrettyUni uni fun => MonadError ( CekEvaluationException NamedDeBruijn uni fun) ( CekM uni fun s) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

type Rep ( EvaluationError user internal) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

type Rep ( EvaluationError user internal) = D1 (' MetaData "EvaluationError" "PlutusCore.Evaluation.Machine.Exception" "plutus-core-1.0.0.1-76bWF9ZEWyb4eDyjHx0kCS" ' False ) ( C1 (' MetaCons "InternalEvaluationError" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 internal)) :+: C1 (' MetaCons "UserEvaluationError" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 user)))

data ExBudgetCategory fun Source #

Instances

Instances details
ExBudgetBuiltin fun ( ExBudgetCategory fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Eq fun => Eq ( ExBudgetCategory fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Ord fun => Ord ( ExBudgetCategory fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Show fun => Show ( ExBudgetCategory fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Generic ( ExBudgetCategory fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Hashable fun => Hashable ( ExBudgetCategory fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

NFData fun => NFData ( ExBudgetCategory fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Show fun => Pretty ( ExBudgetCategory fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

type Rep ( ExBudgetCategory fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

data StepKind Source #

Instances

Instances details
Bounded StepKind Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Enum StepKind Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Eq StepKind Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Ord StepKind Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Show StepKind Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Generic StepKind Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Hashable StepKind Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

NFData StepKind Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

type Rep StepKind Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

type Rep StepKind = D1 (' MetaData "StepKind" "UntypedPlutusCore.Evaluation.Machine.Cek.Internal" "plutus-core-1.0.0.1-76bWF9ZEWyb4eDyjHx0kCS" ' False ) (( C1 (' MetaCons "BConst" ' PrefixI ' False ) ( U1 :: Type -> Type ) :+: ( C1 (' MetaCons "BVar" ' PrefixI ' False ) ( U1 :: Type -> Type ) :+: C1 (' MetaCons "BLamAbs" ' PrefixI ' False ) ( U1 :: Type -> Type ))) :+: (( C1 (' MetaCons "BApply" ' PrefixI ' False ) ( U1 :: Type -> Type ) :+: C1 (' MetaCons "BDelay" ' PrefixI ' False ) ( U1 :: Type -> Type )) :+: ( C1 (' MetaCons "BForce" ' PrefixI ' False ) ( U1 :: Type -> Type ) :+: C1 (' MetaCons "BBuiltin" ' PrefixI ' False ) ( U1 :: Type -> Type ))))

type PrettyUni uni fun = ( GShow uni, Closed uni, Pretty fun, Typeable uni, Typeable fun, Everywhere uni PrettyConst ) Source #

The set of constraints we need to be able to print things in universes, which we need in order to throw exceptions.

runCekDeBruijn :: (uni `Everywhere` ExMemoryUsage , Ix fun, PrettyUni uni fun) => MachineParameters CekMachineCosts CekValue uni fun -> ExBudgetMode cost uni fun -> EmitterMode uni fun -> Term NamedDeBruijn uni fun () -> ( Either ( CekEvaluationException NamedDeBruijn uni fun) ( Term NamedDeBruijn uni fun ()), cost, [ Text ]) Source #

Evaluate a term using the CEK machine and keep track of costing, logging is optional.

dischargeCekValue :: CekValue uni fun -> Term NamedDeBruijn uni fun () Source #

Convert a CekValue into a Term by replacing all bound variables with the terms they're bound to (which themselves have to be obtain by recursively discharging values).