plutus-tx-1.34.0.0: Libraries for Plutus Tx and its prelude
Safe HaskellSafe-Inferred
LanguageHaskell2010

PlutusTx.Builtins

Description

Primitive names and functions for working with Plutus Core builtins.

Synopsis

Bytestring builtins

data BuiltinByteString Source #

An opaque type representing Plutus Core ByteStrings.

Instances

Instances details
Data BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

gfoldl ∷ (∀ d b. Data d ⇒ c (d → b) → d → c b) → (∀ g. g → c g) → BuiltinByteString → c BuiltinByteString Source #

gunfold ∷ (∀ b r. Data b ⇒ c (b → r) → c r) → (∀ r. r → c r) → Constr → c BuiltinByteString Source #

toConstrBuiltinByteStringConstr Source #

dataTypeOfBuiltinByteStringDataType Source #

dataCast1Typeable t ⇒ (∀ d. Data d ⇒ c (t d)) → Maybe (c BuiltinByteString) Source #

dataCast2Typeable t ⇒ (∀ d e. (Data d, Data e) ⇒ c (t d e)) → Maybe (c BuiltinByteString) Source #

gmapT ∷ (∀ b. Data b ⇒ b → b) → BuiltinByteStringBuiltinByteString Source #

gmapQl ∷ (r → r' → r) → r → (∀ d. Data d ⇒ d → r') → BuiltinByteString → r Source #

