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

PlutusTx.Prelude

Synopsis

Documentation

The PlutusTx Prelude is a replacement for the Haskell Prelude that works better with Plutus Tx. You should use it if you're writing code that will be compiled with the Plutus Tx compiler. {-# LANGUAGE NoImplicitPrelude #-} import PlutusTx.Prelude

Monad

(>>=) :: Monad m => m a -> (a -> m b) -> m b infixl 1 Source #

Sequentially compose two actions, passing any value produced by the first as an argument to the second.

'as >>= bs' can be understood as the do expression

do a <- as
   bs a

(=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 Source #

Same as >>=, but with the arguments interchanged.

(>>) :: Monad m => m a -> m b -> m b infixl 1 Source #

Sequentially compose two actions, discarding any value produced by the first, like sequencing operators (such as the semicolon) in imperative languages.

'as >> bs' can be understood as the do expression

do as
   bs

return :: Monad m => a -> m a Source #

Inject a value into the monadic type.

Standard functions, Tuples

Tracing functions

String

data BuiltinString Source #

Instances

Instances details
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 #

IsString BuiltinString Source # 
Instance details

Defined in PlutusTx.Builtins.Class

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

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

FromBuiltin BuiltinString Text Source # 
Instance details

Defined in PlutusTx.Builtins.Class

ToBuiltin Text BuiltinString Source # 
Instance details

Defined in PlutusTx.Builtins.Class

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 #

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.

Error

error :: () -> a Source #

Aborts evaluation with an error.

check :: Bool -> () Source #

Checks a Bool and aborts if it is false.

Booleans

Integer numbers

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

This instance includes a bounds check to prevent maliciously large inputs to fill up the memory of the target system. You can newtype Scientific and provide your own instance using withScientific if you want to allow larger inputs.

Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Integer 
Instance details

Defined in Data.Aeson.Types.FromJSON

ToJSON Integer 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Integer 
Instance details

Defined in Data.Aeson.Types.ToJSON

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 #

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 Source #

Default Integer 
Instance details

Defined in Data.Default.Class

Methods

def :: Integer Source #

NFData Integer 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Integer -> () Source #

Eq Integer 
Instance details

Defined in GHC.Num.Integer

Ord Integer 
Instance details

Defined in GHC.Num.Integer

Hashable Integer 
Instance details

Defined in Data.Hashable.Class

ExMemoryUsage Integer 
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Enum Integer Source # 
Instance details

Defined in PlutusTx.Enum

Eq Integer Source # 
Instance details

Defined in PlutusTx.Eq

Methods

(==) :: Integer -> Integer -> Bool 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

(-) :: 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 #

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 #

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

pretty :: Integer -> Doc ann Source #

prettyList :: [Integer] -> Doc ann Source #

UniformRange Integer 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen 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

Pretty Integer 
Instance details

Defined in Text.PrettyPrint.Annotated.WL

FromBuiltin BuiltinInteger Integer Source # 
Instance details

Defined in PlutusTx.Builtins.Class

ToBuiltin Integer BuiltinInteger Source # 
Instance details

Defined in PlutusTx.Builtins.Class

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 #

Module Integer Rational Source # 
Instance details

Defined in PlutusTx.Ratio

DefaultPrettyBy config Integer 
Instance details

Defined in Text.PrettyBy.Internal

Methods

defaultPrettyBy :: config -> Integer -> Doc ann Source #

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

NonDefaultPrettyBy ConstConfig Integer 
Instance details

Defined in PlutusCore.Pretty.PrettyConst

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

Defined in Text.PrettyBy.Internal

Methods

prettyBy :: config -> Integer -> Doc ann Source #

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

Lift Integer 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

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

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

HasConstantIn DefaultUni term => MakeKnownIn DefaultUni term Integer 
Instance details

Defined in PlutusCore.Default.Universe

Methods

makeKnown :: Integer -> MakeKnownM term Source #

HasConstantIn DefaultUni term => ReadKnownIn DefaultUni term Integer 
Instance details

Defined in PlutusCore.Default.Universe

Methods

readKnown :: term -> ReadKnownM Integer Source #

KnownBuiltinTypeAst DefaultUni Integer => KnownTypeAst DefaultUni Integer 
Instance details

Defined in PlutusCore.Default.Universe

Contains DefaultUni Integer 
Instance details

Defined in PlutusCore.Default.Universe

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 #

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

Defined in Data.Reflection

Methods

reflect :: proxy n -> Integer Source #

type Difference Integer 
Instance details

Defined in Basement.Numerical.Subtractive

type IntBaseType Integer 
Instance details

Defined in Data.IntCast

type IsBuiltin Integer 
Instance details

Defined in PlutusCore.Default.Universe

type IsBuiltin Integer = IsBuiltin (ElaborateBuiltin 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)

divide :: Integer -> Integer -> Integer Source #

Integer division, rounding downwards

>>> divide (-41) 5
-9

modulo :: Integer -> Integer -> Integer Source #

Integer remainder, always positive for a positive divisor

>>> modulo (-41) 5
4

quotient :: Integer -> Integer -> Integer Source #

Integer division, rouding towards zero

>>> quotient (-41) 5
-8

remainder :: Integer -> Integer -> Integer Source #

Integer remainder, same sign as dividend

>>> remainder (-41) 5
-1

Maybe

Either

Lists

map :: (a -> b) -> [a] -> [b] Source #

Plutus Tx version of map.

>>> map (\i -> i + 1) [1, 2, 3]
[2,3,4]

(++) :: [a] -> [a] -> [a] infixr 5 Source #

Plutus Tx version of (++).

>>> [0, 1, 2] ++ [1, 2, 3, 4]
[0,1,2,1,2,3,4]

filter :: (a -> Bool) -> [a] -> [a] Source #

Plutus Tx version of filter.

>>> filter (> 1) [1, 2, 3, 4]
[2,3,4]

listToMaybe :: [a] -> Maybe a Source #

Plutus Tx version of listToMaybe.

uniqueElement :: [a] -> Maybe a Source #

Return the element in the list, if there is precisely one.

findIndices :: (a -> Bool) -> [a] -> [Integer] Source #

Plutus Tx version of findIndices.

findIndex :: (a -> Bool) -> [a] -> Maybe Integer Source #

Plutus Tx version of findIndex.

(!!) :: [a] -> Integer -> a infixl 9 Source #

Plutus Tx version of (!!).

>>> [10, 11, 12] !! 2
12

reverse :: [a] -> [a] Source #

Plutus Tx version of reverse.

zip :: [a] -> [b] -> [(a, b)] Source #

Plutus Tx version of zip.

head :: [a] -> a Source #

Plutus Tx version of head.

tail :: [a] -> [a] Source #

Plutus Tx version of tail.

take :: Integer -> [a] -> [a] Source #

Plutus Tx version of take.

drop :: Integer -> [a] -> [a] Source #

Plutus Tx version of drop.

splitAt :: Integer -> [a] -> ([a], [a]) Source #

Plutus Tx version of splitAt.

nub :: Eq a => [a] -> [a] Source #

Plutus Tx version of nub.

nubBy :: (a -> a -> Bool) -> [a] -> [a] Source #

Plutus Tx version of nubBy.

zipWith :: (a -> b -> c) -> [a] -> [b] -> [c] Source #

Plutus Tx version of zipWith.

dropWhile :: (a -> Bool) -> [a] -> [a] Source #

Plutus Tx version of dropWhile.

partition :: (a -> Bool) -> [a] -> ([a], [a]) Source #

Plutus Tx version of partition.

sort :: Ord a => [a] -> [a] Source #

Plutus Tx version of sort.

sortBy :: (a -> a -> Ordering) -> [a] -> [a] Source #

Plutus Tx version of sortBy.

ByteStrings

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 :: (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 #

IsString BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Class

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

rnf :: BuiltinByteString -> () 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

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

ByteArrayAccess BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

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

FromBuiltin BuiltinByteString ByteString Source # 
Instance details

Defined in PlutusTx.Builtins.Class

ToBuiltin ByteString BuiltinByteString Source # 
Instance details

Defined in PlutusTx.Builtins.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 #

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.

takeByteString :: Integer -> BuiltinByteString -> BuiltinByteString Source #

Returns the n length prefix of a ByteString.

dropByteString :: Integer -> BuiltinByteString -> BuiltinByteString Source #

Returns the suffix of a ByteString after n elements.

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.

decodeUtf8 :: BuiltinByteString -> BuiltinString Source #

Converts a ByteString to a String.

Hashes and Signatures

sha2_256 :: BuiltinByteString -> BuiltinByteString Source #

The SHA2-256 hash of a ByteString

sha3_256 :: BuiltinByteString -> BuiltinByteString Source #

The SHA3-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 (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

Rational numbers

data Rational Source #

Represents an arbitrary-precision ratio.

Instances

Instances details
FromJSON Rational Source #

This mimics the behaviour of Aeson's instance for Rational.

Instance details

Defined in PlutusTx.Ratio

ToJSON Rational Source #

This mimics the behaviour of Aeson's instance for Rational.

Instance details

Defined in PlutusTx.Ratio

Show Rational Source # 
Instance details

Defined in PlutusTx.Ratio

Eq Rational Source # 
Instance details

Defined in PlutusTx.Ratio

Ord Rational Source # 
Instance details

Defined in PlutusTx.Ratio

Eq Rational Source # 
Instance details

Defined in PlutusTx.Ratio

Methods

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

FromData Rational Source # 
Instance details

Defined in PlutusTx.Ratio

ToData Rational Source # 
Instance details

Defined in PlutusTx.Ratio

UnsafeFromData Rational Source # 
Instance details

Defined in PlutusTx.Ratio

AdditiveGroup Rational Source # 
Instance details

Defined in PlutusTx.Ratio

AdditiveMonoid Rational Source # 
Instance details

Defined in PlutusTx.Ratio

Methods

zero :: Rational Source #

AdditiveSemigroup Rational Source # 
Instance details

Defined in PlutusTx.Ratio

MultiplicativeMonoid Rational Source # 
Instance details

Defined in PlutusTx.Ratio

Methods

one :: Rational Source #

MultiplicativeSemigroup Rational Source # 
Instance details

Defined in PlutusTx.Ratio

Ord Rational Source # 
Instance details

Defined in PlutusTx.Ratio

Lift DefaultUni Rational Source # 
Instance details

Defined in PlutusTx.Ratio

Module Integer Rational Source # 
Instance details

Defined in PlutusTx.Ratio

Typeable DefaultUni Rational Source # 
Instance details

Defined in PlutusTx.Ratio

unsafeRatio :: Integer -> Integer -> Rational Source #

Makes a Rational from a numerator and a denominator.

Important note

If given a zero denominator, this function will error. If you don't mind a size increase, and care about safety, use ratio instead.

ratio :: Integer -> Integer -> Maybe Rational Source #

Safely constructs a Rational from a numerator and a denominator. Returns Nothing if given a zero denominator.

fromInteger :: Integer -> Rational Source #

Converts an Integer into the equivalent Rational.

round :: Rational -> Integer Source #

round r returns the nearest Integer value to r. If r is equidistant between two values, the even value will be given.

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 :: (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 #

Show BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

NFData BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

rnf :: BuiltinData -> () Source #

Eq BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

Ord BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.Internal

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

FromBuiltin BuiltinData BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.Class

ToBuiltin BuiltinData BuiltinData Source # 
Instance details

Defined in PlutusTx.Builtins.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 #

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] (BuiltinList BuiltinData) Source # 
Instance details

Defined in PlutusTx.Builtins.Class

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

Defined in PlutusTx.Builtins.Class

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

Defined in PlutusTx.Builtins.Class

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

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