plutus-tx-1.0.0.0: Libraries for Plutus Tx and its prelude
Safe HaskellNone
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
Eq BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Data BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BuiltinByteString -> c BuiltinByteString Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BuiltinByteString Source #

toConstr :: BuiltinByteString -> Constr Source #

dataTypeOf :: BuiltinByteString -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BuiltinByteString) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BuiltinByteString) Source #

gmapT :: (forall b. Data b => b -> b) -> BuiltinByteString -> BuiltinByteString Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BuiltinByteString -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BuiltinByteString -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> BuiltinByteString -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BuiltinByteString -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BuiltinByteString -> m BuiltinByteString Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BuiltinByteString -> m BuiltinByteString Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BuiltinByteString -> m BuiltinByteString Source #

Ord BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Show BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

IsString BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Class

Semigroup BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Monoid BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

NFData BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

rnf :: BuiltinByteString -> () Source #

Serialise BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

encode :: BuiltinByteString -> Encoding

decode :: Decoder s BuiltinByteString

encodeList :: [BuiltinByteString] -> Encoding

decodeList :: Decoder s [BuiltinByteString]

Pretty BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

pretty :: BuiltinByteString -> Doc ann

prettyList :: [BuiltinByteString] -> Doc ann

Hashable BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

ByteArray BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

allocRet :: Int -> (Ptr p -> IO a) -> IO (a, BuiltinByteString)

ByteArrayAccess BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Eq BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Eq

Ord BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Ord

Semigroup BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Semigroup

Monoid BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Monoid

UnsafeFromData BuiltinByteString Source # 
Instance details

Defined in PlutusTx.IsData.Class

FromData BuiltinByteString Source # 
Instance details

Defined in PlutusTx.IsData.Class

ToData BuiltinByteString Source # 
Instance details

Defined in PlutusTx.IsData.Class

Includes uni ByteString => Lift uni BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Lift.Instances

Methods

lift :: BuiltinByteString -> RTCompile uni fun (Term TyName Name uni fun ()) Source #

ToBuiltin ByteString BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Class

Methods

toBuiltin :: ByteString -> BuiltinByteString Source #

FromBuiltin BuiltinByteString ByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Class

Methods

fromBuiltin :: BuiltinByteString -> ByteString Source #

Includes uni ByteString => Typeable uni BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Lift.Instances

Methods

typeRep :: Proxy BuiltinByteString -> RTCompile uni fun (Type TyName uni ()) Source #

consByteString :: Integer -> BuiltinByteString -> BuiltinByteString Source #

Adds a byte to the front of a ByteString.

sliceByteString :: Integer -> Integer -> BuiltinByteString -> BuiltinByteString Source #

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

lengthOfByteString :: BuiltinByteString -> Integer Source #

Returns the length of a ByteString.

indexByteString :: BuiltinByteString -> Integer -> Integer Source #

Returns the byte of a ByteString at index.

emptyByteString :: BuiltinByteString Source #

An empty ByteString.

equalsByteString :: BuiltinByteString -> BuiltinByteString -> Bool Source #

Check if two ByteStrings are equal.

lessThanByteString :: BuiltinByteString -> BuiltinByteString -> Bool Source #

Check if one ByteString is less than another.

lessThanEqualsByteString :: BuiltinByteString -> BuiltinByteString -> Bool Source #

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

greaterThanByteString :: BuiltinByteString -> BuiltinByteString -> Bool Source #

Check if one ByteString is greater than another.

greaterThanEqualsByteString :: BuiltinByteString -> BuiltinByteString -> Bool Source #

Check if one ByteString is greater than another.

sha2_256 :: BuiltinByteString -> BuiltinByteString Source #

The SHA2-256 hash of a ByteString

sha3_256 :: BuiltinByteString -> BuiltinByteString Source #

The SHA3-256 hash of a ByteString

blake2b_256 :: BuiltinByteString -> BuiltinByteString Source #

The BLAKE2B-256 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 (64 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.

Important note

The verification key, the signature, and the message hash must all be of appropriate form and length. This function will error if any of these are not the case.

verifySchnorrSecp256k1Signature Source #

Arguments

:: BuiltinByteString

Verification key (64 bytes)

-> BuiltinByteString

Message

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

Important note

The verification key and signature must all be of appropriate form and length. This function will error if this is not the case.

decodeUtf8 :: BuiltinByteString -> BuiltinString 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.

For more information about this type's representation, see the comments in its implementation.

Instances

Instances details
Enum Integer

Since: base-2.1

Instance details

Defined in GHC.Enum

Eq Integer 
Instance details

Defined in GHC.Integer.Type

Integral Integer

Since: base-2.0.1

Instance details

Defined in GHC.Real

Data Integer

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Integer -> c Integer Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Integer Source #

toConstr :: Integer -> Constr Source #

dataTypeOf :: Integer -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Integer) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Integer) Source #

