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

UntypedPlutusCore.Evaluation.Machine.Cek

Description

The API to the CEK machine.

Synopsis

Running the machine

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

Evaluate a term using the CEK machine with logging enabled and keep track of costing. A wrapper around the internal runCek to debruijn input and undebruijn output. *THIS FUNCTION IS PARTIAL if the input term contains free variables*

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.

runCekNoEmit :: (uni `Everywhere` ExMemoryUsage , Ix fun, PrettyUni uni fun) => MachineParameters CekMachineCosts CekValue uni fun -> ExBudgetMode cost uni fun -> Term Name uni fun () -> ( Either ( CekEvaluationException Name uni fun) ( Term Name uni fun ()), cost) Source #

Evaluate a term using the CEK machine with logging disabled and keep track of costing. *THIS FUNCTION IS PARTIAL if the input term contains free variables*

unsafeRunCekNoEmit :: ( GShow uni, Typeable uni, Closed uni, uni `EverywhereAll` '[ ExMemoryUsage , PrettyConst ], Ix fun, Pretty fun, Typeable fun) => MachineParameters CekMachineCosts CekValue uni fun -> ExBudgetMode cost uni fun -> Term Name uni fun () -> ( EvaluationResult ( Term Name uni fun ()), cost) Source #

Unsafely evaluate a term using the CEK machine with logging disabled and keep track of costing. May throw a CekMachineException . *THIS FUNCTION IS PARTIAL if the input term contains free variables*

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

Evaluate a term using the CEK machine with logging enabled. *THIS FUNCTION IS PARTIAL if the input term contains free variables*

evaluateCekNoEmit :: (uni `Everywhere` ExMemoryUsage , Ix fun, PrettyUni uni fun) => MachineParameters CekMachineCosts CekValue uni fun -> Term Name uni fun () -> Either ( CekEvaluationException Name uni fun) ( Term Name uni fun ()) Source #

Evaluate a term using the CEK machine with logging disabled. *THIS FUNCTION IS PARTIAL if the input term contains free variables*

unsafeEvaluateCek :: ( GShow uni, Typeable uni, Closed uni, uni `EverywhereAll` '[ ExMemoryUsage , PrettyConst ], Ix fun, Pretty fun, Typeable fun) => EmitterMode uni fun -> MachineParameters CekMachineCosts CekValue uni fun -> Term Name uni fun () -> ( EvaluationResult ( Term Name uni fun ()), [ Text ]) Source #

Evaluate a term using the CEK machine with logging enabled. May throw a CekMachineException . *THIS FUNCTION IS PARTIAL if the input term contains free variables*

unsafeEvaluateCekNoEmit :: ( GShow uni, Typeable uni, Closed uni, uni `EverywhereAll` '[ ExMemoryUsage , PrettyConst ], Ix fun, Pretty fun, Typeable fun) => MachineParameters CekMachineCosts CekValue uni fun -> Term Name uni fun () -> EvaluationResult ( Term Name uni fun ()) Source #

Evaluate a term using the CEK machine with logging disabled. May throw a CekMachineException . *THIS FUNCTION IS PARTIAL if the input term contains free variables*

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

Errors

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 ))

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)))

Costing

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

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.

newtype ExBudgetMode cost uni fun Source #

A budgeting mode to execute the CEK machine in.

Constructors

ExBudgetMode

Fields

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 ))))

newtype CekExTally fun Source #

For a detailed report on what costs how much + the same overall budget that Counting gives. The (derived) Monoid instance of CekExTally is the main piece of the machinery.

Instances

