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

PlutusCore.Evaluation.Machine.BuiltinCostModel

Synopsis

Documentation

data BuiltinCostModelBase f Source #

The main model which contains all data required to predict the cost of builtin functions. See md for how this is generated. Calibrated for the CEK machine.

Constructors

BuiltinCostModelBase 

Fields

Instances

Instances details
ConstraintsB BuiltinCostModelBase Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Associated Types

type AllB c BuiltinCostModelBase

Methods

baddDicts :: forall (c :: k -> Constraint) (f :: k -> Type). AllB c BuiltinCostModelBase => BuiltinCostModelBase f -> BuiltinCostModelBase (Product (Dict c) f)

FunctorB BuiltinCostModelBase Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Methods

bmap :: (forall (a :: k). f a -> g a) -> BuiltinCostModelBase f -> BuiltinCostModelBase g

TraversableB BuiltinCostModelBase Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Methods

btraverse :: Applicative e => (forall (a :: k). f a -> e (g a)) -> BuiltinCostModelBase f -> e (BuiltinCostModelBase g)

AllArgumentModels (Lift :: Type -> Constraint) f => Lift (BuiltinCostModelBase f :: Type) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

FromJSON (BuiltinCostModelBase CostingFun) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

ToJSON (BuiltinCostModelBase MCostingFun) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

ToJSON (BuiltinCostModelBase CostingFun) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Generic (BuiltinCostModelBase f) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Associated Types

type Rep (BuiltinCostModelBase f) :: Type -> Type Source #

AllArgumentModels Show f => Show (BuiltinCostModelBase f) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

AllArgumentModels Default f => Default (BuiltinCostModelBase f) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

AllArgumentModels NFData f => NFData (BuiltinCostModelBase f) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

Methods

rnf :: BuiltinCostModelBase f -> () Source #

AllArgumentModels Eq f => Eq (BuiltinCostModelBase f) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

type AllB (c :: Type -> Constraint) BuiltinCostModelBase Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

type AllB (c :: Type -> Constraint) BuiltinCostModelBase = GAll 0 c (GAllRepB BuiltinCostModelBase)
type Rep (BuiltinCostModelBase f) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