gmapT :: (forall b. Data b => b -> b) -> Integer -> Integer Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Integer -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Integer -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Integer -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Integer -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Integer -> m Integer Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Integer -> m Integer Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Integer -> m Integer Source #

Num Integer

Since: base-2.1

Instance details

Defined in GHC.Num

Ord Integer 
Instance details

Defined in GHC.Integer.Type

Read Integer

Since: base-2.1

Instance details

Defined in GHC.Read

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

Ix Integer

Since: base-2.1

Instance details

Defined in GHC.Ix

NFData Integer 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Integer -> () Source #

Serialise Integer 
Instance details

Defined in Codec.Serialise.Class

Methods

encode :: Integer -> Encoding

decode :: Decoder s Integer

encodeList :: [Integer] -> Encoding

decodeList :: Decoder s [Integer]

FromJSON Integer 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Integer

parseJSONList :: Value -> Parser [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

toJSON :: Integer -> Value

toEncoding :: Integer -> Encoding

toJSONList :: [Integer] -> Value

toEncodingList :: [Integer] -> Encoding

ToJSONKey Integer 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSONKey :: ToJSONKeyFunction Integer

toJSONKeyList :: ToJSONKeyFunction [Integer]

Pretty Integer 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Integer -> Doc ann

prettyList :: [Integer] -> Doc ann

Hashable Integer 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Integer -> Int

hash :: Integer -> Int

UniformRange Integer 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Integer, Integer) -> g -> m Integer

Pretty Integer 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

pretty :: Integer -> Doc b

prettyList :: [Integer] -> Doc b

Pretty Rational 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

Methods

pretty :: Rational -> Doc b

prettyList :: [Rational] -> Doc b

Subtractive Integer 
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Integer

Methods

(-) :: Integer -> Integer -> Difference Integer

ExMemoryUsage Integer 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Methods

memoryUsage :: Integer -> ExMemory

Eq Integer Source # 
Instance details

Defined in PlutusTx.Eq

Methods

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

Ord Integer Source # 
Instance details

Defined in PlutusTx.Ord

MultiplicativeMonoid Integer Source # 
Instance details

Defined in PlutusTx.Numeric

Methods

one :: Integer Source #

MultiplicativeSemigroup Integer Source # 
Instance details

Defined in PlutusTx.Numeric

Methods

(*) :: Integer -> Integer -> Integer Source #

AdditiveGroup Integer Source # 
Instance details

Defined in PlutusTx.Numeric

Methods

(-) :: Integer -> Integer -> Integer Source #

AdditiveMonoid Integer Source # 
Instance details

Defined in PlutusTx.Numeric

Methods

zero :: Integer Source #

AdditiveSemigroup Integer Source # 
Instance details

Defined in PlutusTx.Numeric

Methods

(+) :: Integer -> Integer -> Integer Source #

UnsafeFromData Integer Source # 
Instance details

Defined in PlutusTx.IsData.Class

FromData Integer Source # 
Instance details

Defined in PlutusTx.IsData.Class

ToData Integer Source # 
Instance details

Defined in PlutusTx.IsData.Class

Enum Integer Source # 
Instance details

Defined in PlutusTx.Enum

Lift Integer 
Instance details

Defined in Language.Haskell.TH.Syntax

PrettyDefaultBy config Integer => PrettyBy config Integer 
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy :: config -> Integer -> Doc ann

prettyListBy :: config -> [Integer] -> Doc ann

DefaultPrettyBy config Integer 
Instance details

Defined in Text.PrettyBy.Internal

Methods

defaultPrettyBy :: config -> Integer -> Doc ann

defaultPrettyListBy :: config -> [Integer] -> Doc ann

NonDefaultPrettyBy ConstConfig Integer 
Instance details

Defined in PlutusCore.Pretty.PrettyConst

Methods

nonDefaultPrettyBy :: ConstConfig -> Integer -> Doc ann

nonDefaultPrettyListBy :: ConstConfig -> [Integer] -> Doc ann