gmapQr ∷ ∀ r r'. (r' → r → r) → r → (∀ d. Data d ⇒ d → r') → BuiltinByteString → r Source #

gmapQ ∷ (∀ d. Data d ⇒ d → u) → BuiltinByteString → [u] Source #

gmapQiInt → (∀ d. Data d ⇒ d → u) → BuiltinByteString → u Source #

gmapMMonad m ⇒ (∀ d. Data d ⇒ d → m d) → BuiltinByteString → m BuiltinByteString Source #

gmapMpMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → BuiltinByteString → m BuiltinByteString Source #

gmapMoMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → BuiltinByteString → m BuiltinByteString Source #

IsString BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

Monoid BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Semigroup BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Show BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

NFData BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

rnfBuiltinByteString → () Source #

Eq BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Ord BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Hashable BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

ByteArray BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

allocRetInt → (Ptr p → IO a) → IO (a, BuiltinByteString) Source #

ByteArrayAccess BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

HasBlueprintDefinition BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Blueprint.Definition.Unroll

Associated Types

type Unroll BuiltinByteString ∷ [Type] Source #

HasFromBuiltin BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.HasBuiltin

Associated Types

type FromBuiltin BuiltinByteString Source #

Eq BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Eq

FromData BuiltinByteString Source # 
Instance details

Defined in PlutusTx.IsData.Class

ToData BuiltinByteString Source # 
Instance details

Defined in PlutusTx.IsData.Class

UnsafeFromData BuiltinByteString Source # 
Instance details

Defined in PlutusTx.IsData.Class

Monoid BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Monoid

Ord BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Ord

Semigroup BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Semigroup

Show BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Show

Pretty BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Serialise BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

HasBlueprintSchema BuiltinByteString referencedTypes Source # 
Instance details

Defined in PlutusTx.Blueprint.Class

Methods

schemaSchema referencedTypes Source #

HasFromOpaque BuiltinByteString BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

HasToOpaque BuiltinByteString BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

HasTermLevel uni ByteStringLift uni BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Lift.Class

Methods

liftBuiltinByteStringRTCompile uni fun (Term TyName Name uni fun ()) Source #

HasTypeLevel uni ByteStringTypeable uni BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Lift.Class

Methods

typeRepProxy BuiltinByteStringRTCompile uni fun (Type TyName uni ()) Source #

type Unroll BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Blueprint.Definition.Unroll

type FromBuiltin BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.HasBuiltin

consByteStringIntegerBuiltinByteStringBuiltinByteString Source #

Adds a byte to the front of a ByteString.

sliceByteStringIntegerIntegerBuiltinByteStringBuiltinByteString Source #

Returns the substring of a ByteString from index start of length n.

lengthOfByteStringBuiltinByteStringInteger Source #

Returns the length of a ByteString.

indexByteStringBuiltinByteStringIntegerInteger Source #

Returns the byte of a ByteString at index.

emptyByteStringBuiltinByteString Source #

An empty ByteString.

equalsByteStringBuiltinByteStringBuiltinByteStringBool Source #

Check if two ByteStrings are equal.

lessThanByteStringBuiltinByteStringBuiltinByteStringBool Source #

Check if one ByteString is less than another.

lessThanEqualsByteStringBuiltinByteStringBuiltinByteStringBool Source #

Check if one ByteString is less than or equal to another.

greaterThanByteStringBuiltinByteStringBuiltinByteStringBool Source #

Check if one ByteString is greater than another.

greaterThanEqualsByteStringBuiltinByteStringBuiltinByteStringBool Source #

Check if one ByteString is greater than another.

sha2_256BuiltinByteStringBuiltinByteString Source #

The SHA2-256 hash of a ByteString

sha3_256BuiltinByteStringBuiltinByteString Source #

The SHA3-256 hash of a ByteString

blake2b_224BuiltinByteStringBuiltinByteString Source #

The BLAKE2B-224 hash of a ByteString

blake2b_256BuiltinByteStringBuiltinByteString Source #

The BLAKE2B-256 hash of a ByteString

keccak_256BuiltinByteStringBuiltinByteString Source #

The KECCAK-256 hash of a ByteString

ripemd_160BuiltinByteStringBuiltinByteString Source #

The RIPEMD-160 hash of a ByteString

verifyEd25519Signature Source #

Arguments

BuiltinByteString

Public Key (32 bytes)

BuiltinByteString

Message (arbirtary length)

BuiltinByteString

Signature (64 bytes)

Bool 

Ed25519 signature verification. Verify that the signature is a signature of the message by the public key. This will fail if key or the signature are not of the expected length.

verifyEcdsaSecp256k1Signature Source #

Arguments

BuiltinByteString

Verification key (33 bytes)

BuiltinByteString

Message hash (32 bytes)

BuiltinByteString

Signature (64 bytes)

Bool 

Given an ECDSA SECP256k1 verification key, an ECDSA SECP256k1 signature, and an ECDSA SECP256k1 message hash (all as BuiltinByteStrings), verify the hash with that key and signature.

Note

There are additional well-formation requirements for the arguments beyond their length:

  • The first byte of the public key must correspond to the sign of the y coordinate: this is 0x02 if y is even, and 0x03 otherwise.
  • The remaining bytes of the public key must correspond to the x coordinate, as a big-endian integer.
  • The first 32 bytes of the signature must correspond to the big-endian integer representation of _r_.
  • The last 32 bytes of the signature must correspond to the big-endian integer representation of _s_.

While this primitive accepts a hash, any caller should only pass it hashes that they computed themselves: specifically, they should receive the message from a sender and hash it, rather than receiving the hash from said sender. Failure to do so can be dangerous. Other than length, we make no requirements of what hash gets used.

See also

verifySchnorrSecp256k1Signature Source #

Arguments

BuiltinByteString

Verification key (32 bytes)

BuiltinByteString

Message (arbitrary length)

BuiltinByteString

Signature (64 bytes)

Bool 

Given a Schnorr SECP256k1 verification key, a Schnorr SECP256k1 signature, and a message (all as BuiltinByteStrings), verify the message with that key and signature.

Note

There are additional well-formation requirements for the arguments beyond their length. Throughout, we refer to co-ordinates of the point R.

  • The bytes of the public key must correspond to the x coordinate, as a big-endian integer, as specified in BIP-340.
  • The first 32 bytes of the signature must correspond to the x coordinate, as a big-endian integer, as specified in BIP-340.
  • The last 32 bytes of the signature must correspond to the bytes of s, as a big-endian integer, as specified in BIP-340.

See also

decodeUtf8BuiltinByteStringBuiltinString Source #

Converts a ByteString to a String.

Integer builtins

data Integer Source #

Arbitrary precision integers. In contrast with fixed-size integral types such as Int, the Integer type represents the entire infinite range of integers.

Integers are stored in a kind of sign-magnitude form, hence do not expect two's complement form when using bit operations.

If the value is small (fit into an Int), IS constructor is used. Otherwise Integer and IN constructors are used to store a BigNat representing respectively the positive or the negative value magnitude.

Invariant: Integer and IN are used iff value doesn't fit in IS

Instances

Instances details
FromJSON Integer 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON ∷ Value → Parser Integer

parseJSONList ∷ Value → Parser [Integer]

omittedFieldMaybe Integer

FromJSONKey Integer 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

fromJSONKey ∷ FromJSONKeyFunction Integer

fromJSONKeyList ∷ FromJSONKeyFunction [Integer]

ToJSON Integer 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSONInteger → Value

toEncodingInteger → Encoding

toJSONList ∷ [Integer] → Value

toEncodingList ∷ [Integer] → Encoding

omitFieldIntegerBool

ToJSONKey Integer 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSONKey ∷ ToJSONKeyFunction Integer

toJSONKeyList ∷ ToJSONKeyFunction [Integer]

Data Integer

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl ∷ (∀ d b. Data d ⇒ c (d → b) → d → c b) → (∀ g. g → c g) → Integer → c Integer Source #

gunfold ∷ (∀ b r. Data b ⇒ c (b → r) → c r) → (∀ r. r → c r) → Constr → c Integer Source #

toConstrIntegerConstr Source #

dataTypeOfIntegerDataType Source #

dataCast1Typeable t ⇒ (∀ d. Data d ⇒ c (t d)) → Maybe (c Integer) Source #

dataCast2Typeable t ⇒ (∀ d e. (Data d, Data e) ⇒ c (t d e)) → Maybe (c Integer) Source #

gmapT ∷ (∀ b. Data b ⇒ b → b) → IntegerInteger Source #

gmapQl ∷ (r → r' → r) → r → (∀ d. Data d ⇒ d → r') → Integer → r Source #

gmapQr ∷ ∀ r r'. (r' → r → r) → r → (∀ d. Data d ⇒ d → r') → Integer → r Source #

gmapQ ∷ (∀ d. Data d ⇒ d → u) → Integer → [u] Source #

gmapQiInt → (∀ d. Data d ⇒ d → u) → Integer → u Source #

gmapMMonad m ⇒ (∀ d. Data d ⇒ d → m d) → Integer → m Integer Source #

gmapMpMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → Integer → m Integer Source #

gmapMoMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → Integer → m Integer Source #

Enum Integer

Since: base-2.1

Instance details

Defined in GHC.Enum

Ix Integer

Since: base-2.1

Instance details

Defined in GHC.Ix

Num Integer

Since: base-2.1

Instance details

Defined in GHC.Num

Read Integer

Since: base-2.1

Instance details

Defined in GHC.Read

Integral Integer

Since: base-2.0.1

Instance details

Defined in GHC.Real

Real Integer

Since: base-2.0.1

Instance details

Defined in GHC.Real

Show Integer

Since: base-2.1

Instance details

Defined in GHC.Show

Subtractive Integer 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Integer

Methods

(-)IntegerInteger → Difference Integer

Default Integer 
Instance details

Defined in Data.Default.Class

Methods

defInteger Source #

NFData Integer 
Instance details

Defined in Control.DeepSeq

Methods

rnfInteger → () Source #

Eq Integer 
Instance details

Defined in GHC.Num.Integer

Methods

(==)IntegerIntegerBool Source #

(/=)IntegerIntegerBool Source #

Ord Integer 
Instance details

Defined in GHC.Num.Integer

Hashable Integer 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSaltIntIntegerInt Source #

hashIntegerInt Source #

HasBlueprintDefinition Integer Source # 
Instance details

Defined in PlutusTx.Blueprint.Definition.Unroll

Associated Types

type Unroll Integer ∷ [Type] Source #

HasFromBuiltin BuiltinInteger Source # 
Instance details

Defined in PlutusTx.Builtins.HasBuiltin

Associated Types

type FromBuiltin BuiltinInteger Source #

HasToBuiltin Integer Source # 
Instance details

Defined in PlutusTx.Builtins.HasBuiltin

Associated Types

type ToBuiltin Integer Source #

MkNil BuiltinInteger Source # 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

Enum Integer Source # 
Instance details

Defined in PlutusTx.Enum

Eq Integer Source # 
Instance details

Defined in PlutusTx.Eq

Methods

(==)IntegerIntegerBool Source #

FromData Integer Source # 
Instance details

Defined in PlutusTx.IsData.Class

ToData Integer Source # 
Instance details

Defined in PlutusTx.IsData.Class

UnsafeFromData Integer Source # 
Instance details

Defined in PlutusTx.IsData.Class

AdditiveGroup Integer Source # 
Instance details

Defined in PlutusTx.Numeric

Methods

(-)IntegerIntegerInteger Source #

AdditiveMonoid Integer Source # 
Instance details

Defined in PlutusTx.Numeric

Methods

zeroInteger Source #

AdditiveSemigroup Integer Source # 
Instance details

Defined in PlutusTx.Numeric

Methods

(+)IntegerIntegerInteger Source #

MultiplicativeMonoid Integer Source # 
Instance details

Defined in PlutusTx.Numeric

Methods

oneInteger Source #

MultiplicativeSemigroup Integer Source # 
Instance details

Defined in PlutusTx.Numeric

Methods

(*)IntegerIntegerInteger Source #

Ord Integer Source # 
Instance details

Defined in PlutusTx.Ord

Show Integer Source # 
Instance details

Defined in PlutusTx.Show

Pretty Integer
>>> pretty (2^123 :: Integer)
10633823966279326983230456482242756608
Instance details

Defined in Prettyprinter.Internal

Methods

prettyIntegerDoc ann Source #

prettyList ∷ [Integer] → Doc ann Source #

UniformRange Integer 
Instance details

Defined in System.Random.Internal

Methods

uniformRMStatefulGen g m ⇒ (Integer, Integer) → g → m Integer Source #

Serialise Integer

Since: serialise-0.2.0.0

Instance details

Defined in Codec.Serialise.Class

Pretty Rational 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

prettyRational → Doc b

prettyList ∷ [Rational] → Doc b

Pretty Integer 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

prettyInteger → Doc b

prettyList ∷ [Integer] → Doc b

HasBlueprintSchema Integer referencedTypes Source # 
Instance details

Defined in PlutusTx.Blueprint.Class

Methods

schemaSchema referencedTypes Source #

HasFromOpaque BuiltinInteger BuiltinInteger Source # 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

HasToOpaque BuiltinInteger BuiltinInteger Source # 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

HasTermLevel uni IntegerLift uni BuiltinInteger Source # 
Instance details

Defined in PlutusTx.Lift.Class

Methods

liftBuiltinIntegerRTCompile uni fun (Term TyName Name uni fun ()) Source #

Module Integer Rational Source # 
Instance details

Defined in PlutusTx.Ratio

Methods

scaleIntegerRationalRational Source #

DefaultPrettyBy config Integer 
Instance details

Defined in Text.PrettyBy.Internal

Methods

defaultPrettyBy ∷ config → IntegerDoc ann Source #

defaultPrettyListBy ∷ config → [Integer] → Doc ann Source #

NonDefaultPrettyBy ConstConfig Integer 
Instance details

Defined in PlutusCore.Pretty.PrettyConst

PrettyDefaultBy config IntegerPrettyBy config Integer
>>> prettyBy () (2^(123 :: Int) :: Integer)
10633823966279326983230456482242756608
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy ∷ config → IntegerDoc ann Source #

prettyListBy ∷ config → [Integer] → Doc ann Source #

Lift Integer 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

liftQuote m ⇒ Integer → m Exp Source #

liftTyped ∷ ∀ (m ∷ TypeType). Quote m ⇒ IntegerCode m Integer Source #

KnownBuiltinTypeIn DefaultUni term IntegerMakeKnownIn DefaultUni term Integer 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnownIntegerBuiltinResult term Source #

KnownBuiltinTypeIn DefaultUni term IntegerReadKnownIn DefaultUni term Integer 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown ∷ term → ReadKnownM Integer Source #

Contains DefaultUni Integer 
Instance details

Defined in PlutusCore.Default.Universe

HasTypeLevel uni IntegerTypeable uni BuiltinInteger Source # 
Instance details

Defined in PlutusTx.Lift.Class

Methods

typeRepProxy BuiltinIntegerRTCompile uni fun (Type TyName uni ()) Source #

KnownNat n ⇒ Reifies (n ∷ Nat) Integer 
Instance details

Defined in Data.Reflection

Methods

reflect ∷ proxy n → Integer

KnownBuiltinTypeAst tyname DefaultUni IntegerKnownTypeAst tyname DefaultUni Integer 
Instance details

Defined in PlutusCore.Default.Universe

Methods

typeAstType tyname DefaultUni () Source #

type Difference Integer 
Instance details

Defined in Basement.Numerical.Subtractive

type Difference Integer = Integer
type Unroll Integer Source # 
Instance details

Defined in PlutusTx.Blueprint.Definition.Unroll

type FromBuiltin BuiltinInteger Source # 
Instance details

Defined in PlutusTx.Builtins.HasBuiltin

type ToBuiltin Integer Source # 
Instance details

Defined in PlutusTx.Builtins.HasBuiltin

type IsBuiltin DefaultUni Integer 
Instance details

Defined in PlutusCore.Default.Universe

type ToHoles DefaultUni Integer 
Instance details

Defined in PlutusCore.Default.Universe

type ToBinds DefaultUni acc Integer 
Instance details

Defined in PlutusCore.Default.Universe

divideIntegerIntegerIntegerInteger Source #

Divide two integers.

modIntegerIntegerIntegerInteger Source #

Integer modulo operation.

quotientIntegerIntegerIntegerInteger Source #

Quotient of two integers.

remainderIntegerIntegerIntegerInteger Source #

Take the remainder of dividing two Integers.

greaterThanIntegerIntegerIntegerBool Source #

Check whether one Integer is greater than another.

greaterThanEqualsIntegerIntegerIntegerBool Source #

Check whether one Integer is greater than or equal to another.

lessThanIntegerIntegerIntegerBool Source #

Check whether one Integer is less than another.

lessThanEqualsIntegerIntegerIntegerBool Source #

Check whether one Integer is less than or equal to another.

equalsIntegerIntegerIntegerBool Source #

Check if two Integers are equal.

Error

error ∷ () → a Source #

Aborts evaluation with an error.

Data

data BuiltinData Source #

A type corresponding to the Plutus Core builtin equivalent of Data.

The point of this type is to be an opaque equivalent of Data, so as to ensure that it is only used in ways that the compiler can handle.

As such, you should use this type in your on-chain code, and in any data structures that you want to be representable on-chain.

For off-chain usage, there are conversion functions builtinDataToData and dataToBuiltinData, but note that these will not work on-chain.

Instances

Instances details
Data BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

gfoldl ∷ (∀ d b. Data d ⇒ c (d → b) → d → c b) → (∀ g. g → c g) → BuiltinData → c BuiltinData Source #

gunfold ∷ (∀ b r. Data b ⇒ c (b → r) → c r) → (∀ r. r → c r) → Constr → c BuiltinData Source #

toConstrBuiltinDataConstr Source #

dataTypeOfBuiltinDataDataType Source #

dataCast1Typeable t ⇒ (∀ d. Data d ⇒ c (t d)) → Maybe (c BuiltinData) Source #

dataCast2Typeable t ⇒ (∀ d e. (Data d, Data e) ⇒ c (t d e)) → Maybe (c BuiltinData) Source #

gmapT ∷ (∀ b. Data b ⇒ b → b) → BuiltinDataBuiltinData Source #

gmapQl ∷ (r → r' → r) → r → (∀ d. Data d ⇒ d → r') → BuiltinData → r Source #

gmapQr ∷ ∀ r r'. (r' → r → r) → r → (∀ d. Data d ⇒ d → r') → BuiltinData → r Source #

gmapQ ∷ (∀ d. Data d ⇒ d → u) → BuiltinData → [u] Source #

gmapQiInt → (∀ d. Data d ⇒ d → u) → BuiltinData → u Source #

gmapMMonad m ⇒ (∀ d. Data d ⇒ d → m d) → BuiltinData → m BuiltinData Source #

gmapMpMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → BuiltinData → m BuiltinData Source #

gmapMoMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → BuiltinData → m BuiltinData Source #

Generic BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Associated Types

type Rep BuiltinDataTypeType Source #

Show BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

NFData BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

rnfBuiltinData → () Source #

Eq BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Ord BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

HasBlueprintDefinition BuiltinData Source # 
Instance details

Defined in PlutusTx.Blueprint.Definition.Unroll

Associated Types

type Unroll BuiltinData ∷ [Type] Source #

HasFromBuiltin BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.HasBuiltin

Associated Types

type FromBuiltin BuiltinData Source #

MkNil BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

Eq BuiltinData Source # 
Instance details

Defined in PlutusTx.Eq

FromData BuiltinData Source # 
Instance details

Defined in PlutusTx.IsData.Class

ToData BuiltinData Source # 
Instance details

Defined in PlutusTx.IsData.Class

UnsafeFromData BuiltinData Source # 
Instance details

Defined in PlutusTx.IsData.Class

Show BuiltinData Source # 
Instance details

Defined in PlutusTx.Show

Pretty BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

prettyBuiltinDataDoc ann Source #

prettyList ∷ [BuiltinData] → Doc ann Source #

HasBlueprintSchema BuiltinData referencedTypes Source # 
Instance details

Defined in PlutusTx.Blueprint.Class

Methods

schemaSchema referencedTypes Source #

HasFromOpaque BuiltinData BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

HasToOpaque BuiltinData BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

HasTermLevel uni DataLift uni BuiltinData Source # 
Instance details

Defined in PlutusTx.Lift.Class

Methods

liftBuiltinDataRTCompile uni fun (Term TyName Name uni fun ()) Source #

HasTypeLevel uni DataTypeable uni BuiltinData Source # 
Instance details

Defined in PlutusTx.Lift.Class

Methods

typeRepProxy BuiltinDataRTCompile uni fun (Type TyName uni ()) Source #

MkNil (BuiltinPair BuiltinData BuiltinData) Source # 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

HasToOpaque (BuiltinData, BuiltinData) (BuiltinPair BuiltinData BuiltinData) Source # 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

type Rep BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

type Rep BuiltinData = D1 ('MetaData "BuiltinData" "PlutusTx.Builtins.Internal" "plutus-tx-1.34.0.0-inplace" 'False) (C1 ('MetaCons "BuiltinData" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceLazy 'DecidedLazy) (Rec0 Data)))
type Unroll BuiltinData Source # 
Instance details