Instances details
( Show fun, Ord fun) => PrettyBy config ( CekExTally fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

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

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

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

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Generic ( CekExTally fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Associated Types

type Rep ( CekExTally fun) :: Type -> Type Source #

( Eq fun, Hashable fun) => Semigroup ( CekExTally fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

( Eq fun, Hashable fun) => Monoid ( CekExTally fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

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

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

( Show fun, Ord fun) => Pretty ( CekExTally fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

type Rep ( CekExTally fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

type Rep ( CekExTally fun) = D1 (' MetaData "CekExTally" "UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode" "plutus-core-1.0.0.1-76bWF9ZEWyb4eDyjHx0kCS" ' True ) ( C1 (' MetaCons "CekExTally" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( MonoidalHashMap ( ExBudgetCategory fun) ExBudget ))))

newtype CountingSt Source #

For calculating the cost of execution by counting up using the Monoid instance of ExBudget .

Instances

Instances details
Eq CountingSt Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Show CountingSt Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Semigroup CountingSt Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Monoid CountingSt Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

NFData CountingSt Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Pretty CountingSt Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

PrettyBy config CountingSt Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

data TallyingSt fun Source #

Instances

Instances details
( Show fun, Ord fun) => PrettyBy config ( TallyingSt fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

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

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

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

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Generic ( TallyingSt fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Associated Types

type Rep ( TallyingSt fun) :: Type -> Type Source #

( Eq fun, Hashable fun) => Semigroup ( TallyingSt fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

( Eq fun, Hashable fun) => Monoid ( TallyingSt fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

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

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

( Show fun, Ord fun) => Pretty ( TallyingSt fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

type Rep ( TallyingSt fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

newtype RestrictingSt Source #

Instances

Instances details
Eq RestrictingSt Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Show RestrictingSt Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Semigroup RestrictingSt Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Monoid RestrictingSt Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

NFData RestrictingSt Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Pretty RestrictingSt Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

PrettyBy config RestrictingSt Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

data CekMachineCosts Source #

Costs for evaluating AST nodes. Times should be specified in picoseconds, memory sizes in bytes.

Instances

Instances details
Eq CekMachineCosts Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.CekMachineCosts

Show CekMachineCosts Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.CekMachineCosts

Generic CekMachineCosts Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.CekMachineCosts

ToJSON CekMachineCosts Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.CekMachineCosts

FromJSON CekMachineCosts Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.CekMachineCosts

NFData CekMachineCosts Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.CekMachineCosts

NoThunks CekMachineCosts Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.CekMachineCosts

Lift CekMachineCosts Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.CekMachineCosts

type Rep CekMachineCosts Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.CekMachineCosts

Costing modes

counting :: ExBudgetMode CountingSt uni fun Source #

For calculating the cost of execution.

tallying :: ( Eq fun, Hashable fun) => ExBudgetMode ( TallyingSt fun) uni fun Source #

For a detailed report on what costs how much + the same overall budget that Counting gives.

restricting :: forall uni fun. PrettyUni uni fun => ExRestrictingBudget -> ExBudgetMode RestrictingSt uni fun Source #

For execution, to avoid overruns.

enormousBudget :: ExRestrictingBudget Source #

When we want to just evaluate the program we use the Restricting mode with an enormous budget, so that evaluation costs of on-chain budgeting are reflected accurately in benchmarks.

Emitter modes

logEmitter :: EmitterMode uni fun Source #

Emits log only.

logWithTimeEmitter :: EmitterMode uni fun Source #

Emits log with timestamp.

logWithBudgetEmitter :: EmitterMode uni fun Source #

Emits log with the budget.

Misc

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

readKnownCek :: (uni `Everywhere` ExMemoryUsage , ReadKnown ( Term Name uni fun ()) a, Ix fun, PrettyUni uni fun) => MachineParameters CekMachineCosts CekValue uni fun -> Term Name uni fun () -> Either ( CekEvaluationException Name uni fun) a Source #

Unlift a value using the CEK machine. *THIS FUNCTION IS PARTIAL if the input term contains free variables*

class Hashable a Source #

The class of types that can be converted to a hash value.

Minimal implementation: hashWithSalt .

Note: the hash is not guaranteed to be stable across library versions, operating systems or architectures. For stable hashing use named hashes: SHA256, CRC32 etc.

If you are looking for Hashable instance in time package, check time-compat

Instances

Instances details
Hashable Bool
Instance details

Defined in Data.Hashable.Class

Hashable Char
Instance details

Defined in Data.Hashable.Class

Hashable Double

Note : prior to hashable-1.3.0.0 , hash 0.0 /= hash (-0.0)

The hash of NaN is not well defined.

Since: hashable-1.3.0.0

Instance details

Defined in Data.Hashable.Class

Hashable Float

Note : prior to hashable-1.3.0.0 , hash 0.0 /= hash (-0.0)

The hash of NaN is not well defined.

Since: hashable-1.3.0.0

Instance details

Defined in Data.Hashable.Class

Hashable Int
Instance details

Defined in Data.Hashable.Class

Hashable Int8
Instance details

Defined in Data.Hashable.Class

Hashable Int16
Instance details

Defined in Data.Hashable.Class

Hashable Int32
Instance details

Defined in Data.Hashable.Class

Hashable Int64
Instance details

Defined in Data.Hashable.Class

Hashable Integer
Instance details

Defined in Data.Hashable.Class

Hashable Natural
Instance details

Defined in Data.Hashable.Class

Hashable Ordering
Instance details

Defined in Data.Hashable.Class

Hashable Word
Instance details

Defined in Data.Hashable.Class

Hashable Word8
Instance details

Defined in Data.Hashable.Class

Hashable Word16
Instance details

Defined in Data.Hashable.Class

Hashable Word32
Instance details

Defined in Data.Hashable.Class

Hashable Word64
Instance details

Defined in Data.Hashable.Class

Hashable SomeTypeRep
Instance details

Defined in Data.Hashable.Class

Hashable ()
Instance details

Defined in Data.Hashable.Class

Hashable Version
Instance details

Defined in Data.Hashable.Class

Hashable ByteString
Instance details

Defined in Data.Hashable.Class

Hashable ByteString
Instance details

Defined in Data.Hashable.Class

Hashable Scientific

A hash can be safely calculated from a Scientific . No magnitude 10^e is calculated so there's no risk of a blowup in space or time when hashing scientific numbers coming from untrusted sources.

>>> import Data.Hashable (hash)
>>> let x = scientific 1 2
>>> let y = scientific 100 0
>>> (x == y, hash x == hash y)
(True,True)
Instance details

Defined in Data.Scientific

Hashable Text
Instance details

Defined in Data.Hashable.Class

Hashable Value
Instance details

Defined in Data.Aeson.Types.Internal

Hashable Key
Instance details

Defined in Data.Aeson.Key

Hashable ThreadId
Instance details

Defined in Data.Hashable.Class

Hashable Text
Instance details

Defined in Data.Hashable.Class

Hashable Void
Instance details

Defined in Data.Hashable.Class

Hashable Unique
Instance details

Defined in Data.Hashable.Class

Hashable WordPtr
Instance details

Defined in Data.Hashable.Class

Hashable IntPtr
Instance details

Defined in Data.Hashable.Class

Hashable Fingerprint

Since: hashable-1.3.0.0

Instance details

Defined in Data.Hashable.Class

Hashable ShortByteString
Instance details

Defined in Data.Hashable.Class

Hashable IntSet

Since: hashable-1.3.4.0

Instance details

Defined in Data.Hashable.Class

Hashable BigNat
Instance details

Defined in Data.Hashable.Class

Hashable ShortText
Instance details

Defined in Data.Text.Short.Internal

Hashable QuarterOfYear
Instance details

Defined in Data.Time.Calendar.Quarter.Compat

Hashable Quarter
Instance details

Defined in Data.Time.Calendar.Quarter.Compat

Hashable Month
Instance details

Defined in Data.Time.Calendar.Month.Compat

Hashable UUID
Instance details

Defined in Data.UUID.Types.Internal

Hashable TermUnique Source #
Instance details

Defined in PlutusCore.Name

Hashable TypeUnique Source #
Instance details

Defined in PlutusCore.Name

Hashable Unique Source #
Instance details

Defined in PlutusCore.Name

Hashable TyName Source #
Instance details

Defined in PlutusCore.Name

Hashable Name Source #
Instance details

Defined in PlutusCore.Name

Hashable DefaultFun Source #
Instance details

Defined in PlutusCore.Default.Builtins

Hashable StepKind Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Hashable ExtensionFun Source #
Instance details

Defined in PlutusCore.Examples.Builtins

Hashable a => Hashable [a]
Instance details

Defined in Data.Hashable.Class

Hashable a => Hashable ( Maybe a)
Instance details

Defined in Data.Hashable.Class

Hashable a => Hashable ( Ratio a)
Instance details

Defined in Data.Hashable.Class

Hashable ( Ptr a)
Instance details

Defined in Data.Hashable.Class

Hashable ( FunPtr a)
Instance details

Defined in Data.Hashable.Class

Hashable a => Hashable ( Solo a)

Since: OneTuple-0.3.1

Instance details

Defined in Data.Tuple.Solo

Hashable v => Hashable ( KeyMap v)
Instance details

Defined in Data.Aeson.KeyMap

Hashable v => Hashable ( Tree v)

Since: hashable-1.3.4.0

Instance details

Defined in Data.Hashable.Class

Hashable a => Hashable ( Identity a)
Instance details

Defined in Data.Hashable.Class

Hashable a => Hashable ( Complex a)
Instance details

Defined in Data.Hashable.Class

Hashable a => Hashable ( Min a)
Instance details

Defined in Data.Hashable.Class

Hashable a => Hashable ( Max a)
Instance details

Defined in Data.Hashable.Class

Hashable a => Hashable ( First a)
Instance details

Defined in Data.Hashable.Class

Hashable a => Hashable ( Last a)
Instance details

Defined in Data.Hashable.Class

Hashable a => Hashable ( WrappedMonoid a)
Instance details

Defined in Data.Hashable.Class

Hashable a => Hashable ( Option a)
Instance details

Defined in Data.Hashable.Class

Hashable ( StableName a)
Instance details

Defined in Data.Hashable.Class

Hashable a => Hashable ( NonEmpty a)
Instance details

Defined in Data.Hashable.Class

Hashable v => Hashable ( Set v)

Since: hashable-1.3.4.0

Instance details

Defined in Data.Hashable.Class

Hashable v => Hashable ( Seq v)

Since: hashable-1.3.4.0

Instance details

Defined in Data.Hashable.Class

Hashable v => Hashable ( IntMap v)

Since: hashable-1.3.4.0

Instance details

Defined in Data.Hashable.Class

Hashable1 f => Hashable ( Fix f)
Instance details

Defined in Data.Fix

Hashable ( Hashed a)
Instance details

Defined in Data.Hashable.Class

Hashable a => Hashable ( HashSet a)
Instance details

Defined in Data.HashSet.Internal

Hashable a => Hashable ( RAList a)
Instance details

Defined in Data.RAList.Internal

Hashable a => Hashable ( Leaf a)
Instance details

Defined in Data.RAList.Tree.Internal

Hashable a => Hashable ( Maybe a)
Instance details

Defined in Data.Strict.Maybe

Hashable ann => Hashable ( Version ann) Source #
Instance details

Defined in PlutusCore.Core.Type

Hashable ann => Hashable ( Kind ann) Source #
Instance details

Defined in PlutusCore.Core.Type

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

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

( Hashable a, Hashable b) => Hashable ( Either a b)
Instance details

Defined in Data.Hashable.Class

Hashable ( TypeRep a)
Instance details

Defined in Data.Hashable.Class

( Hashable a1, Hashable a2) => Hashable (a1, a2)
Instance details

Defined in Data.Hashable.Class

( Hashable k, Hashable v) => Hashable ( Map k v)

Since: hashable-1.3.4.0

Instance details

Defined in Data.Hashable.Class

( Hashable k, Hashable v) => Hashable ( HashMap k v)
Instance details

Defined in Data.HashMap.Internal

Hashable ( Fixed a)
Instance details

Defined in Data.Hashable.Class

Hashable a => Hashable ( Arg a b)

Note : Prior to hashable-1.3.0.0 the hash computation included the second argument of Arg which wasn't consistent with its Eq instance.

Since: hashable-1.3.0.0

Instance details

Defined in Data.Hashable.Class

Hashable ( Proxy a)
Instance details

Defined in Data.Hashable.Class

( Hashable k, Hashable a) => Hashable ( MonoidalHashMap k a)
Instance details

Defined in Data.HashMap.Monoidal

Hashable (f a) => Hashable ( Node f a)
Instance details

Defined in Data.RAList.Tree.Internal

( Hashable a, Hashable b) => Hashable ( These a b)
Instance details

Defined in Data.These

( Hashable a, Hashable b) => Hashable ( Pair a b)
Instance details

Defined in Data.Strict.Tuple

( Hashable a, Hashable b) => Hashable ( These a b)
Instance details

Defined in Data.Strict.These

( Hashable a, Hashable b) => Hashable ( Either a b)
Instance details

Defined in Data.Strict.Either

( Hashable a1, Hashable a2, Hashable a3) => Hashable (a1, a2, a3)
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> (a1, a2, a3) -> Int Source #

hash :: (a1, a2, a3) -> Int Source #

Hashable a => Hashable ( Const a b)
Instance details

Defined in Data.Hashable.Class

( Hashable a1, Hashable a2, Hashable a3, Hashable a4) => Hashable (a1, a2, a3, a4)
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4) -> Int Source #

hash :: (a1, a2, a3, a4) -> Int Source #

( Hashable1 f, Hashable1 g, Hashable a) => Hashable ( Product f g a)
Instance details

Defined in Data.Hashable.Class

( Hashable1 f, Hashable1 g, Hashable a) => Hashable ( Sum f g a)
Instance details

Defined in Data.Hashable.Class

( Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5) => Hashable (a1, a2, a3, a4, a5)
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4, a5) -> Int Source #

hash :: (a1, a2, a3, a4, a5) -> Int Source #

( Hashable1 f, Hashable1 g, Hashable a) => Hashable ( Compose f g a)

In general, hash (Compose x) ≠ hash x . However, hashWithSalt satisfies its variant of this equivalence.

Instance details

Defined in Data.Hashable.Class

( Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5, Hashable a6) => Hashable (a1, a2, a3, a4, a5, a6)
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4, a5, a6) -> Int Source #

hash :: (a1, a2, a3, a4, a5, a6) -> Int Source #

( Hashable a1, Hashable a2, Hashable a3, Hashable a4, Hashable a5, Hashable a6, Hashable a7) => Hashable (a1, a2, a3, a4, a5, a6, a7)
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> (a1, a2, a3, a4, a5, a6, a7) -> Int Source #

hash :: (a1, a2, a3, a4, a5, a6, a7) -> Int Source #

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.