type Rep (BuiltinCostModelBase f) = D1 ('MetaData "BuiltinCostModelBase" "PlutusCore.Evaluation.Machine.BuiltinCostModel" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'False) (C1 ('MetaCons "BuiltinCostModelBase" 'PrefixI 'True) ((((((S1 ('MetaSel ('Just "paramAddInteger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: S1 ('MetaSel ('Just "paramSubtractInteger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments))) :*: (S1 ('MetaSel ('Just "paramMultiplyInteger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: (S1 ('MetaSel ('Just "paramDivideInteger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: S1 ('MetaSel ('Just "paramQuotientInteger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments))))) :*: ((S1 ('MetaSel ('Just "paramRemainderInteger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: (S1 ('MetaSel ('Just "paramModInteger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: S1 ('MetaSel ('Just "paramEqualsInteger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)))) :*: (S1 ('MetaSel ('Just "paramLessThanInteger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: (S1 ('MetaSel ('Just "paramLessThanEqualsInteger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: S1 ('MetaSel ('Just "paramAppendByteString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)))))) :*: (((S1 ('MetaSel ('Just "paramConsByteString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: S1 ('MetaSel ('Just "paramSliceByteString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelThreeArguments))) :*: (S1 ('MetaSel ('Just "paramLengthOfByteString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)) :*: (S1 ('MetaSel ('Just "paramIndexByteString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: S1 ('MetaSel ('Just "paramEqualsByteString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments))))) :*: ((S1 ('MetaSel ('Just "paramLessThanByteString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: (S1 ('MetaSel ('Just "paramLessThanEqualsByteString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: S1 ('MetaSel ('Just "paramSha2_256") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)))) :*: (S1 ('MetaSel ('Just "paramSha3_256") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)) :*: (S1 ('MetaSel ('Just "paramBlake2b_256") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)) :*: S1 ('MetaSel ('Just "paramVerifyEd25519Signature") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelThreeArguments))))))) :*: ((((S1 ('MetaSel ('Just "paramVerifyEcdsaSecp256k1Signature") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelThreeArguments)) :*: S1 ('MetaSel ('Just "paramVerifySchnorrSecp256k1Signature") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelThreeArguments))) :*: (S1 ('MetaSel ('Just "paramAppendString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: (S1 ('MetaSel ('Just "paramEqualsString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: S1 ('MetaSel ('Just "paramEncodeUtf8") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument))))) :*: ((S1 ('MetaSel ('Just "paramDecodeUtf8") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)) :*: (S1 ('MetaSel ('Just "paramIfThenElse") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelThreeArguments)) :*: S1 ('MetaSel ('Just "paramChooseUnit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)))) :*: (S1 ('MetaSel ('Just "paramTrace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: (S1 ('MetaSel ('Just "paramFstPair") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)) :*: S1 ('MetaSel ('Just "paramSndPair") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)))))) :*: (((S1 ('MetaSel ('Just "paramChooseList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelThreeArguments)) :*: S1 ('MetaSel ('Just "paramMkCons") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments))) :*: (S1 ('MetaSel ('Just "paramHeadList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)) :*: (S1 ('MetaSel ('Just "paramTailList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)) :*: S1 ('MetaSel ('Just "paramNullList") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument))))) :*: ((S1 ('MetaSel ('Just "paramChooseData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelSixArguments)) :*: (S1 ('MetaSel ('Just "paramConstrData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: S1 ('MetaSel ('Just "paramMapData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)))) :*: (S1 ('MetaSel ('Just "paramListData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)) :*: (S1 ('MetaSel ('Just "paramIData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)) :*: S1 ('MetaSel ('Just "paramBData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)))))))) :*: (((((S1 ('MetaSel ('Just "paramUnConstrData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)) :*: S1 ('MetaSel ('Just "paramUnMapData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument))) :*: (S1 ('MetaSel ('Just "paramUnListData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)) :*: (S1 ('MetaSel ('Just "paramUnIData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)) :*: S1 ('MetaSel ('Just "paramUnBData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument))))) :*: ((S1 ('MetaSel ('Just "paramEqualsData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: (S1 ('MetaSel ('Just "paramMkPairData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: S1 ('MetaSel ('Just "paramMkNilData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)))) :*: (S1 ('MetaSel ('Just "paramMkNilPairData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)) :*: (S1 ('MetaSel ('Just "paramSerialiseData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)) :*: S1 ('MetaSel ('Just "paramBls12_381_G1_add") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)))))) :*: (((S1 ('MetaSel ('Just "paramBls12_381_G1_neg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)) :*: S1 ('MetaSel ('Just "paramBls12_381_G1_scalarMul") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments))) :*: (S1 ('MetaSel ('Just "paramBls12_381_G1_equal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: (S1 ('MetaSel ('Just "paramBls12_381_G1_compress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)) :*: S1 ('MetaSel ('Just "paramBls12_381_G1_uncompress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument))))) :*: ((S1 ('MetaSel ('Just "paramBls12_381_G1_hashToGroup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: (S1 ('MetaSel ('Just "paramBls12_381_G2_add") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: S1 ('MetaSel ('Just "paramBls12_381_G2_neg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)))) :*: (S1 ('MetaSel ('Just "paramBls12_381_G2_scalarMul") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: (S1 ('MetaSel ('Just "paramBls12_381_G2_equal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: S1 ('MetaSel ('Just "paramBls12_381_G2_compress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument))))))) :*: ((((S1 ('MetaSel ('Just "paramBls12_381_G2_uncompress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)) :*: S1 ('MetaSel ('Just "paramBls12_381_G2_hashToGroup") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments))) :*: (S1 ('MetaSel ('Just "paramBls12_381_millerLoop") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: (S1 ('MetaSel ('Just "paramBls12_381_mulMlResult") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: S1 ('MetaSel ('Just "paramBls12_381_finalVerify") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments))))) :*: ((S1 ('MetaSel ('Just "paramKeccak_256") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)) :*: (S1 ('MetaSel ('Just "paramBlake2b_224") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)) :*: S1 ('MetaSel ('Just "paramIntegerToByteString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelThreeArguments)))) :*: (S1 ('MetaSel ('Just "paramByteStringToInteger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: (S1 ('MetaSel ('Just "paramAndByteString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelThreeArguments)) :*: S1 ('MetaSel ('Just "paramOrByteString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelThreeArguments)))))) :*: (((S1 ('MetaSel ('Just "paramXorByteString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelThreeArguments)) :*: S1 ('MetaSel ('Just "paramComplementByteString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument))) :*: (S1 ('MetaSel ('Just "paramReadBit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: (S1 ('MetaSel ('Just "paramWriteBits") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelThreeArguments)) :*: S1 ('MetaSel ('Just "paramReplicateByte") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments))))) :*: ((S1 ('MetaSel ('Just "paramShiftByteString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: (S1 ('MetaSel ('Just "paramRotateByteString") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelTwoArguments)) :*: S1 ('MetaSel ('Just "paramCountSetBits") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)))) :*: (S1 ('MetaSel ('Just "paramFindFirstSetBit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)) :*: (S1 ('MetaSel ('Just "paramRipemd_160") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelOneArgument)) :*: S1 ('MetaSel ('Just "paramExpModInteger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (f ModelThreeArguments))))))))))

data CostingFun model Source #

A type of costing functions parametric over a model type. In practice the we have one model type `ModelNArguments` for every N, where N is the arity of the builtin whose costs we want to model. Each model type has a number of constructors defining different "shapes" of N-parameter functions which calculate a cost given the sizes of the builtin's arguments.

Constructors

CostingFun 

Fields

Instances

Instances details
Lift model => Lift (CostingFun model :: Type) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

lift :: Quote m => CostingFun model -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => CostingFun model -> Code m (CostingFun model) Source #

FromJSON (BuiltinCostModelBase CostingFun) 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

FromJSON model => FromJSON (CostingFun model) 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Methods

parseJSON :: Value -> Parser (CostingFun model)

parseJSONList :: Value -> Parser [CostingFun model]

omittedField :: Maybe (CostingFun model)

ToJSON (BuiltinCostModelBase CostingFun) 
Instance details

Defined in PlutusCore.Evaluation.Machine.BuiltinCostModel

ToJSON model => ToJSON (CostingFun model) 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Methods

toJSON :: CostingFun model -> Value

toEncoding :: CostingFun model -> Encoding

toJSONList :: [CostingFun model] -> Value

toEncodingList :: [CostingFun model] -> Encoding

omitField :: CostingFun model -> Bool

Generic (CostingFun model) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep (CostingFun model) :: Type -> Type Source #

Methods

from :: CostingFun model -> Rep (CostingFun model) x Source #

to :: Rep (CostingFun model) x -> CostingFun model Source #

Show model => Show (CostingFun model) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

showsPrec :: Int -> CostingFun model -> ShowS Source #

show :: CostingFun model -> String Source #

showList :: [CostingFun model] -> ShowS Source #

Default model => Default (CostingFun model) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

def :: CostingFun model #

NFData model => NFData (CostingFun model) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnf :: CostingFun model -> () Source #

Eq model => Eq (CostingFun model) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

(==) :: CostingFun model -> CostingFun model -> Bool Source #

(/=) :: CostingFun model -> CostingFun model -> Bool Source #

type Rep (CostingFun model) Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep (CostingFun model) = D1 ('MetaData "CostingFun" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'False) (C1 ('MetaCons "CostingFun" 'PrefixI 'True) (S1 ('MetaSel ('Just "costingFunCpu") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 model) :*: S1 ('MetaSel ('Just "costingFunMemory") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 model)))

class UnimplementedCostingFun a where Source #

In the initial stages of implementing a new builtin it is necessary to provide a temporary costing function which is used until the builtin has been properly costed: `see CostModelGeneration.md`. Each `ModelNArguments` type defines an instance of this class where unimplementedCostingFun is a constant costing function which returns a very high cost for all inputs. This prevents new functions from being used in situations where costs are important until a sensible costing function has been implemented.

newtype Intercept Source #

A wrapped CostingInteger that is supposed to be used as an intercept.

Constructors

Intercept 

Instances

Instances details
FromJSON Intercept 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Methods

parseJSON :: Value -> Parser Intercept

parseJSONList :: Value -> Parser [Intercept]

omittedField :: Maybe Intercept

ToJSON Intercept 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Methods

toJSON :: Intercept -> Value

toEncoding :: Intercept -> Encoding

toJSONList :: [Intercept] -> Value

toEncodingList :: [Intercept] -> Encoding

omitField :: Intercept -> Bool

Generic Intercept Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep Intercept :: Type -> Type Source #

Num Intercept Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Show Intercept Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData Intercept Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnf :: Intercept -> () Source #

Eq Intercept Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift Intercept Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

lift :: Quote m => Intercept -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => Intercept -> Code m Intercept Source #

type Rep Intercept Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep Intercept = D1 ('MetaData "Intercept" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'True) (C1 ('MetaCons "Intercept" 'PrefixI 'True) (S1 ('MetaSel ('Just "unIntercept") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CostingInteger)))

newtype Slope Source #

A wrapped CostingInteger that is supposed to be used as a slope.

Constructors

Slope 

Instances

Instances details
FromJSON Slope 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Methods

parseJSON :: Value -> Parser Slope

parseJSONList :: Value -> Parser [Slope]

omittedField :: Maybe Slope

ToJSON Slope 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Methods

toJSON :: Slope -> Value

toEncoding :: Slope -> Encoding

toJSONList :: [Slope] -> Value

toEncodingList :: [Slope] -> Encoding

omitField :: Slope -> Bool

Generic Slope Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep Slope :: Type -> Type Source #

Methods

from :: Slope -> Rep Slope x Source #

to :: Rep Slope x -> Slope Source #

Num Slope Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Show Slope Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData Slope Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnf :: Slope -> () Source #

Eq Slope Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

(==) :: Slope -> Slope -> Bool Source #

(/=) :: Slope -> Slope -> Bool Source #

Lift Slope Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

lift :: Quote m => Slope -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => Slope -> Code m Slope Source #

type Rep Slope Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep Slope = D1 ('MetaData "Slope" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'True) (C1 ('MetaCons "Slope" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSlope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CostingInteger)))

newtype Coefficient0 Source #

A wrapped CostingInteger that is supposed to be used as the degree 0 coefficient of a polynomial.

Instances

Instances details
FromJSON Coefficient0 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Methods

parseJSON :: Value -> Parser Coefficient0

parseJSONList :: Value -> Parser [Coefficient0]

omittedField :: Maybe Coefficient0

ToJSON Coefficient0 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Methods

toJSON :: Coefficient0 -> Value

toEncoding :: Coefficient0 -> Encoding

toJSONList :: [Coefficient0] -> Value

toEncodingList :: [Coefficient0] -> Encoding

omitField :: Coefficient0 -> Bool

Generic Coefficient0 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep Coefficient0 :: Type -> Type Source #

Num Coefficient0 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Show Coefficient0 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData Coefficient0 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnf :: Coefficient0 -> () Source #

Eq Coefficient0 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift Coefficient0 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

lift :: Quote m => Coefficient0 -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => Coefficient0 -> Code m Coefficient0 Source #

type Rep Coefficient0 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep Coefficient0 = D1 ('MetaData "Coefficient0" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'True) (C1 ('MetaCons "Coefficient0" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCoefficient0") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CostingInteger)))

newtype Coefficient1 Source #

A wrapped CostingInteger that is supposed to be used as the degree 1 coefficient of a polynomial.

Instances

Instances details
FromJSON Coefficient1 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Methods

parseJSON :: Value -> Parser Coefficient1

parseJSONList :: Value -> Parser [Coefficient1]

omittedField :: Maybe Coefficient1

ToJSON Coefficient1 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Methods

toJSON :: Coefficient1 -> Value

toEncoding :: Coefficient1 -> Encoding

toJSONList :: [Coefficient1] -> Value

toEncodingList :: [Coefficient1] -> Encoding

omitField :: Coefficient1 -> Bool

Generic Coefficient1 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep Coefficient1 :: Type -> Type Source #

Num Coefficient1 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Show Coefficient1 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData Coefficient1 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnf :: Coefficient1 -> () Source #

Eq Coefficient1 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift Coefficient1 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

lift :: Quote m => Coefficient1 -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => Coefficient1 -> Code m Coefficient1 Source #

type Rep Coefficient1 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep Coefficient1 = D1 ('MetaData "Coefficient1" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'True) (C1 ('MetaCons "Coefficient1" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCoefficient1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CostingInteger)))

newtype Coefficient2 Source #

A wrapped CostingInteger that is supposed to be used as the degree 2 coefficient of a polynomial.

Instances

Instances details
FromJSON Coefficient2 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Methods

parseJSON :: Value -> Parser Coefficient2

parseJSONList :: Value -> Parser [Coefficient2]

omittedField :: Maybe Coefficient2

ToJSON Coefficient2 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Methods

toJSON :: Coefficient2 -> Value

toEncoding :: Coefficient2 -> Encoding

toJSONList :: [Coefficient2] -> Value

toEncodingList :: [Coefficient2] -> Encoding

omitField :: Coefficient2 -> Bool

Generic Coefficient2 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep Coefficient2 :: Type -> Type Source #

Num Coefficient2 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Show Coefficient2 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData Coefficient2 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnf :: Coefficient2 -> () Source #

Eq Coefficient2 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift Coefficient2 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

lift :: Quote m => Coefficient2 -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => Coefficient2 -> Code m Coefficient2 Source #

type Rep Coefficient2 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep Coefficient2 = D1 ('MetaData "Coefficient2" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'True) (C1 ('MetaCons "Coefficient2" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCoefficient2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CostingInteger)))

newtype Coefficient00 Source #

A wrapped CostingInteger that is supposed to be used as the degree (0,0) coefficient of a two-variable polynomial.

Instances

Instances details
FromJSON Coefficient00 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Methods

parseJSON :: Value -> Parser Coefficient00

parseJSONList :: Value -> Parser [Coefficient00]

omittedField :: Maybe Coefficient00

ToJSON Coefficient00 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Generic Coefficient00 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep Coefficient00 :: Type -> Type Source #

Num Coefficient00 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Show Coefficient00 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData Coefficient00 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnf :: Coefficient00 -> () Source #

Eq Coefficient00 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift Coefficient00 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

lift :: Quote m => Coefficient00 -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => Coefficient00 -> Code m Coefficient00 Source #

type Rep Coefficient00 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep Coefficient00 = D1 ('MetaData "Coefficient00" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'True) (C1 ('MetaCons "Coefficient00" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCoefficient00") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CostingInteger)))

newtype Coefficient10 Source #

A wrapped CostingInteger that is supposed to be used as the degree (1,0) coefficient of a two-variable polynomial.

Instances

Instances details
FromJSON Coefficient10 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Methods

parseJSON :: Value -> Parser Coefficient10

parseJSONList :: Value -> Parser [Coefficient10]

omittedField :: Maybe Coefficient10

ToJSON Coefficient10 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Generic Coefficient10 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep Coefficient10 :: Type -> Type Source #

Num Coefficient10 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Show Coefficient10 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData Coefficient10 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnf :: Coefficient10 -> () Source #

Eq Coefficient10 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift Coefficient10 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

lift :: Quote m => Coefficient10 -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => Coefficient10 -> Code m Coefficient10 Source #

type Rep Coefficient10 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep Coefficient10 = D1 ('MetaData "Coefficient10" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'True) (C1 ('MetaCons "Coefficient10" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCoefficient10") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CostingInteger)))

newtype Coefficient01 Source #

A wrapped CostingInteger that is supposed to be used as the degree (0,1) coefficient of a two-variable polynomial.

Instances

Instances details
FromJSON Coefficient01 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Methods

parseJSON :: Value -> Parser Coefficient01

parseJSONList :: Value -> Parser [Coefficient01]

omittedField :: Maybe Coefficient01

ToJSON Coefficient01 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Generic Coefficient01 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep Coefficient01 :: Type -> Type Source #

Num Coefficient01 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Show Coefficient01 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData Coefficient01 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnf :: Coefficient01 -> () Source #

Eq Coefficient01 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift Coefficient01 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

lift :: Quote m => Coefficient01 -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => Coefficient01 -> Code m Coefficient01 Source #

type Rep Coefficient01 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep Coefficient01 = D1 ('MetaData "Coefficient01" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'True) (C1 ('MetaCons "Coefficient01" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCoefficient01") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CostingInteger)))

newtype Coefficient20 Source #

A wrapped CostingInteger that is supposed to be used as the degree (2,0) coefficient of a two-variable polynomial.

Instances

Instances details
FromJSON Coefficient20 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Methods

parseJSON :: Value -> Parser Coefficient20

parseJSONList :: Value -> Parser [Coefficient20]

omittedField :: Maybe Coefficient20

ToJSON Coefficient20 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Generic Coefficient20 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep Coefficient20 :: Type -> Type Source #

Num Coefficient20 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Show Coefficient20 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData Coefficient20 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnf :: Coefficient20 -> () Source #

Eq Coefficient20 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift Coefficient20 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

lift :: Quote m => Coefficient20 -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => Coefficient20 -> Code m Coefficient20 Source #

type Rep Coefficient20 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep Coefficient20 = D1 ('MetaData "Coefficient20" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'True) (C1 ('MetaCons "Coefficient20" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCoefficient20") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CostingInteger)))

newtype Coefficient11 Source #

A wrapped CostingInteger that is supposed to be used as the degree (1,1) coefficient of a two-variable polynomial.

Instances

Instances details
FromJSON Coefficient11 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Methods

parseJSON :: Value -> Parser Coefficient11

parseJSONList :: Value -> Parser [Coefficient11]

omittedField :: Maybe Coefficient11

ToJSON Coefficient11 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Generic Coefficient11 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep Coefficient11 :: Type -> Type Source #

Num Coefficient11 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Show Coefficient11 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData Coefficient11 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnf :: Coefficient11 -> () Source #

Eq Coefficient11 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift Coefficient11 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

lift :: Quote m => Coefficient11 -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => Coefficient11 -> Code m Coefficient11 Source #

type Rep Coefficient11 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep Coefficient11 = D1 ('MetaData "Coefficient11" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'True) (C1 ('MetaCons "Coefficient11" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCoefficient11") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CostingInteger)))

newtype Coefficient02 Source #

A wrapped CostingInteger that is supposed to be used as the degree (0,2) coefficient of a two-variable polynomial.

Instances

Instances details
FromJSON Coefficient02 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Methods

parseJSON :: Value -> Parser Coefficient02

parseJSONList :: Value -> Parser [Coefficient02]

omittedField :: Maybe Coefficient02

ToJSON Coefficient02 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Generic Coefficient02 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep Coefficient02 :: Type -> Type Source #

Num Coefficient02 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Show Coefficient02 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData Coefficient02 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnf :: Coefficient02 -> () Source #

Eq Coefficient02 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift Coefficient02 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

lift :: Quote m => Coefficient02 -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => Coefficient02 -> Code m Coefficient02 Source #

type Rep Coefficient02 Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep Coefficient02 = D1 ('MetaData "Coefficient02" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'True) (C1 ('MetaCons "Coefficient02" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCoefficient02") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CostingInteger)))

data OneVariableLinearFunction Source #

s * x + I

Instances

Instances details
FromJSON OneVariableLinearFunction 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

ToJSON OneVariableLinearFunction 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Generic OneVariableLinearFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep OneVariableLinearFunction :: Type -> Type Source #

Show OneVariableLinearFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData OneVariableLinearFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Eq OneVariableLinearFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift OneVariableLinearFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep OneVariableLinearFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep OneVariableLinearFunction = D1 ('MetaData "OneVariableLinearFunction" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'False) (C1 ('MetaCons "OneVariableLinearFunction" 'PrefixI 'True) (S1 ('MetaSel ('Just "oneVariableLinearFunctionIntercept") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Intercept) :*: S1 ('MetaSel ('Just "oneVariableLinearFunctionSlope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Slope)))

data OneVariableQuadraticFunction Source #

c0 + c1*x + c2*x^2

Instances

Instances details
FromJSON OneVariableQuadraticFunction 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

ToJSON OneVariableQuadraticFunction 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Generic OneVariableQuadraticFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep OneVariableQuadraticFunction :: Type -> Type Source #

Show OneVariableQuadraticFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData OneVariableQuadraticFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Eq OneVariableQuadraticFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift OneVariableQuadraticFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep OneVariableQuadraticFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep OneVariableQuadraticFunction = D1 ('MetaData "OneVariableQuadraticFunction" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'False) (C1 ('MetaCons "OneVariableQuadraticFunction" 'PrefixI 'True) (S1 ('MetaSel ('Just "oneVariableQuadraticFunctionC0") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Coefficient0) :*: (S1 ('MetaSel ('Just "oneVariableQuadraticFunctionC1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Coefficient1) :*: S1 ('MetaSel ('Just "oneVariableQuadraticFunctionC2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Coefficient2))))

data TwoVariableLinearFunction Source #

s1 * x + s2 * y + I

Instances

Instances details
FromJSON TwoVariableLinearFunction 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

ToJSON TwoVariableLinearFunction 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Generic TwoVariableLinearFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep TwoVariableLinearFunction :: Type -> Type Source #

Show TwoVariableLinearFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData TwoVariableLinearFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Eq TwoVariableLinearFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift TwoVariableLinearFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep TwoVariableLinearFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep TwoVariableLinearFunction = D1 ('MetaData "TwoVariableLinearFunction" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'False) (C1 ('MetaCons "TwoVariableLinearFunction" 'PrefixI 'True) (S1 ('MetaSel ('Just "twoVariableLinearFunctionIntercept") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Intercept) :*: (S1 ('MetaSel ('Just "twoVariableLinearFunctionSlope1") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Slope) :*: S1 ('MetaSel ('Just "twoVariableLinearFunctionSlope2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Slope))))

data TwoVariableQuadraticFunction Source #

c00 + c10*x + c01*y + c20*x^2 + c11*c*y + c02*y^2

Instances

Instances details
FromJSON TwoVariableQuadraticFunction 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

ToJSON TwoVariableQuadraticFunction 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Generic TwoVariableQuadraticFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep TwoVariableQuadraticFunction :: Type -> Type Source #

Show TwoVariableQuadraticFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData TwoVariableQuadraticFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Eq TwoVariableQuadraticFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift TwoVariableQuadraticFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep TwoVariableQuadraticFunction Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep TwoVariableQuadraticFunction = D1 ('MetaData "TwoVariableQuadraticFunction" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'False) (C1 ('MetaCons "TwoVariableQuadraticFunction" 'PrefixI 'True) ((S1 ('MetaSel ('Just "twoVariableQuadraticFunctionMinimum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CostingInteger) :*: (S1 ('MetaSel ('Just "twoVariableQuadraticFunctionC00") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Coefficient00) :*: S1 ('MetaSel ('Just "twoVariableQuadraticFunctionC10") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Coefficient10))) :*: ((S1 ('MetaSel ('Just "twoVariableQuadraticFunctionC01") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Coefficient01) :*: S1 ('MetaSel ('Just "twoVariableQuadraticFunctionC20") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Coefficient20)) :*: (S1 ('MetaSel ('Just "twoVariableQuadraticFunctionC11") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Coefficient11) :*: S1 ('MetaSel ('Just "twoVariableQuadraticFunctionC02") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Coefficient02)))))

data ModelSubtractedSizes Source #

s * (x - y) + I

Instances

Instances details
FromJSON ModelSubtractedSizes 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

ToJSON ModelSubtractedSizes 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Generic ModelSubtractedSizes Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep ModelSubtractedSizes :: Type -> Type Source #

Show ModelSubtractedSizes Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData ModelSubtractedSizes Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Eq ModelSubtractedSizes Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift ModelSubtractedSizes Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep ModelSubtractedSizes Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep ModelSubtractedSizes = D1 ('MetaData "ModelSubtractedSizes" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'False) (C1 ('MetaCons "ModelSubtractedSizes" 'PrefixI 'True) (S1 ('MetaSel ('Just "modelSubtractedSizesIntercept") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Intercept) :*: (S1 ('MetaSel ('Just "modelSubtractedSizesSlope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Slope) :*: S1 ('MetaSel ('Just "modelSubtractedSizesMinimum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CostingInteger))))

data ModelConstantOrOneArgument Source #

if p then f(x) else c; p depends on usage

Instances

Instances details
FromJSON ModelConstantOrOneArgument 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

ToJSON ModelConstantOrOneArgument 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Generic ModelConstantOrOneArgument Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep ModelConstantOrOneArgument :: Type -> Type Source #

Show ModelConstantOrOneArgument Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData ModelConstantOrOneArgument Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Eq ModelConstantOrOneArgument Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift ModelConstantOrOneArgument Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep ModelConstantOrOneArgument Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep ModelConstantOrOneArgument = D1 ('MetaData "ModelConstantOrOneArgument" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'False) (C1 ('MetaCons "ModelConstantOrOneArgument" 'PrefixI 'True) (S1 ('MetaSel ('Just "modelConstantOrOneArgumentConstant") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CostingInteger) :*: S1 ('MetaSel ('Just "modelConstantOrOneArgumentModel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ModelOneArgument)))

data ModelConstantOrTwoArguments Source #

if p then f(x,y) else c; p depends on usage

Instances

Instances details
FromJSON ModelConstantOrTwoArguments 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

ToJSON ModelConstantOrTwoArguments 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Generic ModelConstantOrTwoArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep ModelConstantOrTwoArguments :: Type -> Type Source #

Show ModelConstantOrTwoArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData ModelConstantOrTwoArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Eq ModelConstantOrTwoArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift ModelConstantOrTwoArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep ModelConstantOrTwoArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep ModelConstantOrTwoArguments = D1 ('MetaData "ModelConstantOrTwoArguments" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'False) (C1 ('MetaCons "ModelConstantOrTwoArguments" 'PrefixI 'True) (S1 ('MetaSel ('Just "modelConstantOrTwoArgumentsConstant") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CostingInteger) :*: S1 ('MetaSel ('Just "modelConstantOrTwoArgumentsModel") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ModelTwoArguments)))

data ModelConstantOrLinear Source #

NB: this is subsumed by ModelConstantOrOneArgument, but we have to keep it for the time being. See Note [Backward compatibility for costing functions]. | if p then s*x else c; p depends on usage

Instances

Instances details
FromJSON ModelConstantOrLinear 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

ToJSON ModelConstantOrLinear 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Generic ModelConstantOrLinear Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep ModelConstantOrLinear :: Type -> Type Source #

Show ModelConstantOrLinear Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData ModelConstantOrLinear Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Eq ModelConstantOrLinear Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift ModelConstantOrLinear Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep ModelConstantOrLinear Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep ModelConstantOrLinear = D1 ('MetaData "ModelConstantOrLinear" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'False) (C1 ('MetaCons "ModelConstantOrLinear" 'PrefixI 'True) (S1 ('MetaSel ('Just "modelConstantOrLinearConstant") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CostingInteger) :*: (S1 ('MetaSel ('Just "modelConstantOrLinearIntercept") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Intercept) :*: S1 ('MetaSel ('Just "modelConstantOrLinearSlope") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Slope))))

data ModelOneArgument Source #

Instances

Instances details
FromJSON ModelOneArgument 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

ToJSON ModelOneArgument 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Generic ModelOneArgument Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep ModelOneArgument :: Type -> Type Source #

Show ModelOneArgument Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Default ModelOneArgument Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData ModelOneArgument Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnf :: ModelOneArgument -> () Source #

Eq ModelOneArgument Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

UnimplementedCostingFun ModelOneArgument Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift ModelOneArgument Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep ModelOneArgument Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep ModelOneArgument = D1 ('MetaData "ModelOneArgument" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'False) (C1 ('MetaCons "ModelOneArgumentConstantCost" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CostingInteger)) :+: C1 ('MetaCons "ModelOneArgumentLinearInX" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OneVariableLinearFunction)))

data ModelTwoArguments Source #

Instances

Instances details
FromJSON ModelTwoArguments 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

ToJSON ModelTwoArguments 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Generic ModelTwoArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep ModelTwoArguments :: Type -> Type Source #

Show ModelTwoArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Default ModelTwoArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData ModelTwoArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnf :: ModelTwoArguments -> () Source #

Eq ModelTwoArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

UnimplementedCostingFun ModelTwoArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift ModelTwoArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep ModelTwoArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep ModelTwoArguments = D1 ('MetaData "ModelTwoArguments" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'False) (((C1 ('MetaCons "ModelTwoArgumentsConstantCost" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CostingInteger)) :+: (C1 ('MetaCons "ModelTwoArgumentsLinearInX" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OneVariableLinearFunction)) :+: C1 ('MetaCons "ModelTwoArgumentsLinearInY" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OneVariableLinearFunction)))) :+: ((C1 ('MetaCons "ModelTwoArgumentsLinearInXAndY" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TwoVariableLinearFunction)) :+: C1 ('MetaCons "ModelTwoArgumentsAddedSizes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OneVariableLinearFunction))) :+: (C1 ('MetaCons "ModelTwoArgumentsSubtractedSizes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ModelSubtractedSizes)) :+: C1 ('MetaCons "ModelTwoArgumentsMultipliedSizes" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OneVariableLinearFunction))))) :+: (((C1 ('MetaCons "ModelTwoArgumentsMinSize" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OneVariableLinearFunction)) :+: C1 ('MetaCons "ModelTwoArgumentsMaxSize" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OneVariableLinearFunction))) :+: (C1 ('MetaCons "ModelTwoArgumentsLinearOnDiagonal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ModelConstantOrLinear)) :+: C1 ('MetaCons "ModelTwoArgumentsConstOffDiagonal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ModelConstantOrOneArgument)))) :+: ((C1 ('MetaCons "ModelTwoArgumentsConstAboveDiagonal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ModelConstantOrTwoArguments)) :+: C1 ('MetaCons "ModelTwoArgumentsConstBelowDiagonal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ModelConstantOrTwoArguments))) :+: (C1 ('MetaCons "ModelTwoArgumentsQuadraticInY" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OneVariableQuadraticFunction)) :+: C1 ('MetaCons "ModelTwoArgumentsQuadraticInXAndY" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TwoVariableQuadraticFunction))))))

data ModelThreeArguments Source #

Instances

Instances details
FromJSON ModelThreeArguments 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

ToJSON ModelThreeArguments 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Generic ModelThreeArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep ModelThreeArguments :: Type -> Type Source #

Show ModelThreeArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Default ModelThreeArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData ModelThreeArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Eq ModelThreeArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

UnimplementedCostingFun ModelThreeArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift ModelThreeArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep ModelThreeArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep ModelThreeArguments = D1 ('MetaData "ModelThreeArguments" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'False) (((C1 ('MetaCons "ModelThreeArgumentsConstantCost" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CostingInteger)) :+: C1 ('MetaCons "ModelThreeArgumentsLinearInX" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OneVariableLinearFunction))) :+: (C1 ('MetaCons "ModelThreeArgumentsLinearInY" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OneVariableLinearFunction)) :+: C1 ('MetaCons "ModelThreeArgumentsLinearInZ" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OneVariableLinearFunction)))) :+: ((C1 ('MetaCons "ModelThreeArgumentsQuadraticInZ" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OneVariableQuadraticFunction)) :+: C1 ('MetaCons "ModelThreeArgumentsLiteralInYOrLinearInZ" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OneVariableLinearFunction))) :+: (C1 ('MetaCons "ModelThreeArgumentsLinearInMaxYZ" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 OneVariableLinearFunction)) :+: C1 ('MetaCons "ModelThreeArgumentsLinearInYAndZ" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 TwoVariableLinearFunction)))))

data ModelFourArguments Source #

Instances

Instances details
FromJSON ModelFourArguments 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

ToJSON ModelFourArguments 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Generic ModelFourArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep ModelFourArguments :: Type -> Type Source #

Show ModelFourArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Default ModelFourArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData ModelFourArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnf :: ModelFourArguments -> () Source #

Eq ModelFourArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

UnimplementedCostingFun ModelFourArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift ModelFourArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep ModelFourArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep ModelFourArguments = D1 ('MetaData "ModelFourArguments" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'False) (C1 ('MetaCons "ModelFourArgumentsConstantCost" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CostingInteger)))

data ModelFiveArguments Source #

Instances

Instances details
FromJSON ModelFiveArguments 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

ToJSON ModelFiveArguments 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Generic ModelFiveArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep ModelFiveArguments :: Type -> Type Source #

Show ModelFiveArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Default ModelFiveArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData ModelFiveArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnf :: ModelFiveArguments -> () Source #

Eq ModelFiveArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

UnimplementedCostingFun ModelFiveArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift ModelFiveArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep ModelFiveArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep ModelFiveArguments = D1 ('MetaData "ModelFiveArguments" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'False) (C1 ('MetaCons "ModelFiveArgumentsConstantCost" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CostingInteger)))

data ModelSixArguments Source #

Instances

Instances details
FromJSON ModelSixArguments 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

ToJSON ModelSixArguments 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.JSON

Generic ModelSixArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Associated Types

type Rep ModelSixArguments :: Type -> Type Source #

Show ModelSixArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Default ModelSixArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

NFData ModelSixArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Methods

rnf :: ModelSixArguments -> () Source #

Eq ModelSixArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

UnimplementedCostingFun ModelSixArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

Lift ModelSixArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep ModelSixArguments Source # 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostingFun.Core

type Rep ModelSixArguments = D1 ('MetaData "ModelSixArguments" "PlutusCore.Evaluation.Machine.CostingFun.Core" "plutus-core-1.36.0.0-7ehJj5tIPqoJIiiivXkX9N" 'False) (C1 ('MetaCons "ModelSixArgumentsConstantCost" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 CostingInteger)))

class Eq a => Hashable a #

Instances

Instances details
Hashable Key 
Instance details

Defined in Data.Aeson.Key

Methods

hashWithSalt :: Int -> Key -> Int

hash :: Key -> Int

Hashable Value 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

hashWithSalt :: Int -> Value -> Int

hash :: Value -> Int

Hashable ByteArray 
Instance details

Defined in Data.Hashable.Class

Hashable SomeTypeRep 
Instance details

Defined in Data.Hashable.Class

Hashable Unique 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Unique -> Int

hash :: Unique -> Int

Hashable Version 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Version -> Int

hash :: Version -> Int

Hashable IntPtr 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> IntPtr -> Int

hash :: IntPtr -> Int

Hashable WordPtr 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> WordPtr -> Int

hash :: WordPtr -> Int

Hashable Void 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Void -> Int

hash :: Void -> Int

Hashable ThreadId 
Instance details

Defined in Data.Hashable.Class

Hashable Fingerprint 
Instance details

Defined in Data.Hashable.Class

Hashable Int16 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int16 -> Int

hash :: Int16 -> Int

Hashable Int32 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int32 -> Int

hash :: Int32 -> Int

Hashable Int64 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int64 -> Int

hash :: Int64 -> Int

Hashable Int8 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int8 -> Int

hash :: Int8 -> Int

Hashable Word16 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word16 -> Int

hash :: Word16 -> Int

Hashable Word32 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word32 -> Int

hash :: Word32 -> Int

Hashable Word64 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word64 -> Int

hash :: Word64 -> Int

Hashable Word8 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word8 -> Int

hash :: Word8 -> Int

Hashable ByteString 
Instance details

Defined in Data.Hashable.Class

Hashable ByteString 
Instance details

Defined in Data.Hashable.Class

Hashable ShortByteString 
Instance details

Defined in Data.Hashable.Class

Hashable IntSet 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> IntSet -> Int

hash :: IntSet -> Int

Hashable OsString 
Instance details

Defined in Data.Hashable.Class

Hashable PosixString 
Instance details

Defined in Data.Hashable.Class

Hashable WindowsString 
Instance details

Defined in Data.Hashable.Class

Hashable BigNat 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> BigNat -> Int

hash :: BigNat -> Int

Hashable Ordering 
Instance details

Defined in Data.Hashable.Class

Hashable OsString 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> OsString -> Int

hash :: OsString -> Int

Hashable PosixString 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> PosixString -> Int

hash :: PosixString -> Int

Hashable WindowsString 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> WindowsString -> Int

hash :: WindowsString -> Int

Hashable Ann Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

hashWithSalt :: Int -> Ann -> Int

hash :: Ann -> Int

Hashable Inline Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

hashWithSalt :: Int -> Inline -> Int

hash :: Inline -> Int

Hashable SrcSpan Source # 
Instance details

Defined in PlutusCore.Annotation

Methods

hashWithSalt :: Int -> SrcSpan -> Int

hash :: SrcSpan -> Int

Hashable SrcSpans Source # 
Instance details

Defined in PlutusCore.Annotation

Hashable Element Source # 
Instance details

Defined in PlutusCore.Crypto.BLS12_381.G1

Methods

hashWithSalt :: Int -> Element -> Int

hash :: Element -> Int

Hashable Element Source # 
Instance details

Defined in PlutusCore.Crypto.BLS12_381.G2

Methods

hashWithSalt :: Int -> Element -> Int

hash :: Element -> Int

Hashable MlResult Source # 
Instance details

Defined in PlutusCore.Crypto.BLS12_381.Pairing

Hashable Data Source # 
Instance details

Defined in PlutusCore.Data

Methods

hashWithSalt :: Int -> Data -> Int

hash :: Data -> Int

Hashable DeBruijn Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Hashable FakeNamedDeBruijn Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Hashable Index Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Methods

hashWithSalt :: Int -> Index -> Int

hash :: Index -> Int

Hashable NamedDeBruijn Source # 
Instance details

Defined in PlutusCore.DeBruijn.Internal

Hashable DefaultFun Source # 
Instance details

Defined in PlutusCore.Default.Builtins

Hashable ExtensionFun Source # 
Instance details

Defined in PlutusCore.Examples.Builtins

Hashable Name Source # 
Instance details

Defined in PlutusCore.Name.Unique

Methods

hashWithSalt :: Int -> Name -> Int

hash :: Name -> Int

Hashable TermUnique Source # 
Instance details

Defined in PlutusCore.Name.Unique

Hashable TyName Source # 
Instance details

Defined in PlutusCore.Name.Unique

Methods

hashWithSalt :: Int -> TyName -> Int

hash :: TyName -> Int

Hashable TypeUnique Source # 
Instance details

Defined in PlutusCore.Name.Unique

Hashable Unique Source # 
Instance details

Defined in PlutusCore.Name.Unique

Methods

hashWithSalt :: Int -> Unique -> Int

hash :: Unique -> Int

Hashable Version Source # 
Instance details

Defined in PlutusCore.Version

Methods

hashWithSalt :: Int -> Version -> Int

hash :: Version -> Int

Hashable StepKind Source # 
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Hashable Scientific 
Instance details

Defined in Data.Scientific

Methods

hashWithSalt :: Int -> Scientific -> Int

hash :: Scientific -> Int

Hashable Text 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Text -> Int

hash :: Text -> Int

Hashable Text 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Text -> Int

hash :: Text -> Int

Hashable ShortText 
Instance details

Defined in Data.Text.Short.Internal

Methods

hashWithSalt :: Int -> ShortText -> Int

hash :: ShortText -> Int

Hashable UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

hashWithSalt :: Int -> UUID -> Int

hash :: UUID -> Int

Hashable Integer 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Integer -> Int

hash :: Integer -> Int

Hashable Natural 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Natural -> Int

hash :: Natural -> Int

Hashable () 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> () -> Int

hash :: () -> Int

Hashable Bool 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Bool -> Int

hash :: Bool -> Int

Hashable Char 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Char -> Int

hash :: Char -> Int

Hashable Double 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Double -> Int

hash :: Double -> Int

Hashable Float 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Float -> Int

hash :: Float -> Int

Hashable Int 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int -> Int

hash :: Int -> Int

Hashable Word 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word -> Int

hash :: Word -> Int

Hashable v => Hashable (KeyMap v) 
Instance details

Defined in Data.Aeson.KeyMap

Methods

hashWithSalt :: Int -> KeyMap v -> Int

hash :: KeyMap v -> Int

Hashable a => Hashable (Complex a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Complex a -> Int

hash :: Complex a -> Int

Hashable a => Hashable (Identity a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Identity a -> Int

hash :: Identity a -> Int

Hashable a => Hashable (First a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> First a -> Int

hash :: First a -> Int

Hashable a => Hashable (Last a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Last a -> Int

hash :: Last a -> Int

Hashable a => Hashable (Max a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Max a -> Int

hash :: Max a -> Int

Hashable a => Hashable (Min a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Min a -> Int

hash :: Min a -> Int

Hashable a => Hashable (WrappedMonoid a) 
Instance details

Defined in Data.Hashable.Class

Hashable a => Hashable (NonEmpty a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> NonEmpty a -> Int

hash :: NonEmpty a -> Int

Hashable (FunPtr a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> FunPtr a -> Int

hash :: FunPtr a -> Int

Hashable (Ptr a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Ptr a -> Int

hash :: Ptr a -> Int

Hashable a => Hashable (Ratio a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Ratio a -> Int

hash :: Ratio a -> Int

Hashable (StableName a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> StableName a -> Int

hash :: StableName a -> Int

Hashable v => Hashable (IntMap v) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> IntMap v -> Int

hash :: IntMap v -> Int

Hashable v => Hashable (Seq v) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Seq v -> Int

hash :: Seq v -> Int

Hashable v => Hashable (Set v) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Set v -> Int

hash :: Set v -> Int

Hashable v => Hashable (Tree v) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Tree v -> Int

hash :: Tree v -> Int

Hashable1 f => Hashable (Fix f) 
Instance details

Defined in Data.Fix

Methods

hashWithSalt :: Int -> Fix f -> Int

hash :: Fix f -> Int

Eq a => Hashable (Hashed a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Hashed a -> Int

hash :: Hashed a -> Int

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

Defined in PlutusCore.Core.Type

Methods

hashWithSalt :: Int -> Kind ann -> Int

hash :: Kind ann -> Int

(Closed uni, GEq uni) => Hashable (SomeTypeIn uni) Source # 
Instance details

Defined in Universe.Core

Methods

hashWithSalt :: Int -> SomeTypeIn uni -> Int

hash :: SomeTypeIn uni -> Int

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

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Hashable a => Hashable (Leaf a) 
Instance details

Defined in Data.RAList.Tree.Internal

Methods

hashWithSalt :: Int -> Leaf a -> Int

hash :: Leaf a -> Int

Hashable a => Hashable (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

hashWithSalt :: Int -> Maybe a -> Int

hash :: Maybe a -> Int

Hashable a => Hashable (HashSet a) 
Instance details

Defined in Data.HashSet.Internal

Methods

hashWithSalt :: Int -> HashSet a -> Int

hash :: HashSet a -> Int

Hashable a => Hashable (Vector a) Source # 
Instance details

Defined in UntypedPlutusCore.Core.Instance.Eq

Methods

hashWithSalt :: Int -> Vector a -> Int

hash :: Vector a -> Int

Hashable a => Hashable (Maybe a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Maybe a -> Int

hash :: Maybe a -> Int

Hashable a => Hashable (a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> (a) -> Int

hash :: (a) -> Int

Hashable a => Hashable [a] 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> [a] -> Int

hash :: [a] -> Int

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

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Either a b -> Int

hash :: Either a b -> Int

Hashable (Fixed a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Fixed a -> Int

hash :: Fixed a -> Int

Hashable (Proxy a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Proxy a -> Int

hash :: Proxy a -> Int

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

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Arg a b -> Int

hash :: Arg a b -> Int

Hashable (TypeRep a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> TypeRep a -> Int

hash :: TypeRep a -> Int

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

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Map k v -> Int

hash :: Map k v -> Int

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

Defined in Data.HashMap.Monoidal

Methods

hashWithSalt :: Int -> MonoidalHashMap k a -> Int

hash :: MonoidalHashMap k a -> Int

(Closed uni, GEq uni, Everywhere uni Eq, Everywhere uni Hashable) => Hashable (ValueOf uni a) Source # 
Instance details

Defined in Universe.Core

Methods

hashWithSalt :: Int -> ValueOf uni a -> Int

hash :: ValueOf uni a -> Int

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

Defined in Data.RAList.Tree.Internal

Methods

hashWithSalt :: Int -> Node f a -> Int

hash :: Node f a -> Int

(Closed uni, GEq uni, Everywhere uni Eq, Everywhere uni Hashable) => Hashable (Some (ValueOf uni)) Source # 
Instance details

Defined in Universe.Core

Methods

hashWithSalt :: Int -> Some (ValueOf uni) -> Int

hash :: Some (ValueOf uni) -> Int

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

Defined in Data.Strict.Either

Methods

hashWithSalt :: Int -> Either a b -> Int

hash :: Either a b -> Int

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

Defined in Data.Strict.These

Methods

hashWithSalt :: Int -> These a b -> Int

hash :: These a b -> Int

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

Defined in Data.Strict.Tuple

Methods

hashWithSalt :: Int -> Pair a b -> Int

hash :: Pair a b -> Int

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

Defined in Data.These

Methods

hashWithSalt :: Int -> These a b -> Int

hash :: These a b -> Int

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

Defined in Data.HashMap.Internal

Methods

hashWithSalt :: Int -> HashMap k v -> Int

hash :: HashMap k v -> Int

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

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> (a1, a2) -> Int

hash :: (a1, a2) -> Int

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

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Const a b -> Int

hash :: Const a b -> Int

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

Defined in Data.Hashable.Class

Methods

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

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

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

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Product f g a -> Int

hash :: Product f g a -> Int

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

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Sum f g a -> Int

hash :: Sum f g a -> Int

HashableTermConstraints uni fun ann => Hashable (Term DeBruijn uni fun ann) Source # 
Instance details

Defined in UntypedPlutusCore.Core.Instance.Eq

Methods

hashWithSalt :: Int -> Term DeBruijn uni fun ann -> Int

hash :: Term DeBruijn uni fun ann -> Int

HashableTermConstraints uni fun ann => Hashable (Term FakeNamedDeBruijn uni fun ann) Source # 
Instance details

Defined in UntypedPlutusCore.Core.Instance.Eq

Methods

hashWithSalt :: Int -> Term FakeNamedDeBruijn uni fun ann -> Int

hash :: Term FakeNamedDeBruijn uni fun ann -> Int

HashableTermConstraints uni fun ann => Hashable (Term NamedDeBruijn uni fun ann) Source # 
Instance details

Defined in UntypedPlutusCore.Core.Instance.Eq

Methods

hashWithSalt :: Int -> Term NamedDeBruijn uni fun ann -> Int

hash :: Term NamedDeBruijn uni fun ann -> Int

HashableTermConstraints uni fun ann => Hashable (Term Name uni fun ann) Source # 
Instance details

Defined in UntypedPlutusCore.Core.Instance.Eq

Methods

hashWithSalt :: Int -> Term Name uni fun ann -> Int

hash :: Term Name uni fun ann -> Int

(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

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

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

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Compose f g a -> Int

hash :: Compose f g a -> Int

(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

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

(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

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

(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

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

newtype MCostingFun a Source #

Same as CostingFun but maybe missing. We could use 'Compose Maybe CostinFun' instead but we would then need an orphan ToJSON instance.

Constructors

MCostingFun (Maybe (CostingFun a))