Defined in PlutusTx.Blueprint.Definition.Unroll

type FromBuiltin BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.HasBuiltin

chooseData ∷ ∀ a. BuiltinData → a → a → a → a → a → a Source #

Given five values for the five different constructors of BuiltinData, selects one depending on which corresponds to the actual constructor of the given value.

matchDataBuiltinData → (Integer → [BuiltinData] → r) → ([(BuiltinData, BuiltinData)] → r) → ([BuiltinData] → r) → (Integer → r) → (BuiltinByteString → r) → r Source #

Given a BuiltinData value and matching functions for the five constructors, applies the appropriate matcher to the arguments of the constructor and returns the result.

matchData'BuiltinData → (IntegerBuiltinList BuiltinData → r) → (BuiltinList (BuiltinPair BuiltinData BuiltinData) → r) → (BuiltinList BuiltinData → r) → (Integer → r) → (BuiltinByteString → r) → r Source #

Given a BuiltinData value and matching functions for the five constructors, applies the appropriate matcher to the arguments of the constructor and returns the result.

equalsDataBuiltinDataBuiltinDataBool Source #

Check if two BuiltinDatas are equal.

serialiseDataBuiltinDataBuiltinByteString Source #

Convert a String into a ByteString.

mkConstrInteger → [BuiltinData] → BuiltinData Source #