Includes uni Integer => Lift uni Integer Source # 
Instance details

Defined in PlutusTx.Lift.Instances

Methods

lift :: Integer -> RTCompile uni fun (Term TyName Name uni fun ()) Source #

ToBuiltin Integer BuiltinInteger Source # 
Instance details

Defined in PlutusTx.Builtins.Class

FromBuiltin BuiltinInteger Integer Source # 
Instance details

Defined in PlutusTx.Builtins.Class

Module Integer Rational Source # 
Instance details

Defined in PlutusTx.Ratio

KnownNat n => Reifies (n :: Nat) Integer 
Instance details

Defined in Data.Reflection

Methods

reflect :: proxy n -> Integer

HasConstantIn DefaultUni term => MakeKnownIn DefaultUni term Integer 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnown :: Maybe cause -> Integer -> MakeKnownM cause term

HasConstantIn DefaultUni term => ReadKnownIn DefaultUni term Integer 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown :: Maybe cause -> term -> ReadKnownM cause Integer

Contains DefaultUni Integer 
Instance details

Defined in PlutusCore.Default.Universe

Methods

knownUni :: DefaultUni (Esc Integer)

KnownBuiltinTypeAst DefaultUni Integer => KnownTypeAst DefaultUni Integer 
Instance details

Defined in PlutusCore.Default.Universe

Associated Types

type ToHoles Integer :: [Hole]

type ToBinds Integer :: [Some TyNameRep]

Methods

toTypeAst :: proxy Integer -> Type TyName DefaultUni ()

Includes uni Integer => Typeable uni Integer Source # 
Instance details

Defined in PlutusTx.Lift.Instances

Methods

typeRep :: Proxy Integer -> RTCompile uni fun (Type TyName uni ()) Source #

type IntBaseType Integer 
Instance details

Defined in Data.IntCast

type IntBaseType Integer = 'BigIntTag
type Difference Integer 
Instance details

Defined in Basement.Numerical.Subtractive

type Difference Integer = Integer
type ToBinds Integer 
Instance details

Defined in PlutusCore.Default.Universe

type ToBinds Integer = ToBinds (ElaborateBuiltin Integer)
type ToHoles Integer 
Instance details

Defined in PlutusCore.Default.Universe

type ToHoles Integer = ToHoles (ElaborateBuiltin Integer)

divideInteger :: Integer -> Integer -> Integer Source #

Divide two integers.

modInteger :: Integer -> Integer -> Integer Source #

Integer modulo operation.

quotientInteger :: Integer -> Integer -> Integer Source #

Quotient of two integers.

remainderInteger :: Integer -> Integer -> Integer Source #

Take the remainder of dividing two Integers.

greaterThanInteger :: Integer -> Integer -> Bool Source #

Check whether one Integer is greater than another.

greaterThanEqualsInteger :: Integer -> Integer -> Bool Source #

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

lessThanInteger :: Integer -> Integer -> Bool Source #

Check whether one Integer is less than another.

lessThanEqualsInteger :: Integer -> Integer -> Bool Source #

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

equalsInteger :: Integer -> Integer -> Bool 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
Eq BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Data BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BuiltinData -> c BuiltinData Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BuiltinData Source #

toConstr :: BuiltinData -> Constr Source #

dataTypeOf :: BuiltinData -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BuiltinData) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BuiltinData) Source #

gmapT :: (forall b. Data b => b -> b) -> BuiltinData -> BuiltinData Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BuiltinData -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BuiltinData -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> BuiltinData -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BuiltinData -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BuiltinData -> m BuiltinData Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BuiltinData -> m BuiltinData Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BuiltinData -> m BuiltinData Source #

Ord BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Show BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

NFData BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

rnf :: BuiltinData -> () Source #

Pretty BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

pretty :: BuiltinData -> Doc ann

prettyList :: [BuiltinData] -> Doc ann

Eq BuiltinData Source # 
Instance details

Defined in PlutusTx.Eq

UnsafeFromData BuiltinData Source # 
Instance details

Defined in PlutusTx.IsData.Class

FromData BuiltinData Source # 
Instance details

Defined in PlutusTx.IsData.Class

ToData BuiltinData Source # 
Instance details

Defined in PlutusTx.IsData.Class

Includes uni Data => Lift uni BuiltinData Source # 
Instance details

Defined in PlutusTx.Lift.Instances

Methods

lift :: BuiltinData -> RTCompile uni fun (Term TyName Name uni fun ()) Source #

