-- editorconfig-checker-disable-file
{-# LANGUAGE BangPatterns          #-}
{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE DeriveAnyClass        #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE InstanceSigs          #-}
{-# LANGUAGE LambdaCase            #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings     #-}
{-# LANGUAGE ScopedTypeVariables   #-}
{-# LANGUAGE TypeFamilies          #-}
{-# LANGUAGE TypeOperators         #-}
{-# LANGUAGE UndecidableInstances  #-}

module PlutusCore.Default.Builtins where

import PlutusPrelude

import PlutusCore.Builtin
import PlutusCore.Data (Data (..))
import PlutusCore.Default.Universe
import PlutusCore.Evaluation.Machine.BuiltinCostModel
import PlutusCore.Evaluation.Machine.ExBudgetStream (ExBudgetStream)
import PlutusCore.Evaluation.Machine.ExMemoryUsage (ExMemoryUsage, IntegerCostedLiterally (..),
                                                    ListCostedByLength (..),
                                                    NumBytesCostedAsNumWords (..), memoryUsage,
                                                    singletonRose)
import PlutusCore.Pretty (PrettyConfigPlc)

import PlutusCore.Bitwise qualified as Bitwise
import PlutusCore.Crypto.BLS12_381.G1 qualified as BLS12_381.G1
import PlutusCore.Crypto.BLS12_381.G2 qualified as BLS12_381.G2
import PlutusCore.Crypto.BLS12_381.Pairing qualified as BLS12_381.Pairing
import PlutusCore.Crypto.Ed25519 (verifyEd25519Signature_V1, verifyEd25519Signature_V2)
import PlutusCore.Crypto.ExpMod qualified as ExpMod
import PlutusCore.Crypto.Hash qualified as Hash
import PlutusCore.Crypto.Secp256k1 (verifyEcdsaSecp256k1Signature, verifySchnorrSecp256k1Signature)

import Codec.Serialise (serialise)
import Control.Monad (unless)
import Data.ByteString qualified as BS
import Data.ByteString.Lazy qualified as BSL
import Data.Ix (Ix)
import Data.Text (Text)
import Data.Text.Encoding (decodeUtf8', encodeUtf8)
import Flat hiding (from, to)
import Flat.Decoder (Get, dBEBits8)
import Flat.Encoder as Flat (Encoding, NumBits, eBits)
import NoThunks.Class (NoThunks)
import Prettyprinter (viaShow)

-- See Note [Pattern matching on built-in types].
-- TODO: should we have the commonest built-in functions at the front to have more compact encoding?
-- | Default built-in functions.
--
-- When updating these, make sure to add them to the protocol version listing!
-- See Note [New builtins/language versions and protocol versions]
data DefaultFun
    -- Integers
    = AddInteger
    | SubtractInteger
    | MultiplyInteger
    | DivideInteger
    | QuotientInteger
    | RemainderInteger
    | ModInteger
    | EqualsInteger
    | LessThanInteger
    | LessThanEqualsInteger
    -- Bytestrings
    | AppendByteString
    | ConsByteString
    | SliceByteString
    | LengthOfByteString
    | IndexByteString
    | EqualsByteString
    | LessThanByteString
    | LessThanEqualsByteString
    -- Cryptography and hashes
    | Sha2_256
    | Sha3_256
    | Blake2b_256
    | VerifyEd25519Signature  -- formerly verifySignature
    | VerifyEcdsaSecp256k1Signature
    | VerifySchnorrSecp256k1Signature
    -- Strings
    | AppendString
    | EqualsString
    | EncodeUtf8
    | DecodeUtf8
    -- Bool
    | IfThenElse
    -- Unit
    | ChooseUnit
    -- Tracing
    | Trace
    -- Pairs
    | FstPair
    | SndPair
    -- Lists
    | ChooseList
    | MkCons
    | HeadList
    | TailList
    | NullList
    -- Data
    -- See Note [Pattern matching on built-in types].
    -- It is convenient to have a "choosing" function for a data type that has more than two
    -- constructors to get pattern matching over it and we may end up having multiple such data
    -- types, hence we include the name of the data type as a suffix.
    | ChooseData
    | ConstrData
    | MapData
    | ListData
    | IData
    | BData
    | UnConstrData
    | UnMapData
    | UnListData
    | UnIData
    | UnBData
    | EqualsData
    | SerialiseData
    -- Misc monomorphized constructors.
    -- We could simply replace those with constants, but we use built-in functions for consistency
    -- with monomorphic built-in types. Polymorphic built-in constructors are generally problematic,
    -- See Note [Representable built-in functions over polymorphic built-in types].
    | MkPairData
    | MkNilData
    | MkNilPairData
    -- BLS12_381 operations
    -- G1
    | Bls12_381_G1_add
    | Bls12_381_G1_neg
    | Bls12_381_G1_scalarMul
    | Bls12_381_G1_equal
    | Bls12_381_G1_hashToGroup
    | Bls12_381_G1_compress
    | Bls12_381_G1_uncompress
    -- G2
    | Bls12_381_G2_add
    | Bls12_381_G2_neg
    | Bls12_381_G2_scalarMul
    | Bls12_381_G2_equal
    | Bls12_381_G2_hashToGroup
    | Bls12_381_G2_compress
    | Bls12_381_G2_uncompress
    -- Pairing
    | Bls12_381_millerLoop
    | Bls12_381_mulMlResult
    | Bls12_381_finalVerify
    -- Keccak_256, Blake2b_224
    | Keccak_256
    | Blake2b_224
    -- Conversions
    | IntegerToByteString
    | ByteStringToInteger
    -- Logical
    | AndByteString
    | OrByteString
    | XorByteString
    | ComplementByteString
    | ReadBit
    | WriteBits
    | ReplicateByte
    -- Bitwise
    | ShiftByteString
    | RotateByteString
    | CountSetBits
    | FindFirstSetBit
    -- Ripemd_160
    | Ripemd_160
    | ExpModInteger
    deriving stock (Int -> DefaultFun -> ShowS
[DefaultFun] -> ShowS
DefaultFun -> String
(Int -> DefaultFun -> ShowS)
-> (DefaultFun -> String)
-> ([DefaultFun] -> ShowS)
-> Show DefaultFun
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DefaultFun -> ShowS
showsPrec :: Int -> DefaultFun -> ShowS
$cshow :: DefaultFun -> String
show :: DefaultFun -> String
$cshowList :: [DefaultFun] -> ShowS
showList :: [DefaultFun] -> ShowS
Show, DefaultFun -> DefaultFun -> Bool
(DefaultFun -> DefaultFun -> Bool)
-> (DefaultFun -> DefaultFun -> Bool) -> Eq DefaultFun
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DefaultFun -> DefaultFun -> Bool
== :: DefaultFun -> DefaultFun -> Bool
$c/= :: DefaultFun -> DefaultFun -> Bool
/= :: DefaultFun -> DefaultFun -> Bool
Eq, Eq DefaultFun
Eq DefaultFun =>
(DefaultFun -> DefaultFun -> Ordering)
-> (DefaultFun -> DefaultFun -> Bool)
-> (DefaultFun -> DefaultFun -> Bool)
-> (DefaultFun -> DefaultFun -> Bool)
-> (DefaultFun -> DefaultFun -> Bool)
-> (DefaultFun -> DefaultFun -> DefaultFun)
-> (DefaultFun -> DefaultFun -> DefaultFun)
-> Ord DefaultFun
DefaultFun -> DefaultFun -> Bool
DefaultFun -> DefaultFun -> Ordering
DefaultFun -> DefaultFun -> DefaultFun
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DefaultFun -> DefaultFun -> Ordering
compare :: DefaultFun -> DefaultFun -> Ordering
$c< :: DefaultFun -> DefaultFun -> Bool
< :: DefaultFun -> DefaultFun -> Bool
$c<= :: DefaultFun -> DefaultFun -> Bool
<= :: DefaultFun -> DefaultFun -> Bool
$c> :: DefaultFun -> DefaultFun -> Bool
> :: DefaultFun -> DefaultFun -> Bool
$c>= :: DefaultFun -> DefaultFun -> Bool
>= :: DefaultFun -> DefaultFun -> Bool
$cmax :: DefaultFun -> DefaultFun -> DefaultFun
max :: DefaultFun -> DefaultFun -> DefaultFun
$cmin :: DefaultFun -> DefaultFun -> DefaultFun
min :: DefaultFun -> DefaultFun -> DefaultFun
Ord, Int -> DefaultFun
DefaultFun -> Int
DefaultFun -> [DefaultFun]
DefaultFun -> DefaultFun
DefaultFun -> DefaultFun -> [DefaultFun]
DefaultFun -> DefaultFun -> DefaultFun -> [DefaultFun]
(DefaultFun -> DefaultFun)
-> (DefaultFun -> DefaultFun)
-> (Int -> DefaultFun)
-> (DefaultFun -> Int)
-> (DefaultFun -> [DefaultFun])
-> (DefaultFun -> DefaultFun -> [DefaultFun])
-> (DefaultFun -> DefaultFun -> [DefaultFun])
-> (DefaultFun -> DefaultFun -> DefaultFun -> [DefaultFun])
-> Enum DefaultFun
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: DefaultFun -> DefaultFun
succ :: DefaultFun -> DefaultFun
$cpred :: DefaultFun -> DefaultFun
pred :: DefaultFun -> DefaultFun
$ctoEnum :: Int -> DefaultFun
toEnum :: Int -> DefaultFun
$cfromEnum :: DefaultFun -> Int
fromEnum :: DefaultFun -> Int
$cenumFrom :: DefaultFun -> [DefaultFun]
enumFrom :: DefaultFun -> [DefaultFun]
$cenumFromThen :: DefaultFun -> DefaultFun -> [DefaultFun]
enumFromThen :: DefaultFun -> DefaultFun -> [DefaultFun]
$cenumFromTo :: DefaultFun -> DefaultFun -> [DefaultFun]
enumFromTo :: DefaultFun -> DefaultFun -> [DefaultFun]
$cenumFromThenTo :: DefaultFun -> DefaultFun -> DefaultFun -> [DefaultFun]
enumFromThenTo :: DefaultFun -> DefaultFun -> DefaultFun -> [DefaultFun]
Enum, DefaultFun
DefaultFun -> DefaultFun -> Bounded DefaultFun
forall a. a -> a -> Bounded a
$cminBound :: DefaultFun
minBound :: DefaultFun
$cmaxBound :: DefaultFun
maxBound :: DefaultFun
Bounded, (forall x. DefaultFun -> Rep DefaultFun x)
-> (forall x. Rep DefaultFun x -> DefaultFun) -> Generic DefaultFun
forall x. Rep DefaultFun x -> DefaultFun
forall x. DefaultFun -> Rep DefaultFun x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DefaultFun -> Rep DefaultFun x
from :: forall x. DefaultFun -> Rep DefaultFun x
$cto :: forall x. Rep DefaultFun x -> DefaultFun
to :: forall x. Rep DefaultFun x -> DefaultFun
Generic, Ord DefaultFun
Ord DefaultFun =>
((DefaultFun, DefaultFun) -> [DefaultFun])
-> ((DefaultFun, DefaultFun) -> DefaultFun -> Int)
-> ((DefaultFun, DefaultFun) -> DefaultFun -> Int)
-> ((DefaultFun, DefaultFun) -> DefaultFun -> Bool)
-> ((DefaultFun, DefaultFun) -> Int)
-> ((DefaultFun, DefaultFun) -> Int)
-> Ix DefaultFun
(DefaultFun, DefaultFun) -> Int
(DefaultFun, DefaultFun) -> [DefaultFun]
(DefaultFun, DefaultFun) -> DefaultFun -> Bool
(DefaultFun, DefaultFun) -> DefaultFun -> Int
forall a.
Ord a =>
((a, a) -> [a])
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Int)
-> ((a, a) -> a -> Bool)
-> ((a, a) -> Int)
-> ((a, a) -> Int)
-> Ix a
$crange :: (DefaultFun, DefaultFun) -> [DefaultFun]
range :: (DefaultFun, DefaultFun) -> [DefaultFun]
$cindex :: (DefaultFun, DefaultFun) -> DefaultFun -> Int
index :: (DefaultFun, DefaultFun) -> DefaultFun -> Int
$cunsafeIndex :: (DefaultFun, DefaultFun) -> DefaultFun -> Int
unsafeIndex :: (DefaultFun, DefaultFun) -> DefaultFun -> Int
$cinRange :: (DefaultFun, DefaultFun) -> DefaultFun -> Bool
inRange :: (DefaultFun, DefaultFun) -> DefaultFun -> Bool
$crangeSize :: (DefaultFun, DefaultFun) -> Int
rangeSize :: (DefaultFun, DefaultFun) -> Int
$cunsafeRangeSize :: (DefaultFun, DefaultFun) -> Int
unsafeRangeSize :: (DefaultFun, DefaultFun) -> Int
Ix)
    deriving anyclass (DefaultFun -> ()
(DefaultFun -> ()) -> NFData DefaultFun
forall a. (a -> ()) -> NFData a
$crnf :: DefaultFun -> ()
rnf :: DefaultFun -> ()
NFData, Eq DefaultFun
Eq DefaultFun =>
(Int -> DefaultFun -> Int)
-> (DefaultFun -> Int) -> Hashable DefaultFun
Int -> DefaultFun -> Int
DefaultFun -> Int
forall a. Eq a => (Int -> a -> Int) -> (a -> Int) -> Hashable a
$chashWithSalt :: Int -> DefaultFun -> Int
hashWithSalt :: Int -> DefaultFun -> Int
$chash :: DefaultFun -> Int
hash :: DefaultFun -> Int
Hashable, PrettyBy PrettyConfigPlc)

{- Note [Textual representation of names of built-in functions]. The plc parser
 parses builtin names by looking at an enumeration of all of the built-in
 functions and checking whether the given name matches the pretty-printed name,
 obtained using the instance below.  Thus the definitive forms of the names of
 the built-in functions are obtained by applying the function below to the
 constructor names above. -}
instance Pretty DefaultFun where
    pretty :: forall ann. DefaultFun -> Doc ann
pretty DefaultFun
fun = String -> Doc ann
forall ann. String -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty (String -> Doc ann) -> String -> Doc ann
forall a b. (a -> b) -> a -> b
$ ShowS
lowerInitialChar ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ DefaultFun -> String
forall a. Show a => a -> String
show DefaultFun
fun

instance ExMemoryUsage DefaultFun where
    memoryUsage :: DefaultFun -> CostRose
memoryUsage DefaultFun
_ = CostingInteger -> CostRose
singletonRose CostingInteger
1
    {-# INLINE memoryUsage #-}

-- | Turn a function into another function that 'fail's when its second argument is @0@ or calls the
-- original function otherwise and wraps the result in 'pure'. Useful for correctly handling `div`,
-- `mod`, etc.
nonZeroSecondArg
    :: (Integer -> Integer -> Integer) -> Integer -> Integer -> BuiltinResult Integer
-- If we match against @IS 0#@ instead of @0@, GHC will generate tidier Core for some reason. It
-- probably doesn't really matter performance-wise, but would be easier to read. We don't do it out
-- of paranoia and because it requires importing the 'IS' constructor, which is in different
-- packages depending on the GHC version, so requires a bunch of irritating CPP.
--
-- We could also replace 'div' with 'integerDiv' (and do the same for other division builtins) at
-- the call site of this function in order to avoid double matching against @0@, but that also
-- requires CPP. Perhaps we can afford one additional pattern match for division builtins for the
-- time being, since those aren't particularly fast anyway.
--
-- The bang is to communicate to GHC that the function is strict in both the arguments just in case
-- it'd want to allocate a thunk for the first argument otherwise.
nonZeroSecondArg :: (Integer -> Integer -> Integer)
-> Integer -> Integer -> BuiltinResult Integer
nonZeroSecondArg Integer -> Integer -> Integer
_ !Integer
_ Integer
0 =
    -- See Note [Operational vs structural errors within builtins].
    String -> BuiltinResult Integer
forall a. String -> BuiltinResult a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Cannot divide by zero"
nonZeroSecondArg Integer -> Integer -> Integer
f  Integer
x Integer
y = Integer -> BuiltinResult Integer
forall a. a -> BuiltinResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Integer -> BuiltinResult Integer)
-> Integer -> BuiltinResult Integer
forall a b. (a -> b) -> a -> b
$ Integer -> Integer -> Integer
f Integer
x Integer
y
{-# INLINE nonZeroSecondArg #-}

-- | Turn a function returning 'Either' into another function that 'fail's in the 'Left' case and
-- wraps the result in 'pure' in the 'Right' case.
eitherToBuiltinResult :: Show e => Either e r -> BuiltinResult r
eitherToBuiltinResult :: forall e r. Show e => Either e r -> BuiltinResult r
eitherToBuiltinResult = (e -> BuiltinResult r)
-> (r -> BuiltinResult r) -> Either e r -> BuiltinResult r
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (String -> BuiltinResult r
forall a. String -> BuiltinResult a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> BuiltinResult r)
-> (e -> String) -> e -> BuiltinResult r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. e -> String
forall a. Show a => a -> String
show) r -> BuiltinResult r
forall a. a -> BuiltinResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
{-# INLINE eitherToBuiltinResult #-}

{- Note [Constants vs built-in functions]
A constant is any value of a built-in type. For example, 'Integer' is a built-in type, so anything
of type 'Integer' is a constant.

On the contrary a built-in function can't be of a built-in type, because the type of a built-in
function is always of either the @all a. b@ form or the @a -> b@ one, none of which is a built-in
type. This is checked by the machinery, so if the user tries to add a built-in function that is not
of one of these forms, they'll get a nice custom type error.

A built-in function is associated with its Haskell implementation: there can be many built-in
functions of the same type, all doing different things, and there can be infinitely more _definable_
built-in functions of the same type that are not built-in functions nonetheless, because we didn't
register them as such by providing a Haskell implementation for each of them. This is the difference
between constants and built-in functions: the set of constants (infinite in our case) depends solely
on the set of available built-in types (also infinite in our case, because we have @Integer@,
@[Integer]@, @[[Integer]]@ etc), while the set of built-in functions is defined by explicitly
assigning each member a specific name and an associated with it Haskell implementation. It is
theoretically possible to have an infinite set of built-in functions, but we neither do that nor
need it, hence our set of built-in functions is finite.

The rule of thumb is: constants are raw data and built-in functions are, well, functions.

@(:)@ works as follows: it takes two constants wrapped as values, extracts an integer from the first
constant and a list of integers from the second one, prepends the former to the latter and wraps the
resulting list back into a constant, which gets wrapped into a value.

Why does @(:)@ have to be a built-in function? Because its type is

    all a. a -> list a -> list a

and if we tried to make @(:)@ a constant we'd have to somehow make this type a built-in type and
promise that every value (i.e. every definable function) of this type can be used as a Plutus term,
which doesn't make any sense. Only the particular Haskell implementation that prepends an element to
a list is what we're interested in.

Why may @[]@ not be a built-in function? If its type is hardcoded to @[Integer]@, then that's a
built-in type and we know that anything of a built-in type can be embedded into a term as a
constant. I.e. @[] :: [Integer]@ is perfectly fine as a constant and does not need to be a built-in
function.

Why may @[]@ be a built-in function? If it's polymorphic over the type of the elements, then its
Plutus Core type is @all a. list a@ and that is not a built-in type, hence we have to make that a
built-in function.
-}

{- Note [How to add a built-in function: simple cases]
This Note explains how to add a built-in function and how to read definitions of existing built-in
functions. It does not attempt to explain why things the way they are, that is explained in comments
in relevant modules, check out the following for an overview of the module structure:
https://github.com/IntersectMBO/plutus/blob/97c2b2c6975e41ce25ee5efa1dff0f1bd891a589/plutus-core/docs/BuiltinsOverview.md

In order to add a new built-in function one needs to add a constructor to 'DefaultFun' and handle
it within the @ToBuiltinMeaning uni DefaultFun@ instance. The general pattern is

    toBuiltinMeaning semvar <BuiltinName> =
        let <builtinNameDenotation> :: BS.ByteString -> BS.ByteString
            <builtinNameDenotation> = <denotation>
            {-# INLINE <builtinNameDenotation> #-}
        in makeBuiltinMeaning
            <builtinNameDenotation>
            <costingFunction>

Here's a specific example:

    toBuiltinMeaning _ AddInteger =
        let addIntegerDenotation :: Integer -> Integer -> Integer
            addIntegerDenotation = (+)
            {-# INLINE addIntegerDenotation #-}
        in makeBuiltinMeaning
            addIntegerDenotation
            (runCostingFunTwoArguments . paramAddInteger)

'makeBuiltinMeaning' creates a Plutus builtin out of its denotation (i.e. Haskell implementation)
and a costing function for it. Once a builtin is added, its Plutus type is kind-checked and printed
to a golden file automatically (consult @git status@). 'toBuiltinMeaning' also takes a
'BuiltinSemanticsVariant' argument which allows a particular builtin name to have multiple
associated denotations (see Note [Builtin semantics variants]), but for simplicity we assume in the
examples below that all builtins have only one variant rendering the @semvar@ argument irrelevant.

See Note [Builtin semantics variants] for how @semvar@ enables us to customize the behavior of a
built-in function. For the purpose of these docs we're going to ignore that and use @_@ instead of
@semvar@.

Note that it's very important for the denotation to have an explicit type signature for several
reasons:

1. makes it easier to review the code and make sure it makes sense
2. makes it easier to search for builtins associated with certain types -- just @grep@ for the type
3. most importantly, if we let GHC infer the types, there's a small but very real chance that
   updating a library to a newer version will change the type of some definition used within the
   denotation of a builtin and that may get reflected in the type signature of the builtin without
   us noticing, since the builtins machinery will gladly swallow the change. And since the type
   signature of a builtin determines its behavior via ad hoc polymorphism a change in the type
   signature can cause a sudden hardfork, which would be very bad

hence we specify the type signature for the denotation of each builtin explicitly and always create
a @let@ binding for consistency. We add an @INLINE@ pragma to the @let@ binding to make sure that
the binding doesn't get in the way of performance.

Below we will enumerate what kind of denotations are accepted by 'makeBuiltinMeaning' without
touching any costing stuff.

1. The simplest example of an accepted denotation is a monomorphic function that takes values of
built-in types and returns a value of a built-in type as well. For example

    encodeUtf8 :: Text -> BS.ByteString

You can feed 'encodeUtf8' directly to 'makeBuiltinMeaning' without specifying any types:

    toBuiltinMeaning _ EncodeUtf8 =
        let encodeUtf8Denotation :: Text -> BS.ByteString
            encodeUtf8Denotation = encodeUtf8
            {-# INLINE encodeUtf8Denotation #-}
        in makeBuiltinMeaning
            encodeUtf8Denotation
            <costingFunction>

This will add the builtin, the only two things that remain are implementing costing for this
builtin (out of the scope of this Note) and handling it within the @Flat DefaultFun@ instance
(see Note [Stable encoding of TPLC]).

2. Unconstrained type variables are fine, you don't need to instantiate them. For example

    toBuiltinMeaning _ IfThenElse =
        let ifThenElseDenotation :: Bool -> a -> a -> a
            ifThenElseDenotation b x y = if b then x else y
            {-# INLINE ifThenElseDenotation #-}
        in makeBuiltinMeaning
            ifThenElseDenotation
            <costingFunction>

works alright. The Haskell type of the denotation is

    forall a. Bool -> a -> a -> a

whose counterpart in Plutus is

    all a. bool -> a -> a -> a

and unsurprisingly it's the exact Plutus type of the added builtin.

It may seem like getting the latter from the former is entirely trivial, however
'makeBuiltinMeaning' jumps through quite a few hoops to achieve that and below we'll consider those
of them that are important to know to be able to use 'makeBuiltinMeaning' in cases that are more
complicated than a simple monomorphic or polymorphic function. But for now let's talk about a few
more simple cases.

3. Certain types are not built-in, but can be represented via built-in ones. For example, we don't
have 'Int' built-in, but we have 'Integer' and we can represent the former in terms of the
latter. The conversions between the two types are handled by 'makeBuiltinMeaning', so that the user
doesn't need to write them themselves and can just write

    toBuiltinMeaning _ LengthOfByteString =
        let lengthOfByteStringDenotation :: BS.ByteString -> Int
            lengthOfByteStringDenotation = BS.length
            {-# INLINE lengthOfByteStringDenotation #-}
        in makeBuiltinMeaning
            lengthOfByteStringDenotation
            <costingFunction>

directly (where @BS.length :: BS.ByteString -> Int@).

Note however that while it's always safe to convert an 'Int' to an 'Integer', doing the opposite is
not safe in general, because an 'Integer' may not fit into the range of 'Int'. For this reason

    YOU MUST NEVER USE 'fromIntegral' AND SIMILAR FUNCTIONS THAT CAN SILENTLY UNDER- OR OVERFLOW
    WHEN DEFINING A BUILT-IN FUNCTION

For example defining a builtin that takes an 'Integer' and converts it to an 'Int' using
'fromIntegral' is not allowed under any circumstances and can be a huge vulnerability.

It's completely fine to define a builtin that takes an 'Int' directly, though. How so? That's due
to the fact that the builtin application machinery checks that an 'Integer' is in the bounds of
'Int' before doing the conversion. If the bounds check succeeds, then the 'Integer' gets converted
to the corresponding 'Int', and if it doesn't, then the builtin application fails.

For the list of types that can be converted to/from built-in ones look into the file with the
default universe. If you need to add a new such type, just copy-paste what's done for an existing
one and adjust.

Speaking of builtin application failing:

4. A built-in function can fail. Whenever a builtin fails, evaluation of the whole program fails.
There's a number of ways a builtin can fail:

- as we've just seen a type conversion can fail due to an unsuccessful bounds check
- if the builtin expects, say, a 'Text' argument, but gets fed an 'Integer' argument
- if the builtin expects any constant, but gets fed a non-constant
- if its denotation runs in the 'BuiltinResult' monad and an 'evaluationFailure' gets returned

Most of these are not a concern to the user defining a built-in function (conversions are handled
within the builtin application machinery, type mismatches are on the type checker and the person
writing the program etc), however explicitly returning 'evaluationFailure' from a builtin is
something that happens commonly.

One simple example is a monomorphic function matching on a certain constructor and failing in all
other cases:

    toBuiltinMeaning _ UnIData =
        let unIDataDenotation :: Data -> BuiltinResult Integer
            unIDataDenotation = \case
                I i -> pure i
                _   -> evaluationFailure
            {-# INLINE unIDataDenotation #-}
        in makeBuiltinMeaning
            unIDataDenotation
            <costingFunction>

The type of the denotation is

    Data -> BuiltinResult Integer

and the Plutus type of the builtin is

    data -> integer

because the error effect is implicit in Plutus.

Returning @BuiltinResult a@ for a type variable @a@ is also fine, i.e. it doesn't matter whether
the denotation is monomorphic or polymorphic w.r.t. failing.

But note that

    'BuiltinResult' MUST BE EXPLICITLY USED FOR ANY FAILING BUILTIN AND THROWING AN EXCEPTION
    VIA 'error' OR 'throw' OR ELSE IS NOT ALLOWED AND CAN BE A HUGE VULNERABILITY. MAKE SURE THAT
    NONE OF THE FUNCTIONS THAT YOU USE TO DEFINE A BUILTIN THROW EXCEPTIONS

An argument of a builtin can't have 'BuiltinResult' in its type -- only the result.

5. A builtin can emit log messages. For that its denotation needs to run in the 'BuiltinResult' as
in case of failing. The ergonomics are the same. For example:

    toBuiltinMeaning _ Trace =
        let traceDenotation :: Text -> a -> BuiltinResult a
            traceDenotation text a = a <$ emit text
            {-# INLINE traceDenotation #-}
        in makeBuiltinMeaning
            traceDenotation
            <costingFunction>

The type of the denotation is

    forall a. Text -> a -> Builtin a

and the Plutus type of the builtin is

    all a. text -> a -> a

because just like with the error effect, whether a function logs anything or not is not reflected
in its type.

This concludes the list of simple cases. Before we jump to the hard ones, we need to talk about how
polymorphism gets elaborated, so read Note [Elaboration of polymorphism] next.
-}

{- Note [Elaboration of polymorphism]
In Note [How to add a built-in function: simple cases] we defined the following builtin:

    toBuiltinMeaning _ IfThenElse =
        let ifThenElseDenotation :: Bool -> a -> a -> a
            ifThenElseDenotation b x y = if b then x else y
            {-# INLINE ifThenElseDenotation #-}
        in makeBuiltinMeaning
            ifThenElseDenotation
            <costingFunction>

whose Haskell type is

    forall a. Bool -> a -> a -> a

The way 'makeBuiltinMeaning' handles such a type is by traversing it and instantiating every type
variable. What a type variable gets instantiated to depends on where it appears. When the entire
type of an argument is a single type variable, it gets instantiated to @Opaque val VarN@ where
@VarN@ is pseudocode for "a Haskell type representing a Plutus type variable with 'Unique' N"
For the purpose of this explanation it doesn't matter what @VarN@ actually is and the representation
is subject to change anyway (see Note [Implementation of polymorphic built-in functions] if you want
to know the details). 'Opaque' however is more fundamental and so we need to talk about it.
Here's how it's defined:

    newtype Opaque val (rep :: GHC.Type) = Opaque
        { unOpaque :: val
        }

I.e. @Opaque val rep@ is a wrapper around @val@, which stands for the type of value that an
evaluator uses (the builtins machinery is designed to work with any evaluator and different
evaluators define their type of values differently, for example 'CkValue' if the type of value for
the CK machine). The idea is simple: in order to apply the denotation of a builtin expecting, say,
an 'Integer' constant we need to actually extract that 'Integer' from the AST of the given value,
but if the denotation is polymorphic over the type of its argument, then we don't need to extract
anything, we can just pass the AST of the value directly to the denotation (which means the value
doesn't have to be a 'Constant', it can be completely arbitrary). I.e. in order for a polymorphic
function to become a monomorphic denotation (denotations are always monomorpic) all type variables
in the type of that function need to be instantiated at the type of value that a given evaluator
uses.

If we used just @val@ rather than @Opaque val rep@, we'd specialize

    forall a. Bool -> a -> a -> a

to

    Bool -> val -> val -> val

however then we'd need to separately specify the Plutus type of this builtin, since we can't infer
it from all these @val@s in the general case, for example does

    val -> val -> val

stand for

    all a. a -> a -> a

or

    all a b. a -> b -> a

or something else?

So we use the @Opaque val rep@ wrapper, which is basically a @val@ with a @rep@ attached to it where
@rep@ represents the Plutus type of the argument/result, which is how we arrive at

    Bool -> Opaque val Var0 -> Opaque val Var0 -> Opaque val Var0

This encoding allows us to specify both the Haskell and the Plutus types of the builtin
simultaneously.

If we wanted to we could add explicit 'Opaque' while still having explicit polymorphism (leaving out
the @Var0@ thing for the elaboration machinery to figure out):

    toBuiltinMeaning _ IfThenElse =
        let ifThenElseDenotation :: Bool -> Opaque val a -> Opaque val a -> Opaque val a
            ifThenElseDenotation b x y = if b then x else y
            {-# INLINE ifThenElseDenotation #-}
        in makeBuiltinMeaning
            ifThenElseDenotation
            <costingFunction>

and it would be equivalent to the original definition, but note how @a@ is now an argument to
'Opaque' rather than the entire type of an argument. In order for this definition to elaborate to
the same type as before @a@ needs to be instantiated to just @Var0@, as opposed to @Opaque val
Var0@, because the 'Opaque' part is already there, so this is what the elaboration machinery does.

So regardless of which method of defining 'IfThenElse' we choose, the type of its denotation gets
elaborated to the same

    Bool -> Opaque val Var0 -> Opaque val Var0 -> Opaque val Var0

which then gets digested, so that we can compute what Plutus type it corresponds to. The procedure
is simple: collect all distinct type variables, @all@-bind them and replace the usages with the
bound variables. This turns the type above into

    all a. bool -> a -> a -> a

which is the Plutus type of the 'IfThenElse' builtin.

It's of course allowed to have multiple type variables, e.g. in the following snippet:

    toBuiltinMeaning _ Const =
        let constDenotation :: a -> b -> a
            constDenotation = Prelude.const
            {-# INLINE constDenotation #-}
        in makeBuiltinMeaning
            constDenotation
            <costingFunction>

the Haskell type of 'const' is

    forall a b. a -> b -> a

which the elaboration machinery turns into

    Opaque val Var0 -> Opaque val Var1 -> Opaque val Var0

The elaboration machinery respects the explicitly specified parts of the type and does not attempt
to argue with them. For example if the user insisted that the instantiated type of 'const' had
@Var0@ and @Var1@ swapped:

    Opaque val Var1 -> Opaque val Var0 -> Opaque val Var1

the elaboration machinery wouldn't make a fuss about that.

As a final simple example, consider

    toBuiltinMeaning _ Trace =
        let traceDenotation :: Text -> a -> BuiltinResult a
            traceDenotation text a = a <$ emit text
            {-# INLINE traceDenotation #-}
        in makeBuiltinMeaning
            traceDenotation
            <costingFunction>

from [How to add a built-in function: simple cases]. The type of the denotation is

    forall a. Text -> a -> BuiltinResult a

which elaborates to

    Text -> Opaque val Var0 -> BuiltinResult (Opaque val Var0)

Elaboration machinery is able to look under 'BuiltinResult' even if there's a type variable inside
that does not appear anywhere else in the type signature, for example the type of the denotation in

    toBuiltinMeaning _ ErrorPrime =
        let errorPrimeDenotation :: BuiltinResult a
            errorPrimeDenotation = evaluationFailure
            {-# INLINE errorPrimeDenotation #-}
        in makeBuiltinMeaning
            errorPrimeDenotation
            <costingFunction>

is

    forall a. BuiltinResult a

which gets elaborated to

    BuiltinResult (Opaque val Var0)

from which the final Plutus type of the builtin is computed:

    all a. a

Read Note [How to add a built-in function: complicated cases] next.
-}

{- Note [How to add a built-in function: complicated cases]
Now let's talk about more complicated built-in functions.

1. In Note [Elaboration of polymorphism] we saw how a Haskell type variable gets elaborated to an
@Opaque val VarN@ and we learned that this type can be used directly as opposed to being inferred.
However there exist more ways to use 'Opaque' explicitly. Here's a simple example:

    toBuiltinMeaning _ IdAssumeBool =
        let idAssumeBoolDenotation :: Opaque val Bool -> Opaque val Bool
            idAssumeBoolDenotation = Prelude.id
            {-# INLINE idAssumeBoolDenotation #-}
        in makeBuiltinMeaning
            idAssumeBoolDenotation
            <costingFunction>

This creates a built-in function whose Plutus type is

    id : bool -> bool

i.e. the Plutus type signature of the built-in function is the same as with

    toBuiltinMeaning _ IdBool =
        let idBoolDenotation :: Bool -> Bool
            idBoolDenotation = Prelude.id
            {-# INLINE idBoolDenotation #-}
        in makeBuiltinMeaning
            idBoolDenotation
            <costingFunction>

but the two evaluate differently: the former takes a value and returns it right away while the
latter takes a value, extracts a 'Bool' constant out of it and then lifts that constant back into
@val@. The difference is not only in performance (obviously returning something right away is
cheaper than unlifting-then-lifting-back), but also in semantics: the former returns its argument
during evaluation regardless of what that argument is, so if someone generates Untyped Plutus Core
directly, they can apply @IdAssumeBool@ to a term that doesn't evaluate to a 'Bool' constant or
even a constant at all and that won't be a runtime error, while the latter has to be applied to
a term evaluating to a 'Bool' constant in order not to fail at runtime.

2. @val@ in @Opaque val rep@ is not completely arbitrary, it has to implement 'HasConstant', which
makes it possible to unlift @val@ as a constant or lift a constant back into @val@. There's a
'HasConstant' instance for @Opaque val rep@ whenever there's one for @val@, so if we, for some
reason, wanted to have 'Opaque' in the type signature of the denotation, but still unlift the
argument as a 'Bool', we could do that:

    toBuiltinMeaning _ IdAssumeCheckBool =
        let idAssumeCheckBoolDenotation :: Opaque val Bool -> BuiltinResult Bool
            idAssumeCheckBoolDenotation val = asConstant val of
                Right (Some (ValueOf DefaultUniBool b)) -> pure b
                _                                       -> evaluationFailure
            {-# INLINE idAssumeCheckBoolDenotation #-}
        in makeBuiltinMeaning
            idAssumeCheckBoolDenotation
            <costingFunction>

Here in the denotation we unlift the given value as a constant, check that its type tag is
'DefaultUniBool' and return the unlifted 'Bool'. If any of that fails, we return an explicit
'evaluationFailure'.

This achieves almost the same as 'IdBool', which keeps all the bookkeeping behind the scenes, but
there is a minor difference: in case of error its message is ignored. It would be easy to allow for
returning an unlifting error from a builtin explicitly, but we don't need that for anything, hence
it's not implemented.

We call this style of manually calling 'asConstant' and matching on the type tag "manual unlifting".
As opposed to "automatic unlifting" that we were using before where 'Bool' in the type of the
denotation of a builtin causes the builtins machinery to convert the given argument to a 'Bool'
constant automatically behind the scenes.

3. There's a middle ground between automatic and manual unlifting to 'Bool', one can unlift a value
automatically as a constant and then unlift the result manually to 'Bool' using the 'SomeConstant'
wrapper:

    newtype SomeConstant uni (rep :: GHC.Type) = SomeConstant
        { unSomeConstant :: Some (ValueOf uni)
        }

'SomeConstant' is similar to 'Opaque' in that it has a @rep@ representing a Plutus type.
The difference is that 'Opaque' is a wrapper around an arbitrary value and 'SomeConstant' is a
wrapper around a constant. 'SomeConstant' allows one to automatically unlift an argument of a
built-in function as a constant with all 'asConstant' business kept behind the scenes, for example:

    toBuiltinMeaning _ IdSomeConstantBool =
        let idSomeConstantBoolDenotation :: SomeConstant uni Bool -> BuiltinResult Bool
            idSomeConstantBoolDenotation = \case
                SomeConstant (Some (ValueOf DefaultUniBool b)) -> pure b
                _                                              -> evaluationFailure
            {-# INLINE idSomeConstantBoolDenotation #-}
        in makeBuiltinMeaning
            idSomeConstantBoolDenotation
            <costingFunction>

Note how we no longer call 'asConstant' manually, but still manually match on 'DefaultUniBool'.

So there's a whole range of how "low-level" one can choose to be when defining a built-in function.
However it's not always possible to use automatic unlifting, see next.

4. If we try to define the following built-in function:

    toBuiltinMeaning _ NullList =
        let nullListDenotation :: [a] -> Bool
            nullListDenotation = null
            {-# INLINE nullListDenotation #-}
        in makeBuiltinMeaning
            nullListDenotation
            <costingFunction>

we'll get an error, saying that a polymorphic built-in type can't be applied to a type variable.
It's not impossible to make it work, see Note [Unlifting a term as a value of a built-in type], but
not in the general case, plus it has to be very inefficient.

Instead we have to use 'SomeConstant' to automatically unlift the argument as a constant and then
check that the value inside of it is a list (by matching on the type tag):

    toBuiltinMeaning _ NullList =
        let nullListDenotation :: SomeConstant uni [a] -> BuiltinResult Bool
            nullListDenotation (SomeConstant (Some (ValueOf uniListA xs))) = do
                case uniListA of
                    DefaultUniList _ -> pure $ null xs
                    _ -> throwing _StructuralUnliftingError "Expected a list but got something else"
            {-# INLINE nullListDenotation #-}
        in makeBuiltinMeaning
            nullListDenotation
            <costingFunction>

As before, we have to match on the type tag, because there's no relation between @rep@ from
@SomeConstant uni rep@ and the constant that the built-in function actually receives at runtime
(someone could generate Untyped Plutus Core directly and apply 'nullPlc' to an 'Integer' or
whatever). @rep@ is only for the Plutus type checker to look at, it doesn't influence evaluation
in any way.

Here's a similar built-in function:

    toBuiltinMeaning _ FstPair =
        let fstPairDenotation :: SomeConstant uni (a, b) -> BuiltinResult (Opaque val a)
            fstPairDenotation (SomeConstant (Some (ValueOf uniPairAB xy))) = do
                case uniPairAB of
                    DefaultUniPair uniA _ ->              -- [1]
                        pure . fromValueOf uniA $ fst xy  -- [2]
                    _ ->
                        throwing _StructuralUnliftingError "Expected a pair but got something else"
            {-# INLINE fstPairDenotation #-}
        in makeBuiltinMeaning
            fstPairDenotation
            <costingFunction>

In this definition we extract the first element of a pair by checking that the given constant is
indeed a pair [1] and lifting its first element into @val@ using the type tag for the first
element [2] (extracted from the type tag for the whole pair constant [1]).

Note that it's fine to mix automatic unlifting for polymorphism not related to built-in types and
manual unlifting for arguments having non-monomorphized polymorphic built-in types, for example:

    toBuiltinMeaning _ ChooseList =
        let chooseListDenotation :: SomeConstant uni [a] -> b -> b -> BuiltinResult b
            chooseListDenotation (SomeConstant (Some (ValueOf uniListA xs))) a b = do
                case uniListA of
                    DefaultUniList _ -> pure $ case xs of
                        []    -> a
                        _ : _ -> b
                    _ -> throwing _StructuralUnliftingError "Expected a list but got something else"
            {-# INLINE chooseListDenotation #-}
        in makeBuiltinMeaning
            chooseListDenotation
            (runCostingFunThreeArguments . paramChooseList)
            <costingFunction>

Here @a@ appears inside @[]@, which is a polymorphic built-in type, and so we have to use
'SomeConstant' and check that the given constant is indeed a list, while @b@ doesn't appear inside
of any built-in type and so we don't need to instantiate it to 'Opaque' manually, the elaboration
machinery will do it for us.

Our final example is this:

    toBuiltinMeaning _ MkCons =
        let mkConsDenotation
                :: SomeConstant uni a -> SomeConstant uni [a] -> BuiltinResult (Opaque val [a])
            mkConsDenotation
              (SomeConstant (Some (ValueOf uniA x)))
              (SomeConstant (Some (ValueOf uniListA xs))) = do
                case uniListA of
                    DefaultUniList uniA' -> case uniA `geq` uniA' of       -- [1]
                        Just Refl ->                                       -- [2]
                            pure . fromValueOf uniListA $ x : xs           -- [3]
                        _ -> throwing _StructuralUnliftingError
                            "The type of the value does not match the type of elements in the list"
                    _ -> throwing _StructuralUnliftingError "Expected a list but got something else"
            {-# INLINE mkConsDenotation #-}
        in makeBuiltinMeaning
            mkConsDenotation
            <costingFunction>

Here we prepend an element to a list [3] after checking that the second argument is indeed a
list [1] and that the type tag of the element being prepended equals the type tag for elements of
the list [2] (extracted from the type tag for the whole list constant [1]).
-}

{- Note [Builtins and Plutus type checking]
There's a direct correspondence between the Haskell type of the denotation of a builtin and the
Plutus type of the builtin:

1. elaboration turns a Haskell type variable into a concrete Haskell type representing a Plutus type
   variable, which later becomes demoted (in the regular @singletons@ sense via 'KnownSymbol' etc)
   to a regular Haskell value representing a Plutus type variable (as a part of the AST)
2. a builtin head (i.e. a completely uninstantiated built-in type such as @Bool@ and @[]@) is
   considered abstract by the Plutus type checker. All the type checker cares about is being able to
   get the (Plutus) kind of a builtin head and check two builtin heads for equality
3. Plutus type normalization tears partially or fully instantiated built-in types (such as
   @[Integer]@) apart and creates a Plutus type application for each Haskell type application
4. 'BuiltinResult' does not appear on the Plutus side, since the logging and failure effects are
   implicit in Plutus as was discussed above
5. 'Opaque' and 'SomeConstant' both carry a Haskell @rep@ type argument representing some Plutus
   type to be used for Plutus type checking

This last part means that one can attach any (legal) @rep@ to an 'Opaque' or 'SomeConstant' and
it'll be used by the Plutus type checker completely regardless of what the built-in function
actually does. Let's look at some examples.

1. The following built-in function unlifts to 'Bool' and lifts the result back:

    toBuiltinMeaning _ IdIntegerAsBool =
        let idIntegerAsBoolDenotation
                :: SomeConstant uni Integer -> BuiltinResult (SomeConstant uni Integer)
            idIntegerAsBoolDenotation = \case
                con@(SomeConstant (Some (ValueOf DefaultUniBool _))) -> pure con
                _                                                    -> evaluationFailure
            {-# INLINE idIntegerAsBoolDenotation #-}
        in makeBuiltinMeaning
            idIntegerAsBoolDenotation
            <costingFunction>

but on the Plutus side its type is

    integer -> integer

because the @rep@ that 'SomeConstant' carries is 'Integer' in both the cases (in the type of the
argument, as well as in the type of the result).

This means that for this built-in function the Plutus type checker will accept a program that fails
at runtime due to a type mismatch and will reject a program that runs successfully. Other built-in
functions also can fail, e.g. the type of @ifThenElse@ says that the builtin expects a @Bool@ and
feeding it something else will result in evaluation failure, but 'idIntegerAsBool' is different:
it's respecting its type signature is what causes a failure, not disrespecting it.

2. Another example of an unsafe built-in function is this one that checks whether an argument is a
constant or not:

    toBuiltinMeaning _ IsConstant =
        let isConstantDenotation :: Opaque val a -> Bool
            isConstantDenotation = isRight . asConstant
            {-# INLINE isConstantDenotation #-}
        in makeBuiltinMeaning
            isConstantDenotation
            <costingFunction>

Its type on the Plutus side is

    all a. a -> bool

By parametricity any inhabitant of this type has to be either bottom or a function ignoring its
argument, but @IsConstant@ actually uses the argument and so we break parametricity with this
built-in function.

3. Finally, we can have a Plutus version of @unsafeCoerce@:

    toBuiltinMeaning _ UnsafeCoerce =
        let unsafeCoerceDenotation :: Opaque val a -> Opaque val b
            unsafeCoerceDenotation = Opaque . unOpaque
            {-# INLINE unsafeCoerceDenotation #-}
        in makeBuiltinMeaning
            unsafeCoerceDenotation
            <costingFunction>

Its type on the Plutus side is

    all a b. a -> b

and thus this built-in function allows for viewing any Plutus expression as having an arbitrary
type. Which is of course not nearly as bad as @unsafeCoerce@ in Haskell, because in Plutus a
blob of memory representing an @Integer@ is not going to be viewed as a @[Bool]@ and an attempt to
actually extract that @[Bool]@ will result in evaluation failure, but this built-in function is
still not a good citizen of the Plutus type system.

One could of course simply wrap Haskell's @unsafeCoerce@ as a built-in function in Plutus, but it
goes without saying that this is not supposed to be done.

So overall one needs to be very careful when defining built-in functions that have explicit
'Opaque' and 'SomeConstant' arguments. Expressiveness doesn't come for free.

Read Note [Pattern matching on built-in types] next.
-}

{- Note [Pattern matching on built-in types]
At the moment we really only support direct pattern matching on enumeration types: 'Void', 'Unit',
'Bool' etc. This is because the denotation of a builtin cannot construct general terms (as opposed
to constants), only juggle the ones that were provided as arguments without changing them.
So e.g. if we wanted to add the following data type:

    newtype AnInt = AnInt Int

as a built-in type, we wouldn't be able to add the following function as its pattern matcher:

    matchAnInt :: AnInt -> (Int -> r) -> r
    matchAnInt (AnInt i) f = f i

because currently we cannot express the @f i@ part using the builtins machinery as that would
require applying an arbitrary Plutus Core function in the denotation of a builtin, which would
allow us to return arbitrary terms from the builtin application machinery, which is something
that we originally had, but decided to abandon due to performance concerns.

But it's still possible to have @AnInt@ as a built-in type, it's just that instead of trying to
make its pattern matcher into a builtin we can have the following builtin:

    anIntToInt :: AnInt -> Int
    anIntToInt (AnInt i) = i

which fits perfectly well into the builtins machinery.

Although that becomes annoying for more complex data types. For tuples we need to provide two
projection functions ('fst' and 'snd') instead of a single pattern matcher, which is not too bad,
but to get pattern matching on lists we need a more complicated setup. For example we can have three
built-in functions: @null@, @head@ and @tail@, plus require `Bool` to be in the universe, so that we
can define an equivalent of

    matchList :: [a] -> r -> (a -> [a] -> r) -> r
    matchList xs z f = if null xs then z else f (head xs) (tail xs)

If a constructor stores more than one value, the corresponding projection function packs them
into a (possibly nested) pair, for example for

    data Data
        = Constr Integer [Data]
        | <...>

we have (pseudocode):

    unConstrData (Constr i ds) = (i, ds)

In order to get pattern matching over 'Data' we need a projection function per constructor as well
as with lists, but writing (where the @Data@ suffix indicates that a function is a builtin that
somehow corresponds to a constructor of 'Data')

    if isConstrData d
        then uncurry fConstr $ unConstrData d
        else if isMapData d
            then fMap $ unMapData d
            else if isListData d
                then fList $ unListData d
                else <...>

is tedious and inefficient and so instead we have a single @chooseData@ builtin that matches on
its @Data@ argument and chooses the appropriate branch (type instantiations and strictness concerns
are omitted for clarity):

     chooseData
        (uncurry fConstr $ unConstrData d)
        (fMap $ unMapData d)
        (fList $ unListData d)
        <...>
        d

which, for example, evaluates to @fMap es@ when @d@ is @Map es@

We decided to handle lists the same way by using @chooseList@ rather than @null@ for consistency.

On the bright side, this encoding of pattern matchers does work, so maybe it's indeed worth to
prioritize performance over convenience, especially given the fact that performance is of a concern
to every single end user while the inconvenience is only a concern for the compiler writers and
we don't add complex built-in types too often.

It is not however clear if we can't get more performance gains by defining matchers directly as
higher-order built-in functions compared to forbidding them. Particularly since if higher-order
built-in functions were allowed, we could define not only matchers, but also folds and keep
recursion on the Haskell side for conversions from 'Data', which can potentially have a huge
positive impact on performance.

See https://github.com/IntersectMBO/plutus/pull/5486 for how higher-order builtins would look
like.

Read Note [Representable built-in functions over polymorphic built-in types] next.
-}

{- Note [Representable built-in functions over polymorphic built-in types]
In Note [Pattern matching on built-in types] we discussed how general higher-order polymorphic
built-in functions are troubling, but polymorphic built-in functions can be troubling even in
the first-order case. In a Plutus program we always pair constants of built-in types with their
tags from the universe, which means that in order to produce a constant embedded into a program
we need the tag of the type of that constant. We can't get that tag from a Plutus type -- those
are gone at runtime, so the only place we can get a type tag from during evaluation is some already
existing constant. I.e. the following built-in function is representable:

    tail : all a. [a] -> [a]

because for constructing the result we need a type tag for @[a]@, but we have a value of that type
as an argument and so we can extract the type tag from it. Same applies to

    swap : all a b. (a, b) -> (b, a)

since 'SomeConstantOf' always contains a type tag for each type that a polymorphic built-in type is
instantiated with and so constructing a type tag for @(b, a)@ given type tags for @a@ and @b@ is
unproblematic.

And so neither

    cons : all a. a -> [a] -> [a]

is troubling (even though that ones requires checking at runtime that the element to be prepended
is of the same type as the type of the elements of the list as it's impossible to enforce this kind
of type safety in Haskell over possibly untyped PLC).

However consider the following imaginary builtin:

    nil : all a. [a]

we can't represent it for two reasons:

1. we don't have any argument providing us a type tag for @a@ and hence we can't construct a type
   tag for @[a]@
2. it would be a very unsound builtin to have. We can only instantiate built-in types with other
   built-in types and so allowing @nil {some_non_built_in_type}@ would be a lie that couldn't reduce
   to anything since it's not even possible to represent a built-in list with non-built-in elements
   (even if there's zero of them)

"Wait, but wouldn't @cons {some_non_built_in_type}@ be a lie as well?" -- No! Since @cons@ does not
just construct a list filled with elements of a non-built-in type but also expects one as an
argument and providing such an argument is impossible, 'cause it's pretty much the same thing as
populating 'Void' -- both values are equally unrepresentable. And so @cons {some_non_built_in_type}@
is a way to say @absurd@, which is perfectly fine to have.

Finally,

    comma :: all a b. a -> b -> (a, b)

is representable (because we can require arguments to be constants carrying universes with them,
which we can use to construct the resulting universe), but is still a lie, because instantiating
that builtin with non-built-in types is possible and so the PLC type checker won't throw on such
an instantiation, which will become 'evalutionFailure' at runtime the moment unlifting of a
non-constant is attempted when a constant is expected.

So could we still get @nil@ or a safe version of @comma@ somehow? Well, we could have this
weirdness:

    nilOfTypeOf : all a. [a] -> [a]

i.e. ask for an already existing list, but ignore the actual list and only use the type tag.

But since we're ignoring the actual list, can't we just not pass it in the first place? And instead
pass around our good old friends, singletons. We should be able to do that, but it hasn't been
investigated. Perhaps something along the lines of adding the following constructor to 'DefaultUni':

    DefaultUniProtoSing :: DefaultUni (Esc (Proxy @GHC.Type))

and then defining

    nil : all a. sing a -> [a]

and then the Plutus Tx compiler can provide a type class or something for constructing singletons
for built-in types.

This was investigated in https://github.com/IntersectMBO/plutus/pull/4337 but we decided not to
do it quite yet, even though it worked (the Plutus Tx part wasn't implemented).
-}

{- Note [Operational vs structural errors within builtins]
See the Haddock of 'EvaluationError' to understand why we sometimes use 'fail' (to throw an
"operational" evaluation error) and sometimes use @throwing _StructuralUnliftingError@ (to throw a
"structural" evaluation error). Please respect the distinction when adding new built-in functions.
-}

instance uni ~ DefaultUni => ToBuiltinMeaning uni DefaultFun where
    type CostingPart uni DefaultFun = BuiltinCostModel

    {- | Allow different variants of builtins with different implementations, and
       possibly different semantics.  Note that DefaultFunSemanticsVariantA,
       DefaultFunSemanticsVariantB etc. do not correspond directly to PlutusV1,
       PlutusV2 etc. in plutus-ledger-api: see Note [Builtin semantics variants]. -}
    data BuiltinSemanticsVariant DefaultFun
        = DefaultFunSemanticsVariantA
        | DefaultFunSemanticsVariantB
        | DefaultFunSemanticsVariantC
        deriving stock (BuiltinSemanticsVariant DefaultFun
-> BuiltinSemanticsVariant DefaultFun -> Bool
(BuiltinSemanticsVariant DefaultFun
 -> BuiltinSemanticsVariant DefaultFun -> Bool)
-> (BuiltinSemanticsVariant DefaultFun
    -> BuiltinSemanticsVariant DefaultFun -> Bool)
-> Eq (BuiltinSemanticsVariant DefaultFun)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BuiltinSemanticsVariant DefaultFun
-> BuiltinSemanticsVariant DefaultFun -> Bool
== :: BuiltinSemanticsVariant DefaultFun
-> BuiltinSemanticsVariant DefaultFun -> Bool
$c/= :: BuiltinSemanticsVariant DefaultFun
-> BuiltinSemanticsVariant DefaultFun -> Bool
/= :: BuiltinSemanticsVariant DefaultFun
-> BuiltinSemanticsVariant DefaultFun -> Bool
Eq, Int -> BuiltinSemanticsVariant DefaultFun
BuiltinSemanticsVariant DefaultFun -> Int
BuiltinSemanticsVariant DefaultFun
-> [BuiltinSemanticsVariant DefaultFun]
BuiltinSemanticsVariant DefaultFun
-> BuiltinSemanticsVariant DefaultFun
BuiltinSemanticsVariant DefaultFun
-> BuiltinSemanticsVariant DefaultFun
-> [BuiltinSemanticsVariant DefaultFun]
BuiltinSemanticsVariant DefaultFun
-> BuiltinSemanticsVariant DefaultFun
-> BuiltinSemanticsVariant DefaultFun
-> [BuiltinSemanticsVariant DefaultFun]
(BuiltinSemanticsVariant DefaultFun
 -> BuiltinSemanticsVariant DefaultFun)
-> (BuiltinSemanticsVariant DefaultFun
    -> BuiltinSemanticsVariant DefaultFun)
-> (Int -> BuiltinSemanticsVariant DefaultFun)
-> (BuiltinSemanticsVariant DefaultFun -> Int)
-> (BuiltinSemanticsVariant DefaultFun
    -> [BuiltinSemanticsVariant DefaultFun])
-> (BuiltinSemanticsVariant DefaultFun
    -> BuiltinSemanticsVariant DefaultFun
    -> [BuiltinSemanticsVariant DefaultFun])
-> (BuiltinSemanticsVariant DefaultFun
    -> BuiltinSemanticsVariant DefaultFun
    -> [BuiltinSemanticsVariant DefaultFun])
-> (BuiltinSemanticsVariant DefaultFun
    -> BuiltinSemanticsVariant DefaultFun
    -> BuiltinSemanticsVariant DefaultFun
    -> [BuiltinSemanticsVariant DefaultFun])
-> Enum (BuiltinSemanticsVariant DefaultFun)
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: BuiltinSemanticsVariant DefaultFun
-> BuiltinSemanticsVariant DefaultFun
succ :: BuiltinSemanticsVariant DefaultFun
-> BuiltinSemanticsVariant DefaultFun
$cpred :: BuiltinSemanticsVariant DefaultFun
-> BuiltinSemanticsVariant DefaultFun
pred :: BuiltinSemanticsVariant DefaultFun
-> BuiltinSemanticsVariant DefaultFun
$ctoEnum :: Int -> BuiltinSemanticsVariant DefaultFun
toEnum :: Int -> BuiltinSemanticsVariant DefaultFun
$cfromEnum :: BuiltinSemanticsVariant DefaultFun -> Int
fromEnum :: BuiltinSemanticsVariant DefaultFun -> Int
$cenumFrom :: BuiltinSemanticsVariant DefaultFun
-> [BuiltinSemanticsVariant DefaultFun]
enumFrom :: BuiltinSemanticsVariant DefaultFun
-> [BuiltinSemanticsVariant DefaultFun]
$cenumFromThen :: BuiltinSemanticsVariant DefaultFun
-> BuiltinSemanticsVariant DefaultFun
-> [BuiltinSemanticsVariant DefaultFun]
enumFromThen :: BuiltinSemanticsVariant DefaultFun
-> BuiltinSemanticsVariant DefaultFun
-> [BuiltinSemanticsVariant DefaultFun]
$cenumFromTo :: BuiltinSemanticsVariant DefaultFun
-> BuiltinSemanticsVariant DefaultFun
-> [BuiltinSemanticsVariant DefaultFun]
enumFromTo :: BuiltinSemanticsVariant DefaultFun
-> BuiltinSemanticsVariant DefaultFun
-> [BuiltinSemanticsVariant DefaultFun]
$cenumFromThenTo :: BuiltinSemanticsVariant DefaultFun
-> BuiltinSemanticsVariant DefaultFun
-> BuiltinSemanticsVariant DefaultFun
-> [BuiltinSemanticsVariant DefaultFun]
enumFromThenTo :: BuiltinSemanticsVariant DefaultFun
-> BuiltinSemanticsVariant DefaultFun
-> BuiltinSemanticsVariant DefaultFun
-> [BuiltinSemanticsVariant DefaultFun]
Enum, BuiltinSemanticsVariant DefaultFun
BuiltinSemanticsVariant DefaultFun
-> BuiltinSemanticsVariant DefaultFun
-> Bounded (BuiltinSemanticsVariant DefaultFun)
forall a. a -> a -> Bounded a
$cminBound :: BuiltinSemanticsVariant DefaultFun
minBound :: BuiltinSemanticsVariant DefaultFun
$cmaxBound :: BuiltinSemanticsVariant DefaultFun
maxBound :: BuiltinSemanticsVariant DefaultFun
Bounded, Int -> BuiltinSemanticsVariant DefaultFun -> ShowS
[BuiltinSemanticsVariant DefaultFun] -> ShowS
BuiltinSemanticsVariant DefaultFun -> String
(Int -> BuiltinSemanticsVariant DefaultFun -> ShowS)
-> (BuiltinSemanticsVariant DefaultFun -> String)
-> ([BuiltinSemanticsVariant DefaultFun] -> ShowS)
-> Show (BuiltinSemanticsVariant DefaultFun)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BuiltinSemanticsVariant DefaultFun -> ShowS
showsPrec :: Int -> BuiltinSemanticsVariant DefaultFun -> ShowS
$cshow :: BuiltinSemanticsVariant DefaultFun -> String
show :: BuiltinSemanticsVariant DefaultFun -> String
$cshowList :: [BuiltinSemanticsVariant DefaultFun] -> ShowS
showList :: [BuiltinSemanticsVariant DefaultFun] -> ShowS
Show, (forall x.
 BuiltinSemanticsVariant DefaultFun
 -> Rep (BuiltinSemanticsVariant DefaultFun) x)
-> (forall x.
    Rep (BuiltinSemanticsVariant DefaultFun) x
    -> BuiltinSemanticsVariant DefaultFun)
-> Generic (BuiltinSemanticsVariant DefaultFun)
forall x.
Rep (BuiltinSemanticsVariant DefaultFun) x
-> BuiltinSemanticsVariant DefaultFun
forall x.
BuiltinSemanticsVariant DefaultFun
-> Rep (BuiltinSemanticsVariant DefaultFun) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
BuiltinSemanticsVariant DefaultFun
-> Rep (BuiltinSemanticsVariant DefaultFun) x
from :: forall x.
BuiltinSemanticsVariant DefaultFun
-> Rep (BuiltinSemanticsVariant DefaultFun) x
$cto :: forall x.
Rep (BuiltinSemanticsVariant DefaultFun) x
-> BuiltinSemanticsVariant DefaultFun
to :: forall x.
Rep (BuiltinSemanticsVariant DefaultFun) x
-> BuiltinSemanticsVariant DefaultFun
Generic)
        deriving anyclass (BuiltinSemanticsVariant DefaultFun -> ()
(BuiltinSemanticsVariant DefaultFun -> ())
-> NFData (BuiltinSemanticsVariant DefaultFun)
forall a. (a -> ()) -> NFData a
$crnf :: BuiltinSemanticsVariant DefaultFun -> ()
rnf :: BuiltinSemanticsVariant DefaultFun -> ()
NFData, Context
-> BuiltinSemanticsVariant DefaultFun -> IO (Maybe ThunkInfo)
Proxy (BuiltinSemanticsVariant DefaultFun) -> String
(Context
 -> BuiltinSemanticsVariant DefaultFun -> IO (Maybe ThunkInfo))
-> (Context
    -> BuiltinSemanticsVariant DefaultFun -> IO (Maybe ThunkInfo))
-> (Proxy (BuiltinSemanticsVariant DefaultFun) -> String)
-> NoThunks (BuiltinSemanticsVariant DefaultFun)
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context
-> BuiltinSemanticsVariant DefaultFun -> IO (Maybe ThunkInfo)
noThunks :: Context
-> BuiltinSemanticsVariant DefaultFun -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context
-> BuiltinSemanticsVariant DefaultFun -> IO (Maybe ThunkInfo)
wNoThunks :: Context
-> BuiltinSemanticsVariant DefaultFun -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy (BuiltinSemanticsVariant DefaultFun) -> String
showTypeOf :: Proxy (BuiltinSemanticsVariant DefaultFun) -> String
NoThunks)

    -- Integers
    toBuiltinMeaning
        :: forall val. HasMeaningIn uni val
        => BuiltinSemanticsVariant DefaultFun
        -> DefaultFun
        -> BuiltinMeaning val BuiltinCostModel

    toBuiltinMeaning :: forall val.
HasMeaningIn uni val =>
BuiltinSemanticsVariant DefaultFun
-> DefaultFun -> BuiltinMeaning val BuiltinCostModel
toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
AddInteger =
        let addIntegerDenotation :: Integer -> Integer -> Integer
            addIntegerDenotation :: Integer -> Integer -> Integer
addIntegerDenotation = Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
(+)
            {-# INLINE addIntegerDenotation #-}
        in (Integer -> Integer -> Integer)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Integer -> Integer -> Integer)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Integer -> Integer -> Integer)
-> (cost
    -> FoldArgs
         (GetArgs (Integer -> Integer -> Integer)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Integer -> Integer -> Integer
addIntegerDenotation
            (CostingFun ModelTwoArguments
-> Integer -> Integer -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> Integer -> Integer -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Integer
-> Integer
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramAddInteger)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
SubtractInteger =
        let subtractIntegerDenotation :: Integer -> Integer -> Integer
            subtractIntegerDenotation :: Integer -> Integer -> Integer
subtractIntegerDenotation = (-)
            {-# INLINE subtractIntegerDenotation #-}
        in (Integer -> Integer -> Integer)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Integer -> Integer -> Integer)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Integer -> Integer -> Integer)
-> (cost
    -> FoldArgs
         (GetArgs (Integer -> Integer -> Integer)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Integer -> Integer -> Integer
subtractIntegerDenotation
            (CostingFun ModelTwoArguments
-> Integer -> Integer -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> Integer -> Integer -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Integer
-> Integer
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramSubtractInteger)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
MultiplyInteger =
        let multiplyIntegerDenotation :: Integer -> Integer -> Integer
            multiplyIntegerDenotation :: Integer -> Integer -> Integer
multiplyIntegerDenotation = Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
(*)
            {-# INLINE multiplyIntegerDenotation #-}
        in (Integer -> Integer -> Integer)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Integer -> Integer -> Integer)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Integer -> Integer -> Integer)
-> (cost
    -> FoldArgs
         (GetArgs (Integer -> Integer -> Integer)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Integer -> Integer -> Integer
multiplyIntegerDenotation
            (CostingFun ModelTwoArguments
-> Integer -> Integer -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> Integer -> Integer -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Integer
-> Integer
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramMultiplyInteger)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
DivideInteger =
        let divideIntegerDenotation :: Integer -> Integer -> BuiltinResult Integer
            divideIntegerDenotation :: Integer -> Integer -> BuiltinResult Integer
divideIntegerDenotation = (Integer -> Integer -> Integer)
-> Integer -> Integer -> BuiltinResult Integer
nonZeroSecondArg Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
div
            {-# INLINE divideIntegerDenotation #-}
        in (Integer -> Integer -> BuiltinResult Integer)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Integer -> Integer -> BuiltinResult Integer))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Integer -> Integer -> BuiltinResult Integer)
-> (cost
    -> FoldArgs
         (GetArgs (Integer -> Integer -> BuiltinResult Integer))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Integer -> Integer -> BuiltinResult Integer
divideIntegerDenotation
            (CostingFun ModelTwoArguments
-> Integer -> Integer -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> Integer -> Integer -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Integer
-> Integer
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramDivideInteger)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
QuotientInteger =
        let quotientIntegerDenotation :: Integer -> Integer -> BuiltinResult Integer
            quotientIntegerDenotation :: Integer -> Integer -> BuiltinResult Integer
quotientIntegerDenotation = (Integer -> Integer -> Integer)
-> Integer -> Integer -> BuiltinResult Integer
nonZeroSecondArg Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
quot
            {-# INLINE quotientIntegerDenotation #-}
        in (Integer -> Integer -> BuiltinResult Integer)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Integer -> Integer -> BuiltinResult Integer))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Integer -> Integer -> BuiltinResult Integer)
-> (cost
    -> FoldArgs
         (GetArgs (Integer -> Integer -> BuiltinResult Integer))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Integer -> Integer -> BuiltinResult Integer
quotientIntegerDenotation
            (CostingFun ModelTwoArguments
-> Integer -> Integer -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> Integer -> Integer -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Integer
-> Integer
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramQuotientInteger)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
RemainderInteger =
        let remainderIntegerDenotation :: Integer -> Integer -> BuiltinResult Integer
            remainderIntegerDenotation :: Integer -> Integer -> BuiltinResult Integer
remainderIntegerDenotation = (Integer -> Integer -> Integer)
-> Integer -> Integer -> BuiltinResult Integer
nonZeroSecondArg Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
rem
            {-# INLINE remainderIntegerDenotation #-}
        in (Integer -> Integer -> BuiltinResult Integer)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Integer -> Integer -> BuiltinResult Integer))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Integer -> Integer -> BuiltinResult Integer)
-> (cost
    -> FoldArgs
         (GetArgs (Integer -> Integer -> BuiltinResult Integer))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Integer -> Integer -> BuiltinResult Integer
remainderIntegerDenotation
            (CostingFun ModelTwoArguments
-> Integer -> Integer -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> Integer -> Integer -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Integer
-> Integer
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramRemainderInteger)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
ModInteger =
        let modIntegerDenotation :: Integer -> Integer -> BuiltinResult Integer
            modIntegerDenotation :: Integer -> Integer -> BuiltinResult Integer
modIntegerDenotation = (Integer -> Integer -> Integer)
-> Integer -> Integer -> BuiltinResult Integer
nonZeroSecondArg Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
mod
            {-# INLINE modIntegerDenotation #-}
        in (Integer -> Integer -> BuiltinResult Integer)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Integer -> Integer -> BuiltinResult Integer))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Integer -> Integer -> BuiltinResult Integer)
-> (cost
    -> FoldArgs
         (GetArgs (Integer -> Integer -> BuiltinResult Integer))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Integer -> Integer -> BuiltinResult Integer
modIntegerDenotation
            (CostingFun ModelTwoArguments
-> Integer -> Integer -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> Integer -> Integer -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Integer
-> Integer
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramModInteger)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
EqualsInteger =
        let equalsIntegerDenotation :: Integer -> Integer -> Bool
            equalsIntegerDenotation :: Integer -> Integer -> Bool
equalsIntegerDenotation = Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
(==)
            {-# INLINE equalsIntegerDenotation #-}
        in (Integer -> Integer -> Bool)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (Integer -> Integer -> Bool)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Integer -> Integer -> Bool)
-> (cost
    -> FoldArgs (GetArgs (Integer -> Integer -> Bool)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Integer -> Integer -> Bool
equalsIntegerDenotation
            (CostingFun ModelTwoArguments
-> Integer -> Integer -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> Integer -> Integer -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Integer
-> Integer
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramEqualsInteger)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
LessThanInteger =
        let lessThanIntegerDenotation :: Integer -> Integer -> Bool
            lessThanIntegerDenotation :: Integer -> Integer -> Bool
lessThanIntegerDenotation = Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
(<)
            {-# INLINE lessThanIntegerDenotation #-}
        in (Integer -> Integer -> Bool)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (Integer -> Integer -> Bool)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Integer -> Integer -> Bool)
-> (cost
    -> FoldArgs (GetArgs (Integer -> Integer -> Bool)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Integer -> Integer -> Bool
lessThanIntegerDenotation
            (CostingFun ModelTwoArguments
-> Integer -> Integer -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> Integer -> Integer -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Integer
-> Integer
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramLessThanInteger)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
LessThanEqualsInteger =
        let lessThanEqualsIntegerDenotation :: Integer -> Integer -> Bool
            lessThanEqualsIntegerDenotation :: Integer -> Integer -> Bool
lessThanEqualsIntegerDenotation = Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
(<=)
            {-# INLINE lessThanEqualsIntegerDenotation #-}
        in (Integer -> Integer -> Bool)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (Integer -> Integer -> Bool)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Integer -> Integer -> Bool)
-> (cost
    -> FoldArgs (GetArgs (Integer -> Integer -> Bool)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Integer -> Integer -> Bool
lessThanEqualsIntegerDenotation
            (CostingFun ModelTwoArguments
-> Integer -> Integer -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> Integer -> Integer -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Integer
-> Integer
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramLessThanEqualsInteger)

    -- Bytestrings
    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
AppendByteString =
        let appendByteStringDenotation :: BS.ByteString -> BS.ByteString -> BS.ByteString
            appendByteStringDenotation :: ByteString -> ByteString -> ByteString
appendByteStringDenotation = ByteString -> ByteString -> ByteString
BS.append
            {-# INLINE appendByteStringDenotation #-}
        in (ByteString -> ByteString -> ByteString)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (ByteString -> ByteString -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> ByteString -> ByteString)
-> (cost
    -> FoldArgs
         (GetArgs (ByteString -> ByteString -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> ByteString -> ByteString
appendByteStringDenotation
            (CostingFun ModelTwoArguments
-> ByteString -> ByteString -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> ByteString -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> ByteString
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramAppendByteString)

    -- See Note [Builtin semantics variants]
    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
semvar DefaultFun
ConsByteString =
        -- The costing function is the same for all variants of this builtin,
        -- but since the denotation of the builtin accepts constants of
        -- different types ('Integer' vs 'Word8'), the costing function needs to
        -- by polymorphic over the type of constant.
        let costingFun
                :: ExMemoryUsage a => BuiltinCostModel -> a -> BS.ByteString -> ExBudgetStream
            costingFun :: forall a.
ExMemoryUsage a =>
BuiltinCostModel -> a -> ByteString -> ExBudgetStream
costingFun = CostingFun ModelTwoArguments -> a -> ByteString -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments -> a -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> a
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramConsByteString
            {-# INLINE costingFun #-}
            consByteStringMeaning_V1 :: BuiltinMeaning val BuiltinCostModel
consByteStringMeaning_V1 =
                let consByteStringDenotation :: Integer -> BS.ByteString -> BS.ByteString
                    consByteStringDenotation :: Integer -> ByteString -> ByteString
consByteStringDenotation Integer
n ByteString
xs = Word8 -> ByteString -> ByteString
BS.cons (Integer -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
n) ByteString
xs
                    -- Earlier instructions say never to use `fromIntegral` in the definition of a
                    -- builtin; however in this case it reduces its argument modulo 256 to get a
                    -- `Word8`, which is exactly what we want.
                    {-# INLINE consByteStringDenotation #-}
                in (Integer -> ByteString -> ByteString)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Integer -> ByteString -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Integer -> ByteString -> ByteString)
-> (cost
    -> FoldArgs
         (GetArgs (Integer -> ByteString -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
                    Integer -> ByteString -> ByteString
consByteStringDenotation
                    BuiltinCostModel
-> FoldArgs
     (GetArgs (Integer -> ByteString -> ByteString)) ExBudgetStream
BuiltinCostModel -> Integer -> ByteString -> ExBudgetStream
forall a.
ExMemoryUsage a =>
BuiltinCostModel -> a -> ByteString -> ExBudgetStream
costingFun
            -- For builtin semantics variants larger than 'DefaultFunSemanticsVariantA', the first
            -- input must be in range @[0..255]@.
            consByteStringMeaning_V2 :: BuiltinMeaning val BuiltinCostModel
consByteStringMeaning_V2 =
                let consByteStringDenotation :: Word8 -> BS.ByteString -> BS.ByteString
                    consByteStringDenotation :: Word8 -> ByteString -> ByteString
consByteStringDenotation = Word8 -> ByteString -> ByteString
BS.cons
                    {-# INLINE consByteStringDenotation #-}
                in (Word8 -> ByteString -> ByteString)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Word8 -> ByteString -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Word8 -> ByteString -> ByteString)
-> (cost
    -> FoldArgs
         (GetArgs (Word8 -> ByteString -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
                    Word8 -> ByteString -> ByteString
consByteStringDenotation
                    BuiltinCostModel
-> FoldArgs
     (GetArgs (Word8 -> ByteString -> ByteString)) ExBudgetStream
BuiltinCostModel -> Word8 -> ByteString -> ExBudgetStream
forall a.
ExMemoryUsage a =>
BuiltinCostModel -> a -> ByteString -> ExBudgetStream
costingFun
        in case BuiltinSemanticsVariant DefaultFun
semvar of
            BuiltinSemanticsVariant DefaultFun
R:BuiltinSemanticsVariantDefaultFun
DefaultFunSemanticsVariantA -> BuiltinMeaning val BuiltinCostModel
consByteStringMeaning_V1
            BuiltinSemanticsVariant DefaultFun
R:BuiltinSemanticsVariantDefaultFun
DefaultFunSemanticsVariantB -> BuiltinMeaning val BuiltinCostModel
consByteStringMeaning_V1
            BuiltinSemanticsVariant DefaultFun
R:BuiltinSemanticsVariantDefaultFun
DefaultFunSemanticsVariantC -> BuiltinMeaning val BuiltinCostModel
consByteStringMeaning_V2

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
SliceByteString =
        let sliceByteStringDenotation :: Int -> Int -> BS.ByteString -> BS.ByteString
            sliceByteStringDenotation :: Int -> Int -> ByteString -> ByteString
sliceByteStringDenotation Int
start Int
n ByteString
xs = Int -> ByteString -> ByteString
BS.take Int
n (Int -> ByteString -> ByteString
BS.drop Int
start ByteString
xs)
            {-# INLINE sliceByteStringDenotation #-}
        in (Int -> Int -> ByteString -> ByteString)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Int -> Int -> ByteString -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Int -> Int -> ByteString -> ByteString)
-> (cost
    -> FoldArgs
         (GetArgs (Int -> Int -> ByteString -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Int -> Int -> ByteString -> ByteString
sliceByteStringDenotation
            (CostingFun ModelThreeArguments
-> Int -> Int -> ByteString -> ExBudgetStream
forall a1 a2 a3.
(ExMemoryUsage a1, ExMemoryUsage a2, ExMemoryUsage a3) =>
CostingFun ModelThreeArguments -> a1 -> a2 -> a3 -> ExBudgetStream
runCostingFunThreeArguments (CostingFun ModelThreeArguments
 -> Int -> Int -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelThreeArguments)
-> BuiltinCostModel
-> Int
-> Int
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelThreeArguments
forall (f :: * -> *).
BuiltinCostModelBase f -> f ModelThreeArguments
paramSliceByteString)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
LengthOfByteString =
        let lengthOfByteStringDenotation :: BS.ByteString -> Int
            lengthOfByteStringDenotation :: ByteString -> Int
lengthOfByteStringDenotation = ByteString -> Int
BS.length
            {-# INLINE lengthOfByteStringDenotation #-}
        in (ByteString -> Int)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (ByteString -> Int)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> Int)
-> (cost -> FoldArgs (GetArgs (ByteString -> Int)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> Int
lengthOfByteStringDenotation
            (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramLengthOfByteString)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
IndexByteString =
        let indexByteStringDenotation :: BS.ByteString -> Int -> BuiltinResult Word8
            indexByteStringDenotation :: ByteString -> Int -> BuiltinResult Word8
indexByteStringDenotation ByteString
xs Int
n = do
                Bool -> BuiltinResult () -> BuiltinResult ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> Bool -> Bool
&& Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< ByteString -> Int
BS.length ByteString
xs) (BuiltinResult () -> BuiltinResult ())
-> BuiltinResult () -> BuiltinResult ()
forall a b. (a -> b) -> a -> b
$
                    -- See Note [Operational vs structural errors within builtins].
                    -- The arguments are going to be printed in the "cause" part of the error
                    -- message, so we don't need to repeat them here.
                    String -> BuiltinResult ()
forall a. String -> BuiltinResult a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Index out of bounds"
                Word8 -> BuiltinResult Word8
forall a. a -> BuiltinResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Word8 -> BuiltinResult Word8) -> Word8 -> BuiltinResult Word8
forall a b. (a -> b) -> a -> b
$ HasCallStack => ByteString -> Int -> Word8
ByteString -> Int -> Word8
BS.index ByteString
xs Int
n
            {-# INLINE indexByteStringDenotation #-}
        in (ByteString -> Int -> BuiltinResult Word8)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (ByteString -> Int -> BuiltinResult Word8))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> Int -> BuiltinResult Word8)
-> (cost
    -> FoldArgs
         (GetArgs (ByteString -> Int -> BuiltinResult Word8))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> Int -> BuiltinResult Word8
indexByteStringDenotation
            (CostingFun ModelTwoArguments -> ByteString -> Int -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> ByteString -> Int -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> ByteString
-> Int
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramIndexByteString)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
EqualsByteString =
        let equalsByteStringDenotation :: BS.ByteString -> BS.ByteString -> Bool
            equalsByteStringDenotation :: ByteString -> ByteString -> Bool
equalsByteStringDenotation = ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
(==)
            {-# INLINE equalsByteStringDenotation #-}
        in (ByteString -> ByteString -> Bool)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (ByteString -> ByteString -> Bool)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> ByteString -> Bool)
-> (cost
    -> FoldArgs
         (GetArgs (ByteString -> ByteString -> Bool)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> ByteString -> Bool
equalsByteStringDenotation
            (CostingFun ModelTwoArguments
-> ByteString -> ByteString -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> ByteString -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> ByteString
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramEqualsByteString)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
LessThanByteString =
        let lessThanByteStringDenotation :: BS.ByteString -> BS.ByteString -> Bool
            lessThanByteStringDenotation :: ByteString -> ByteString -> Bool
lessThanByteStringDenotation = ByteString -> ByteString -> Bool
forall a. Ord a => a -> a -> Bool
(<)
            {-# INLINE lessThanByteStringDenotation #-}
        in (ByteString -> ByteString -> Bool)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (ByteString -> ByteString -> Bool)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> ByteString -> Bool)
-> (cost
    -> FoldArgs
         (GetArgs (ByteString -> ByteString -> Bool)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> ByteString -> Bool
lessThanByteStringDenotation
            (CostingFun ModelTwoArguments
-> ByteString -> ByteString -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> ByteString -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> ByteString
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramLessThanByteString)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
LessThanEqualsByteString =
        let lessThanEqualsByteStringDenotation :: BS.ByteString -> BS.ByteString -> Bool
            lessThanEqualsByteStringDenotation :: ByteString -> ByteString -> Bool
lessThanEqualsByteStringDenotation = ByteString -> ByteString -> Bool
forall a. Ord a => a -> a -> Bool
(<=)
            {-# INLINE lessThanEqualsByteStringDenotation #-}
        in (ByteString -> ByteString -> Bool)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (ByteString -> ByteString -> Bool)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> ByteString -> Bool)
-> (cost
    -> FoldArgs
         (GetArgs (ByteString -> ByteString -> Bool)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> ByteString -> Bool
lessThanEqualsByteStringDenotation
            (CostingFun ModelTwoArguments
-> ByteString -> ByteString -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> ByteString -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> ByteString
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramLessThanEqualsByteString)

    -- Cryptography and hashes
    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Sha2_256 =
        let sha2_256Denotation :: BS.ByteString -> BS.ByteString
            sha2_256Denotation :: ByteString -> ByteString
sha2_256Denotation = ByteString -> ByteString
Hash.sha2_256
            {-# INLINE sha2_256Denotation #-}
        in (ByteString -> ByteString)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (ByteString -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> ByteString)
-> (cost
    -> FoldArgs (GetArgs (ByteString -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> ByteString
sha2_256Denotation
            (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramSha2_256)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Sha3_256 =
        let sha3_256Denotation :: BS.ByteString -> BS.ByteString
            sha3_256Denotation :: ByteString -> ByteString
sha3_256Denotation = ByteString -> ByteString
Hash.sha3_256
            {-# INLINE sha3_256Denotation #-}
        in (ByteString -> ByteString)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (ByteString -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> ByteString)
-> (cost
    -> FoldArgs (GetArgs (ByteString -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> ByteString
sha3_256Denotation
            (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramSha3_256)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Blake2b_256 =
        let blake2b_256Denotation :: BS.ByteString -> BS.ByteString
            blake2b_256Denotation :: ByteString -> ByteString
blake2b_256Denotation = ByteString -> ByteString
Hash.blake2b_256
            {-# INLINE blake2b_256Denotation #-}
        in (ByteString -> ByteString)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (ByteString -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> ByteString)
-> (cost
    -> FoldArgs (GetArgs (ByteString -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> ByteString
blake2b_256Denotation
            (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramBlake2b_256)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
semvar DefaultFun
VerifyEd25519Signature =
        let verifyEd25519SignatureDenotation
                :: BS.ByteString -> BS.ByteString -> BS.ByteString -> BuiltinResult Bool
            verifyEd25519SignatureDenotation :: ByteString -> ByteString -> ByteString -> BuiltinResult Bool
verifyEd25519SignatureDenotation =
                case BuiltinSemanticsVariant DefaultFun
semvar of
                  BuiltinSemanticsVariant DefaultFun
R:BuiltinSemanticsVariantDefaultFun
DefaultFunSemanticsVariantA -> ByteString -> ByteString -> ByteString -> BuiltinResult Bool
verifyEd25519Signature_V1
                  BuiltinSemanticsVariant DefaultFun
R:BuiltinSemanticsVariantDefaultFun
DefaultFunSemanticsVariantB -> ByteString -> ByteString -> ByteString -> BuiltinResult Bool
verifyEd25519Signature_V2
                  BuiltinSemanticsVariant DefaultFun
R:BuiltinSemanticsVariantDefaultFun
DefaultFunSemanticsVariantC -> ByteString -> ByteString -> ByteString -> BuiltinResult Bool
verifyEd25519Signature_V2
            {-# INLINE verifyEd25519SignatureDenotation #-}
        in (ByteString -> ByteString -> ByteString -> BuiltinResult Bool)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs
            (ByteString -> ByteString -> ByteString -> BuiltinResult Bool))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> ByteString -> ByteString -> BuiltinResult Bool)
-> (cost
    -> FoldArgs
         (GetArgs
            (ByteString -> ByteString -> ByteString -> BuiltinResult Bool))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> ByteString -> ByteString -> BuiltinResult Bool
verifyEd25519SignatureDenotation
            -- Benchmarks indicate that the two variants have very similar
            -- execution times, so it's safe to use the same costing function for
            -- both.
            (CostingFun ModelThreeArguments
-> ByteString -> ByteString -> ByteString -> ExBudgetStream
forall a1 a2 a3.
(ExMemoryUsage a1, ExMemoryUsage a2, ExMemoryUsage a3) =>
CostingFun ModelThreeArguments -> a1 -> a2 -> a3 -> ExBudgetStream
runCostingFunThreeArguments (CostingFun ModelThreeArguments
 -> ByteString -> ByteString -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelThreeArguments)
-> BuiltinCostModel
-> ByteString
-> ByteString
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelThreeArguments
forall (f :: * -> *).
BuiltinCostModelBase f -> f ModelThreeArguments
paramVerifyEd25519Signature)

    {- Note [ECDSA secp256k1 signature verification].  An ECDSA signature
       consists of a pair of values (r,s), and for each value of r there are in
       fact two valid values of s, one effectively the negative of the other.
       The Bitcoin implementation that underlies `verifyEcdsaSecp256k1Signature`
       expects that the lower of the two possible values of the s component of
       the signature is used, returning `false` immediately if that's not the
       case.  It appears that this restriction is peculiar to Bitcoin, and ECDSA
       schemes in general don't require it.  Thus this function may be more
       restrictive than expected.  See

          https://github.com/bitcoin/bips/blob/master/bip-0146.mediawiki#LOW_S

       and the implementation of secp256k1_ecdsa_verify in

          https://github.com/bitcoin-core/secp256k1.
     -}
    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
VerifyEcdsaSecp256k1Signature =
        let verifyEcdsaSecp256k1SignatureDenotation
                :: BS.ByteString -> BS.ByteString -> BS.ByteString -> BuiltinResult Bool
            verifyEcdsaSecp256k1SignatureDenotation :: ByteString -> ByteString -> ByteString -> BuiltinResult Bool
verifyEcdsaSecp256k1SignatureDenotation = ByteString -> ByteString -> ByteString -> BuiltinResult Bool
verifyEcdsaSecp256k1Signature
            {-# INLINE verifyEcdsaSecp256k1SignatureDenotation #-}
        in (ByteString -> ByteString -> ByteString -> BuiltinResult Bool)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs
            (ByteString -> ByteString -> ByteString -> BuiltinResult Bool))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> ByteString -> ByteString -> BuiltinResult Bool)
-> (cost
    -> FoldArgs
         (GetArgs
            (ByteString -> ByteString -> ByteString -> BuiltinResult Bool))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> ByteString -> ByteString -> BuiltinResult Bool
verifyEcdsaSecp256k1SignatureDenotation
            (CostingFun ModelThreeArguments
-> ByteString -> ByteString -> ByteString -> ExBudgetStream
forall a1 a2 a3.
(ExMemoryUsage a1, ExMemoryUsage a2, ExMemoryUsage a3) =>
CostingFun ModelThreeArguments -> a1 -> a2 -> a3 -> ExBudgetStream
runCostingFunThreeArguments (CostingFun ModelThreeArguments
 -> ByteString -> ByteString -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelThreeArguments)
-> BuiltinCostModel
-> ByteString
-> ByteString
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelThreeArguments
forall (f :: * -> *).
BuiltinCostModelBase f -> f ModelThreeArguments
paramVerifyEcdsaSecp256k1Signature)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
VerifySchnorrSecp256k1Signature =
        let verifySchnorrSecp256k1SignatureDenotation
                :: BS.ByteString -> BS.ByteString -> BS.ByteString -> BuiltinResult Bool
            verifySchnorrSecp256k1SignatureDenotation :: ByteString -> ByteString -> ByteString -> BuiltinResult Bool
verifySchnorrSecp256k1SignatureDenotation = ByteString -> ByteString -> ByteString -> BuiltinResult Bool
verifySchnorrSecp256k1Signature
            {-# INLINE verifySchnorrSecp256k1SignatureDenotation #-}
        in (ByteString -> ByteString -> ByteString -> BuiltinResult Bool)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs
            (ByteString -> ByteString -> ByteString -> BuiltinResult Bool))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> ByteString -> ByteString -> BuiltinResult Bool)
-> (cost
    -> FoldArgs
         (GetArgs
            (ByteString -> ByteString -> ByteString -> BuiltinResult Bool))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> ByteString -> ByteString -> BuiltinResult Bool
verifySchnorrSecp256k1SignatureDenotation
            (CostingFun ModelThreeArguments
-> ByteString -> ByteString -> ByteString -> ExBudgetStream
forall a1 a2 a3.
(ExMemoryUsage a1, ExMemoryUsage a2, ExMemoryUsage a3) =>
CostingFun ModelThreeArguments -> a1 -> a2 -> a3 -> ExBudgetStream
runCostingFunThreeArguments (CostingFun ModelThreeArguments
 -> ByteString -> ByteString -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelThreeArguments)
-> BuiltinCostModel
-> ByteString
-> ByteString
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelThreeArguments
forall (f :: * -> *).
BuiltinCostModelBase f -> f ModelThreeArguments
paramVerifySchnorrSecp256k1Signature)

    -- Strings
    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
AppendString =
        let appendStringDenotation :: Text -> Text -> Text
            appendStringDenotation :: Text -> Text -> Text
appendStringDenotation = Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
(<>)
            {-# INLINE appendStringDenotation #-}
        in (Text -> Text -> Text)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (Text -> Text -> Text)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Text -> Text -> Text)
-> (cost
    -> FoldArgs (GetArgs (Text -> Text -> Text)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Text -> Text -> Text
appendStringDenotation
            (CostingFun ModelTwoArguments -> Text -> Text -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments -> Text -> Text -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Text
-> Text
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramAppendString)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
EqualsString =
        let equalsStringDenotation :: Text -> Text -> Bool
            equalsStringDenotation :: Text -> Text -> Bool
equalsStringDenotation = Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
(==)
            {-# INLINE equalsStringDenotation #-}
        in (Text -> Text -> Bool)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (Text -> Text -> Bool)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Text -> Text -> Bool)
-> (cost
    -> FoldArgs (GetArgs (Text -> Text -> Bool)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Text -> Text -> Bool
equalsStringDenotation
            (CostingFun ModelTwoArguments -> Text -> Text -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments -> Text -> Text -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Text
-> Text
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramEqualsString)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
EncodeUtf8 =
        let encodeUtf8Denotation :: Text -> BS.ByteString
            encodeUtf8Denotation :: Text -> ByteString
encodeUtf8Denotation = Text -> ByteString
encodeUtf8
            {-# INLINE encodeUtf8Denotation #-}
        in (Text -> ByteString)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (Text -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Text -> ByteString)
-> (cost -> FoldArgs (GetArgs (Text -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Text -> ByteString
encodeUtf8Denotation
            (CostingFun ModelOneArgument -> Text -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> Text -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> Text
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramEncodeUtf8)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
DecodeUtf8 =
        let decodeUtf8Denotation :: BS.ByteString -> BuiltinResult Text
            decodeUtf8Denotation :: ByteString -> BuiltinResult Text
decodeUtf8Denotation = Either UnicodeException Text -> BuiltinResult Text
forall e r. Show e => Either e r -> BuiltinResult r
eitherToBuiltinResult (Either UnicodeException Text -> BuiltinResult Text)
-> (ByteString -> Either UnicodeException Text)
-> ByteString
-> BuiltinResult Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either UnicodeException Text
decodeUtf8'
            {-# INLINE decodeUtf8Denotation #-}
        in (ByteString -> BuiltinResult Text)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (ByteString -> BuiltinResult Text)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> BuiltinResult Text)
-> (cost
    -> FoldArgs
         (GetArgs (ByteString -> BuiltinResult Text)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> BuiltinResult Text
decodeUtf8Denotation
            (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramDecodeUtf8)

    -- Bool
    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
IfThenElse =
        let ifThenElseDenotation :: Bool -> a -> a -> a
            ifThenElseDenotation :: forall a. Bool -> a -> a -> a
ifThenElseDenotation Bool
b a
x a
y = if Bool
b then a
x else a
y
            {-# INLINE ifThenElseDenotation #-}
        in (Bool
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> Opaque val (TyVarRep ('TyNameRep "a" 0)))
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs
            (Bool
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Bool
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> Opaque val (TyVarRep ('TyNameRep "a" 0)))
-> (cost
    -> FoldArgs
         (GetArgs
            (Bool
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Bool
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
forall a. Bool -> a -> a -> a
ifThenElseDenotation
            (CostingFun ModelThreeArguments
-> Bool
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> ExBudgetStream
forall a1 a2 a3.
(ExMemoryUsage a1, ExMemoryUsage a2, ExMemoryUsage a3) =>
CostingFun ModelThreeArguments -> a1 -> a2 -> a3 -> ExBudgetStream
runCostingFunThreeArguments (CostingFun ModelThreeArguments
 -> Bool
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelThreeArguments)
-> BuiltinCostModel
-> Bool
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelThreeArguments
forall (f :: * -> *).
BuiltinCostModelBase f -> f ModelThreeArguments
paramIfThenElse)

    -- Unit
    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
ChooseUnit =
        let chooseUnitDenotation :: () -> a -> a
            chooseUnitDenotation :: forall a. () -> a -> a
chooseUnitDenotation () a
x = a
x
            {-# INLINE chooseUnitDenotation #-}
        in (()
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> Opaque val (TyVarRep ('TyNameRep "a" 0)))
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs
            (()
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(()
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> Opaque val (TyVarRep ('TyNameRep "a" 0)))
-> (cost
    -> FoldArgs
         (GetArgs
            (()
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ()
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
forall a. () -> a -> a
chooseUnitDenotation
            (CostingFun ModelTwoArguments
-> () -> Opaque val (TyVarRep ('TyNameRep "a" 0)) -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> ()
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> ()
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramChooseUnit)

    -- Tracing
    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Trace =
        let traceDenotation :: Text -> a -> BuiltinResult a
            traceDenotation :: forall a. Text -> a -> BuiltinResult a
traceDenotation Text
text a
a = a
a a -> BuiltinResult () -> BuiltinResult a
forall a b. a -> BuiltinResult b -> BuiltinResult a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> BuiltinResult ()
emit Text
text
            {-# INLINE traceDenotation #-}
        in (Text
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "a" 0))))
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs
            (Text
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))
             -> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "a" 0)))))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Text
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "a" 0))))
-> (cost
    -> FoldArgs
         (GetArgs
            (Text
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))
             -> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "a" 0)))))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Text
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "a" 0)))
forall a. Text -> a -> BuiltinResult a
traceDenotation
            (CostingFun ModelTwoArguments
-> Text
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> Text
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Text
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramTrace)

    -- Pairs
    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
FstPair =
        let fstPairDenotation :: SomeConstant uni (a, b) -> BuiltinResult (Opaque val a)
            fstPairDenotation :: forall a b. SomeConstant uni (a, b) -> BuiltinResult (Opaque val a)
fstPairDenotation (SomeConstant (Some (ValueOf uni (Esc a)
uniPairAB a
xy))) = do
                case uni (Esc a)
uniPairAB of
                    DefaultUniPair DefaultUni (Esc a2)
uniA DefaultUni (Esc a1)
_ -> Opaque val a -> BuiltinResult (Opaque val a)
forall a. a -> BuiltinResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Opaque val a -> BuiltinResult (Opaque val a))
-> (a2 -> Opaque val a) -> a2 -> BuiltinResult (Opaque val a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UniOf (Opaque val a) (Esc a2) -> a2 -> Opaque val a
forall a term. HasConstant term => UniOf term (Esc a) -> a -> term
fromValueOf UniOf (Opaque val a) (Esc a2)
DefaultUni (Esc a2)
uniA (a2 -> BuiltinResult (Opaque val a))
-> a2 -> BuiltinResult (Opaque val a)
forall a b. (a -> b) -> a -> b
$ (a2, a1) -> a2
forall a b. (a, b) -> a
fst a
(a2, a1)
xy
                    uni (Esc a)
_                     ->
                        -- See Note [Operational vs structural errors within builtins].
                        AReview BuiltinError UnliftingError
-> UnliftingError -> BuiltinResult (Opaque val a)
forall e (m :: * -> *) t x.
MonadError e m =>
AReview e t -> t -> m x
throwing AReview BuiltinError UnliftingError
forall err. AsBuiltinError err => Prism' err UnliftingError
Prism' BuiltinError UnliftingError
_StructuralUnliftingError UnliftingError
"Expected a pair but got something else"
            {-# INLINE fstPairDenotation #-}
        in (SomeConstant
   uni (TyVarRep ('TyNameRep "a" 0), TyVarRep ('TyNameRep "b" 1))
 -> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "a" 0))))
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs
            (SomeConstant
               uni (TyVarRep ('TyNameRep "a" 0), TyVarRep ('TyNameRep "b" 1))
             -> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "a" 0)))))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(SomeConstant
   uni (TyVarRep ('TyNameRep "a" 0), TyVarRep ('TyNameRep "b" 1))
 -> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "a" 0))))
-> (cost
    -> FoldArgs
         (GetArgs
            (SomeConstant
               uni (TyVarRep ('TyNameRep "a" 0), TyVarRep ('TyNameRep "b" 1))
             -> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "a" 0)))))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            SomeConstant
  uni (TyVarRep ('TyNameRep "a" 0), TyVarRep ('TyNameRep "b" 1))
-> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "a" 0)))
forall a b. SomeConstant uni (a, b) -> BuiltinResult (Opaque val a)
fstPairDenotation
            (CostingFun ModelOneArgument
-> SomeConstant
     DefaultUni
     (TyVarRep ('TyNameRep "a" 0), TyVarRep ('TyNameRep "b" 1))
-> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument
 -> SomeConstant
      DefaultUni
      (TyVarRep ('TyNameRep "a" 0), TyVarRep ('TyNameRep "b" 1))
 -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> SomeConstant
     DefaultUni
     (TyVarRep ('TyNameRep "a" 0), TyVarRep ('TyNameRep "b" 1))
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramFstPair)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
SndPair =
        let sndPairDenotation :: SomeConstant uni (a, b) -> BuiltinResult (Opaque val b)
            sndPairDenotation :: forall a b. SomeConstant uni (a, b) -> BuiltinResult (Opaque val b)
sndPairDenotation (SomeConstant (Some (ValueOf uni (Esc a)
uniPairAB a
xy))) = do
                case uni (Esc a)
uniPairAB of
                    DefaultUniPair DefaultUni (Esc a2)
_ DefaultUni (Esc a1)
uniB -> Opaque val b -> BuiltinResult (Opaque val b)
forall a. a -> BuiltinResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Opaque val b -> BuiltinResult (Opaque val b))
-> (a1 -> Opaque val b) -> a1 -> BuiltinResult (Opaque val b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UniOf (Opaque val b) (Esc a1) -> a1 -> Opaque val b
forall a term. HasConstant term => UniOf term (Esc a) -> a -> term
fromValueOf UniOf (Opaque val b) (Esc a1)
DefaultUni (Esc a1)
uniB (a1 -> BuiltinResult (Opaque val b))
-> a1 -> BuiltinResult (Opaque val b)
forall a b. (a -> b) -> a -> b
$ (a2, a1) -> a1
forall a b. (a, b) -> b
snd a
(a2, a1)
xy
                    uni (Esc a)
_                     ->
                        -- See Note [Operational vs structural errors within builtins].
                        AReview BuiltinError UnliftingError
-> UnliftingError -> BuiltinResult (Opaque val b)
forall e (m :: * -> *) t x.
MonadError e m =>
AReview e t -> t -> m x
throwing AReview BuiltinError UnliftingError
forall err. AsBuiltinError err => Prism' err UnliftingError
Prism' BuiltinError UnliftingError
_StructuralUnliftingError UnliftingError
"Expected a pair but got something else"
            {-# INLINE sndPairDenotation #-}
        in (SomeConstant
   uni (TyVarRep ('TyNameRep "a" 0), TyVarRep ('TyNameRep "b" 1))
 -> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "b" 1))))
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs
            (SomeConstant
               uni (TyVarRep ('TyNameRep "a" 0), TyVarRep ('TyNameRep "b" 1))
             -> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "b" 1)))))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(SomeConstant
   uni (TyVarRep ('TyNameRep "a" 0), TyVarRep ('TyNameRep "b" 1))
 -> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "b" 1))))
-> (cost
    -> FoldArgs
         (GetArgs
            (SomeConstant
               uni (TyVarRep ('TyNameRep "a" 0), TyVarRep ('TyNameRep "b" 1))
             -> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "b" 1)))))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            SomeConstant
  uni (TyVarRep ('TyNameRep "a" 0), TyVarRep ('TyNameRep "b" 1))
-> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "b" 1)))
forall a b. SomeConstant uni (a, b) -> BuiltinResult (Opaque val b)
sndPairDenotation
            (CostingFun ModelOneArgument
-> SomeConstant
     DefaultUni
     (TyVarRep ('TyNameRep "a" 0), TyVarRep ('TyNameRep "b" 1))
-> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument
 -> SomeConstant
      DefaultUni
      (TyVarRep ('TyNameRep "a" 0), TyVarRep ('TyNameRep "b" 1))
 -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> SomeConstant
     DefaultUni
     (TyVarRep ('TyNameRep "a" 0), TyVarRep ('TyNameRep "b" 1))
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramSndPair)

    -- Lists
    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
ChooseList =
        let chooseListDenotation :: SomeConstant uni [a] -> b -> b -> BuiltinResult b
            chooseListDenotation :: forall a b. SomeConstant uni [a] -> b -> b -> BuiltinResult b
chooseListDenotation (SomeConstant (Some (ValueOf uni (Esc a)
uniListA a
xs))) b
a b
b = do
                case uni (Esc a)
uniListA of
                    DefaultUniList DefaultUni (Esc a1)
_ -> b -> BuiltinResult b
forall a. a -> BuiltinResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (b -> BuiltinResult b) -> b -> BuiltinResult b
forall a b. (a -> b) -> a -> b
$ case a
xs of
                        []    -> b
a
                        a1
_ : [a1]
_ -> b
b
                    -- See Note [Operational vs structural errors within builtins].
                    uni (Esc a)
_ -> AReview BuiltinError UnliftingError
-> UnliftingError -> BuiltinResult b
forall e (m :: * -> *) t x.
MonadError e m =>
AReview e t -> t -> m x
throwing AReview BuiltinError UnliftingError
forall err. AsBuiltinError err => Prism' err UnliftingError
Prism' BuiltinError UnliftingError
_StructuralUnliftingError UnliftingError
"Expected a list but got something else"
            {-# INLINE chooseListDenotation #-}
        in (SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
 -> Opaque val (TyVarRep ('TyNameRep "b" 1))
 -> Opaque val (TyVarRep ('TyNameRep "b" 1))
 -> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "b" 1))))
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs
            (SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
             -> Opaque val (TyVarRep ('TyNameRep "b" 1))
             -> Opaque val (TyVarRep ('TyNameRep "b" 1))
             -> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "b" 1)))))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
 -> Opaque val (TyVarRep ('TyNameRep "b" 1))
 -> Opaque val (TyVarRep ('TyNameRep "b" 1))
 -> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "b" 1))))
-> (cost
    -> FoldArgs
         (GetArgs
            (SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
             -> Opaque val (TyVarRep ('TyNameRep "b" 1))
             -> Opaque val (TyVarRep ('TyNameRep "b" 1))
             -> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "b" 1)))))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
-> Opaque val (TyVarRep ('TyNameRep "b" 1))
-> Opaque val (TyVarRep ('TyNameRep "b" 1))
-> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "b" 1)))
forall a b. SomeConstant uni [a] -> b -> b -> BuiltinResult b
chooseListDenotation
            (CostingFun ModelThreeArguments
-> SomeConstant DefaultUni [TyVarRep ('TyNameRep "a" 0)]
-> Opaque val (TyVarRep ('TyNameRep "b" 1))
-> Opaque val (TyVarRep ('TyNameRep "b" 1))
-> ExBudgetStream
forall a1 a2 a3.
(ExMemoryUsage a1, ExMemoryUsage a2, ExMemoryUsage a3) =>
CostingFun ModelThreeArguments -> a1 -> a2 -> a3 -> ExBudgetStream
runCostingFunThreeArguments (CostingFun ModelThreeArguments
 -> SomeConstant DefaultUni [TyVarRep ('TyNameRep "a" 0)]
 -> Opaque val (TyVarRep ('TyNameRep "b" 1))
 -> Opaque val (TyVarRep ('TyNameRep "b" 1))
 -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelThreeArguments)
-> BuiltinCostModel
-> SomeConstant DefaultUni [TyVarRep ('TyNameRep "a" 0)]
-> Opaque val (TyVarRep ('TyNameRep "b" 1))
-> Opaque val (TyVarRep ('TyNameRep "b" 1))
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelThreeArguments
forall (f :: * -> *).
BuiltinCostModelBase f -> f ModelThreeArguments
paramChooseList)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
MkCons =
        let mkConsDenotation
                :: SomeConstant uni a -> SomeConstant uni [a] -> BuiltinResult (Opaque val [a])
            mkConsDenotation :: forall a.
SomeConstant uni a
-> SomeConstant uni [a] -> BuiltinResult (Opaque val [a])
mkConsDenotation
              (SomeConstant (Some (ValueOf uni (Esc a)
uniA a
x)))
              (SomeConstant (Some (ValueOf uni (Esc a)
uniListA a
xs))) = do
                -- See Note [Operational vs structural errors within builtins].
                case uni (Esc a)
uniListA of
                    DefaultUniList DefaultUni (Esc a1)
uniA' -> case uni (Esc a)
uniA uni (Esc a) -> uni (Esc a1) -> Maybe (Esc a :~: Esc a1)
forall a b. uni a -> uni b -> Maybe (a :~: b)
forall k (f :: k -> *) (a :: k) (b :: k).
GEq f =>
f a -> f b -> Maybe (a :~: b)
`geq` uni (Esc a1)
DefaultUni (Esc a1)
uniA' of
                        Just Esc a :~: Esc a1
Refl -> Opaque val [a] -> BuiltinResult (Opaque val [a])
forall a. a -> BuiltinResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Opaque val [a] -> BuiltinResult (Opaque val [a]))
-> ([a] -> Opaque val [a]) -> [a] -> BuiltinResult (Opaque val [a])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UniOf (Opaque val [a]) (Esc [a]) -> [a] -> Opaque val [a]
forall a term. HasConstant term => UniOf term (Esc a) -> a -> term
fromValueOf uni (Esc a)
UniOf (Opaque val [a]) (Esc [a])
uniListA ([a] -> BuiltinResult (Opaque val [a]))
-> [a] -> BuiltinResult (Opaque val [a])
forall a b. (a -> b) -> a -> b
$ a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: a
[a]
xs
                        Maybe (Esc a :~: Esc a1)
_         -> AReview BuiltinError UnliftingError
-> UnliftingError -> BuiltinResult (Opaque val [a])
forall e (m :: * -> *) t x.
MonadError e m =>
AReview e t -> t -> m x
throwing AReview BuiltinError UnliftingError
forall err. AsBuiltinError err => Prism' err UnliftingError
Prism' BuiltinError UnliftingError
_StructuralUnliftingError
                            UnliftingError
"The type of the value does not match the type of elements in the list"
                    uni (Esc a)
_ -> AReview BuiltinError UnliftingError
-> UnliftingError -> BuiltinResult (Opaque val [a])
forall e (m :: * -> *) t x.
MonadError e m =>
AReview e t -> t -> m x
throwing AReview BuiltinError UnliftingError
forall err. AsBuiltinError err => Prism' err UnliftingError
Prism' BuiltinError UnliftingError
_StructuralUnliftingError UnliftingError
"Expected a list but got something else"
            {-# INLINE mkConsDenotation #-}
        in (SomeConstant uni (TyVarRep ('TyNameRep "a" 0))
 -> SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
 -> BuiltinResult (Opaque val [TyVarRep ('TyNameRep "a" 0)]))
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs
            (SomeConstant uni (TyVarRep ('TyNameRep "a" 0))
             -> SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
             -> BuiltinResult (Opaque val [TyVarRep ('TyNameRep "a" 0)])))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(SomeConstant uni (TyVarRep ('TyNameRep "a" 0))
 -> SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
 -> BuiltinResult (Opaque val [TyVarRep ('TyNameRep "a" 0)]))
-> (cost
    -> FoldArgs
         (GetArgs
            (SomeConstant uni (TyVarRep ('TyNameRep "a" 0))
             -> SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
             -> BuiltinResult (Opaque val [TyVarRep ('TyNameRep "a" 0)])))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            SomeConstant uni (TyVarRep ('TyNameRep "a" 0))
-> SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
-> BuiltinResult (Opaque val [TyVarRep ('TyNameRep "a" 0)])
forall a.
SomeConstant uni a
-> SomeConstant uni [a] -> BuiltinResult (Opaque val [a])
mkConsDenotation
            (CostingFun ModelTwoArguments
-> SomeConstant DefaultUni (TyVarRep ('TyNameRep "a" 0))
-> SomeConstant DefaultUni [TyVarRep ('TyNameRep "a" 0)]
-> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> SomeConstant DefaultUni (TyVarRep ('TyNameRep "a" 0))
 -> SomeConstant DefaultUni [TyVarRep ('TyNameRep "a" 0)]
 -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> SomeConstant DefaultUni (TyVarRep ('TyNameRep "a" 0))
-> SomeConstant DefaultUni [TyVarRep ('TyNameRep "a" 0)]
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramMkCons)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
HeadList =
        let headListDenotation :: SomeConstant uni [a] -> BuiltinResult (Opaque val a)
            headListDenotation :: forall a. SomeConstant uni [a] -> BuiltinResult (Opaque val a)
headListDenotation (SomeConstant (Some (ValueOf uni (Esc a)
uniListA a
xs))) = do
                -- See Note [Operational vs structural errors within builtins].
                case uni (Esc a)
uniListA of
                    DefaultUniList DefaultUni (Esc a1)
uniA -> case a
xs of
                        []    -> String -> BuiltinResult (Opaque val a)
forall a. String -> BuiltinResult a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Expected a non-empty list but got an empty one"
                        a1
x : [a1]
_ -> Opaque val a -> BuiltinResult (Opaque val a)
forall a. a -> BuiltinResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Opaque val a -> BuiltinResult (Opaque val a))
-> Opaque val a -> BuiltinResult (Opaque val a)
forall a b. (a -> b) -> a -> b
$ UniOf (Opaque val a) (Esc a1) -> a1 -> Opaque val a
forall a term. HasConstant term => UniOf term (Esc a) -> a -> term
fromValueOf UniOf (Opaque val a) (Esc a1)
DefaultUni (Esc a1)
uniA a1
x
                    uni (Esc a)
_ -> AReview BuiltinError UnliftingError
-> UnliftingError -> BuiltinResult (Opaque val a)
forall e (m :: * -> *) t x.
MonadError e m =>
AReview e t -> t -> m x
throwing AReview BuiltinError UnliftingError
forall err. AsBuiltinError err => Prism' err UnliftingError
Prism' BuiltinError UnliftingError
_StructuralUnliftingError UnliftingError
"Expected a list but got something else"
            {-# INLINE headListDenotation #-}
        in (SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
 -> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "a" 0))))
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs
            (SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
             -> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "a" 0)))))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
 -> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "a" 0))))
-> (cost
    -> FoldArgs
         (GetArgs
            (SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
             -> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "a" 0)))))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
-> BuiltinResult (Opaque val (TyVarRep ('TyNameRep "a" 0)))
forall a. SomeConstant uni [a] -> BuiltinResult (Opaque val a)
headListDenotation
            (CostingFun ModelOneArgument
-> SomeConstant DefaultUni [TyVarRep ('TyNameRep "a" 0)]
-> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument
 -> SomeConstant DefaultUni [TyVarRep ('TyNameRep "a" 0)]
 -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> SomeConstant DefaultUni [TyVarRep ('TyNameRep "a" 0)]
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramHeadList)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
TailList =
        let tailListDenotation :: SomeConstant uni [a] -> BuiltinResult (Opaque val [a])
            tailListDenotation :: forall a. SomeConstant uni [a] -> BuiltinResult (Opaque val [a])
tailListDenotation (SomeConstant (Some (ValueOf uni (Esc a)
uniListA a
xs))) = do
                -- See Note [Operational vs structural errors within builtins].
                case uni (Esc a)
uniListA of
                    DefaultUniList DefaultUni (Esc a1)
_ -> case a
xs of
                        []      -> String -> BuiltinResult (Opaque val [a])
forall a. String -> BuiltinResult a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Expected a non-empty list but got an empty one"
                        a1
_ : [a1]
xs' -> Opaque val [a] -> BuiltinResult (Opaque val [a])
forall a. a -> BuiltinResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Opaque val [a] -> BuiltinResult (Opaque val [a]))
-> Opaque val [a] -> BuiltinResult (Opaque val [a])
forall a b. (a -> b) -> a -> b
$ UniOf (Opaque val [a]) (Esc [a1]) -> [a1] -> Opaque val [a]
forall a term. HasConstant term => UniOf term (Esc a) -> a -> term
fromValueOf uni (Esc a)
UniOf (Opaque val [a]) (Esc [a1])
uniListA [a1]
xs'
                    uni (Esc a)
_ -> AReview BuiltinError UnliftingError
-> UnliftingError -> BuiltinResult (Opaque val [a])
forall e (m :: * -> *) t x.
MonadError e m =>
AReview e t -> t -> m x
throwing AReview BuiltinError UnliftingError
forall err. AsBuiltinError err => Prism' err UnliftingError
Prism' BuiltinError UnliftingError
_StructuralUnliftingError UnliftingError
"Expected a list but got something else"
            {-# INLINE tailListDenotation #-}
        in (SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
 -> BuiltinResult (Opaque val [TyVarRep ('TyNameRep "a" 0)]))
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs
            (SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
             -> BuiltinResult (Opaque val [TyVarRep ('TyNameRep "a" 0)])))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
 -> BuiltinResult (Opaque val [TyVarRep ('TyNameRep "a" 0)]))
-> (cost
    -> FoldArgs
         (GetArgs
            (SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
             -> BuiltinResult (Opaque val [TyVarRep ('TyNameRep "a" 0)])))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
-> BuiltinResult (Opaque val [TyVarRep ('TyNameRep "a" 0)])
forall a. SomeConstant uni [a] -> BuiltinResult (Opaque val [a])
tailListDenotation
            (CostingFun ModelOneArgument
-> SomeConstant DefaultUni [TyVarRep ('TyNameRep "a" 0)]
-> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument
 -> SomeConstant DefaultUni [TyVarRep ('TyNameRep "a" 0)]
 -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> SomeConstant DefaultUni [TyVarRep ('TyNameRep "a" 0)]
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramTailList)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
NullList =
        let nullListDenotation :: SomeConstant uni [a] -> BuiltinResult Bool
            nullListDenotation :: forall a. SomeConstant uni [a] -> BuiltinResult Bool
nullListDenotation (SomeConstant (Some (ValueOf uni (Esc a)
uniListA a
xs))) = do
                case uni (Esc a)
uniListA of
                    DefaultUniList DefaultUni (Esc a1)
_ -> Bool -> BuiltinResult Bool
forall a. a -> BuiltinResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> BuiltinResult Bool) -> Bool -> BuiltinResult Bool
forall a b. (a -> b) -> a -> b
$ [a1] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null a
[a1]
xs
                    uni (Esc a)
_                ->
                        -- See Note [Operational vs structural errors within builtins].
                        AReview BuiltinError UnliftingError
-> UnliftingError -> BuiltinResult Bool
forall e (m :: * -> *) t x.
MonadError e m =>
AReview e t -> t -> m x
throwing AReview BuiltinError UnliftingError
forall err. AsBuiltinError err => Prism' err UnliftingError
Prism' BuiltinError UnliftingError
_StructuralUnliftingError UnliftingError
"Expected a list but got something else"
            {-# INLINE nullListDenotation #-}
        in (SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
 -> BuiltinResult Bool)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs
            (SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
             -> BuiltinResult Bool))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
 -> BuiltinResult Bool)
-> (cost
    -> FoldArgs
         (GetArgs
            (SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
             -> BuiltinResult Bool))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            SomeConstant uni [TyVarRep ('TyNameRep "a" 0)]
-> BuiltinResult Bool
forall a. SomeConstant uni [a] -> BuiltinResult Bool
nullListDenotation
            (CostingFun ModelOneArgument
-> SomeConstant DefaultUni [TyVarRep ('TyNameRep "a" 0)]
-> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument
 -> SomeConstant DefaultUni [TyVarRep ('TyNameRep "a" 0)]
 -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> SomeConstant DefaultUni [TyVarRep ('TyNameRep "a" 0)]
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramNullList)

    -- Data
    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
ChooseData =
        let chooseDataDenotation :: Data -> a -> a -> a -> a -> a -> a
            chooseDataDenotation :: forall a. Data -> a -> a -> a -> a -> a -> a
chooseDataDenotation Data
d a
xConstr a
xMap a
xList a
xI a
xB =
                case Data
d of
                    Constr {} -> a
xConstr
                    Map    {} -> a
xMap
                    List   {} -> a
xList
                    I      {} -> a
xI
                    B      {} -> a
xB
            {-# INLINE chooseDataDenotation #-}
        in (Data
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> Opaque val (TyVarRep ('TyNameRep "a" 0)))
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs
            (Data
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Data
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> Opaque val (TyVarRep ('TyNameRep "a" 0)))
-> (cost
    -> FoldArgs
         (GetArgs
            (Data
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))
             -> Opaque val (TyVarRep ('TyNameRep "a" 0))))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Data
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
forall a. Data -> a -> a -> a -> a -> a -> a
chooseDataDenotation
            (CostingFun ModelSixArguments
-> Data
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> ExBudgetStream
forall a1 a2 a3 a4 a5 a6.
(ExMemoryUsage a1, ExMemoryUsage a2, ExMemoryUsage a3,
 ExMemoryUsage a4, ExMemoryUsage a5, ExMemoryUsage a6) =>
CostingFun ModelSixArguments
-> a1 -> a2 -> a3 -> a4 -> a5 -> a6 -> ExBudgetStream
runCostingFunSixArguments (CostingFun ModelSixArguments
 -> Data
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> Opaque val (TyVarRep ('TyNameRep "a" 0))
 -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelSixArguments)
-> BuiltinCostModel
-> Data
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> Opaque val (TyVarRep ('TyNameRep "a" 0))
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelSixArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelSixArguments
paramChooseData)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
ConstrData =
        let constrDataDenotation :: Integer -> [Data] -> Data
            constrDataDenotation :: Integer -> [Data] -> Data
constrDataDenotation = Integer -> [Data] -> Data
Constr
            {-# INLINE constrDataDenotation #-}
        in (Integer -> [Data] -> Data)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (Integer -> [Data] -> Data)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Integer -> [Data] -> Data)
-> (cost
    -> FoldArgs (GetArgs (Integer -> [Data] -> Data)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Integer -> [Data] -> Data
constrDataDenotation
            (CostingFun ModelTwoArguments -> Integer -> [Data] -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> Integer -> [Data] -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Integer
-> [Data]
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramConstrData)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
MapData =
        let mapDataDenotation :: [(Data, Data)] -> Data
            mapDataDenotation :: [(Data, Data)] -> Data
mapDataDenotation = [(Data, Data)] -> Data
Map
            {-# INLINE mapDataDenotation #-}
        in ([(Data, Data)] -> Data)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs ([(Data, Data)] -> Data)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
([(Data, Data)] -> Data)
-> (cost
    -> FoldArgs (GetArgs ([(Data, Data)] -> Data)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            [(Data, Data)] -> Data
mapDataDenotation
            (CostingFun ModelOneArgument -> [(Data, Data)] -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> [(Data, Data)] -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> [(Data, Data)]
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramMapData)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
ListData =
        let listDataDenotation :: [Data] -> Data
            listDataDenotation :: [Data] -> Data
listDataDenotation = [Data] -> Data
List
            {-# INLINE listDataDenotation #-}
        in ([Data] -> Data)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs ([Data] -> Data)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
([Data] -> Data)
-> (cost -> FoldArgs (GetArgs ([Data] -> Data)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            [Data] -> Data
listDataDenotation
            (CostingFun ModelOneArgument -> [Data] -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> [Data] -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> [Data]
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramListData)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
IData =
        let iDataDenotation :: Integer -> Data
            iDataDenotation :: Integer -> Data
iDataDenotation = Integer -> Data
I
            {-# INLINE iDataDenotation #-}
        in (Integer -> Data)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (Integer -> Data)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Integer -> Data)
-> (cost -> FoldArgs (GetArgs (Integer -> Data)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Integer -> Data
iDataDenotation
            (CostingFun ModelOneArgument -> Integer -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> Integer -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> Integer
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramIData)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
BData =
        let bDataDenotation :: BS.ByteString -> Data
            bDataDenotation :: ByteString -> Data
bDataDenotation = ByteString -> Data
B
            {-# INLINE bDataDenotation #-}
        in (ByteString -> Data)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (ByteString -> Data)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> Data)
-> (cost -> FoldArgs (GetArgs (ByteString -> Data)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> Data
bDataDenotation
            (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramBData)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
UnConstrData =
        let unConstrDataDenotation :: Data -> BuiltinResult (Integer, [Data])
            unConstrDataDenotation :: Data -> BuiltinResult (Integer, [Data])
unConstrDataDenotation = \case
                Constr Integer
i [Data]
ds -> (Integer, [Data]) -> BuiltinResult (Integer, [Data])
forall a. a -> BuiltinResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Integer
i, [Data]
ds)
                -- See Note [Operational vs structural errors within builtins].
                Data
_           -> String -> BuiltinResult (Integer, [Data])
forall a. String -> BuiltinResult a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Expected the Constr constructor but got a different one"
            {-# INLINE unConstrDataDenotation #-}
        in (Data -> BuiltinResult (Integer, [Data]))
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Data -> BuiltinResult (Integer, [Data]))) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Data -> BuiltinResult (Integer, [Data]))
-> (cost
    -> FoldArgs
         (GetArgs (Data -> BuiltinResult (Integer, [Data]))) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Data -> BuiltinResult (Integer, [Data])
unConstrDataDenotation
            (CostingFun ModelOneArgument -> Data -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> Data -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> Data
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramUnConstrData)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
UnMapData =
        let unMapDataDenotation :: Data -> BuiltinResult [(Data, Data)]
            unMapDataDenotation :: Data -> BuiltinResult [(Data, Data)]
unMapDataDenotation = \case
                Map [(Data, Data)]
es -> [(Data, Data)] -> BuiltinResult [(Data, Data)]
forall a. a -> BuiltinResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [(Data, Data)]
es
                -- See Note [Operational vs structural errors within builtins].
                Data
_      -> String -> BuiltinResult [(Data, Data)]
forall a. String -> BuiltinResult a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Expected the Map constructor but got a different one"
            {-# INLINE unMapDataDenotation #-}
        in (Data -> BuiltinResult [(Data, Data)])
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Data -> BuiltinResult [(Data, Data)])) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Data -> BuiltinResult [(Data, Data)])
-> (cost
    -> FoldArgs
         (GetArgs (Data -> BuiltinResult [(Data, Data)])) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Data -> BuiltinResult [(Data, Data)]
unMapDataDenotation
            (CostingFun ModelOneArgument -> Data -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> Data -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> Data
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramUnMapData)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
UnListData =
        let unListDataDenotation :: Data -> BuiltinResult [Data]
            unListDataDenotation :: Data -> BuiltinResult [Data]
unListDataDenotation = \case
                List [Data]
ds -> [Data] -> BuiltinResult [Data]
forall a. a -> BuiltinResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [Data]
ds
                -- See Note [Operational vs structural errors within builtins].
                Data
_       -> String -> BuiltinResult [Data]
forall a. String -> BuiltinResult a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Expected the List constructor but got a different one"
            {-# INLINE unListDataDenotation #-}
        in (Data -> BuiltinResult [Data])
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Data -> BuiltinResult [Data])) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Data -> BuiltinResult [Data])
-> (cost
    -> FoldArgs
         (GetArgs (Data -> BuiltinResult [Data])) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Data -> BuiltinResult [Data]
unListDataDenotation
            (CostingFun ModelOneArgument -> Data -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> Data -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> Data
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramUnListData)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
UnIData =
        let unIDataDenotation :: Data -> BuiltinResult Integer
            unIDataDenotation :: Data -> BuiltinResult Integer
unIDataDenotation = \case
                I Integer
i -> Integer -> BuiltinResult Integer
forall a. a -> BuiltinResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Integer
i
                -- See Note [Operational vs structural errors within builtins].
                Data
_   -> String -> BuiltinResult Integer
forall a. String -> BuiltinResult a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Expected the I constructor but got a different one"
            {-# INLINE unIDataDenotation #-}
        in (Data -> BuiltinResult Integer)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Data -> BuiltinResult Integer)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Data -> BuiltinResult Integer)
-> (cost
    -> FoldArgs
         (GetArgs (Data -> BuiltinResult Integer)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Data -> BuiltinResult Integer
unIDataDenotation
            (CostingFun ModelOneArgument -> Data -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> Data -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> Data
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramUnIData)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
UnBData =
        let unBDataDenotation :: Data -> BuiltinResult BS.ByteString
            unBDataDenotation :: Data -> BuiltinResult ByteString
unBDataDenotation = \case
                B ByteString
b -> ByteString -> BuiltinResult ByteString
forall a. a -> BuiltinResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
b
                -- See Note [Operational vs structural errors within builtins].
                Data
_   -> String -> BuiltinResult ByteString
forall a. String -> BuiltinResult a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Expected the B constructor but got a different one"
            {-# INLINE unBDataDenotation #-}
        in (Data -> BuiltinResult ByteString)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Data -> BuiltinResult ByteString)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Data -> BuiltinResult ByteString)
-> (cost
    -> FoldArgs
         (GetArgs (Data -> BuiltinResult ByteString)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Data -> BuiltinResult ByteString
unBDataDenotation
            (CostingFun ModelOneArgument -> Data -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> Data -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> Data
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramUnBData)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
EqualsData =
        let equalsDataDenotation :: Data -> Data -> Bool
            equalsDataDenotation :: Data -> Data -> Bool
equalsDataDenotation = Data -> Data -> Bool
forall a. Eq a => a -> a -> Bool
(==)
            {-# INLINE equalsDataDenotation #-}
        in (Data -> Data -> Bool)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (Data -> Data -> Bool)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Data -> Data -> Bool)
-> (cost
    -> FoldArgs (GetArgs (Data -> Data -> Bool)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Data -> Data -> Bool
equalsDataDenotation
            (CostingFun ModelTwoArguments -> Data -> Data -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments -> Data -> Data -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Data
-> Data
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramEqualsData)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
SerialiseData =
        let serialiseDataDenotation :: Data -> BS.ByteString
            serialiseDataDenotation :: Data -> ByteString
serialiseDataDenotation = ByteString -> ByteString
BSL.toStrict (ByteString -> ByteString)
-> (Data -> ByteString) -> Data -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Data -> ByteString
forall a. Serialise a => a -> ByteString
serialise
            {-# INLINE serialiseDataDenotation #-}
        in (Data -> ByteString)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (Data -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Data -> ByteString)
-> (cost -> FoldArgs (GetArgs (Data -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Data -> ByteString
serialiseDataDenotation
            (CostingFun ModelOneArgument -> Data -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> Data -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> Data
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramSerialiseData)

    -- Misc constructors
    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
MkPairData =
        let mkPairDataDenotation :: Data -> Data -> (Data, Data)
            mkPairDataDenotation :: Data -> Data -> (Data, Data)
mkPairDataDenotation = (,)
            {-# INLINE mkPairDataDenotation #-}
        in (Data -> Data -> (Data, Data))
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Data -> Data -> (Data, Data))) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Data -> Data -> (Data, Data))
-> (cost
    -> FoldArgs
         (GetArgs (Data -> Data -> (Data, Data))) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Data -> Data -> (Data, Data)
mkPairDataDenotation
            (CostingFun ModelTwoArguments -> Data -> Data -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments -> Data -> Data -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Data
-> Data
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramMkPairData)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
MkNilData =
        -- Nullary built-in functions don't work, so we need a unit argument.
        -- We don't really need this built-in function, see Note [Constants vs built-in functions],
        -- but we keep it around for historical reasons and convenience.
        let mkNilDataDenotation :: () -> [Data]
            mkNilDataDenotation :: () -> [Data]
mkNilDataDenotation () = []
            {-# INLINE mkNilDataDenotation #-}
        in (() -> [Data])
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (() -> [Data])) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(() -> [Data])
-> (cost -> FoldArgs (GetArgs (() -> [Data])) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            () -> [Data]
mkNilDataDenotation
            (CostingFun ModelOneArgument -> () -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> () -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> ()
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramMkNilData)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
MkNilPairData =
        -- Nullary built-in functions don't work, so we need a unit argument.
        -- We don't really need this built-in function, see Note [Constants vs built-in functions],
        -- but we keep it around for historical reasons and convenience.
        let mkNilPairDataDenotation :: () -> [(Data, Data)]
            mkNilPairDataDenotation :: () -> [(Data, Data)]
mkNilPairDataDenotation () = []
            {-# INLINE mkNilPairDataDenotation #-}
        in (() -> [(Data, Data)])
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (() -> [(Data, Data)])) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(() -> [(Data, Data)])
-> (cost
    -> FoldArgs (GetArgs (() -> [(Data, Data)])) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            () -> [(Data, Data)]
mkNilPairDataDenotation
            (CostingFun ModelOneArgument -> () -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> () -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> ()
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramMkNilPairData)

    -- BLS12_381.G1
    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Bls12_381_G1_add =
        let bls12_381_G1_addDenotation
                :: BLS12_381.G1.Element -> BLS12_381.G1.Element -> BLS12_381.G1.Element
            bls12_381_G1_addDenotation :: Element -> Element -> Element
bls12_381_G1_addDenotation = Element -> Element -> Element
BLS12_381.G1.add
            {-# INLINE bls12_381_G1_addDenotation #-}
        in (Element -> Element -> Element)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Element -> Element -> Element)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Element -> Element -> Element)
-> (cost
    -> FoldArgs
         (GetArgs (Element -> Element -> Element)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Element -> Element -> Element
bls12_381_G1_addDenotation
            (CostingFun ModelTwoArguments
-> Element -> Element -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> Element -> Element -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Element
-> Element
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramBls12_381_G1_add)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Bls12_381_G1_neg =
        let bls12_381_G1_negDenotation :: BLS12_381.G1.Element -> BLS12_381.G1.Element
            bls12_381_G1_negDenotation :: Element -> Element
bls12_381_G1_negDenotation = Element -> Element
BLS12_381.G1.neg
            {-# INLINE bls12_381_G1_negDenotation #-}
        in (Element -> Element)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (Element -> Element)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Element -> Element)
-> (cost -> FoldArgs (GetArgs (Element -> Element)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Element -> Element
bls12_381_G1_negDenotation
            (CostingFun ModelOneArgument -> Element -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> Element -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> Element
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramBls12_381_G1_neg)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Bls12_381_G1_scalarMul =
        let bls12_381_G1_scalarMulDenotation
                :: Integer -> BLS12_381.G1.Element -> BLS12_381.G1.Element
            bls12_381_G1_scalarMulDenotation :: Integer -> Element -> Element
bls12_381_G1_scalarMulDenotation = Integer -> Element -> Element
BLS12_381.G1.scalarMul
            {-# INLINE bls12_381_G1_scalarMulDenotation #-}
        in (Integer -> Element -> Element)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Integer -> Element -> Element)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Integer -> Element -> Element)
-> (cost
    -> FoldArgs
         (GetArgs (Integer -> Element -> Element)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Integer -> Element -> Element
bls12_381_G1_scalarMulDenotation
            (CostingFun ModelTwoArguments
-> Integer -> Element -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> Integer -> Element -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Integer
-> Element
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramBls12_381_G1_scalarMul)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Bls12_381_G1_compress =
        let bls12_381_G1_compressDenotation :: BLS12_381.G1.Element -> BS.ByteString
            bls12_381_G1_compressDenotation :: Element -> ByteString
bls12_381_G1_compressDenotation = Element -> ByteString
BLS12_381.G1.compress
            {-# INLINE bls12_381_G1_compressDenotation #-}
        in (Element -> ByteString)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (Element -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Element -> ByteString)
-> (cost
    -> FoldArgs (GetArgs (Element -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Element -> ByteString
bls12_381_G1_compressDenotation
            (CostingFun ModelOneArgument -> Element -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> Element -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> Element
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramBls12_381_G1_compress)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Bls12_381_G1_uncompress =
        let bls12_381_G1_uncompressDenotation
                :: BS.ByteString -> BuiltinResult BLS12_381.G1.Element
            bls12_381_G1_uncompressDenotation :: ByteString -> BuiltinResult Element
bls12_381_G1_uncompressDenotation = Either BLSTError Element -> BuiltinResult Element
forall e r. Show e => Either e r -> BuiltinResult r
eitherToBuiltinResult (Either BLSTError Element -> BuiltinResult Element)
-> (ByteString -> Either BLSTError Element)
-> ByteString
-> BuiltinResult Element
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either BLSTError Element
BLS12_381.G1.uncompress
            {-# INLINE bls12_381_G1_uncompressDenotation #-}
        in (ByteString -> BuiltinResult Element)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (ByteString -> BuiltinResult Element)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> BuiltinResult Element)
-> (cost
    -> FoldArgs
         (GetArgs (ByteString -> BuiltinResult Element)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> BuiltinResult Element
bls12_381_G1_uncompressDenotation
            (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramBls12_381_G1_uncompress)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Bls12_381_G1_hashToGroup =
        let bls12_381_G1_hashToGroupDenotation
                :: BS.ByteString -> BS.ByteString -> BuiltinResult BLS12_381.G1.Element
            bls12_381_G1_hashToGroupDenotation :: ByteString -> ByteString -> BuiltinResult Element
bls12_381_G1_hashToGroupDenotation = Either BLS12_381_Error Element -> BuiltinResult Element
forall e r. Show e => Either e r -> BuiltinResult r
eitherToBuiltinResult (Either BLS12_381_Error Element -> BuiltinResult Element)
-> (ByteString -> ByteString -> Either BLS12_381_Error Element)
-> ByteString
-> ByteString
-> BuiltinResult Element
forall c d a b. (c -> d) -> (a -> b -> c) -> a -> b -> d
.* ByteString -> ByteString -> Either BLS12_381_Error Element
BLS12_381.G1.hashToGroup
            {-# INLINE bls12_381_G1_hashToGroupDenotation #-}
        in (ByteString -> ByteString -> BuiltinResult Element)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (ByteString -> ByteString -> BuiltinResult Element))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> ByteString -> BuiltinResult Element)
-> (cost
    -> FoldArgs
         (GetArgs (ByteString -> ByteString -> BuiltinResult Element))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> ByteString -> BuiltinResult Element
bls12_381_G1_hashToGroupDenotation
            (CostingFun ModelTwoArguments
-> ByteString -> ByteString -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> ByteString -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> ByteString
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramBls12_381_G1_hashToGroup)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Bls12_381_G1_equal =
        let bls12_381_G1_equalDenotation :: BLS12_381.G1.Element -> BLS12_381.G1.Element -> Bool
            bls12_381_G1_equalDenotation :: Element -> Element -> Bool
bls12_381_G1_equalDenotation = Element -> Element -> Bool
forall a. Eq a => a -> a -> Bool
(==)
            {-# INLINE bls12_381_G1_equalDenotation #-}
        in (Element -> Element -> Bool)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (Element -> Element -> Bool)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Element -> Element -> Bool)
-> (cost
    -> FoldArgs (GetArgs (Element -> Element -> Bool)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Element -> Element -> Bool
bls12_381_G1_equalDenotation
            (CostingFun ModelTwoArguments
-> Element -> Element -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> Element -> Element -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Element
-> Element
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramBls12_381_G1_equal)

    -- BLS12_381.G2
    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Bls12_381_G2_add =
        let bls12_381_G2_addDenotation
                :: BLS12_381.G2.Element -> BLS12_381.G2.Element -> BLS12_381.G2.Element
            bls12_381_G2_addDenotation :: Element -> Element -> Element
bls12_381_G2_addDenotation = Element -> Element -> Element
BLS12_381.G2.add
            {-# INLINE bls12_381_G2_addDenotation #-}
        in (Element -> Element -> Element)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Element -> Element -> Element)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Element -> Element -> Element)
-> (cost
    -> FoldArgs
         (GetArgs (Element -> Element -> Element)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Element -> Element -> Element
bls12_381_G2_addDenotation
            (CostingFun ModelTwoArguments
-> Element -> Element -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> Element -> Element -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Element
-> Element
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramBls12_381_G2_add)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Bls12_381_G2_neg =
        let bls12_381_G2_negDenotation :: BLS12_381.G2.Element -> BLS12_381.G2.Element
            bls12_381_G2_negDenotation :: Element -> Element
bls12_381_G2_negDenotation = Element -> Element
BLS12_381.G2.neg
            {-# INLINE bls12_381_G2_negDenotation #-}
        in (Element -> Element)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (Element -> Element)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Element -> Element)
-> (cost -> FoldArgs (GetArgs (Element -> Element)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Element -> Element
bls12_381_G2_negDenotation
            (CostingFun ModelOneArgument -> Element -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> Element -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> Element
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramBls12_381_G2_neg)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Bls12_381_G2_scalarMul =
        let bls12_381_G2_scalarMulDenotation
                :: Integer -> BLS12_381.G2.Element -> BLS12_381.G2.Element
            bls12_381_G2_scalarMulDenotation :: Integer -> Element -> Element
bls12_381_G2_scalarMulDenotation = Integer -> Element -> Element
BLS12_381.G2.scalarMul
            {-# INLINE bls12_381_G2_scalarMulDenotation #-}
        in (Integer -> Element -> Element)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Integer -> Element -> Element)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Integer -> Element -> Element)
-> (cost
    -> FoldArgs
         (GetArgs (Integer -> Element -> Element)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Integer -> Element -> Element
bls12_381_G2_scalarMulDenotation
            (CostingFun ModelTwoArguments
-> Integer -> Element -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> Integer -> Element -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Integer
-> Element
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramBls12_381_G2_scalarMul)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Bls12_381_G2_compress =
        let bls12_381_G2_compressDenotation :: BLS12_381.G2.Element -> BS.ByteString
            bls12_381_G2_compressDenotation :: Element -> ByteString
bls12_381_G2_compressDenotation = Element -> ByteString
BLS12_381.G2.compress
            {-# INLINE bls12_381_G2_compressDenotation #-}
        in (Element -> ByteString)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (Element -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Element -> ByteString)
-> (cost
    -> FoldArgs (GetArgs (Element -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Element -> ByteString
bls12_381_G2_compressDenotation
            (CostingFun ModelOneArgument -> Element -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> Element -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> Element
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramBls12_381_G2_compress)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Bls12_381_G2_uncompress =
        let bls12_381_G2_uncompressDenotation
                :: BS.ByteString -> BuiltinResult BLS12_381.G2.Element
            bls12_381_G2_uncompressDenotation :: ByteString -> BuiltinResult Element
bls12_381_G2_uncompressDenotation = Either BLSTError Element -> BuiltinResult Element
forall e r. Show e => Either e r -> BuiltinResult r
eitherToBuiltinResult (Either BLSTError Element -> BuiltinResult Element)
-> (ByteString -> Either BLSTError Element)
-> ByteString
-> BuiltinResult Element
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Either BLSTError Element
BLS12_381.G2.uncompress
            {-# INLINE bls12_381_G2_uncompressDenotation #-}
        in (ByteString -> BuiltinResult Element)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (ByteString -> BuiltinResult Element)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> BuiltinResult Element)
-> (cost
    -> FoldArgs
         (GetArgs (ByteString -> BuiltinResult Element)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> BuiltinResult Element
bls12_381_G2_uncompressDenotation
            (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramBls12_381_G2_uncompress)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Bls12_381_G2_hashToGroup =
        let bls12_381_G2_hashToGroupDenotation
                :: BS.ByteString -> BS.ByteString -> BuiltinResult BLS12_381.G2.Element
            bls12_381_G2_hashToGroupDenotation :: ByteString -> ByteString -> BuiltinResult Element
bls12_381_G2_hashToGroupDenotation = Either BLS12_381_Error Element -> BuiltinResult Element
forall e r. Show e => Either e r -> BuiltinResult r
eitherToBuiltinResult (Either BLS12_381_Error Element -> BuiltinResult Element)
-> (ByteString -> ByteString -> Either BLS12_381_Error Element)
-> ByteString
-> ByteString
-> BuiltinResult Element
forall c d a b. (c -> d) -> (a -> b -> c) -> a -> b -> d
.* ByteString -> ByteString -> Either BLS12_381_Error Element
BLS12_381.G2.hashToGroup
            {-# INLINE bls12_381_G2_hashToGroupDenotation #-}
        in (ByteString -> ByteString -> BuiltinResult Element)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (ByteString -> ByteString -> BuiltinResult Element))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> ByteString -> BuiltinResult Element)
-> (cost
    -> FoldArgs
         (GetArgs (ByteString -> ByteString -> BuiltinResult Element))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> ByteString -> BuiltinResult Element
bls12_381_G2_hashToGroupDenotation
            (CostingFun ModelTwoArguments
-> ByteString -> ByteString -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> ByteString -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> ByteString
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramBls12_381_G2_hashToGroup)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Bls12_381_G2_equal =
        let bls12_381_G2_equalDenotation :: BLS12_381.G2.Element -> BLS12_381.G2.Element -> Bool
            bls12_381_G2_equalDenotation :: Element -> Element -> Bool
bls12_381_G2_equalDenotation = Element -> Element -> Bool
forall a. Eq a => a -> a -> Bool
(==)
            {-# INLINE bls12_381_G2_equalDenotation #-}
        in (Element -> Element -> Bool)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (Element -> Element -> Bool)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Element -> Element -> Bool)
-> (cost
    -> FoldArgs (GetArgs (Element -> Element -> Bool)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Element -> Element -> Bool
bls12_381_G2_equalDenotation
            (CostingFun ModelTwoArguments
-> Element -> Element -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> Element -> Element -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Element
-> Element
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramBls12_381_G2_equal)

    -- BLS12_381.Pairing
    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Bls12_381_millerLoop =
        let bls12_381_millerLoopDenotation
                :: BLS12_381.G1.Element -> BLS12_381.G2.Element -> BLS12_381.Pairing.MlResult
            bls12_381_millerLoopDenotation :: Element -> Element -> MlResult
bls12_381_millerLoopDenotation = Element -> Element -> MlResult
BLS12_381.Pairing.millerLoop
            {-# INLINE bls12_381_millerLoopDenotation #-}
        in (Element -> Element -> MlResult)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Element -> Element -> MlResult)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Element -> Element -> MlResult)
-> (cost
    -> FoldArgs
         (GetArgs (Element -> Element -> MlResult)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Element -> Element -> MlResult
bls12_381_millerLoopDenotation
            (CostingFun ModelTwoArguments
-> Element -> Element -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> Element -> Element -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Element
-> Element
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramBls12_381_millerLoop)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Bls12_381_mulMlResult =
        let bls12_381_mulMlResultDenotation
                :: BLS12_381.Pairing.MlResult
                -> BLS12_381.Pairing.MlResult
                -> BLS12_381.Pairing.MlResult
            bls12_381_mulMlResultDenotation :: MlResult -> MlResult -> MlResult
bls12_381_mulMlResultDenotation = MlResult -> MlResult -> MlResult
BLS12_381.Pairing.mulMlResult
            {-# INLINE bls12_381_mulMlResultDenotation #-}
        in (MlResult -> MlResult -> MlResult)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (MlResult -> MlResult -> MlResult)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(MlResult -> MlResult -> MlResult)
-> (cost
    -> FoldArgs
         (GetArgs (MlResult -> MlResult -> MlResult)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            MlResult -> MlResult -> MlResult
bls12_381_mulMlResultDenotation
            (CostingFun ModelTwoArguments
-> MlResult -> MlResult -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> MlResult -> MlResult -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> MlResult
-> MlResult
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramBls12_381_mulMlResult)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Bls12_381_finalVerify =
        let bls12_381_finalVerifyDenotation
                :: BLS12_381.Pairing.MlResult -> BLS12_381.Pairing.MlResult -> Bool
            bls12_381_finalVerifyDenotation :: MlResult -> MlResult -> Bool
bls12_381_finalVerifyDenotation = MlResult -> MlResult -> Bool
BLS12_381.Pairing.finalVerify
            {-# INLINE bls12_381_finalVerifyDenotation #-}
        in (MlResult -> MlResult -> Bool)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (MlResult -> MlResult -> Bool)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(MlResult -> MlResult -> Bool)
-> (cost
    -> FoldArgs
         (GetArgs (MlResult -> MlResult -> Bool)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            MlResult -> MlResult -> Bool
bls12_381_finalVerifyDenotation
            (CostingFun ModelTwoArguments
-> MlResult -> MlResult -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> MlResult -> MlResult -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> MlResult
-> MlResult
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramBls12_381_finalVerify)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Keccak_256 =
        let keccak_256Denotation :: BS.ByteString -> BS.ByteString
            keccak_256Denotation :: ByteString -> ByteString
keccak_256Denotation = ByteString -> ByteString
Hash.keccak_256
            {-# INLINE keccak_256Denotation #-}
        in (ByteString -> ByteString)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (ByteString -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> ByteString)
-> (cost
    -> FoldArgs (GetArgs (ByteString -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> ByteString
keccak_256Denotation
            (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramKeccak_256)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Blake2b_224 =
        let blake2b_224Denotation :: BS.ByteString -> BS.ByteString
            blake2b_224Denotation :: ByteString -> ByteString
blake2b_224Denotation = ByteString -> ByteString
Hash.blake2b_224
            {-# INLINE blake2b_224Denotation #-}
        in (ByteString -> ByteString)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (ByteString -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> ByteString)
-> (cost
    -> FoldArgs (GetArgs (ByteString -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> ByteString
blake2b_224Denotation
            (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramBlake2b_224)


    -- Extra bytestring operations

    -- Conversions
    {- See Note [Input length limitation for IntegerToByteString] -}
    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
IntegerToByteString =
        let integerToByteStringDenotation :: Bool -> NumBytesCostedAsNumWords -> Integer -> BuiltinResult BS.ByteString
            {- The second argument is wrapped in a NumBytesCostedAsNumWords to allow us to
               interpret it as a size during costing. -}
            integerToByteStringDenotation :: Bool
-> NumBytesCostedAsNumWords -> Integer -> BuiltinResult ByteString
integerToByteStringDenotation Bool
b (NumBytesCostedAsNumWords Integer
w) = Bool -> Integer -> Integer -> BuiltinResult ByteString
Bitwise.integerToByteString Bool
b Integer
w
            {-# INLINE integerToByteStringDenotation #-}
        in (Bool
 -> NumBytesCostedAsNumWords -> Integer -> BuiltinResult ByteString)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs
            (Bool
             -> NumBytesCostedAsNumWords
             -> Integer
             -> BuiltinResult ByteString))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Bool
 -> NumBytesCostedAsNumWords -> Integer -> BuiltinResult ByteString)
-> (cost
    -> FoldArgs
         (GetArgs
            (Bool
             -> NumBytesCostedAsNumWords
             -> Integer
             -> BuiltinResult ByteString))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Bool
-> NumBytesCostedAsNumWords -> Integer -> BuiltinResult ByteString
integerToByteStringDenotation
            (CostingFun ModelThreeArguments
-> Bool -> NumBytesCostedAsNumWords -> Integer -> ExBudgetStream
forall a1 a2 a3.
(ExMemoryUsage a1, ExMemoryUsage a2, ExMemoryUsage a3) =>
CostingFun ModelThreeArguments -> a1 -> a2 -> a3 -> ExBudgetStream
runCostingFunThreeArguments (CostingFun ModelThreeArguments
 -> Bool -> NumBytesCostedAsNumWords -> Integer -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelThreeArguments)
-> BuiltinCostModel
-> Bool
-> NumBytesCostedAsNumWords
-> Integer
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelThreeArguments
forall (f :: * -> *).
BuiltinCostModelBase f -> f ModelThreeArguments
paramIntegerToByteString)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
ByteStringToInteger =
        let byteStringToIntegerDenotation :: Bool -> BS.ByteString -> Integer
            byteStringToIntegerDenotation :: Bool -> ByteString -> Integer
byteStringToIntegerDenotation = Bool -> ByteString -> Integer
Bitwise.byteStringToInteger
            {-# INLINE byteStringToIntegerDenotation #-}
        in (Bool -> ByteString -> Integer)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Bool -> ByteString -> Integer)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Bool -> ByteString -> Integer)
-> (cost
    -> FoldArgs
         (GetArgs (Bool -> ByteString -> Integer)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Bool -> ByteString -> Integer
byteStringToIntegerDenotation
            (CostingFun ModelTwoArguments
-> Bool -> ByteString -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> Bool -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> Bool
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramByteStringToInteger)

    -- Logical
    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
AndByteString =
        let andByteStringDenotation :: Bool -> BS.ByteString -> BS.ByteString -> BS.ByteString
            andByteStringDenotation :: Bool -> ByteString -> ByteString -> ByteString
andByteStringDenotation = Bool -> ByteString -> ByteString -> ByteString
Bitwise.andByteString
            {-# INLINE andByteStringDenotation #-}
        in (Bool -> ByteString -> ByteString -> ByteString)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Bool -> ByteString -> ByteString -> ByteString))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Bool -> ByteString -> ByteString -> ByteString)
-> (cost
    -> FoldArgs
         (GetArgs (Bool -> ByteString -> ByteString -> ByteString))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Bool -> ByteString -> ByteString -> ByteString
andByteStringDenotation
            (CostingFun ModelThreeArguments
-> Bool -> ByteString -> ByteString -> ExBudgetStream
forall a1 a2 a3.
(ExMemoryUsage a1, ExMemoryUsage a2, ExMemoryUsage a3) =>
CostingFun ModelThreeArguments -> a1 -> a2 -> a3 -> ExBudgetStream
runCostingFunThreeArguments (CostingFun ModelThreeArguments
 -> Bool -> ByteString -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelThreeArguments)
-> BuiltinCostModel
-> Bool
-> ByteString
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelThreeArguments
forall (f :: * -> *).
BuiltinCostModelBase f -> f ModelThreeArguments
paramAndByteString)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
OrByteString =
        let orByteStringDenotation :: Bool -> BS.ByteString -> BS.ByteString -> BS.ByteString
            orByteStringDenotation :: Bool -> ByteString -> ByteString -> ByteString
orByteStringDenotation = Bool -> ByteString -> ByteString -> ByteString
Bitwise.orByteString
            {-# INLINE orByteStringDenotation #-}
        in (Bool -> ByteString -> ByteString -> ByteString)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Bool -> ByteString -> ByteString -> ByteString))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Bool -> ByteString -> ByteString -> ByteString)
-> (cost
    -> FoldArgs
         (GetArgs (Bool -> ByteString -> ByteString -> ByteString))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Bool -> ByteString -> ByteString -> ByteString
orByteStringDenotation
            (CostingFun ModelThreeArguments
-> Bool -> ByteString -> ByteString -> ExBudgetStream
forall a1 a2 a3.
(ExMemoryUsage a1, ExMemoryUsage a2, ExMemoryUsage a3) =>
CostingFun ModelThreeArguments -> a1 -> a2 -> a3 -> ExBudgetStream
runCostingFunThreeArguments (CostingFun ModelThreeArguments
 -> Bool -> ByteString -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelThreeArguments)
-> BuiltinCostModel
-> Bool
-> ByteString
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelThreeArguments
forall (f :: * -> *).
BuiltinCostModelBase f -> f ModelThreeArguments
paramOrByteString)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
XorByteString =
        let xorByteStringDenotation :: Bool -> BS.ByteString -> BS.ByteString -> BS.ByteString
            xorByteStringDenotation :: Bool -> ByteString -> ByteString -> ByteString
xorByteStringDenotation = Bool -> ByteString -> ByteString -> ByteString
Bitwise.xorByteString
            {-# INLINE xorByteStringDenotation #-}
        in (Bool -> ByteString -> ByteString -> ByteString)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Bool -> ByteString -> ByteString -> ByteString))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Bool -> ByteString -> ByteString -> ByteString)
-> (cost
    -> FoldArgs
         (GetArgs (Bool -> ByteString -> ByteString -> ByteString))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Bool -> ByteString -> ByteString -> ByteString
xorByteStringDenotation
            (CostingFun ModelThreeArguments
-> Bool -> ByteString -> ByteString -> ExBudgetStream
forall a1 a2 a3.
(ExMemoryUsage a1, ExMemoryUsage a2, ExMemoryUsage a3) =>
CostingFun ModelThreeArguments -> a1 -> a2 -> a3 -> ExBudgetStream
runCostingFunThreeArguments (CostingFun ModelThreeArguments
 -> Bool -> ByteString -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelThreeArguments)
-> BuiltinCostModel
-> Bool
-> ByteString
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelThreeArguments
forall (f :: * -> *).
BuiltinCostModelBase f -> f ModelThreeArguments
paramXorByteString)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
ComplementByteString =
        let complementByteStringDenotation :: BS.ByteString -> BS.ByteString
            complementByteStringDenotation :: ByteString -> ByteString
complementByteStringDenotation = ByteString -> ByteString
Bitwise.complementByteString
            {-# INLINE complementByteStringDenotation #-}
        in (ByteString -> ByteString)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (ByteString -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> ByteString)
-> (cost
    -> FoldArgs (GetArgs (ByteString -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> ByteString
complementByteStringDenotation
            (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramComplementByteString)

    -- Bitwise operations

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
ReadBit =
        let readBitDenotation :: BS.ByteString -> Int -> BuiltinResult Bool
            readBitDenotation :: ByteString -> Int -> BuiltinResult Bool
readBitDenotation = ByteString -> Int -> BuiltinResult Bool
Bitwise.readBit
            {-# INLINE readBitDenotation #-}
        in (ByteString -> Int -> BuiltinResult Bool)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (ByteString -> Int -> BuiltinResult Bool)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> Int -> BuiltinResult Bool)
-> (cost
    -> FoldArgs
         (GetArgs (ByteString -> Int -> BuiltinResult Bool)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> Int -> BuiltinResult Bool
readBitDenotation
            (CostingFun ModelTwoArguments -> ByteString -> Int -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> ByteString -> Int -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> ByteString
-> Int
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramReadBit)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
WriteBits =
        let writeBitsDenotation
              :: BS.ByteString
              -> ListCostedByLength Integer
              -> ListCostedByLength Bool
              -> BuiltinResult BS.ByteString
            writeBitsDenotation :: ByteString
-> ListCostedByLength Integer
-> ListCostedByLength Bool
-> BuiltinResult ByteString
writeBitsDenotation ByteString
s (ListCostedByLength [Integer]
ixs) (ListCostedByLength [Bool]
bits) = ByteString -> [Integer] -> [Bool] -> BuiltinResult ByteString
Bitwise.writeBits ByteString
s [Integer]
ixs [Bool]
bits
            {-# INLINE writeBitsDenotation #-}
        in (ByteString
 -> ListCostedByLength Integer
 -> ListCostedByLength Bool
 -> BuiltinResult ByteString)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs
            (ByteString
             -> ListCostedByLength Integer
             -> ListCostedByLength Bool
             -> BuiltinResult ByteString))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString
 -> ListCostedByLength Integer
 -> ListCostedByLength Bool
 -> BuiltinResult ByteString)
-> (cost
    -> FoldArgs
         (GetArgs
            (ByteString
             -> ListCostedByLength Integer
             -> ListCostedByLength Bool
             -> BuiltinResult ByteString))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString
-> ListCostedByLength Integer
-> ListCostedByLength Bool
-> BuiltinResult ByteString
writeBitsDenotation
            (CostingFun ModelThreeArguments
-> ByteString
-> ListCostedByLength Integer
-> ListCostedByLength Bool
-> ExBudgetStream
forall a1 a2 a3.
(ExMemoryUsage a1, ExMemoryUsage a2, ExMemoryUsage a3) =>
CostingFun ModelThreeArguments -> a1 -> a2 -> a3 -> ExBudgetStream
runCostingFunThreeArguments (CostingFun ModelThreeArguments
 -> ByteString
 -> ListCostedByLength Integer
 -> ListCostedByLength Bool
 -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelThreeArguments)
-> BuiltinCostModel
-> ByteString
-> ListCostedByLength Integer
-> ListCostedByLength Bool
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelThreeArguments
forall (f :: * -> *).
BuiltinCostModelBase f -> f ModelThreeArguments
paramWriteBits)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
ReplicateByte =
        let replicateByteDenotation :: NumBytesCostedAsNumWords -> Word8 -> BuiltinResult BS.ByteString
            replicateByteDenotation :: NumBytesCostedAsNumWords -> Word8 -> BuiltinResult ByteString
replicateByteDenotation (NumBytesCostedAsNumWords Integer
n) Word8
w = Integer -> Word8 -> BuiltinResult ByteString
Bitwise.replicateByte Integer
n Word8
w
            {-# INLINE replicateByteDenotation #-}
        in (NumBytesCostedAsNumWords -> Word8 -> BuiltinResult ByteString)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs
            (NumBytesCostedAsNumWords -> Word8 -> BuiltinResult ByteString))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(NumBytesCostedAsNumWords -> Word8 -> BuiltinResult ByteString)
-> (cost
    -> FoldArgs
         (GetArgs
            (NumBytesCostedAsNumWords -> Word8 -> BuiltinResult ByteString))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            NumBytesCostedAsNumWords -> Word8 -> BuiltinResult ByteString
replicateByteDenotation
            (CostingFun ModelTwoArguments
-> NumBytesCostedAsNumWords -> Word8 -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> NumBytesCostedAsNumWords -> Word8 -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> NumBytesCostedAsNumWords
-> Word8
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramReplicateByte)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
ShiftByteString =
        let shiftByteStringDenotation :: BS.ByteString -> IntegerCostedLiterally -> BS.ByteString
            shiftByteStringDenotation :: ByteString -> IntegerCostedLiterally -> ByteString
shiftByteStringDenotation ByteString
s (IntegerCostedLiterally Integer
n) = ByteString -> Integer -> ByteString
Bitwise.shiftByteString ByteString
s Integer
n
            {-# INLINE shiftByteStringDenotation #-}
        in (ByteString -> IntegerCostedLiterally -> ByteString)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (ByteString -> IntegerCostedLiterally -> ByteString))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> IntegerCostedLiterally -> ByteString)
-> (cost
    -> FoldArgs
         (GetArgs (ByteString -> IntegerCostedLiterally -> ByteString))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> IntegerCostedLiterally -> ByteString
shiftByteStringDenotation
            (CostingFun ModelTwoArguments
-> ByteString -> IntegerCostedLiterally -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> ByteString -> IntegerCostedLiterally -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> ByteString
-> IntegerCostedLiterally
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramShiftByteString)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
RotateByteString =
        let rotateByteStringDenotation :: BS.ByteString -> IntegerCostedLiterally -> BS.ByteString
            rotateByteStringDenotation :: ByteString -> IntegerCostedLiterally -> ByteString
rotateByteStringDenotation ByteString
s (IntegerCostedLiterally Integer
n) = ByteString -> Integer -> ByteString
Bitwise.rotateByteString ByteString
s Integer
n
            {-# INLINE rotateByteStringDenotation #-}
        in (ByteString -> IntegerCostedLiterally -> ByteString)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (ByteString -> IntegerCostedLiterally -> ByteString))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> IntegerCostedLiterally -> ByteString)
-> (cost
    -> FoldArgs
         (GetArgs (ByteString -> IntegerCostedLiterally -> ByteString))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> IntegerCostedLiterally -> ByteString
rotateByteStringDenotation
            (CostingFun ModelTwoArguments
-> ByteString -> IntegerCostedLiterally -> ExBudgetStream
forall a1 a2.
(ExMemoryUsage a1, ExMemoryUsage a2) =>
CostingFun ModelTwoArguments -> a1 -> a2 -> ExBudgetStream
runCostingFunTwoArguments (CostingFun ModelTwoArguments
 -> ByteString -> IntegerCostedLiterally -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelTwoArguments)
-> BuiltinCostModel
-> ByteString
-> IntegerCostedLiterally
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelTwoArguments
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelTwoArguments
paramRotateByteString)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
CountSetBits =
        let countSetBitsDenotation :: BS.ByteString -> Int
            countSetBitsDenotation :: ByteString -> Int
countSetBitsDenotation = ByteString -> Int
Bitwise.countSetBits
            {-# INLINE countSetBitsDenotation #-}
        in (ByteString -> Int)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (ByteString -> Int)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> Int)
-> (cost -> FoldArgs (GetArgs (ByteString -> Int)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> Int
countSetBitsDenotation
            (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramCountSetBits)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
FindFirstSetBit =
        let findFirstSetBitDenotation :: BS.ByteString -> Int
            findFirstSetBitDenotation :: ByteString -> Int
findFirstSetBitDenotation = ByteString -> Int
Bitwise.findFirstSetBit
            {-# INLINE findFirstSetBitDenotation #-}
        in (ByteString -> Int)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (ByteString -> Int)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> Int)
-> (cost -> FoldArgs (GetArgs (ByteString -> Int)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> Int
findFirstSetBitDenotation
            (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramFindFirstSetBit)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
Ripemd_160 =
        let ripemd_160Denotation :: BS.ByteString -> BS.ByteString
            ripemd_160Denotation :: ByteString -> ByteString
ripemd_160Denotation = ByteString -> ByteString
Hash.ripemd_160
            {-# INLINE ripemd_160Denotation #-}
        in (ByteString -> ByteString)
-> (BuiltinCostModel
    -> FoldArgs (GetArgs (ByteString -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(ByteString -> ByteString)
-> (cost
    -> FoldArgs (GetArgs (ByteString -> ByteString)) ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            ByteString -> ByteString
ripemd_160Denotation
            (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream
forall a1.
ExMemoryUsage a1 =>
CostingFun ModelOneArgument -> a1 -> ExBudgetStream
runCostingFunOneArgument (CostingFun ModelOneArgument -> ByteString -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelOneArgument)
-> BuiltinCostModel
-> ByteString
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelOneArgument
forall (f :: * -> *). BuiltinCostModelBase f -> f ModelOneArgument
paramRipemd_160)

    toBuiltinMeaning BuiltinSemanticsVariant DefaultFun
_semvar DefaultFun
ExpModInteger =
        let expModIntegerDenotation :: Integer -> Integer -> Natural -> BuiltinResult Natural
            expModIntegerDenotation :: Integer -> Integer -> Natural -> BuiltinResult Natural
expModIntegerDenotation = Integer -> Integer -> Natural -> BuiltinResult Natural
ExpMod.expMod
            {-# INLINE expModIntegerDenotation #-}
        in (Integer -> Integer -> Natural -> BuiltinResult Natural)
-> (BuiltinCostModel
    -> FoldArgs
         (GetArgs (Integer -> Integer -> Natural -> BuiltinResult Natural))
         ExBudgetStream)
-> BuiltinMeaning val BuiltinCostModel
forall cost.
(Integer -> Integer -> Natural -> BuiltinResult Natural)
-> (cost
    -> FoldArgs
         (GetArgs (Integer -> Integer -> Natural -> BuiltinResult Natural))
         ExBudgetStream)
-> BuiltinMeaning val cost
forall a val cost.
MakeBuiltinMeaning a val =>
a
-> (cost -> FoldArgs (GetArgs a) ExBudgetStream)
-> BuiltinMeaning val cost
makeBuiltinMeaning
            Integer -> Integer -> Natural -> BuiltinResult Natural
expModIntegerDenotation
            (CostingFun ModelThreeArguments
-> Integer -> Integer -> Natural -> ExBudgetStream
forall a1 a2 a3.
(ExMemoryUsage a1, ExMemoryUsage a2, ExMemoryUsage a3) =>
CostingFun ModelThreeArguments -> a1 -> a2 -> a3 -> ExBudgetStream
runCostingFunThreeArguments (CostingFun ModelThreeArguments
 -> Integer -> Integer -> Natural -> ExBudgetStream)
-> (BuiltinCostModel -> CostingFun ModelThreeArguments)
-> BuiltinCostModel
-> Integer
-> Integer
-> Natural
-> ExBudgetStream
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinCostModel -> CostingFun ModelThreeArguments
forall (f :: * -> *).
BuiltinCostModelBase f -> f ModelThreeArguments
paramExpModInteger)

    -- See Note [Inlining meanings of builtins].
    {-# INLINE toBuiltinMeaning #-}

    {- *** IMPORTANT! *** When you're adding a new builtin above you typically won't
       be able to add a sensible costing function until the implementation is
       complete and you can benchmark it.  It's still necessary to supply
       `toBuiltinMeaning` with some costing function though: this **MUST** be
       `unimplementedCostingFun`: this will assign a very large cost to any
       invocation of the function, preventing it from being used in places where
       costs are important (for example on testnets) until the implementation is
       complete and a proper costing function has been defined.  Once the
       builtin is ready for general use replace `unimplementedCostingFun` with
       the appropriate `param<BuiltinName>` from BuiltinCostModelBase.

       Please leave this comment immediately after the definition of the final
       builtin to maximise the chances of it being seen the next time someone
       implements a new builtin.
    -}

instance Default (BuiltinSemanticsVariant DefaultFun) where
    def :: BuiltinSemanticsVariant DefaultFun
def = BuiltinSemanticsVariant DefaultFun
forall a. Bounded a => a
maxBound

instance Pretty (BuiltinSemanticsVariant DefaultFun) where
    pretty :: forall ann. BuiltinSemanticsVariant DefaultFun -> Doc ann
pretty = BuiltinSemanticsVariant DefaultFun -> Doc ann
forall a ann. Show a => a -> Doc ann
viaShow

-- It's set deliberately to give us "extra room" in the binary format to add things without running
-- out of space for tags (expanding the space would change the binary format for people who're
-- implementing it manually). So we have to set it manually.
-- | Using 7 bits to encode builtin tags.
builtinTagWidth :: NumBits
builtinTagWidth :: Int
builtinTagWidth = Int
7

encodeBuiltin :: Word8 -> Flat.Encoding
encodeBuiltin :: Word8 -> Encoding
encodeBuiltin = Int -> Word8 -> Encoding
eBits Int
builtinTagWidth

decodeBuiltin :: Get Word8
decodeBuiltin :: Get Word8
decodeBuiltin = Int -> Get Word8
dBEBits8 Int
builtinTagWidth

-- See Note [Stable encoding of TPLC]
instance Flat DefaultFun where
    encode :: DefaultFun -> Encoding
encode = Word8 -> Encoding
encodeBuiltin (Word8 -> Encoding)
-> (DefaultFun -> Word8) -> DefaultFun -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
              DefaultFun
AddInteger                      -> Word8
0
              DefaultFun
SubtractInteger                 -> Word8
1
              DefaultFun
MultiplyInteger                 -> Word8
2
              DefaultFun
DivideInteger                   -> Word8
3
              DefaultFun
QuotientInteger                 -> Word8
4
              DefaultFun
RemainderInteger                -> Word8
5
              DefaultFun
ModInteger                      -> Word8
6
              DefaultFun
EqualsInteger                   -> Word8
7
              DefaultFun
LessThanInteger                 -> Word8
8
              DefaultFun
LessThanEqualsInteger           -> Word8
9

              DefaultFun
AppendByteString                -> Word8
10
              DefaultFun
ConsByteString                  -> Word8
11
              DefaultFun
SliceByteString                 -> Word8
12
              DefaultFun
LengthOfByteString              -> Word8
13
              DefaultFun
IndexByteString                 -> Word8
14
              DefaultFun
EqualsByteString                -> Word8
15
              DefaultFun
LessThanByteString              -> Word8
16
              DefaultFun
LessThanEqualsByteString        -> Word8
17

              DefaultFun
Sha2_256                        -> Word8
18
              DefaultFun
Sha3_256                        -> Word8
19
              DefaultFun
Blake2b_256                     -> Word8
20
              DefaultFun
VerifyEd25519Signature          -> Word8
21

              DefaultFun
AppendString                    -> Word8
22
              DefaultFun
EqualsString                    -> Word8
23
              DefaultFun
EncodeUtf8                      -> Word8
24
              DefaultFun
DecodeUtf8                      -> Word8
25

              DefaultFun
IfThenElse                      -> Word8
26

              DefaultFun
ChooseUnit                      -> Word8
27

              DefaultFun
Trace                           -> Word8
28

              DefaultFun
FstPair                         -> Word8
29
              DefaultFun
SndPair                         -> Word8
30

              DefaultFun
ChooseList                      -> Word8
31
              DefaultFun
MkCons                          -> Word8
32
              DefaultFun
HeadList                        -> Word8
33
              DefaultFun
TailList                        -> Word8
34
              DefaultFun
NullList                        -> Word8
35

              DefaultFun
ChooseData                      -> Word8
36
              DefaultFun
ConstrData                      -> Word8
37
              DefaultFun
MapData                         -> Word8
38
              DefaultFun
ListData                        -> Word8
39
              DefaultFun
IData                           -> Word8
40
              DefaultFun
BData                           -> Word8
41
              DefaultFun
UnConstrData                    -> Word8
42
              DefaultFun
UnMapData                       -> Word8
43
              DefaultFun
UnListData                      -> Word8
44
              DefaultFun
UnIData                         -> Word8
45
              DefaultFun
UnBData                         -> Word8
46
              DefaultFun
EqualsData                      -> Word8
47
              DefaultFun
MkPairData                      -> Word8
48
              DefaultFun
MkNilData                       -> Word8
49
              DefaultFun
MkNilPairData                   -> Word8
50
              DefaultFun
SerialiseData                   -> Word8
51
              DefaultFun
VerifyEcdsaSecp256k1Signature   -> Word8
52
              DefaultFun
VerifySchnorrSecp256k1Signature -> Word8
53
              DefaultFun
Bls12_381_G1_add                -> Word8
54
              DefaultFun
Bls12_381_G1_neg                -> Word8
55
              DefaultFun
Bls12_381_G1_scalarMul          -> Word8
56
              DefaultFun
Bls12_381_G1_equal              -> Word8
57
              DefaultFun
Bls12_381_G1_compress           -> Word8
58
              DefaultFun
Bls12_381_G1_uncompress         -> Word8
59
              DefaultFun
Bls12_381_G1_hashToGroup        -> Word8
60
              DefaultFun
Bls12_381_G2_add                -> Word8
61
              DefaultFun
Bls12_381_G2_neg                -> Word8
62
              DefaultFun
Bls12_381_G2_scalarMul          -> Word8
63
              DefaultFun
Bls12_381_G2_equal              -> Word8
64
              DefaultFun
Bls12_381_G2_compress           -> Word8
65
              DefaultFun
Bls12_381_G2_uncompress         -> Word8
66
              DefaultFun
Bls12_381_G2_hashToGroup        -> Word8
67
              DefaultFun
Bls12_381_millerLoop            -> Word8
68
              DefaultFun
Bls12_381_mulMlResult           -> Word8
69
              DefaultFun
Bls12_381_finalVerify           -> Word8
70
              DefaultFun
Keccak_256                      -> Word8
71
              DefaultFun
Blake2b_224                     -> Word8
72

              DefaultFun
IntegerToByteString             -> Word8
73
              DefaultFun
ByteStringToInteger             -> Word8
74
              DefaultFun
AndByteString                   -> Word8
75
              DefaultFun
OrByteString                    -> Word8
76
              DefaultFun
XorByteString                   -> Word8
77
              DefaultFun
ComplementByteString            -> Word8
78
              DefaultFun
ReadBit                         -> Word8
79
              DefaultFun
WriteBits                       -> Word8
80
              DefaultFun
ReplicateByte                   -> Word8
81

              DefaultFun
ShiftByteString                 -> Word8
82
              DefaultFun
RotateByteString                -> Word8
83
              DefaultFun
CountSetBits                    -> Word8
84
              DefaultFun
FindFirstSetBit                 -> Word8
85
              DefaultFun
Ripemd_160                      -> Word8
86

              DefaultFun
ExpModInteger           -> Word8
87

    decode :: Get DefaultFun
decode = Word8 -> Get DefaultFun
forall {a} {f :: * -> *}.
(Eq a, Num a, MonadFail f, Show a) =>
a -> f DefaultFun
go (Word8 -> Get DefaultFun) -> Get Word8 -> Get DefaultFun
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Get Word8
decodeBuiltin
        where go :: a -> f DefaultFun
go a
0  = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
AddInteger
              go a
1  = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
SubtractInteger
              go a
2  = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
MultiplyInteger
              go a
3  = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
DivideInteger
              go a
4  = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
QuotientInteger
              go a
5  = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
RemainderInteger
              go a
6  = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
ModInteger
              go a
7  = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
EqualsInteger
              go a
8  = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
LessThanInteger
              go a
9  = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
LessThanEqualsInteger
              go a
10 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
AppendByteString
              go a
11 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
ConsByteString
              go a
12 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
SliceByteString
              go a
13 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
LengthOfByteString
              go a
14 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
IndexByteString
              go a
15 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
EqualsByteString
              go a
16 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
LessThanByteString
              go a
17 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
LessThanEqualsByteString
              go a
18 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Sha2_256
              go a
19 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Sha3_256
              go a
20 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Blake2b_256
              go a
21 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
VerifyEd25519Signature
              go a
22 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
AppendString
              go a
23 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
EqualsString
              go a
24 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
EncodeUtf8
              go a
25 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
DecodeUtf8
              go a
26 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
IfThenElse
              go a
27 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
ChooseUnit
              go a
28 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Trace
              go a
29 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
FstPair
              go a
30 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
SndPair
              go a
31 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
ChooseList
              go a
32 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
MkCons
              go a
33 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
HeadList
              go a
34 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
TailList
              go a
35 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
NullList
              go a
36 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
ChooseData
              go a
37 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
ConstrData
              go a
38 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
MapData
              go a
39 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
ListData
              go a
40 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
IData
              go a
41 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
BData
              go a
42 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
UnConstrData
              go a
43 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
UnMapData
              go a
44 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
UnListData
              go a
45 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
UnIData
              go a
46 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
UnBData
              go a
47 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
EqualsData
              go a
48 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
MkPairData
              go a
49 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
MkNilData
              go a
50 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
MkNilPairData
              go a
51 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
SerialiseData
              go a
52 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
VerifyEcdsaSecp256k1Signature
              go a
53 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
VerifySchnorrSecp256k1Signature
              go a
54 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Bls12_381_G1_add
              go a
55 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Bls12_381_G1_neg
              go a
56 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Bls12_381_G1_scalarMul
              go a
57 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Bls12_381_G1_equal
              go a
58 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Bls12_381_G1_compress
              go a
59 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Bls12_381_G1_uncompress
              go a
60 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Bls12_381_G1_hashToGroup
              go a
61 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Bls12_381_G2_add
              go a
62 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Bls12_381_G2_neg
              go a
63 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Bls12_381_G2_scalarMul
              go a
64 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Bls12_381_G2_equal
              go a
65 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Bls12_381_G2_compress
              go a
66 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Bls12_381_G2_uncompress
              go a
67 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Bls12_381_G2_hashToGroup
              go a
68 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Bls12_381_millerLoop
              go a
69 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Bls12_381_mulMlResult
              go a
70 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Bls12_381_finalVerify
              go a
71 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Keccak_256
              go a
72 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Blake2b_224
              go a
73 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
IntegerToByteString
              go a
74 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
ByteStringToInteger
              go a
75 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
AndByteString
              go a
76 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
OrByteString
              go a
77 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
XorByteString
              go a
78 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
ComplementByteString
              go a
79 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
ReadBit
              go a
80 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
WriteBits
              go a
81 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
ReplicateByte
              go a
82 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
ShiftByteString
              go a
83 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
RotateByteString
              go a
84 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
CountSetBits
              go a
85 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
FindFirstSetBit
              go a
86 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
Ripemd_160
              go a
87 = DefaultFun -> f DefaultFun
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure DefaultFun
ExpModInteger
              go a
t  = String -> f DefaultFun
forall a. String -> f a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> f DefaultFun) -> String -> f DefaultFun
forall a b. (a -> b) -> a -> b
$ String
"Failed to decode builtin tag, got: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
t

    size :: DefaultFun -> Int -> Int
size DefaultFun
_ Int
n = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
builtinTagWidth