Constructs a BuiltinData value with the Constr constructor.

mkMap ∷ [(BuiltinData, BuiltinData)] → BuiltinData Source #

Constructs a BuiltinData value with the Map constructor.

mkList ∷ [BuiltinData] → BuiltinData Source #

Constructs a BuiltinData value with the List constructor.

mkIIntegerBuiltinData Source #

Constructs a BuiltinData value with the I constructor.

mkBBuiltinByteStringBuiltinData Source #

Constructs a BuiltinData value with the B constructor.

unsafeDataAsConstrBuiltinData → (Integer, [BuiltinData]) Source #

Deconstructs a BuiltinData as a Constr, or fails if it is not one.

unsafeDataAsMapBuiltinData → [(BuiltinData, BuiltinData)] Source #

Deconstructs a BuiltinData as a Map, or fails if it is not one.

unsafeDataAsListBuiltinData → [BuiltinData] Source #

Deconstructs a BuiltinData as a List, or fails if it is not one.

unsafeDataAsIBuiltinDataInteger Source #

Deconstructs a BuiltinData as an I, or fails if it is not one.

unsafeDataAsBBuiltinDataBuiltinByteString Source #

Deconstructs a BuiltinData as a B, or fails if it is not one.

builtinDataToDataBuiltinDataData Source #