ToBuiltin BuiltinData BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.Class

FromBuiltin BuiltinData BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.Class

Includes uni Data => Typeable uni BuiltinData Source # 
Instance details

Defined in PlutusTx.Lift.Instances

Methods

typeRep :: Proxy BuiltinData -> RTCompile uni fun (Type TyName uni ()) Source #

ToBuiltin [(BuiltinData, BuiltinData)] (BuiltinList (BuiltinPair BuiltinData BuiltinData)) Source # 
Instance details

Defined in PlutusTx.Builtins.Class

ToBuiltin [BuiltinData] (BuiltinList BuiltinData) Source # 
Instance details

Defined in PlutusTx.Builtins.Class

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

Defined in PlutusTx.Builtins.Class

chooseData :: forall 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.

matchData :: BuiltinData -> (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 -> (Integer -> BuiltinList 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.

equalsData :: BuiltinData -> BuiltinData -> Bool Source #

Check if two BuiltinDatas are equal.

serialiseData :: BuiltinData -> BuiltinByteString Source #

Convert a String into a ByteString.

mkConstr :: Integer -> [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.

mkI :: Integer -> BuiltinData Source #

Constructs a BuiltinData value with the I constructor.

mkB :: BuiltinByteString -> BuiltinData Source #

Constructs a BuiltinData value with the B constructor.

unsafeDataAsConstr :: BuiltinData -> (Integer, [BuiltinData]) Source #

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

unsafeDataAsMap :: BuiltinData -> [(BuiltinData, BuiltinData)] Source #

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

unsafeDataAsList :: BuiltinData -> [BuiltinData] Source #

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

unsafeDataAsI :: BuiltinData -> Integer Source #

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

unsafeDataAsB :: BuiltinData -> BuiltinByteString Source #

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

builtinDataToData :: BuiltinData -> Data Source #

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

dataToBuiltinData :: Data -> BuiltinData Source #

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

Strings

data BuiltinString Source #

Instances

Instances details
Eq BuiltinString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Data BuiltinString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BuiltinString -> c BuiltinString Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BuiltinString Source #

toConstr :: BuiltinString -> Constr Source #

dataTypeOf :: BuiltinString -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BuiltinString) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BuiltinString) Source #

gmapT :: (forall b. Data b => b -> b) -> BuiltinString -> BuiltinString Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BuiltinString -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BuiltinString -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> BuiltinString -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BuiltinString -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BuiltinString -> m BuiltinString Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BuiltinString -> m BuiltinString Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BuiltinString -> m BuiltinString Source #

Ord BuiltinString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Show BuiltinString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

IsString BuiltinString Source # 
Instance details

Defined in PlutusTx.Builtins.Class

Eq BuiltinString Source # 
Instance details

Defined in PlutusTx.Eq

Semigroup BuiltinString Source # 
Instance details

Defined in PlutusTx.Semigroup

Monoid BuiltinString Source # 
Instance details

Defined in PlutusTx.Monoid

Includes uni Text => Lift uni BuiltinString Source # 
Instance details

Defined in PlutusTx.Lift.Instances

Methods

lift :: BuiltinString -> RTCompile uni fun (Term TyName Name uni fun ()) Source #

ToBuiltin Text BuiltinString Source # 
Instance details

Defined in PlutusTx.Builtins.Class

Methods

toBuiltin :: Text -> BuiltinString Source #

FromBuiltin BuiltinString Text Source # 
Instance details

Defined in PlutusTx.Builtins.Class

Methods

fromBuiltin :: BuiltinString -> Text Source #

Includes uni Text => Typeable uni BuiltinString Source # 
Instance details

Defined in PlutusTx.Lift.Instances

Methods

typeRep :: Proxy BuiltinString -> RTCompile uni fun (Type TyName uni ()) Source #

emptyString :: BuiltinString Source #

An empty String.

equalsString :: BuiltinString -> BuiltinString -> Bool Source #

Check if two strings are equal

encodeUtf8 :: BuiltinString -> BuiltinByteString Source #

Convert a String into a ByteString.

Lists

matchList :: forall a r. BuiltinList a -> r -> (a -> BuiltinList a -> r) -> r Source #

Tracing

trace :: BuiltinString -> a -> a Source #

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

Conversions

fromBuiltin :: FromBuiltin arep a => arep -> a Source #

toBuiltin :: ToBuiltin a arep => a -> arep Source #