Convert a BuiltinData into a Data. Only works off-chain.

dataToBuiltinDataDataBuiltinData Source #

Convert a Data into a BuiltinData. Only works off-chain.

Strings

data BuiltinString Source #

Instances

Instances details
Data BuiltinString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

gfoldl ∷ (∀ d b. Data d ⇒ c (d → b) → d → c b) → (∀ g. g → c g) → BuiltinString → c BuiltinString Source #

gunfold ∷ (∀ b r. Data b ⇒ c (b → r) → c r) → (∀ r. r → c r) → Constr → c BuiltinString Source #

toConstrBuiltinStringConstr Source #

dataTypeOfBuiltinStringDataType Source #

dataCast1Typeable t ⇒ (∀ d. Data d ⇒ c (t d)) → Maybe (c BuiltinString) Source #

dataCast2Typeable t ⇒ (∀ d e. (Data d, Data e) ⇒ c (t d e)) → Maybe (c BuiltinString) Source #

gmapT ∷ (∀ b. Data b ⇒ b → b) → BuiltinStringBuiltinString Source #

gmapQl ∷ (r → r' → r) → r → (∀ d. Data d ⇒ d → r') → BuiltinString → r Source #

gmapQr ∷ ∀ r r'. (r' → r → r) → r → (∀ d. Data d ⇒ d → r') → BuiltinString → r Source #

gmapQ ∷ (∀ d. Data d ⇒ d → u) → BuiltinString → [u] Source #

gmapQiInt → (∀ d. Data d ⇒ d → u) → BuiltinString → u Source #

gmapMMonad m ⇒ (∀ d. Data d ⇒ d → m d) → BuiltinString → m BuiltinString Source #

gmapMpMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → BuiltinString → m BuiltinString Source #

gmapMoMonadPlus m ⇒ (∀ d. Data d ⇒ d → m d) → BuiltinString → m BuiltinString Source #

IsString BuiltinString Source # 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

Show BuiltinString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Eq BuiltinString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Ord BuiltinString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

HasBlueprintDefinition BuiltinString Source # 
Instance details

Defined in PlutusTx.Blueprint.Definition.Unroll

Associated Types

type Unroll BuiltinString ∷ [Type] Source #

HasFromBuiltin BuiltinString Source # 
Instance details

Defined in PlutusTx.Builtins.HasBuiltin

Associated Types

type FromBuiltin BuiltinString Source #

Eq BuiltinString Source # 
Instance details

Defined in PlutusTx.Eq

Monoid BuiltinString Source # 
Instance details

Defined in PlutusTx.Monoid

Semigroup BuiltinString Source # 
Instance details

Defined in PlutusTx.Semigroup

Show BuiltinString Source # 
Instance details

Defined in PlutusTx.Show

HasBlueprintSchema BuiltinString referencedTypes Source # 
Instance details

Defined in PlutusTx.Blueprint.Class

Methods

schemaSchema referencedTypes Source #

HasFromOpaque BuiltinString BuiltinString Source # 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

HasToOpaque BuiltinString BuiltinString Source # 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

HasTermLevel uni TextLift uni BuiltinString Source # 
Instance details

Defined in PlutusTx.Lift.Class

Methods

liftBuiltinStringRTCompile uni fun (Term TyName Name uni fun ()) Source #

HasTypeLevel uni TextTypeable uni BuiltinString Source # 
Instance details

Defined in PlutusTx.Lift.Class

Methods

typeRepProxy BuiltinStringRTCompile uni fun (Type TyName uni ()) Source #

type Unroll BuiltinString Source # 
Instance details

Defined in PlutusTx.Blueprint.Definition.Unroll

type FromBuiltin BuiltinString Source # 
Instance details

Defined in PlutusTx.Builtins.HasBuiltin

emptyStringBuiltinString Source #

An empty String.

equalsStringBuiltinStringBuiltinStringBool Source #

Check if two strings are equal

encodeUtf8BuiltinStringBuiltinByteString Source #

Convert a String into a ByteString.

Pairs

pairToPairBuiltinPair a b → (a, b) Source #

Turn a builtin pair into a normal pair, useful in patterns.

Lists

mkNilMkNil arep ⇒ BuiltinList arep Source #

mkNilOpaqueBuiltinList a Source #

The empty list of elements of the given type that gets spotted by the plugin (grep for mkNilOpaque in the plugin code) and replaced by the actual empty list constant for types that are supported (a subset of built-in types).

null ∷ ∀ a. BuiltinList a → Bool Source #

matchList ∷ ∀ a r. BuiltinList a → (() → r) → (a → BuiltinList a → r) → r Source #

matchList' ∷ ∀ a r. BuiltinList a → r → (a → BuiltinList a → r) → r Source #

Like matchList but evaluates nilCase strictly.

headBuiltinList a → a Source #

unconsBuiltinList a → Maybe (a, BuiltinList a) Source #

Uncons a builtin list, failing if the list is empty, useful in patterns.

unsafeUnconsBuiltinList a → (a, BuiltinList a) Source #

Uncons a builtin list, failing if the list is empty, useful in patterns.

Tracing

traceBuiltinString → a → a Source #

Emit the given string as a trace message before evaluating the argument.

BLS12_381

data BuiltinBLS12_381_G1_Element Source #

Instances

Instances details
Show BuiltinBLS12_381_G1_Element Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

NFData BuiltinBLS12_381_G1_Element Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Eq BuiltinBLS12_381_G1_Element Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

HasFromBuiltin BuiltinBLS12_381_G1_Element Source # 
Instance details

Defined in PlutusTx.Builtins.HasBuiltin

Eq BuiltinBLS12_381_G1_Element Source # 
Instance details

Defined in PlutusTx.Eq

FromData BuiltinBLS12_381_G1_Element Source # 
Instance details

Defined in PlutusTx.IsData.Class

ToData BuiltinBLS12_381_G1_Element Source #

For the BLS12-381 G1 and G2 types we use the compress functions to convert to a ByteString and then encode that as Data as usual. We have to be more careful going the other way because we decode a Data object to (possibly) get a BuiltinByteString and then uncompress the underlying ByteString to get a group element. However uncompression can fail so we have to check what happens: we don't use bls12_381_G?_uncompress because that invokes error if something goes wrong (but we do use it for unsafeFromData).

Instance details

Defined in PlutusTx.IsData.Class

UnsafeFromData BuiltinBLS12_381_G1_Element Source # 
Instance details

Defined in PlutusTx.IsData.Class

Pretty BuiltinBLS12_381_G1_Element Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

HasFromOpaque BuiltinBLS12_381_G1_Element BuiltinBLS12_381_G1_Element Source # 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

HasToOpaque BuiltinBLS12_381_G1_Element BuiltinBLS12_381_G1_Element Source # 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

HasTermLevel uni ElementLift uni BuiltinBLS12_381_G1_Element Source # 
Instance details

Defined in PlutusTx.Lift.Class

Methods

liftBuiltinBLS12_381_G1_ElementRTCompile uni fun (Term TyName Name uni fun ()) Source #

HasTypeLevel uni ElementTypeable uni BuiltinBLS12_381_G1_Element Source # 
Instance details

Defined in PlutusTx.Lift.Class

type FromBuiltin BuiltinBLS12_381_G1_Element Source # 
Instance details

Defined in PlutusTx.Builtins.HasBuiltin

data BuiltinBLS12_381_G2_Element Source #

Instances

Instances details
Show BuiltinBLS12_381_G2_Element Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

NFData BuiltinBLS12_381_G2_Element Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Eq BuiltinBLS12_381_G2_Element Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

HasFromBuiltin BuiltinBLS12_381_G2_Element Source # 
Instance details

Defined in PlutusTx.Builtins.HasBuiltin

Eq BuiltinBLS12_381_G2_Element Source # 
Instance details

Defined in PlutusTx.Eq

FromData BuiltinBLS12_381_G2_Element Source # 
Instance details

Defined in PlutusTx.IsData.Class

ToData BuiltinBLS12_381_G2_Element Source # 
Instance details

Defined in PlutusTx.IsData.Class

UnsafeFromData BuiltinBLS12_381_G2_Element Source # 
Instance details

Defined in PlutusTx.IsData.Class

Pretty BuiltinBLS12_381_G2_Element Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

HasFromOpaque BuiltinBLS12_381_G2_Element BuiltinBLS12_381_G2_Element Source # 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

HasToOpaque BuiltinBLS12_381_G2_Element BuiltinBLS12_381_G2_Element Source # 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

HasTermLevel uni ElementLift uni BuiltinBLS12_381_G2_Element Source # 
Instance details

Defined in PlutusTx.Lift.Class

Methods

liftBuiltinBLS12_381_G2_ElementRTCompile uni fun (Term TyName Name uni fun ()) Source #

HasTypeLevel uni ElementTypeable uni BuiltinBLS12_381_G2_Element Source # 
Instance details

Defined in PlutusTx.Lift.Class

type FromBuiltin BuiltinBLS12_381_G2_Element Source # 
Instance details

Defined in PlutusTx.Builtins.HasBuiltin

data BuiltinBLS12_381_MlResult Source #

Instances

Instances details
Show BuiltinBLS12_381_MlResult Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

NFData BuiltinBLS12_381_MlResult Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Eq BuiltinBLS12_381_MlResult Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

HasFromBuiltin BuiltinBLS12_381_MlResult Source # 
Instance details

Defined in PlutusTx.Builtins.HasBuiltin

(TypeError ('Text "fromBuiltinData is not supported for BuiltinBLS12_381_MlResult") ∷ Constraint) ⇒ FromData BuiltinBLS12_381_MlResult Source # 
Instance details

Defined in PlutusTx.IsData.Class

(TypeError ('Text "toBuiltinData is not supported for BuiltinBLS12_381_MlResult") ∷ Constraint) ⇒ ToData BuiltinBLS12_381_MlResult Source #

We do not provide instances of any of these classes for BuiltinBLS12_381_MlResult since there is no serialisation format: we expect that values of that type will only occur as the result of on-chain computations.

Instance details

Defined in PlutusTx.IsData.Class

(TypeError ('Text "unsafeFromBuiltinData is not supported for BuiltinBLS12_381_MlResult") ∷ Constraint) ⇒ UnsafeFromData BuiltinBLS12_381_MlResult Source # 
Instance details

Defined in PlutusTx.IsData.Class

Pretty BuiltinBLS12_381_MlResult Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

HasFromOpaque BuiltinBLS12_381_MlResult BuiltinBLS12_381_MlResult Source # 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

HasToOpaque BuiltinBLS12_381_MlResult BuiltinBLS12_381_MlResult Source # 
Instance details

Defined in PlutusTx.Builtins.HasOpaque

HasTermLevel uni MlResultLift uni BuiltinBLS12_381_MlResult Source # 
Instance details

Defined in PlutusTx.Lift.Class

Methods

liftBuiltinBLS12_381_MlResultRTCompile uni fun (Term TyName Name uni fun ()) Source #

HasTypeLevel uni MlResultTypeable uni BuiltinBLS12_381_MlResult Source # 
Instance details

Defined in PlutusTx.Lift.Class

type FromBuiltin BuiltinBLS12_381_MlResult Source # 
Instance details

Defined in PlutusTx.Builtins.HasBuiltin

Conversions

fromOpaqueHasFromOpaque arep a ⇒ arep → a Source #

toOpaqueHasToOpaque a arep ⇒ a → arep Source #

useToOpaque ∷ a → a Source #

useFromOpaque ∷ a → a Source #

fromBuiltinHasFromBuiltin arep ⇒ arep → FromBuiltin arep Source #

Logical

data ByteOrder Source #

Byte ordering.

Constructors

BigEndian

most-significant-byte occurs in lowest address.

LittleEndian

least-significant-byte occurs in lowest address.

Instances

Instances details
Bounded ByteOrder

Since: base-4.11.0.0

Instance details

Defined in GHC.ByteOrder

Enum ByteOrder

Since: base-4.11.0.0

Instance details

Defined in GHC.ByteOrder

Generic ByteOrder 
Instance details

Defined in GHC.ByteOrder

Associated Types

type Rep ByteOrderTypeType Source #

Read ByteOrder

Since: base-4.11.0.0

Instance details

Defined in GHC.ByteOrder

Show ByteOrder

Since: base-4.11.0.0

Instance details

Defined in GHC.ByteOrder

Eq ByteOrder

Since: base-4.11.0.0

Instance details

Defined in GHC.ByteOrder

Ord ByteOrder

Since: base-4.11.0.0

Instance details

Defined in GHC.ByteOrder

type Rep ByteOrder

Since: base-4.15.0.0

Instance details

Defined in GHC.ByteOrder

type Rep ByteOrder = D1 ('MetaData "ByteOrder" "GHC.ByteOrder" "base" 'False) (C1 ('MetaCons "BigEndian" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "LittleEndian" 'PrefixI 'False) (U1TypeType))

integerToByteStringByteOrderIntegerIntegerBuiltinByteString Source #

Convert a BuiltinInteger into a BuiltinByteString, as described in CIP-121. The first argument indicates the endianness of the conversion and the third argument is the integer to be converted, which must be non-negative. The second argument must also be non-negative and it indicates the required width of the output. If the width is zero then the output is the smallest bytestring which can contain the converted input (and in this case, the integer 0 encodes to the empty bytestring). If the width is nonzero then the output bytestring will be padded to the required width with 0x00 bytes (on the left for big-endian conversions and on the right for little-endian conversions); if the input integer is too big to fit into a bytestring of the specified width then the conversion will fail. Conversion will also fail if the specified width is greater than 8192 or the input integer is too big to fit into a bytestring of length 8192.

byteStringToIntegerByteOrderBuiltinByteStringInteger Source #

Convert a BuiltinByteString to a BuiltinInteger, as described in CIP-121. The first argument indicates the endianness of the conversion and the second is the bytestring to be converted. There is no limitation on the size of the bytestring. The empty bytestring is converted to the integer 0.

andByteStringBoolBuiltinByteStringBuiltinByteStringBuiltinByteString Source #

Perform logical AND on two BuiltinByteString arguments, as described in CIP-122.

The first argument indicates whether padding semantics should be used or not; if False, truncation semantics will be used instead.

See also

orByteStringBoolBuiltinByteStringBuiltinByteStringBuiltinByteString Source #

Perform logical OR on two BuiltinByteString arguments, as described here.

The first argument indicates whether padding semantics should be used or not; if False, truncation semantics will be used instead.

See also

xorByteStringBoolBuiltinByteStringBuiltinByteStringBuiltinByteString Source #

Perform logical XOR on two BuiltinByteString arguments, as described here.

The first argument indicates whether padding semantics should be used or not; if False, truncation semantics will be used instead.

See also

complementByteStringBuiltinByteStringBuiltinByteString Source #

Perform logical complement on a BuiltinByteString, as described here.

See also

readBitBuiltinByteStringIntegerBool Source #

Read a bit at the _bit_ index given by the Integer argument in the BuiltinByteString argument. The result will be True if the corresponding bit is set, and False if it is clear. Will error if given an out-of-bounds index argument; that is, if the index is either negative, or equal to or greater than the total number of bits in the BuiltinByteString argument.

See also

writeBitsBuiltinByteString → [Integer] → [Bool] → BuiltinByteString Source #

Given a BuiltinByteString, a list of indexes to change, and a list of values to change those indexes to, set the bit at each of the specified index as follows:

  • If the corresponding entry in the list of values is True, set that bit;
  • Otherwise, clear that bit.

Will error if any of the indexes are out-of-bounds: that is, if the index is either negative, or equal to or greater than the total number of bits in the BuiltinByteString argument.

If the two list arguments have mismatched lengths, the longer argument will be truncated to match the length of the shorter one:

  • writeBits bs [0, 1, 4] [True] is the same as writeBits bs [0] [True]
  • writeBits bs [0] [True, False, True] is the same as writeBits bs [0] [True]

Note

This differs slightly from the description of the corresponding operation in CIP-122; instead of a single changelist argument comprised of pairs, we instead pass two lists, one for indexes to change, and one for the values to change those indexes to. Effectively, we are passing the changelist argument 'unzipped'.

See also

replicateByteIntegerIntegerBuiltinByteString Source #

Given a length (first argument) and a byte (second argument), produce a BuiltinByteString of that length, with that byte in every position. Will error if given a negative length, or a second argument that isn't a byte (less than 0, greater than 255).

See also

Bitwise

countSetBitsBuiltinByteStringInteger Source #

Count the set bits in a BuiltinByteString, as per CIP-123.

findFirstSetBitBuiltinByteStringInteger Source #

Find the lowest index of a set bit in a BuiltinByteString, as per CIP-123.

If given a BuiltinByteString which consists only of zero bytes (including the empty BuiltinByteString, this returns -1.