plutarch-1.9.0
Safe HaskellSafe-Inferred
LanguageGHC2021

Plutarch.Prelude

Synopsis

Documentation

newtype PDataNewtype (a :: S -> Type) (s :: S) Source #

Since: 1.7.0

Constructors

PDataNewtype (Term s (PAsData a)) 

Instances

Instances details
(PIsData a, PTryFrom PData (PAsData a)) => PTryFrom PData (PDataNewtype a) Source #

Since: 1.7.0

Instance details

Defined in Plutarch.Builtin

Associated Types

type PTryFromExcess PData (PDataNewtype a) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PDataNewtype a), Reduce (PTryFromExcess PData (PDataNewtype a) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData (PDataNewtype a)) Source #

Since: 1.7.0

Instance details

Defined in Plutarch.Builtin

Associated Types

type PTryFromExcess PData (PAsData (PDataNewtype a)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PDataNewtype a)), Reduce (PTryFromExcess PData (PAsData (PDataNewtype a)) s)) -> Term s r) -> Term s r Source #

PEq (PDataNewtype a) Source #

Since: 1.7.0

Instance details

Defined in Plutarch.Builtin

Methods

(#==) :: forall (s :: S). Term s (PDataNewtype a) -> Term s (PDataNewtype a) -> Term s PBool Source #

PIsData (PDataNewtype a) Source #

Since: 1.7.0

Instance details

Defined in Plutarch.Builtin

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData (PDataNewtype a)) -> Term s (PDataNewtype a) Source #

pdataImpl :: forall (s :: S). Term s (PDataNewtype a) -> Term s PData Source #

(PIsData a, POrd a) => POrd (PDataNewtype a) Source #

Since: 1.7.0

Instance details

Defined in Plutarch.Builtin

Methods

(#<=) :: forall (s :: S). Term s (PDataNewtype a) -> Term s (PDataNewtype a) -> Term s PBool Source #

(#<) :: forall (s :: S). Term s (PDataNewtype a) -> Term s (PDataNewtype a) -> Term s PBool Source #

pmax :: forall (s :: S). Term s (PDataNewtype a) -> Term s (PDataNewtype a) -> Term s (PDataNewtype a) Source #

pmin :: forall (s :: S). Term s (PDataNewtype a) -> Term s (PDataNewtype a) -> Term s (PDataNewtype a) Source #

PlutusType (PDataNewtype a) Source #

Since: 1.7.0

Instance details

Defined in Plutarch.Builtin

Methods

pcon' :: forall (s :: S). PDataNewtype a s -> Term s (PInner (PDataNewtype a)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PDataNewtype a)) -> (PDataNewtype a s -> Term s b) -> Term s b Source #

(PIsData a, PShow a) => PShow (PDataNewtype a) Source #

Since: 1.7.0

Instance details

Defined in Plutarch.Builtin

Methods

pshow' :: forall (s :: S). Bool -> Term s (PDataNewtype a) -> Term s PString Source #

Generic (PDataNewtype a s) Source # 
Instance details

Defined in Plutarch.Builtin

Associated Types

type Rep (PDataNewtype a s) :: Type -> Type Source #

Methods

from :: PDataNewtype a s -> Rep (PDataNewtype a s) x Source #

to :: Rep (PDataNewtype a s) x -> PDataNewtype a s Source #

type PTryFromExcess PData (PDataNewtype a) Source # 
Instance details

Defined in Plutarch.Builtin

type PTryFromExcess PData (PAsData (PDataNewtype a)) Source # 
Instance details

Defined in Plutarch.Builtin

type PContravariant' (PDataNewtype a) Source # 
Instance details

Defined in Plutarch.Builtin

type PCovariant' (PDataNewtype a) Source # 
Instance details

Defined in Plutarch.Builtin

type PInner (PDataNewtype a) Source # 
Instance details

Defined in Plutarch.Builtin

type PVariant' (PDataNewtype a) Source # 
Instance details

Defined in Plutarch.Builtin

type Rep (PDataNewtype a s) Source #

Since: 1.7.0

Instance details

Defined in Plutarch.Builtin

type Rep (PDataNewtype a s) = D1 ('MetaData "PDataNewtype" "Plutarch.Builtin" "plutarch-1.9.0-FtN0mhIoM9oEvz7Q98pjWP" 'True) (C1 ('MetaCons "PDataNewtype" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PAsData a)))))

Boolean

data PBool (s :: S) Source #

Builtin Plutus boolean.

@since WIP

Constructors

PTrue 
PFalse 

Instances

Instances details
PEq PBool Source # 
Instance details

Defined in Plutarch.Internal.Eq

Methods

(#==) :: forall (s :: S). Term s PBool -> Term s PBool -> Term s PBool Source #

PIsData PBool Source # 
Instance details

Defined in Plutarch.Internal.IsData

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PBool) -> Term s PBool Source #

pdataImpl :: forall (s :: S). Term s PBool -> Term s PData Source #

PLiftable PBool Source # 
Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type AsHaskell PBool Source #

type PlutusRepr PBool Source #

POrd PBool Source # 
Instance details

Defined in Plutarch.Internal.Ord

Methods

(#<=) :: forall (s :: S). Term s PBool -> Term s PBool -> Term s PBool Source #

(#<) :: forall (s :: S). Term s PBool -> Term s PBool -> Term s PBool Source #

pmax :: forall (s :: S). Term s PBool -> Term s PBool -> Term s PBool Source #

pmin :: forall (s :: S). Term s PBool -> Term s PBool -> Term s PBool Source #

PlutusType PBool Source #

@since WIP

Instance details

Defined in Plutarch.Internal.PlutusType

Methods

pcon' :: forall (s :: S). PBool s -> Term s (PInner PBool) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PBool) -> (PBool s -> Term s b) -> Term s b Source #

PShow PBool Source # 
Instance details

Defined in Plutarch.Internal.Show

Methods

pshow' :: forall (s :: S). Bool -> Term s PBool -> Term s PString Source #

PTryFrom PData (PAsData PBool) Source #

Since: 1.7.0

Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData (PAsData PBool) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData PBool), Reduce (PTryFromExcess PData (PAsData PBool) s)) -> Term s r) -> Term s r Source #

Show (PBool s) Source #

@since WIP

Instance details

Defined in Plutarch.Builtin.Bool

type AsHaskell PBool Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Lift

type PlutusRepr PBool Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PContravariant' PBool Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PCovariant' PBool Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PInner PBool Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PVariant' PBool Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PTryFromExcess PData (PAsData PBool) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

pand' :: forall (s :: S). Term s (PBool :--> (PBool :--> PBool)) Source #

As pand, but strict.

@since WIP

pcond :: forall (a :: S -> Type) (s :: S). [(Term s PBool, Term s a)] -> Term s a -> Term s a Source #

Essentially multi-way pif. More precisely, given a list of condition-action pairs, and an 'action of last resort', construct a left-to-right 'chain' of pifs, using the conditions to determine which action gets taken. The 'action of last resort' finishes the 'chain'. For example:

pcond [(cond1, act1), (cond2, act2)] act3

does the same thing as

pif cond1 act1 (pif cond2 act2 act3)

@since WIP

pif :: forall (a :: S -> Type) (s :: S). Term s PBool -> Term s a -> Term s a -> Term s a Source #

Lazy if-then-else.

@since WIP

pif' :: forall (a :: S -> Type) (s :: S). Term s (PBool :--> (a :--> (a :--> a))) Source #

Strict if-then-else. Emits slightly less code than the lazy version.

@since WIP

pnot :: forall (s :: S). Term s (PBool :--> PBool) Source #

Boolean negation.

@since WIP

por' :: Term s (PBool :--> (PBool :--> PBool)) Source #

As por, but strict.

@since WIP

(#&&) :: forall (s :: S). Term s PBool -> Term s PBool -> Term s PBool infixr 3 Source #

Lazy AND for terms.

@since WIP

(#||) :: forall (s :: S). Term s PBool -> Term s PBool -> Term s PBool infixr 2 Source #

Lazy OR for terms.

@since WIP

Bytestring

data PByte (s :: S) Source #

A Plutarch-level representation of bytes.

Note =

This type is intentionally quite restrictive, as it's not really meant to be computed with. Instead, it ensures certain operations' type safety while also allowing more sensible signatures. If you want to do anything with PBytes, we recommend converting them to PIntegers first.

@since WIP

Instances

Instances details
PEq PByte Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Eq

Methods

(#==) :: forall (s :: S). Term s PByte -> Term s PByte -> Term s PBool Source #

PLiftable PByte Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type AsHaskell PByte Source #

type PlutusRepr PByte Source #

POrd PByte Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Ord

Methods

(#<=) :: forall (s :: S). Term s PByte -> Term s PByte -> Term s PBool Source #

(#<) :: forall (s :: S). Term s PByte -> Term s PByte -> Term s PBool Source #

pmax :: forall (s :: S). Term s PByte -> Term s PByte -> Term s PByte Source #

pmin :: forall (s :: S). Term s PByte -> Term s PByte -> Term s PByte Source #

DerivePlutusType PByte Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Associated Types

type DPTStrat PByte Source #

PlutusType PByte Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Methods

pcon' :: forall (s :: S). PByte s -> Term s (PInner PByte) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PByte) -> (PByte s -> Term s b) -> Term s b Source #

Generic (PByte s) Source # 
Instance details

Defined in Plutarch.Builtin.ByteString

Associated Types

type Rep (PByte s) :: Type -> Type Source #

Methods

from :: PByte s -> Rep (PByte s) x Source #

to :: Rep (PByte s) x -> PByte s Source #

type AsHaskell PByte Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PlutusRepr PByte Source # 
Instance details

Defined in Plutarch.Internal.Lift

type DPTStrat PByte Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PContravariant' PByte Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PCovariant' PByte Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PInner PByte Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PVariant' PByte Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type Rep (PByte s) Source #

@since WIP

Instance details

Defined in Plutarch.Builtin.ByteString

type Rep (PByte s) = D1 ('MetaData "PByte" "Plutarch.Builtin.ByteString" "plutarch-1.9.0-FtN0mhIoM9oEvz7Q98pjWP" 'True) (C1 ('MetaCons "PByte" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s POpaque))))

data PByteString s Source #

Plutus BuiltinByteString

Instances

Instances details
PEq PByteString Source # 
Instance details

Defined in Plutarch.Internal.Eq

Methods

(#==) :: forall (s :: S). Term s PByteString -> Term s PByteString -> Term s PBool Source #

PIsData PByteString Source # 
Instance details

Defined in Plutarch.Internal.IsData

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PByteString) -> Term s PByteString Source #

pdataImpl :: forall (s :: S). Term s PByteString -> Term s PData Source #

PLiftable PByteString Source # 
Instance details

Defined in Plutarch.Internal.Lift

POrd PByteString Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Ord

Methods

(#<=) :: forall (s :: S). Term s PByteString -> Term s PByteString -> Term s PBool Source #

(#<) :: forall (s :: S). Term s PByteString -> Term s PByteString -> Term s PBool Source #

pmax :: forall (s :: S). Term s PByteString -> Term s PByteString -> Term s PByteString Source #

pmin :: forall (s :: S). Term s PByteString -> Term s PByteString -> Term s PByteString Source #

DerivePlutusType PByteString Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Associated Types

type DPTStrat PByteString Source #

PlutusType PByteString Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Methods

pcon' :: forall (s :: S). PByteString s -> Term s (PInner PByteString) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PByteString) -> (PByteString s -> Term s b) -> Term s b Source #

PShow PByteString Source # 
Instance details

Defined in Plutarch.Internal.Show

Methods

pshow' :: forall (s :: S). Bool -> Term s PByteString -> Term s PString Source #

PTryFrom PData (PAsData PByteString) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData PByteString), Reduce (PTryFromExcess PData (PAsData PByteString) s)) -> Term s r) -> Term s r Source #

Generic (PByteString s) Source # 
Instance details

Defined in Plutarch.Builtin.ByteString

Associated Types

type Rep (PByteString s) :: Type -> Type Source #

PLiftable (PAsData PByteString) Source # 
Instance details

Defined in Plutarch.Internal.Lift

Monoid (Term s PByteString) Source # 
Instance details

Defined in Plutarch.Builtin.ByteString

Semigroup (Term s PByteString) Source # 
Instance details

Defined in Plutarch.Builtin.ByteString

type AsHaskell PByteString Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Lift

type PlutusRepr PByteString Source # 
Instance details

Defined in Plutarch.Internal.Lift

type DPTStrat PByteString Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PContravariant' PByteString Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PCovariant' PByteString Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PInner PByteString Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PVariant' PByteString Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PTryFromExcess PData (PAsData PByteString) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type Rep (PByteString s) Source # 
Instance details

Defined in Plutarch.Builtin.ByteString

type Rep (PByteString s) = D1 ('MetaData "PByteString" "Plutarch.Builtin.ByteString" "plutarch-1.9.0-FtN0mhIoM9oEvz7Q98pjWP" 'True) (C1 ('MetaCons "PByteString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s POpaque))))
type AsHaskell (PAsData PByteString) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PlutusRepr (PAsData PByteString) Source # 
Instance details

Defined in Plutarch.Internal.Lift

data PLogicOpSemantics (s :: S) Source #

Type designating whether logical operations should use padding or truncation semantics. See CIP-122 for more details on this.

@since WIP

Instances

Instances details
PEq PLogicOpSemantics Source # 
Instance details

Defined in Plutarch.Internal.Eq

Methods

(#==) :: forall (s :: S). Term s PLogicOpSemantics -> Term s PLogicOpSemantics -> Term s PBool Source #

POrd PLogicOpSemantics Source # 
Instance details

Defined in Plutarch.Internal.Ord

DerivePlutusType PLogicOpSemantics Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Associated Types

type DPTStrat PLogicOpSemantics Source #

PlutusType PLogicOpSemantics Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Methods

pcon' :: forall (s :: S). PLogicOpSemantics s -> Term s (PInner PLogicOpSemantics) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PLogicOpSemantics) -> (PLogicOpSemantics s -> Term s b) -> Term s b Source #

Generic (PLogicOpSemantics s) Source # 
Instance details

Defined in Plutarch.Builtin.ByteString

Associated Types

type Rep (PLogicOpSemantics s) :: Type -> Type Source #

type DPTStrat PLogicOpSemantics Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PContravariant' PLogicOpSemantics Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PCovariant' PLogicOpSemantics Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PInner PLogicOpSemantics Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PVariant' PLogicOpSemantics Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type Rep (PLogicOpSemantics s) Source # 
Instance details

Defined in Plutarch.Builtin.ByteString

type Rep (PLogicOpSemantics s) = D1 ('MetaData "PLogicOpSemantics" "Plutarch.Builtin.ByteString" "plutarch-1.9.0-FtN0mhIoM9oEvz7Q98pjWP" 'True) (C1 ('MetaCons "PLogicOpSemantics" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s PBool))))

pandBS :: forall (s :: S). Term s (PLogicOpSemantics :--> (PByteString :--> (PByteString :--> PByteString))) Source #

Perform the logical AND of two PByteStrings, as per CIP-122. The PLogicOpSemantics argument specifies what should be done if the lengths of the two PByteString arguments do not match.

@since WIP

pbyteToInteger :: Term s (PByte :--> PInteger) Source #

Convert a PByte into its corresponding PInteger.

@since WIP

pcomplementBS :: forall (s :: S). Term s (PByteString :--> PByteString) Source #

Perform the logical complement of a PByteString, as per CIP-122.

@since WIP

pconsBS :: Term s (PByte :--> (PByteString :--> PByteString)) Source #

Prepend a PByte to a 'PByteString.

@since WIP

phexByteStr :: HasCallStack => String -> Term s PByteString Source #

Interpret a hex string as a PByteString.

pindexBS :: Term s (PByteString :--> (PInteger :--> PByte)) Source #

Given a valid index into a PByteString, returns the PByte at that index. Will crash if given an out-of-bounds index.

@since WIP

pintegerToByte :: Term s (PInteger :--> PByte) Source #

Try to convert a PInteger into its corresponding PByte. This operation unchecked: use with care.

@since WIP

porBS :: forall (s :: S). Term s (PLogicOpSemantics :--> (PByteString :--> (PByteString :--> PByteString))) Source #

Perform the logical OR of two PByteStrings, as per CIP-122. The PLogicOpSemantics argument specifies what should be done if the lengths of the two PByteString arguments do not match.

@since WIP

ppadding :: forall (s :: S). Term s PLogicOpSemantics Source #

Indicates that padding semantics should be used.

@since WIP

preplicateBS :: forall (s :: S). Term s (PInteger :--> (PByte :--> PByteString)) Source #

Given a desired length and a PByte, construct a PByteString of the specified length (0 if negative) consisting entirely of that PByte.

@since WIP

psliceBS :: Term s (PInteger :--> (PInteger :--> (PByteString :--> PByteString))) Source #

Slice a PByteString with given start index and slice length.

>>> (pslice # 2 # 3 phexByteStr "4102afde5b2a") #== phexByteStr "afde5b"

ptruncation :: forall (s :: S). Term s PLogicOpSemantics Source #

Indicates that truncation semantics should be used.

@since WIP

pxorBS :: forall (s :: S). Term s (PLogicOpSemantics :--> (PByteString :--> (PByteString :--> PByteString))) Source #

Perform the logical XOR of two PByteStrings, as per CIP-122. The PLogicOpSemantics argument specifies what should be done if the lengths of the two PByteString arguments do not match.

@since WIP

Cryptographic primitives

pverifySignature :: Term s (PByteString :--> (PByteString :--> (PByteString :--> PBool))) Source #

Deprecated: use one of the Ed25519, Schnorr- or ECDSA Secp256k1 signature verification functions

Verify the signature against the public key and message.

Data encoding

newtype PAsData (a :: S -> Type) (s :: S) Source #

Constructors

PAsData (Term s a) 

Instances

Instances details
PFromDataable a (PAsData a) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal.FromData

Methods

pmaybeFromAsData :: forall (s :: S). Term s (PAsData a) -> Term s (PAsData a) Source #

PTryFrom PData (PAsData (PDataNewtype a)) Source #

Since: 1.7.0

Instance details

Defined in Plutarch.Builtin

Associated Types

type PTryFromExcess PData (PAsData (PDataNewtype a)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PDataNewtype a)), Reduce (PTryFromExcess PData (PAsData (PDataNewtype a)) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData PBool) Source #

Since: 1.7.0

Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData (PAsData PBool) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData PBool), Reduce (PTryFromExcess PData (PAsData PBool) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData PByteString) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData PByteString), Reduce (PTryFromExcess PData (PAsData PByteString) s)) -> Term s r) -> Term s r Source #

(PTryFrom PData (PAsData a), PIsData a) => PTryFrom PData (PAsData (PBuiltinList (PAsData a))) Source #

Recover a `PBuiltinList (PAsData a)`

Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData (PAsData (PBuiltinList (PAsData a))) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PBuiltinList (PAsData a))), Reduce (PTryFromExcess PData (PAsData (PBuiltinList (PAsData a))) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData (PBuiltinList PData)) Source #

This verifies a list to be indeed a list but doesn't recover the inner data use this instance instead of the one for `PData (PAsData (PBuiltinList (PAsData a)))` as this is O(1) instead of O(n)

Instance details

Defined in Plutarch.Internal.TryFrom

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PBuiltinList PData)), Reduce (PTryFromExcess PData (PAsData (PBuiltinList PData)) s)) -> Term s r) -> Term s r Source #

(PTryFrom PData a, a ~ PAsData a', PIsData a', PTryFrom PData b, b ~ PAsData b', PIsData b') => PTryFrom PData (PAsData (PBuiltinPair a b)) Source #

Recover a `PAsData (PBuiltinPair a b)`

Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData (PAsData (PBuiltinPair a b)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PBuiltinPair a b)), Reduce (PTryFromExcess PData (PAsData (PBuiltinPair a b)) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData PData) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData (PAsData PData) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData PData), Reduce (PTryFromExcess PData (PAsData PData) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData PInteger) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData (PAsData PInteger) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData PInteger), Reduce (PTryFromExcess PData (PAsData PInteger) s)) -> Term s r) -> Term s r Source #

(PTryFrom (PBuiltinList PData) (PDataRecord as), PTryFromExcess (PBuiltinList PData) (PDataRecord as) ~ HRecP ase) => PTryFrom PData (PAsData (PDataRecord as)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Associated Types

type PTryFromExcess PData (PAsData (PDataRecord as)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PDataRecord as)), Reduce (PTryFromExcess PData (PAsData (PDataRecord as)) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PDataSum ys) => PTryFrom PData (PAsData (PDataSum ys)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Associated Types

type PTryFromExcess PData (PAsData (PDataSum ys)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PDataSum ys)), Reduce (PTryFromExcess PData (PAsData (PDataSum ys)) s)) -> Term s r) -> Term s r Source #

(PTryFrom PData a, PTryFrom PData b) => PTryFrom PData (PAsData (PEitherData a b)) Source #

@since WIP

Instance details

Defined in Plutarch.Either

Associated Types

type PTryFromExcess PData (PAsData (PEitherData a b)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PEitherData a b)), Reduce (PTryFromExcess PData (PAsData (PEitherData a b)) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData PPositive) Source #

@since WIP

Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData (PAsData PPositive) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData PPositive), Reduce (PTryFromExcess PData (PAsData PPositive) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData PRational) Source #

NOTE: This instance produces a verified PPositive as the excess output.

Instance details

Defined in Plutarch.Rational

Associated Types

type PTryFromExcess PData (PAsData PRational) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData PRational), Reduce (PTryFromExcess PData (PAsData PRational) s)) -> Term s r) -> Term s r Source #

(PIsData a, PDataFields a) => PDataFields (PAsData a) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal.Field

Associated Types

type PFields (PAsData a) :: [PLabeledType] Source #

Methods

ptoFields :: forall (s :: S). Term s (PAsData a) -> Term s (PDataRecord (PFields (PAsData a))) Source #

PEq (PAsData a) Source # 
Instance details

Defined in Plutarch.Internal.Eq

Methods

(#==) :: forall (s :: S). Term s (PAsData a) -> Term s (PAsData a) -> Term s PBool Source #

PLiftable (PAsData PByteString) Source # 
Instance details

Defined in Plutarch.Internal.Lift

PLiftable (PAsData PData) Source # 
Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type AsHaskell (PAsData PData) Source #

type PlutusRepr (PAsData PData) Source #

(ToData (AsHaskell a), FromData (AsHaskell a), PIsData a) => PLiftable (PAsData a) Source # 
Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type AsHaskell (PAsData a) Source #

type PlutusRepr (PAsData a) Source #

PIsData a => PlutusType (PAsData a) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Associated Types

type PInner (PAsData a) :: PType Source #

type PCovariant' (PAsData a) Source #

type PContravariant' (PAsData a) Source #

type PVariant' (PAsData a) Source #

Methods

pcon' :: forall (s :: S). PAsData a s -> Term s (PInner (PAsData a)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PAsData a)) -> (PAsData a s -> Term s b) -> Term s b Source #

(PIsData a, PShow a) => PShow (PAsData a) Source # 
Instance details

Defined in Plutarch.Internal.Show

Methods

pshow' :: forall (s :: S). Bool -> Term s (PAsData a) -> Term s PString Source #

PIsData (PBuiltinPair (PAsData a) (PAsData b)) Source # 
Instance details

Defined in Plutarch.Internal.IsData

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData (PBuiltinPair (PAsData a) (PAsData b))) -> Term s (PBuiltinPair (PAsData a) (PAsData b)) Source #

pdataImpl :: forall (s :: S). Term s (PBuiltinPair (PAsData a) (PAsData b)) -> Term s PData Source #

type PTryFromExcess PData (PAsData (PDataNewtype a)) Source # 
Instance details

Defined in Plutarch.Builtin

type PTryFromExcess PData (PAsData PBool) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type PTryFromExcess PData (PAsData PByteString) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type PTryFromExcess PData (PAsData (PBuiltinList (PAsData a))) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type PTryFromExcess PData (PAsData (PBuiltinList PData)) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type PTryFromExcess PData (PAsData (PBuiltinPair a b)) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type PTryFromExcess PData (PAsData PData) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type PTryFromExcess PData (PAsData PInteger) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type PTryFromExcess PData (PAsData (PDataRecord as)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

type PTryFromExcess PData (PAsData (PDataSum ys)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

type PTryFromExcess PData (PAsData (PEitherData a b)) Source # 
Instance details

Defined in Plutarch.Either

type PTryFromExcess PData (PAsData PPositive) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type PTryFromExcess PData (PAsData PRational) Source # 
Instance details

Defined in Plutarch.Rational

type PFields (PAsData a) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal.Field

type PFields (PAsData a) = PFields a
type AsHaskell (PAsData PByteString) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type AsHaskell (PAsData PData) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type AsHaskell (PAsData a) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PlutusRepr (PAsData PByteString) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PlutusRepr (PAsData PData) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PlutusRepr (PAsData PData) = Data
type PlutusRepr (PAsData a) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PlutusRepr (PAsData a) = Data
type PContravariant' (PAsData a) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PCovariant' (PAsData a) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PInner (PAsData a) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PInner (PAsData a)
type PVariant' (PAsData a) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

data PBuiltinList (a :: S -> Type) (s :: S) Source #

Plutus BuiltinList

Constructors

PCons (Term s a) (Term s (PBuiltinList a)) 
PNil 

Instances

Instances details
PListLike PBuiltinList Source # 
Instance details

Defined in Plutarch.Internal.ListLike

Associated Types

type PElemConstraint PBuiltinList a Source #

Methods

pelimList :: forall (a :: S -> Type) (s :: S) (r :: PType). PElemConstraint PBuiltinList a => (Term s a -> Term s (PBuiltinList a) -> Term s r) -> Term s r -> Term s (PBuiltinList a) -> Term s r Source #

pcons :: forall (a :: S -> Type) (s :: S). PElemConstraint PBuiltinList a => Term s (a :--> (PBuiltinList a :--> PBuiltinList a)) Source #

pnil :: forall (a :: S -> Type) (s :: S). PElemConstraint PBuiltinList a => Term s (PBuiltinList a) Source #

phead :: forall (a :: S -> Type) (s :: S). PElemConstraint PBuiltinList a => Term s (PBuiltinList a :--> a) Source #

ptail :: forall (a :: S -> Type) (s :: S). PElemConstraint PBuiltinList a => Term s (PBuiltinList a :--> PBuiltinList a) Source #

pnull :: forall (a :: S -> Type) (s :: S). PElemConstraint PBuiltinList a => Term s (PBuiltinList a :--> PBool) Source #

(PTryFrom PData (PAsData a), PIsData a) => PTryFrom PData (PAsData (PBuiltinList (PAsData a))) Source #

Recover a `PBuiltinList (PAsData a)`

Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData (PAsData (PBuiltinList (PAsData a))) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PBuiltinList (PAsData a))), Reduce (PTryFromExcess PData (PAsData (PBuiltinList (PAsData a))) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData (PBuiltinList PData)) Source #

This verifies a list to be indeed a list but doesn't recover the inner data use this instance instead of the one for `PData (PAsData (PBuiltinList (PAsData a)))` as this is O(1) instead of O(n)

Instance details

Defined in Plutarch.Internal.TryFrom

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PBuiltinList PData)), Reduce (PTryFromExcess PData (PAsData (PBuiltinList PData)) s)) -> Term s r) -> Term s r Source #

Fc (F a) a => PEq (PBuiltinList a) Source # 
Instance details

Defined in Plutarch.Internal.Eq

Methods

(#==) :: forall (s :: S). Term s (PBuiltinList a) -> Term s (PBuiltinList a) -> Term s PBool Source #

PSubtype PData a => PIsData (PBuiltinList a) Source # 
Instance details

Defined in Plutarch.Internal.IsData

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData (PBuiltinList a)) -> Term s (PBuiltinList a) Source #

pdataImpl :: forall (s :: S). Term s (PBuiltinList a) -> Term s PData Source #

(PLiftable a, Contains DefaultUni (PlutusRepr a)) => PLiftable (PBuiltinList a) Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type AsHaskell (PBuiltinList a) Source #

type PlutusRepr (PBuiltinList a) Source #

Contains DefaultUni (PlutusRepr a) => PlutusType (PBuiltinList a) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Methods

pcon' :: forall (s :: S). PBuiltinList a s -> Term s (PInner (PBuiltinList a)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PBuiltinList a)) -> (PBuiltinList a s -> Term s b) -> Term s b Source #

(PShow a, Contains DefaultUni (PlutusRepr a)) => PShow (PBuiltinList a) Source # 
Instance details

Defined in Plutarch.Internal.Show

Methods

pshow' :: forall (s :: S). Bool -> Term s (PBuiltinList a) -> Term s PString Source #

(Helper2 (PSubtype' PData pty) pty, PTryFrom (PBuiltinList PData) (PDataRecord as), PTryFromExcess (PBuiltinList PData) (PDataRecord as) ~ HRecP ase) => PTryFrom (PBuiltinList PData) (PDataRecord ((name ':= pty) ': as)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Associated Types

type PTryFromExcess (PBuiltinList PData) (PDataRecord ((name ':= pty) ': as)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s (PBuiltinList PData) -> ((Term s (PDataRecord ((name ':= pty) ': as)), Reduce (PTryFromExcess (PBuiltinList PData) (PDataRecord ((name ':= pty) ': as)) s)) -> Term s r) -> Term s r Source #

PTryFrom (PBuiltinList PData) (PDataRecord ('[] :: [PLabeledType])) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Associated Types

type PTryFromExcess (PBuiltinList PData) (PDataRecord '[]) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s (PBuiltinList PData) -> ((Term s (PDataRecord '[]), Reduce (PTryFromExcess (PBuiltinList PData) (PDataRecord '[]) s)) -> Term s r) -> Term s r Source #

PIsData (PBuiltinPair PInteger (PBuiltinList PData)) Source # 
Instance details

Defined in Plutarch.Internal.IsData

type PElemConstraint PBuiltinList a Source # 
Instance details

Defined in Plutarch.Internal.ListLike

type PElemConstraint PBuiltinList a = Contains DefaultUni (PlutusRepr a)
type PTryFromExcess PData (PAsData (PBuiltinList (PAsData a))) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type PTryFromExcess PData (PAsData (PBuiltinList PData)) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type AsHaskell (PBuiltinList a) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PlutusRepr (PBuiltinList a) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PContravariant' (PBuiltinList a) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PCovariant' (PBuiltinList a) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PInner (PBuiltinList a) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PVariant' (PBuiltinList a) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PTryFromExcess (PBuiltinList PData) (PDataRecord ((name ':= pty) ': as)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

type PTryFromExcess (PBuiltinList PData) (PDataRecord ((name ':= pty) ': as))
type PTryFromExcess (PBuiltinList PData) (PDataRecord ('[] :: [PLabeledType])) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

newtype PBuiltinPair (a :: S -> Type) (b :: S -> Type) (s :: S) Source #

Constructors

PBuiltinPair (Term s (PBuiltinPair a b)) 

Instances

Instances details
(PTryFrom PData a, a ~ PAsData a', PIsData a', PTryFrom PData b, b ~ PAsData b', PIsData b') => PTryFrom PData (PAsData (PBuiltinPair a b)) Source #

Recover a `PAsData (PBuiltinPair a b)`

Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData (PAsData (PBuiltinPair a b)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PBuiltinPair a b)), Reduce (PTryFromExcess PData (PAsData (PBuiltinPair a b)) s)) -> Term s r) -> Term s r Source #

(PEq a, PEq b) => PEq (PBuiltinPair a b) Source # 
Instance details

Defined in Plutarch.Internal.Eq

Methods

(#==) :: forall (s :: S). Term s (PBuiltinPair a b) -> Term s (PBuiltinPair a b) -> Term s PBool Source #

PIsData (PBuiltinPair (PAsData a) (PAsData b)) Source # 
Instance details

Defined in Plutarch.Internal.IsData

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData (PBuiltinPair (PAsData a) (PAsData b))) -> Term s (PBuiltinPair (PAsData a) (PAsData b)) Source #

pdataImpl :: forall (s :: S). Term s (PBuiltinPair (PAsData a) (PAsData b)) -> Term s PData Source #

PIsData (PBuiltinPair PData PData) Source # 
Instance details

Defined in Plutarch.Internal.IsData

PIsData (PBuiltinPair PInteger (PBuiltinList PData)) Source # 
Instance details

Defined in Plutarch.Internal.IsData

(PLiftable a, Contains DefaultUni (PlutusRepr a), PLiftable b, Contains DefaultUni (PlutusRepr b)) => PLiftable (PBuiltinPair a b) Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type AsHaskell (PBuiltinPair a b) Source #

type PlutusRepr (PBuiltinPair a b) Source #

PlutusType (PBuiltinPair a b) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Methods

pcon' :: forall (s :: S). PBuiltinPair a b s -> Term s (PInner (PBuiltinPair a b)) Source #

pmatch' :: forall (s :: S) (b0 :: PType). Term s (PInner (PBuiltinPair a b)) -> (PBuiltinPair a b s -> Term s b0) -> Term s b0 Source #

(PShow a, PShow b) => PShow (PBuiltinPair a b) Source # 
Instance details

Defined in Plutarch.Internal.Show

Methods

pshow' :: forall (s :: S). Bool -> Term s (PBuiltinPair a b) -> Term s PString Source #

type PTryFromExcess PData (PAsData (PBuiltinPair a b)) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type AsHaskell (PBuiltinPair a b) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PlutusRepr (PBuiltinPair a b) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PContravariant' (PBuiltinPair a b) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PCovariant' (PBuiltinPair a b) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PInner (PBuiltinPair a b) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PVariant' (PBuiltinPair a b) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

newtype PData (s :: S) Source #

Constructors

PData (Term s PData) 

Instances

Instances details
PEq PData Source # 
Instance details

Defined in Plutarch.Internal.Eq

Methods

(#==) :: forall (s :: S). Term s PData -> Term s PData -> Term s PBool Source #

PIsData PData Source # 
Instance details

Defined in Plutarch.Internal.IsData

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PData) -> Term s PData Source #

pdataImpl :: forall (s :: S). Term s PData -> Term s PData Source #

PLiftable PData Source # 
Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type AsHaskell PData Source #

type PlutusRepr PData Source #

PlutusType PData Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Methods

pcon' :: forall (s :: S). PData s -> Term s (PInner PData) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PData) -> (PData s -> Term s b) -> Term s b Source #

PShow PData Source # 
Instance details

Defined in Plutarch.Internal.Show

Methods

pshow' :: forall (s :: S). Bool -> Term s PData -> Term s PString Source #

PTryFrom PData PData Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData PData :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s PData, Reduce (PTryFromExcess PData PData s)) -> Term s r) -> Term s r Source #

(PIsData a, PTryFrom PData (PAsData a)) => PTryFrom PData (PDataNewtype a) Source #

Since: 1.7.0

Instance details

Defined in Plutarch.Builtin

Associated Types

type PTryFromExcess PData (PDataNewtype a) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PDataNewtype a), Reduce (PTryFromExcess PData (PDataNewtype a) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData (PDataNewtype a)) Source #

Since: 1.7.0

Instance details

Defined in Plutarch.Builtin

Associated Types

type PTryFromExcess PData (PAsData (PDataNewtype a)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PDataNewtype a)), Reduce (PTryFromExcess PData (PAsData (PDataNewtype a)) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData PBool) Source #

Since: 1.7.0

Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData (PAsData PBool) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData PBool), Reduce (PTryFromExcess PData (PAsData PBool) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData PByteString) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData PByteString), Reduce (PTryFromExcess PData (PAsData PByteString) s)) -> Term s r) -> Term s r Source #

(PTryFrom PData (PAsData a), PIsData a) => PTryFrom PData (PAsData (PBuiltinList (PAsData a))) Source #

Recover a `PBuiltinList (PAsData a)`

Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData (PAsData (PBuiltinList (PAsData a))) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PBuiltinList (PAsData a))), Reduce (PTryFromExcess PData (PAsData (PBuiltinList (PAsData a))) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData (PBuiltinList PData)) Source #

This verifies a list to be indeed a list but doesn't recover the inner data use this instance instead of the one for `PData (PAsData (PBuiltinList (PAsData a)))` as this is O(1) instead of O(n)

Instance details

Defined in Plutarch.Internal.TryFrom

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PBuiltinList PData)), Reduce (PTryFromExcess PData (PAsData (PBuiltinList PData)) s)) -> Term s r) -> Term s r Source #

(PTryFrom PData a, a ~ PAsData a', PIsData a', PTryFrom PData b, b ~ PAsData b', PIsData b') => PTryFrom PData (PAsData (PBuiltinPair a b)) Source #

Recover a `PAsData (PBuiltinPair a b)`

Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData (PAsData (PBuiltinPair a b)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PBuiltinPair a b)), Reduce (PTryFromExcess PData (PAsData (PBuiltinPair a b)) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData PData) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData (PAsData PData) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData PData), Reduce (PTryFromExcess PData (PAsData PData) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData PInteger) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData (PAsData PInteger) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData PInteger), Reduce (PTryFromExcess PData (PAsData PInteger) s)) -> Term s r) -> Term s r Source #

(PTryFrom (PBuiltinList PData) (PDataRecord as), PTryFromExcess (PBuiltinList PData) (PDataRecord as) ~ HRecP ase) => PTryFrom PData (PAsData (PDataRecord as)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Associated Types

type PTryFromExcess PData (PAsData (PDataRecord as)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PDataRecord as)), Reduce (PTryFromExcess PData (PAsData (PDataRecord as)) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PDataSum ys) => PTryFrom PData (PAsData (PDataSum ys)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Associated Types

type PTryFromExcess PData (PAsData (PDataSum ys)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PDataSum ys)), Reduce (PTryFromExcess PData (PAsData (PDataSum ys)) s)) -> Term s r) -> Term s r Source #

(PTryFrom PData a, PTryFrom PData b) => PTryFrom PData (PAsData (PEitherData a b)) Source #

@since WIP

Instance details

Defined in Plutarch.Either

Associated Types

type PTryFromExcess PData (PAsData (PEitherData a b)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PEitherData a b)), Reduce (PTryFromExcess PData (PAsData (PEitherData a b)) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData PPositive) Source #

@since WIP

Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData (PAsData PPositive) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData PPositive), Reduce (PTryFromExcess PData (PAsData PPositive) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData PRational) Source #

NOTE: This instance produces a verified PPositive as the excess output.

Instance details

Defined in Plutarch.Rational

Associated Types

type PTryFromExcess PData (PAsData PRational) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData PRational), Reduce (PTryFromExcess PData (PAsData PRational) s)) -> Term s r) -> Term s r Source #

SumValidation 0 ys => PTryFrom PData (PDataSum ys) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Associated Types

type PTryFromExcess PData (PDataSum ys) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PDataSum ys), Reduce (PTryFromExcess PData (PDataSum ys) s)) -> Term s r) -> Term s r Source #

(PTryFrom PData a, PTryFrom PData b) => PTryFrom PData (PEitherData a b) Source #

@since WIP

Instance details

Defined in Plutarch.Either

Associated Types

type PTryFromExcess PData (PEitherData a b) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PEitherData a b), Reduce (PTryFromExcess PData (PEitherData a b) s)) -> Term s r) -> Term s r Source #

PLiftable (PAsData PData) Source # 
Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type AsHaskell (PAsData PData) Source #

type PlutusRepr (PAsData PData) Source #

(Helper2 (PSubtype' PData pty) pty, PTryFrom (PBuiltinList PData) (PDataRecord as), PTryFromExcess (PBuiltinList PData) (PDataRecord as) ~ HRecP ase) => PTryFrom (PBuiltinList PData) (PDataRecord ((name ':= pty) ': as)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Associated Types

type PTryFromExcess (PBuiltinList PData) (PDataRecord ((name ':= pty) ': as)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s (PBuiltinList PData) -> ((Term s (PDataRecord ((name ':= pty) ': as)), Reduce (PTryFromExcess (PBuiltinList PData) (PDataRecord ((name ':= pty) ': as)) s)) -> Term s r) -> Term s r Source #

PTryFrom (PBuiltinList PData) (PDataRecord ('[] :: [PLabeledType])) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Associated Types

type PTryFromExcess (PBuiltinList PData) (PDataRecord '[]) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s (PBuiltinList PData) -> ((Term s (PDataRecord '[]), Reduce (PTryFromExcess (PBuiltinList PData) (PDataRecord '[]) s)) -> Term s r) -> Term s r Source #

PIsData (PBuiltinPair PData PData) Source # 
Instance details

Defined in Plutarch.Internal.IsData

PIsData (PBuiltinPair PInteger (PBuiltinList PData)) Source # 
Instance details

Defined in Plutarch.Internal.IsData

type AsHaskell PData Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Lift

type PlutusRepr PData Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PContravariant' PData Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PCovariant' PData Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PCovariant' PData = ()
type PInner PData Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PVariant' PData Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PVariant' PData = ()
type PTryFromExcess PData PData Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type PTryFromExcess PData (PDataNewtype a) Source # 
Instance details

Defined in Plutarch.Builtin

type PTryFromExcess PData (PAsData (PDataNewtype a)) Source # 
Instance details

Defined in Plutarch.Builtin

type PTryFromExcess PData (PAsData PBool) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type PTryFromExcess PData (PAsData PByteString) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type PTryFromExcess PData (PAsData (PBuiltinList (PAsData a))) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type PTryFromExcess PData (PAsData (PBuiltinList PData)) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type PTryFromExcess PData (PAsData (PBuiltinPair a b)) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type PTryFromExcess PData (PAsData PData) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type PTryFromExcess PData (PAsData PInteger) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type PTryFromExcess PData (PAsData (PDataRecord as)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

type PTryFromExcess PData (PAsData (PDataSum ys)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

type PTryFromExcess PData (PAsData (PEitherData a b)) Source # 
Instance details

Defined in Plutarch.Either

type PTryFromExcess PData (PAsData PPositive) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type PTryFromExcess PData (PAsData PRational) Source # 
Instance details

Defined in Plutarch.Rational

type PTryFromExcess PData (PDataSum ys) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

type PTryFromExcess PData (PDataSum ys) = Const () :: S -> Type
type PTryFromExcess PData (PEitherData a b) Source # 
Instance details

Defined in Plutarch.Either

type AsHaskell (PAsData PData) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PlutusRepr (PAsData PData) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PlutusRepr (PAsData PData) = Data
type PTryFromExcess (PBuiltinList PData) (PDataRecord ((name ':= pty) ': as)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

type PTryFromExcess (PBuiltinList PData) (PDataRecord ((name ':= pty) ': as))
type PTryFromExcess (PBuiltinList PData) (PDataRecord ('[] :: [PLabeledType])) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

pchooseData :: Term s (PData :--> (a :--> (a :--> (a :--> (a :--> (a :--> a)))))) Source #

ppairDataBuiltin :: Term s (PAsData a :--> (PAsData b :--> PBuiltinPair (PAsData a) (PAsData b))) Source #

Construct a builtin pair of PData elements.

Uses PAsData to preserve more information about the underlying PData.

pserialiseData :: Term s (PData :--> PByteString) Source #

Serialise any builtin data to its cbor represented by a builtin bytestring

Integer

data PInteger s Source #

A builtin Plutus integer.

@since WIP

Instances

Instances details
PCountable PInteger Source #

@since WIP

Instance details

Defined in Plutarch.Enum

Methods

psuccessor :: forall (s :: S). Term s (PInteger :--> PInteger) Source #

psuccessorN :: forall (s :: S). Term s (PPositive :--> (PInteger :--> PInteger)) Source #

PEnumerable PInteger Source #

@since WIP

Instance details

Defined in Plutarch.Enum

Methods

ppredecessor :: forall (s :: S). Term s (PInteger :--> PInteger) Source #

ppredecessorN :: forall (s :: S). Term s (PPositive :--> (PInteger :--> PInteger)) Source #

PEq PInteger Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Eq

Methods

(#==) :: forall (s :: S). Term s PInteger -> Term s PInteger -> Term s PBool Source #

PIsData PInteger Source # 
Instance details

Defined in Plutarch.Internal.IsData

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PInteger) -> Term s PInteger Source #

pdataImpl :: forall (s :: S). Term s PInteger -> Term s PData Source #

PLiftable PInteger Source # 
Instance details

Defined in Plutarch.Internal.Lift

PAdditiveGroup PInteger Source #

@since WIP

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

pnegate :: forall (s :: S). Term s (PInteger :--> PInteger) Source #

(#-) :: forall (s :: S). Term s PInteger -> Term s PInteger -> Term s PInteger Source #

pscaleInteger :: forall (s :: S). Term s (PInteger :--> (PInteger :--> PInteger)) Source #

PAdditiveMonoid PInteger Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

pzero :: forall (s :: S). Term s PInteger Source #

PAdditiveSemigroup PInteger Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

(#+) :: forall (s :: S). Term s PInteger -> Term s PInteger -> Term s PInteger Source #

pscalePositive :: forall (s :: S). Term s (PInteger :--> (PPositive :--> PInteger)) Source #

PIntegralDomain PInteger Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

psignum :: forall (s :: S). Term s (PInteger :--> PInteger) Source #

pabs :: forall (s :: S). Term s (PInteger :--> PInteger) Source #

PMultiplicativeMonoid PInteger Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

pone :: forall (s :: S). Term s PInteger Source #

PMultiplicativeSemigroup PInteger Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

(#*) :: forall (s :: S). Term s PInteger -> Term s PInteger -> Term s PInteger Source #

ppowPositive :: forall (s :: S). Term s (PInteger :--> (PPositive :--> PInteger)) Source #

PRing PInteger Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

pfromInteger :: forall (s :: S). Integer -> Term s PInteger Source #

POrd PInteger Source # 
Instance details

Defined in Plutarch.Internal.Ord

Methods

(#<=) :: forall (s :: S). Term s PInteger -> Term s PInteger -> Term s PBool Source #

(#<) :: forall (s :: S). Term s PInteger -> Term s PInteger -> Term s PBool Source #

pmax :: forall (s :: S). Term s PInteger -> Term s PInteger -> Term s PInteger Source #

pmin :: forall (s :: S). Term s PInteger -> Term s PInteger -> Term s PInteger Source #

DerivePlutusType PInteger Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Associated Types

type DPTStrat PInteger Source #

PlutusType PInteger Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Methods

pcon' :: forall (s :: S). PInteger s -> Term s (PInner PInteger) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PInteger) -> (PInteger s -> Term s b) -> Term s b Source #

PShow PInteger Source # 
Instance details

Defined in Plutarch.Internal.Show

Methods

pshow' :: forall (s :: S). Bool -> Term s PInteger -> Term s PString Source #

PTryFrom PInteger PPositive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PInteger PPositive :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PInteger -> ((Term s PPositive, Reduce (PTryFromExcess PInteger PPositive s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData PInteger) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData (PAsData PInteger) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData PInteger), Reduce (PTryFromExcess PData (PAsData PInteger) s)) -> Term s r) -> Term s r Source #

Generic (PInteger s) Source # 
Instance details

Defined in Plutarch.Builtin.Integer

Associated Types

type Rep (PInteger s) :: Type -> Type Source #

Methods

from :: PInteger s -> Rep (PInteger s) x Source #

to :: Rep (PInteger s) x -> PInteger s Source #

PIsData (PBuiltinPair PInteger (PBuiltinList PData)) Source # 
Instance details

Defined in Plutarch.Internal.IsData

type AsHaskell PInteger Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PlutusRepr PInteger Source # 
Instance details

Defined in Plutarch.Internal.Lift

type DPTStrat PInteger Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PContravariant' PInteger Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PCovariant' PInteger Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PInner PInteger Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PVariant' PInteger Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PTryFromExcess PInteger PPositive Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type PTryFromExcess PData (PAsData PInteger) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type Rep (PInteger s) Source # 
Instance details

Defined in Plutarch.Builtin.Integer

type Rep (PInteger s) = D1 ('MetaData "PInteger" "Plutarch.Builtin.Integer" "plutarch-1.9.0-FtN0mhIoM9oEvz7Q98pjWP" 'True) (C1 ('MetaCons "PInteger" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s POpaque))))

Opaque

newtype POpaque s Source #

An Arbitrary Term with an unknown type

Constructors

POpaque (Term s POpaque) 

Instances

Instances details
PlutusType POpaque Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Methods

pcon' :: forall (s :: S). POpaque s -> Term s (PInner POpaque) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner POpaque) -> (POpaque s -> Term s b) -> Term s b Source #

type PContravariant' POpaque Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PCovariant' POpaque Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PInner POpaque Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PVariant' POpaque Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PVariant' POpaque = ()

popaque :: Term s a -> Term s POpaque Source #

Erase the type of a Term

String

data PString s Source #

Plutus BuiltinString values

Instances

Instances details
PEq PString Source # 
Instance details

Defined in Plutarch.Internal.Eq

Methods

(#==) :: forall (s :: S). Term s PString -> Term s PString -> Term s PBool Source #

PLiftable PString Source # 
Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type AsHaskell PString Source #

type PlutusRepr PString Source #

DerivePlutusType PString Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Associated Types

type DPTStrat PString Source #

PlutusType PString Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Methods

pcon' :: forall (s :: S). PString s -> Term s (PInner PString) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PString) -> (PString s -> Term s b) -> Term s b Source #

PShow PString Source # 
Instance details

Defined in Plutarch.Internal.Show

Methods

pshow' :: forall (s :: S). Bool -> Term s PString -> Term s PString Source #

Generic (PString s) Source # 
Instance details

Defined in Plutarch.Builtin.String

Associated Types

type Rep (PString s) :: Type -> Type Source #

Methods

from :: PString s -> Rep (PString s) x Source #

to :: Rep (PString s) x -> PString s Source #

IsString (Term s PString) Source # 
Instance details

Defined in Plutarch.Builtin.String

Monoid (Term s PString) Source # 
Instance details

Defined in Plutarch.Builtin.String

Semigroup (Term s PString) Source # 
Instance details

Defined in Plutarch.Builtin.String

type AsHaskell PString Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PlutusRepr PString Source # 
Instance details

Defined in Plutarch.Internal.Lift

type DPTStrat PString Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PContravariant' PString Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PCovariant' PString Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PInner PString Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PVariant' PString Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type Rep (PString s) Source # 
Instance details

Defined in Plutarch.Builtin.String

type Rep (PString s) = D1 ('MetaData "PString" "Plutarch.Builtin.String" "plutarch-1.9.0-FtN0mhIoM9oEvz7Q98pjWP" 'True) (C1 ('MetaCons "PString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s POpaque))))

pencodeUtf8 :: Term s (PString :--> PByteString) Source #

Encode a PString using UTF-8.

Unit

data PUnit (s :: S) Source #

Constructors

PUnit 

Instances

Instances details
PEq PUnit Source # 
Instance details

Defined in Plutarch.Internal.Eq

Methods

(#==) :: forall (s :: S). Term s PUnit -> Term s PUnit -> Term s PBool Source #

PIsData PUnit Source # 
Instance details

Defined in Plutarch.Internal.IsData

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PUnit) -> Term s PUnit Source #

pdataImpl :: forall (s :: S). Term s PUnit -> Term s PData Source #

PLiftable PUnit Source # 
Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type AsHaskell PUnit Source #

type PlutusRepr PUnit Source #

POrd PUnit Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Ord

Methods

(#<=) :: forall (s :: S). Term s PUnit -> Term s PUnit -> Term s PBool Source #

(#<) :: forall (s :: S). Term s PUnit -> Term s PUnit -> Term s PBool Source #

pmax :: forall (s :: S). Term s PUnit -> Term s PUnit -> Term s PUnit Source #

pmin :: forall (s :: S). Term s PUnit -> Term s PUnit -> Term s PUnit Source #

PlutusType PUnit Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Methods

pcon' :: forall (s :: S). PUnit s -> Term s (PInner PUnit) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PUnit) -> (PUnit s -> Term s b) -> Term s b Source #

PShow PUnit Source # 
Instance details

Defined in Plutarch.Internal.Show

Methods

pshow' :: forall (s :: S). Bool -> Term s PUnit -> Term s PString Source #

Monoid (Term s PUnit) Source # 
Instance details

Defined in Plutarch.Builtin.Unit

Semigroup (Term s PUnit) Source # 
Instance details

Defined in Plutarch.Builtin.Unit

type AsHaskell PUnit Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Lift

type PlutusRepr PUnit Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PContravariant' PUnit Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PCovariant' PUnit Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PInner PUnit Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PVariant' PUnit Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

DataRepr

class PDataFields (a :: S -> Type) Source #

Class allowing letFields to work for a PType, usually via PIsDataRepr, but is derived for some other types for convenience.

Instances

Instances details
(PIsData a, PDataFields a) => PDataFields (PAsData a) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal.Field

Associated Types

type PFields (PAsData a) :: [PLabeledType] Source #

Methods

ptoFields :: forall (s :: S). Term s (PAsData a) -> Term s (PDataRecord (PFields (PAsData a))) Source #

PDataFields (PDataRecord as) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal.Field

Associated Types

type PFields (PDataRecord as) :: [PLabeledType] Source #

Methods

ptoFields :: forall (s :: S). Term s (PDataRecord as) -> Term s (PDataRecord (PFields (PDataRecord as))) Source #

PDataFields (PDataSum '[as]) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal.Field

Associated Types

type PFields (PDataSum '[as]) :: [PLabeledType] Source #

Methods

ptoFields :: forall (s :: S). Term s (PDataSum '[as]) -> Term s (PDataRecord (PFields (PDataSum '[as]))) Source #

data PDataRecord (as :: [PLabeledType]) (s :: S) Source #

A "record" of `exists a. PAsData a`. The underlying representation is `PBuiltinList PData`.

Instances

Instances details
(PTryFrom (PBuiltinList PData) (PDataRecord as), PTryFromExcess (PBuiltinList PData) (PDataRecord as) ~ HRecP ase) => PTryFrom PData (PAsData (PDataRecord as)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Associated Types

type PTryFromExcess PData (PAsData (PDataRecord as)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PDataRecord as)), Reduce (PTryFromExcess PData (PAsData (PDataRecord as)) s)) -> Term s r) -> Term s r Source #

PDataFields (PDataRecord as) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal.Field

Associated Types

type PFields (PDataRecord as) :: [PLabeledType] Source #

Methods

ptoFields :: forall (s :: S). Term s (PDataRecord as) -> Term s (PDataRecord (PFields (PDataRecord as))) Source #

PEq (PDataRecord xs) Source #

This uses data equality. PEq instances of elements don't make any difference.

Instance details

Defined in Plutarch.DataRepr.Internal

Methods

(#==) :: forall (s :: S). Term s (PDataRecord xs) -> Term s (PDataRecord xs) -> Term s PBool Source #

PIsData (PDataRecord xs) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData (PDataRecord xs)) -> Term s (PDataRecord xs) Source #

pdataImpl :: forall (s :: S). Term s (PDataRecord xs) -> Term s PData Source #

(SListI xs, POrd x, PIsData x, POrd (PDataRecord (x' ': xs))) => POrd (PDataRecord ((label ':= x) ': (x' ': xs))) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

(#<=) :: forall (s :: S). Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s PBool Source #

(#<) :: forall (s :: S). Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s PBool Source #

pmax :: forall (s :: S). Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s (PDataRecord ((label ':= x) ': (x' ': xs))) Source #

pmin :: forall (s :: S). Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s (PDataRecord ((label ':= x) ': (x' ': xs))) Source #

(POrd x, PIsData x) => POrd (PDataRecord '[label ':= x]) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

(#<=) :: forall (s :: S). Term s (PDataRecord '[label ':= x]) -> Term s (PDataRecord '[label ':= x]) -> Term s PBool Source #

(#<) :: forall (s :: S). Term s (PDataRecord '[label ':= x]) -> Term s (PDataRecord '[label ':= x]) -> Term s PBool Source #

pmax :: forall (s :: S). Term s (PDataRecord '[label ':= x]) -> Term s (PDataRecord '[label ':= x]) -> Term s (PDataRecord '[label ':= x]) Source #

pmin :: forall (s :: S). Term s (PDataRecord '[label ':= x]) -> Term s (PDataRecord '[label ':= x]) -> Term s (PDataRecord '[label ':= x]) Source #

POrd (PDataRecord ('[] :: [PLabeledType])) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

(#<=) :: forall (s :: S). Term s (PDataRecord '[]) -> Term s (PDataRecord '[]) -> Term s PBool Source #

(#<) :: forall (s :: S). Term s (PDataRecord '[]) -> Term s (PDataRecord '[]) -> Term s PBool Source #

pmax :: forall (s :: S). Term s (PDataRecord '[]) -> Term s (PDataRecord '[]) -> Term s (PDataRecord '[]) Source #

pmin :: forall (s :: S). Term s (PDataRecord '[]) -> Term s (PDataRecord '[]) -> Term s (PDataRecord '[]) Source #

SListI l => PlutusType (PDataRecord l) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

pcon' :: forall (s :: S). PDataRecord l s -> Term s (PInner (PDataRecord l)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PDataRecord l)) -> (PDataRecord l s -> Term s b) -> Term s b Source #

(All (Top :: PLabeledType -> Constraint) xs, KnownSymbol label, PIsData x, PShow x, PShow (PDataRecordShowHelper xs)) => PShow (PDataRecord ((label ':= x) ': xs)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

pshow' :: forall (s :: S). Bool -> Term s (PDataRecord ((label ':= x) ': xs)) -> Term s PString Source #

PShow (PDataRecord ('[] :: [PLabeledType])) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

pshow' :: forall (s :: S). Bool -> Term s (PDataRecord '[]) -> Term s PString Source #

(Helper2 (PSubtype' PData pty) pty, PTryFrom (PBuiltinList PData) (PDataRecord as), PTryFromExcess (PBuiltinList PData) (PDataRecord as) ~ HRecP ase) => PTryFrom (PBuiltinList PData) (PDataRecord ((name ':= pty) ': as)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Associated Types

type PTryFromExcess (PBuiltinList PData) (PDataRecord ((name ':= pty) ': as)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s (PBuiltinList PData) -> ((Term s (PDataRecord ((name ':= pty) ': as)), Reduce (PTryFromExcess (PBuiltinList PData) (PDataRecord ((name ':= pty) ': as)) s)) -> Term s r) -> Term s r Source #

PTryFrom (PBuiltinList PData) (PDataRecord ('[] :: [PLabeledType])) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Associated Types

type PTryFromExcess (PBuiltinList PData) (PDataRecord '[]) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s (PBuiltinList PData) -> ((Term s (PDataRecord '[]), Reduce (PTryFromExcess (PBuiltinList PData) (PDataRecord '[]) s)) -> Term s r) -> Term s r Source #

type PTryFromExcess PData (PAsData (PDataRecord as)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

type PFields (PDataRecord as) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal.Field

type PFields (PDataRecord as) = as
type PContravariant' (PDataRecord l) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

type PCovariant' (PDataRecord l) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

type PInner (PDataRecord l) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

type PVariant' (PDataRecord l) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

type PTryFromExcess (PBuiltinList PData) (PDataRecord ((name ':= pty) ': as)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

type PTryFromExcess (PBuiltinList PData) (PDataRecord ((name ':= pty) ': as))
type PTryFromExcess (PBuiltinList PData) (PDataRecord ('[] :: [PLabeledType])) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

data PDataSum defs s Source #

A sum of PDataRecords. The underlying representation is the Constr constructor, where the integer is the index of the variant and the list is the record.

Instances

Instances details
PTryFrom PData (PDataSum ys) => PTryFrom PData (PAsData (PDataSum ys)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Associated Types

type PTryFromExcess PData (PAsData (PDataSum ys)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PDataSum ys)), Reduce (PTryFromExcess PData (PAsData (PDataSum ys)) s)) -> Term s r) -> Term s r Source #

SumValidation 0 ys => PTryFrom PData (PDataSum ys) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Associated Types

type PTryFromExcess PData (PDataSum ys) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PDataSum ys), Reduce (PTryFromExcess PData (PDataSum ys) s)) -> Term s r) -> Term s r Source #

PDataFields (PDataSum '[as]) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal.Field

Associated Types

type PFields (PDataSum '[as]) :: [PLabeledType] Source #

Methods

ptoFields :: forall (s :: S). Term s (PDataSum '[as]) -> Term s (PDataRecord (PFields (PDataSum '[as]))) Source #

PEq (PDataSum defs) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

(#==) :: forall (s :: S). Term s (PDataSum defs) -> Term s (PDataSum defs) -> Term s PBool Source #

PIsData (PDataSum defs) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData (PDataSum defs)) -> Term s (PDataSum defs) Source #

pdataImpl :: forall (s :: S). Term s (PDataSum defs) -> Term s PData Source #

All (Compose POrd PDataRecord) defs => POrd (PDataSum defs) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

(#<=) :: forall (s :: S). Term s (PDataSum defs) -> Term s (PDataSum defs) -> Term s PBool Source #

(#<) :: forall (s :: S). Term s (PDataSum defs) -> Term s (PDataSum defs) -> Term s PBool Source #

pmax :: forall (s :: S). Term s (PDataSum defs) -> Term s (PDataSum defs) -> Term s (PDataSum defs) Source #

pmin :: forall (s :: S). Term s (PDataSum defs) -> Term s (PDataSum defs) -> Term s (PDataSum defs) Source #

SListI defs => PlutusType (PDataSum defs) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Associated Types

type PInner (PDataSum defs) :: PType Source #

type PCovariant' (PDataSum defs) Source #

type PContravariant' (PDataSum defs) Source #

type PVariant' (PDataSum defs) Source #

Methods

pcon' :: forall (s :: S). PDataSum defs s -> Term s (PInner (PDataSum defs)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PDataSum defs)) -> (PDataSum defs s -> Term s b) -> Term s b Source #

(All (Top :: [PLabeledType] -> Constraint) defs, All (Compose PShow PDataRecord) defs) => PShow (PDataSum defs) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

pshow' :: forall (s :: S). Bool -> Term s (PDataSum defs) -> Term s PString Source #

type PTryFromExcess PData (PAsData (PDataSum ys)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

type PTryFromExcess PData (PDataSum ys) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

type PTryFromExcess PData (PDataSum ys) = Const () :: S -> Type
type PFields (PDataSum '[as]) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal.Field

type PFields (PDataSum '[as]) = as
type PContravariant' (PDataSum defs) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

type PCovariant' (PDataSum defs) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

type PCovariant' (PDataSum defs) = All2 PCovariant'' (PCode (PDataSum defs))
type PInner (PDataSum defs) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

type PInner (PDataSum defs) = PData
type PVariant' (PDataSum defs) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

type PVariant' (PDataSum defs) = All2 PVariant'' (PCode (PDataSum defs))

data PLabeledType Source #

Constructors

Symbol := (S -> Type) 

Instances

Instances details
PDataFields (PDataSum '[as]) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal.Field

Associated Types

type PFields (PDataSum '[as]) :: [PLabeledType] Source #

Methods

ptoFields :: forall (s :: S). Term s (PDataSum '[as]) -> Term s (PDataRecord (PFields (PDataSum '[as]))) Source #

(SListI xs, POrd x, PIsData x, POrd (PDataRecord (x' ': xs))) => POrd (PDataRecord ((label ':= x) ': (x' ': xs))) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

(#<=) :: forall (s :: S). Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s PBool Source #

(#<) :: forall (s :: S). Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s PBool Source #

pmax :: forall (s :: S). Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s (PDataRecord ((label ':= x) ': (x' ': xs))) Source #

pmin :: forall (s :: S). Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s (PDataRecord ((label ':= x) ': (x' ': xs))) Source #

(POrd x, PIsData x) => POrd (PDataRecord '[label ':= x]) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

(#<=) :: forall (s :: S). Term s (PDataRecord '[label ':= x]) -> Term s (PDataRecord '[label ':= x]) -> Term s PBool Source #

(#<) :: forall (s :: S). Term s (PDataRecord '[label ':= x]) -> Term s (PDataRecord '[label ':= x]) -> Term s PBool Source #

pmax :: forall (s :: S). Term s (PDataRecord '[label ':= x]) -> Term s (PDataRecord '[label ':= x]) -> Term s (PDataRecord '[label ':= x]) Source #

pmin :: forall (s :: S). Term s (PDataRecord '[label ':= x]) -> Term s (PDataRecord '[label ':= x]) -> Term s (PDataRecord '[label ':= x]) Source #

POrd (PDataRecord ('[] :: [PLabeledType])) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

(#<=) :: forall (s :: S). Term s (PDataRecord '[]) -> Term s (PDataRecord '[]) -> Term s PBool Source #

(#<) :: forall (s :: S). Term s (PDataRecord '[]) -> Term s (PDataRecord '[]) -> Term s PBool Source #

pmax :: forall (s :: S). Term s (PDataRecord '[]) -> Term s (PDataRecord '[]) -> Term s (PDataRecord '[]) Source #

pmin :: forall (s :: S). Term s (PDataRecord '[]) -> Term s (PDataRecord '[]) -> Term s (PDataRecord '[]) Source #

(All (Top :: PLabeledType -> Constraint) xs, KnownSymbol label, PIsData x, PShow x, PShow (PDataRecordShowHelper xs)) => PShow (PDataRecord ((label ':= x) ': xs)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

pshow' :: forall (s :: S). Bool -> Term s (PDataRecord ((label ':= x) ': xs)) -> Term s PString Source #

PShow (PDataRecord ('[] :: [PLabeledType])) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

pshow' :: forall (s :: S). Bool -> Term s (PDataRecord '[]) -> Term s PString Source #

(Helper2 (PSubtype' PData pty) pty, PTryFrom (PBuiltinList PData) (PDataRecord as), PTryFromExcess (PBuiltinList PData) (PDataRecord as) ~ HRecP ase) => PTryFrom (PBuiltinList PData) (PDataRecord ((name ':= pty) ': as)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Associated Types

type PTryFromExcess (PBuiltinList PData) (PDataRecord ((name ':= pty) ': as)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s (PBuiltinList PData) -> ((Term s (PDataRecord ((name ':= pty) ': as)), Reduce (PTryFromExcess (PBuiltinList PData) (PDataRecord ((name ':= pty) ': as)) s)) -> Term s r) -> Term s r Source #

PTryFrom (PBuiltinList PData) (PDataRecord ('[] :: [PLabeledType])) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Associated Types

type PTryFromExcess (PBuiltinList PData) (PDataRecord '[]) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s (PBuiltinList PData) -> ((Term s (PDataRecord '[]), Reduce (PTryFromExcess (PBuiltinList PData) (PDataRecord '[]) s)) -> Term s r) -> Term s r Source #

type PFields (PDataSum '[as]) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal.Field

type PFields (PDataSum '[as]) = as
type PTryFromExcess (PBuiltinList PData) (PDataRecord ((name ':= pty) ': as)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

type PTryFromExcess (PBuiltinList PData) (PDataRecord ((name ':= pty) ': as))
type PTryFromExcess (PBuiltinList PData) (PDataRecord ('[] :: [PLabeledType])) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

pdcons :: forall label a l s. Term s (PAsData a :--> (PDataRecord l :--> PDataRecord ((label ':= a) ': l))) Source #

Cons a field to a data record.

You can specify the label to associate with the field using type applications-

foo :: Term s (PDataRecord '[ "fooField" ':= PByteString ])
foo = pdcons @"fooField" # pdata (phexByteStr "ab") # pdnil

pfield :: forall name b p s a as n. (PDataFields p, as ~ PFields p, n ~ PLabelIndex name as, KnownNat n, a ~ PUnLabel (IndexList n as), PFromDataable a b) => Term s (p :--> b) Source #

Get a single field from a Term.

  • NB*: If you access more than one field from the same value you should use pletFields instead, which will generate the bindings more efficiently.

pletFields :: forall fs a s b ps bs. (PDataFields a, ps ~ PFields a, bs ~ Bindings ps fs, BindFields ps bs) => Term s a -> (HRecOf a fs s -> Term s b) -> Term s b Source #

Bind a HRec of named fields containing all the specified fields.

Either

data PEither (a :: S -> Type) (b :: S -> Type) (s :: S) Source #

Scott-encoded Either.

Constructors

PLeft (Term s a) 
PRight (Term s b) 

Instances

Instances details
(PEq a, PEq b) => PEq (PEither a b) Source # 
Instance details

Defined in Plutarch.Either

Methods

(#==) :: forall (s :: S). Term s (PEither a b) -> Term s (PEither a b) -> Term s PBool Source #

(PLiftable a, PLiftable b) => PLiftable (PEither a b) Source #

@since WIP

Instance details

Defined in Plutarch.Either

Associated Types

type AsHaskell (PEither a b) Source #

type PlutusRepr (PEither a b) Source #

DerivePlutusType (PEither a b) Source # 
Instance details

Defined in Plutarch.Either

Associated Types

type DPTStrat (PEither a b) Source #

PlutusType (PEither a b) Source # 
Instance details

Defined in Plutarch.Either

Associated Types

type PInner (PEither a b) :: PType Source #

type PCovariant' (PEither a b) Source #

type PContravariant' (PEither a b) Source #

type PVariant' (PEither a b) Source #

Methods

pcon' :: forall (s :: S). PEither a b s -> Term s (PInner (PEither a b)) Source #

pmatch' :: forall (s :: S) (b0 :: PType). Term s (PInner (PEither a b)) -> (PEither a b s -> Term s b0) -> Term s b0 Source #

(PShow a, PShow b) => PShow (PEither a b) Source # 
Instance details

Defined in Plutarch.Either

Methods

pshow' :: forall (s :: S). Bool -> Term s (PEither a b) -> Term s PString Source #

Generic (PEither a b s) Source # 
Instance details

Defined in Plutarch.Either

Associated Types

type Rep (PEither a b s) :: Type -> Type Source #

Methods

from :: PEither a b s -> Rep (PEither a b s) x Source #

to :: Rep (PEither a b s) x -> PEither a b s Source #

type AsHaskell (PEither a b) Source # 
Instance details

Defined in Plutarch.Either

type PlutusRepr (PEither a b) Source # 
Instance details

Defined in Plutarch.Either

type DPTStrat (PEither a b) Source # 
Instance details

Defined in Plutarch.Either

type PContravariant' (PEither a b) Source # 
Instance details

Defined in Plutarch.Either

type PCovariant' (PEither a b) Source # 
Instance details

Defined in Plutarch.Either

type PCovariant' (PEither a b) = All2 PCovariant'' (PCode (PEither a b))
type PInner (PEither a b) Source # 
Instance details

Defined in Plutarch.Either

type PInner (PEither a b) = DerivedPInner (DPTStrat (PEither a b)) (PEither a b)
type PVariant' (PEither a b) Source # 
Instance details

Defined in Plutarch.Either

type PVariant' (PEither a b) = All2 PVariant'' (PCode (PEither a b))
type Rep (PEither a b s) Source # 
Instance details

Defined in Plutarch.Either

type Rep (PEither a b s) = D1 ('MetaData "PEither" "Plutarch.Either" "plutarch-1.9.0-FtN0mhIoM9oEvz7Q98pjWP" 'False) (C1 ('MetaCons "PLeft" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s a))) :+: C1 ('MetaCons "PRight" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s b))))

Enumerable and Countable

class POrd a => PCountable (a :: S -> Type) where Source #

A notion of 'next' value. More formally, instances of this type class are discrete linear orders with no maximal element.

Laws

  1. x /= psuccessor x
  2. y < x = psuccessor y <= x
  3. x < psuccessor y = x <= y

If you define psuccessorN, you must also ensure the following hold; the default implementation ensures this.

  1. psuccessorN 1 = psuccessor
  2. psuccessorN n . psuccessorN m = psuccessorN (n + m)

Law 1 ensures no value is its own successor. Laws 2 and 3 ensure that there are no 'gaps': every value is 'reachable' from any lower value by a finite number of applications of successor.

@since WIP

Minimal complete definition

psuccessor

Methods

psuccessor :: forall (s :: S). Term s (a :--> a) Source #

@since WIP

psuccessorN :: forall (s :: S). Term s (PPositive :--> (a :--> a)) Source #

The default implementation of this function is inefficient: if at all possible, give instances an optimized version that doesn't require recursion.

@since WIP

Instances

Instances details
PCountable PInteger Source #

@since WIP

Instance details

Defined in Plutarch.Enum

Methods

psuccessor :: forall (s :: S). Term s (PInteger :--> PInteger) Source #

psuccessorN :: forall (s :: S). Term s (PPositive :--> (PInteger :--> PInteger)) Source #

PCountable PPositive Source #

@since WIP

Instance details

Defined in Plutarch.Enum

Methods

psuccessor :: forall (s :: S). Term s (PPositive :--> PPositive) Source #

psuccessorN :: forall (s :: S). Term s (PPositive :--> (PPositive :--> PPositive)) Source #

class PCountable a => PEnumerable (a :: S -> Type) where Source #

Similar to PCountable, but has the ability to get a 'previous' value as well. More formally, instances of this type class are discrete linear orders with no maximal or minimal element.

Laws

  1. ppredecessor . psuccessor = psuccessor . ppredecessor = id

If you define ppredecessorN, you must also ensure the following hold; the default implementation ensures this.

  1. ppredecessorN 1 = ppredecessor
  2. ppredecessorN n . ppredecessorN m = ppredecessorN (n + m)

From Law 1, we obtain the following theorem:

  • x /= predecessor x

@since WIP

Minimal complete definition

ppredecessor

Methods

ppredecessor :: forall (s :: S). Term s (a :--> a) Source #

@since WIP

ppredecessorN :: forall (s :: S). Term s (PPositive :--> (a :--> a)) Source #

The default implementation of this function is inefficient: if at all possible, give instances an optimized version that doesn't require recursion.

@since WIP

Instances

Instances details
PEnumerable PInteger Source #

@since WIP

Instance details

Defined in Plutarch.Enum

Methods

ppredecessor :: forall (s :: S). Term s (PInteger :--> PInteger) Source #

ppredecessorN :: forall (s :: S). Term s (PPositive :--> (PInteger :--> PInteger)) Source #

Eq and Ord

class PEq t where Source #

Minimal complete definition

Nothing

Methods

(#==) :: Term s t -> Term s t -> Term s PBool infix 4 Source #

default (#==) :: (PGeneric t, PlutusType t, All2 PEq (PCode t)) => Term s t -> Term s t -> Term s PBool Source #

Instances

Instances details
PEq PBitString Source #

@since WIP

Instance details

Defined in Plutarch.BitString

Methods

(#==) :: forall (s :: S). Term s PBitString -> Term s PBitString -> Term s PBool Source #

PEq PBuiltinBLS12_381_G1_Element Source # 
Instance details

Defined in Plutarch.Internal.Eq

PEq PBuiltinBLS12_381_G2_Element Source # 
Instance details

Defined in Plutarch.Internal.Eq

PEq PBool Source # 
Instance details

Defined in Plutarch.Internal.Eq

Methods

(#==) :: forall (s :: S). Term s PBool -> Term s PBool -> Term s PBool Source #

PEq PByte Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Eq

Methods

(#==) :: forall (s :: S). Term s PByte -> Term s PByte -> Term s PBool Source #

PEq PByteString Source # 
Instance details

Defined in Plutarch.Internal.Eq

Methods

(#==) :: forall (s :: S). Term s PByteString -> Term s PByteString -> Term s PBool Source #

PEq PEndianness Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Eq

Methods

(#==) :: forall (s :: S). Term s PEndianness -> Term s PEndianness -> Term s PBool Source #

PEq PLogicOpSemantics Source # 
Instance details

Defined in Plutarch.Internal.Eq

Methods

(#==) :: forall (s :: S). Term s PLogicOpSemantics -> Term s PLogicOpSemantics -> Term s PBool Source #

PEq PData Source # 
Instance details

Defined in Plutarch.Internal.Eq

Methods

(#==) :: forall (s :: S). Term s PData -> Term s PData -> Term s PBool Source #

PEq PInteger Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Eq

Methods

(#==) :: forall (s :: S). Term s PInteger -> Term s PInteger -> Term s PBool Source #

PEq PString Source # 
Instance details

Defined in Plutarch.Internal.Eq

Methods

(#==) :: forall (s :: S). Term s PString -> Term s PString -> Term s PBool Source #

PEq PUnit Source # 
Instance details

Defined in Plutarch.Internal.Eq

Methods

(#==) :: forall (s :: S). Term s PUnit -> Term s PUnit -> Term s PBool Source #

PEq PPositive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

(#==) :: forall (s :: S). Term s PPositive -> Term s PPositive -> Term s PBool Source #

PEq PRational Source # 
Instance details

Defined in Plutarch.Rational

Methods

(#==) :: forall (s :: S). Term s PRational -> Term s PRational -> Term s PBool Source #

PEq (PDataNewtype a) Source #

Since: 1.7.0

Instance details

Defined in Plutarch.Builtin

Methods

(#==) :: forall (s :: S). Term s (PDataNewtype a) -> Term s (PDataNewtype a) -> Term s PBool Source #

PEq (PAsData a) Source # 
Instance details

Defined in Plutarch.Internal.Eq

Methods

(#==) :: forall (s :: S). Term s (PAsData a) -> Term s (PAsData a) -> Term s PBool Source #

Fc (F a) a => PEq (PBuiltinList a) Source # 
Instance details

Defined in Plutarch.Internal.Eq

Methods

(#==) :: forall (s :: S). Term s (PBuiltinList a) -> Term s (PBuiltinList a) -> Term s PBool Source #

PEq (PDataRecord xs) Source #

This uses data equality. PEq instances of elements don't make any difference.

Instance details

Defined in Plutarch.DataRepr.Internal

Methods

(#==) :: forall (s :: S). Term s (PDataRecord xs) -> Term s (PDataRecord xs) -> Term s PBool Source #

PEq (PDataSum defs) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

(#==) :: forall (s :: S). Term s (PDataSum defs) -> Term s (PDataSum defs) -> Term s PBool Source #

PEq a => PEq (PList a) Source # 
Instance details

Defined in Plutarch.List

Methods

(#==) :: forall (s :: S). Term s (PList a) -> Term s (PList a) -> Term s PBool Source #

PEq a => PEq (PMaybe a) Source # 
Instance details

Defined in Plutarch.Maybe

Methods

(#==) :: forall (s :: S). Term s (PMaybe a) -> Term s (PMaybe a) -> Term s PBool Source #

PEq a => PEq (PMaybeSoP a) Source # 
Instance details

Defined in Plutarch.Maybe

Methods

(#==) :: forall (s :: S). Term s (PMaybeSoP a) -> Term s (PMaybeSoP a) -> Term s PBool Source #

PEq (PDataRec struct) Source #

@since WIP

Instance details

Defined in Plutarch.Repr.Data

Methods

(#==) :: forall (s :: S). Term s (PDataRec struct) -> Term s (PDataRec struct) -> Term s PBool Source #

PEq (PDataStruct struct) Source #

@since WIP

Instance details

Defined in Plutarch.Repr.Data

Methods

(#==) :: forall (s :: S). Term s (PDataStruct struct) -> Term s (PDataStruct struct) -> Term s PBool Source #

All PEq struct => PEq (PSOPRec struct) Source #

@since WIP

Instance details

Defined in Plutarch.Repr.SOP

Methods

(#==) :: forall (s :: S). Term s (PSOPRec struct) -> Term s (PSOPRec struct) -> Term s PBool Source #

(PlutusType (PSOPStruct struct), All2 PEq struct) => PEq (PSOPStruct struct) Source # 
Instance details

Defined in Plutarch.Repr.SOP

Methods

(#==) :: forall (s :: S). Term s (PSOPStruct struct) -> Term s (PSOPStruct struct) -> Term s PBool Source #

All PEq struct => PEq (PScottRec struct) Source #

@since WIP

Instance details

Defined in Plutarch.Repr.Scott

Methods

(#==) :: forall (s :: S). Term s (PScottRec struct) -> Term s (PScottRec struct) -> Term s PBool Source #

(PlutusType (PScottStruct struct), SListI2 struct, All2 PEq struct) => PEq (PScottStruct struct) Source #

@since WIP

Instance details

Defined in Plutarch.Repr.Scott

Methods

(#==) :: forall (s :: S). Term s (PScottStruct struct) -> Term s (PScottStruct struct) -> Term s PBool Source #

(PEq a, PEq b) => PEq (PBuiltinPair a b) Source # 
Instance details

Defined in Plutarch.Internal.Eq

Methods

(#==) :: forall (s :: S). Term s (PBuiltinPair a b) -> Term s (PBuiltinPair a b) -> Term s PBool Source #

(PEq a, PEq b) => PEq (PEither a b) Source # 
Instance details

Defined in Plutarch.Either

Methods

(#==) :: forall (s :: S). Term s (PEither a b) -> Term s (PEither a b) -> Term s PBool Source #

PEq (PEitherData a b) Source #

@since WIP

Instance details

Defined in Plutarch.Either

Methods

(#==) :: forall (s :: S). Term s (PEitherData a b) -> Term s (PEitherData a b) -> Term s PBool Source #

(PEq a, PEq b) => PEq (PPair a b) Source # 
Instance details

Defined in Plutarch.Pair

Methods

(#==) :: forall (s :: S). Term s (PPair a b) -> Term s (PPair a b) -> Term s PBool Source #

class PEq t => POrd t where Source #

Total ordering relation.

Laws

#<= must form a total order. More precisely:

  1. x #<= x = pcon PTrue (reflexivity)
  2. (y #< x) #|| (z #< y) #|| (x #<= z) = pcon PTrue (transitivity)
  3. (x #<= y) #|| (y #<= x) = pcon PTrue (totality)

Furthermore, #< must be an equivalent strict total order to #<=:

  1. x #< x = pcon PFalse (irreflexivity)
  2. (y #<= x) #|| (z #<= y) #|| (x #< z) = pcon PTrue (transitivity)
  3. (x #< y) #|| (y #< x) #|| (x #== z) = pcon PTrue (trichotomy)
  4. x #<= y = (x #< y) #|| (x #== y) (strict equivalence)

If you define pmax or pmin, ensure the following also hold:

  1. pmax # x # y = pmax # y # x (commutativity, also for @pmin)
  2. pmax # x #$ pmax y z = pmax # (pmax # x # y) # z (associativity, also for @pmin)
  3. pmax # x #$ pmin # y # z = pmin # (pmax # x # y) # (pmax # x # z) (pmax distributes over pmin, also equivalent for pmin)
  4. pmin x y = pif' (x #<= y) x y
  5. pmax x y = pif' (x #<= y) y x

Laws 8-12 hold if you use the defaults provided by this type class.

@since WIP

Minimal complete definition

Nothing

Methods

(#<=) :: Term s t -> Term s t -> Term s PBool infix 4 Source #

@since WIP

default (#<=) :: POrd (PInner t) => Term s t -> Term s t -> Term s PBool Source #

(#<) :: Term s t -> Term s t -> Term s PBool infix 4 Source #

@since WIP

default (#<) :: POrd (PInner t) => Term s t -> Term s t -> Term s PBool Source #

pmax :: forall (s :: S). Term s t -> Term s t -> Term s t Source #

@since WIP

pmin :: forall (s :: S). Term s t -> Term s t -> Term s t Source #

@since WIP

Instances

Instances details
POrd PBitString Source #

@since WIP

Instance details

Defined in Plutarch.BitString

Methods

(#<=) :: forall (s :: S). Term s PBitString -> Term s PBitString -> Term s PBool Source #

(#<) :: forall (s :: S). Term s PBitString -> Term s PBitString -> Term s PBool Source #

pmax :: forall (s :: S). Term s PBitString -> Term s PBitString -> Term s PBitString Source #

pmin :: forall (s :: S). Term s PBitString -> Term s PBitString -> Term s PBitString Source #

POrd PBool Source # 
Instance details

Defined in Plutarch.Internal.Ord

Methods

(#<=) :: forall (s :: S). Term s PBool -> Term s PBool -> Term s PBool Source #

(#<) :: forall (s :: S). Term s PBool -> Term s PBool -> Term s PBool Source #

pmax :: forall (s :: S). Term s PBool -> Term s PBool -> Term s PBool Source #

pmin :: forall (s :: S). Term s PBool -> Term s PBool -> Term s PBool Source #

POrd PByte Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Ord

Methods

(#<=) :: forall (s :: S). Term s PByte -> Term s PByte -> Term s PBool Source #

(#<) :: forall (s :: S). Term s PByte -> Term s PByte -> Term s PBool Source #

pmax :: forall (s :: S). Term s PByte -> Term s PByte -> Term s PByte Source #

pmin :: forall (s :: S). Term s PByte -> Term s PByte -> Term s PByte Source #

POrd PByteString Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Ord

Methods

(#<=) :: forall (s :: S). Term s PByteString -> Term s PByteString -> Term s PBool Source #

(#<) :: forall (s :: S). Term s PByteString -> Term s PByteString -> Term s PBool Source #

pmax :: forall (s :: S). Term s PByteString -> Term s PByteString -> Term s PByteString Source #

pmin :: forall (s :: S). Term s PByteString -> Term s PByteString -> Term s PByteString Source #

POrd PEndianness Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Ord

Methods

(#<=) :: forall (s :: S). Term s PEndianness -> Term s PEndianness -> Term s PBool Source #

(#<) :: forall (s :: S). Term s PEndianness -> Term s PEndianness -> Term s PBool Source #

pmax :: forall (s :: S). Term s PEndianness -> Term s PEndianness -> Term s PEndianness Source #

pmin :: forall (s :: S). Term s PEndianness -> Term s PEndianness -> Term s PEndianness Source #

POrd PLogicOpSemantics Source # 
Instance details

Defined in Plutarch.Internal.Ord

POrd PInteger Source # 
Instance details

Defined in Plutarch.Internal.Ord

Methods

(#<=) :: forall (s :: S). Term s PInteger -> Term s PInteger -> Term s PBool Source #

(#<) :: forall (s :: S). Term s PInteger -> Term s PInteger -> Term s PBool Source #

pmax :: forall (s :: S). Term s PInteger -> Term s PInteger -> Term s PInteger Source #

pmin :: forall (s :: S). Term s PInteger -> Term s PInteger -> Term s PInteger Source #

POrd PUnit Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Ord

Methods

(#<=) :: forall (s :: S). Term s PUnit -> Term s PUnit -> Term s PBool Source #

(#<) :: forall (s :: S). Term s PUnit -> Term s PUnit -> Term s PBool Source #

pmax :: forall (s :: S). Term s PUnit -> Term s PUnit -> Term s PUnit Source #

pmin :: forall (s :: S). Term s PUnit -> Term s PUnit -> Term s PUnit Source #

POrd PPositive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

(#<=) :: forall (s :: S). Term s PPositive -> Term s PPositive -> Term s PBool Source #

(#<) :: forall (s :: S). Term s PPositive -> Term s PPositive -> Term s PBool Source #

pmax :: forall (s :: S). Term s PPositive -> Term s PPositive -> Term s PPositive Source #

pmin :: forall (s :: S). Term s PPositive -> Term s PPositive -> Term s PPositive Source #

POrd PRational Source # 
Instance details

Defined in Plutarch.Rational

Methods

(#<=) :: forall (s :: S). Term s PRational -> Term s PRational -> Term s PBool Source #

(#<) :: forall (s :: S). Term s PRational -> Term s PRational -> Term s PBool Source #

pmax :: forall (s :: S). Term s PRational -> Term s PRational -> Term s PRational Source #

pmin :: forall (s :: S). Term s PRational -> Term s PRational -> Term s PRational Source #

(PIsData a, POrd a) => POrd (PDataNewtype a) Source #

Since: 1.7.0

Instance details

Defined in Plutarch.Builtin

Methods

(#<=) :: forall (s :: S). Term s (PDataNewtype a) -> Term s (PDataNewtype a) -> Term s PBool Source #

(#<) :: forall (s :: S). Term s (PDataNewtype a) -> Term s (PDataNewtype a) -> Term s PBool Source #

pmax :: forall (s :: S). Term s (PDataNewtype a) -> Term s (PDataNewtype a) -> Term s (PDataNewtype a) Source #

pmin :: forall (s :: S). Term s (PDataNewtype a) -> Term s (PDataNewtype a) -> Term s (PDataNewtype a) Source #

(SListI xs, POrd x, PIsData x, POrd (PDataRecord (x' ': xs))) => POrd (PDataRecord ((label ':= x) ': (x' ': xs))) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

(#<=) :: forall (s :: S). Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s PBool Source #

(#<) :: forall (s :: S). Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s PBool Source #

pmax :: forall (s :: S). Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s (PDataRecord ((label ':= x) ': (x' ': xs))) Source #

pmin :: forall (s :: S). Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s (PDataRecord ((label ':= x) ': (x' ': xs))) -> Term s (PDataRecord ((label ':= x) ': (x' ': xs))) Source #

(POrd x, PIsData x) => POrd (PDataRecord '[label ':= x]) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

(#<=) :: forall (s :: S). Term s (PDataRecord '[label ':= x]) -> Term s (PDataRecord '[label ':= x]) -> Term s PBool Source #

(#<) :: forall (s :: S). Term s (PDataRecord '[label ':= x]) -> Term s (PDataRecord '[label ':= x]) -> Term s PBool Source #

pmax :: forall (s :: S). Term s (PDataRecord '[label ':= x]) -> Term s (PDataRecord '[label ':= x]) -> Term s (PDataRecord '[label ':= x]) Source #

pmin :: forall (s :: S). Term s (PDataRecord '[label ':= x]) -> Term s (PDataRecord '[label ':= x]) -> Term s (PDataRecord '[label ':= x]) Source #

POrd (PDataRecord ('[] :: [PLabeledType])) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

(#<=) :: forall (s :: S). Term s (PDataRecord '[]) -> Term s (PDataRecord '[]) -> Term s PBool Source #

(#<) :: forall (s :: S). Term s (PDataRecord '[]) -> Term s (PDataRecord '[]) -> Term s PBool Source #

pmax :: forall (s :: S). Term s (PDataRecord '[]) -> Term s (PDataRecord '[]) -> Term s (PDataRecord '[]) Source #

pmin :: forall (s :: S). Term s (PDataRecord '[]) -> Term s (PDataRecord '[]) -> Term s (PDataRecord '[]) Source #

All (Compose POrd PDataRecord) defs => POrd (PDataSum defs) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

(#<=) :: forall (s :: S). Term s (PDataSum defs) -> Term s (PDataSum defs) -> Term s PBool Source #

(#<) :: forall (s :: S). Term s (PDataSum defs) -> Term s (PDataSum defs) -> Term s PBool Source #

pmax :: forall (s :: S). Term s (PDataSum defs) -> Term s (PDataSum defs) -> Term s (PDataSum defs) Source #

pmin :: forall (s :: S). Term s (PDataSum defs) -> Term s (PDataSum defs) -> Term s (PDataSum defs) Source #

(POrd a, POrd b, PIsData a, PIsData b) => POrd (PEitherData a b) Source #

@since WIP

Instance details

Defined in Plutarch.Either

Methods

(#<=) :: forall (s :: S). Term s (PEitherData a b) -> Term s (PEitherData a b) -> Term s PBool Source #

(#<) :: forall (s :: S). Term s (PEitherData a b) -> Term s (PEitherData a b) -> Term s PBool Source #

pmax :: forall (s :: S). Term s (PEitherData a b) -> Term s (PEitherData a b) -> Term s (PEitherData a b) Source #

pmin :: forall (s :: S). Term s (PEitherData a b) -> Term s (PEitherData a b) -> Term s (PEitherData a b) Source #

(#>) :: forall (a :: S -> Type) (s :: S). POrd a => Term s a -> Term s a -> Term s PBool infix 4 Source #

@since WIP

(#>=) :: forall (a :: S -> Type) (s :: S). POrd a => Term s a -> Term s a -> Term s PBool infix 4 Source #

@since WIP

Fixed point

pfix :: Term s (((a :--> b) :--> (a :--> b)) :--> (a :--> b)) Source #

Fixpoint recursion. Used to encode recursive functions.

Example:

iterateN' ::
 Term s (PInteger :--> (a :--> a) :--> a :--> a) ->
 Term s PInteger ->
 Term s (a :--> a) ->
 Term s a
iterateN' self n f x =
  pif (n #== 0) x (self # n - 1 #$ f x)

iterateN :: Term s (PInteger :--> (a :--> a) :--> a :--> a)
iterateN = pfix #$ plam iterateN'

Further examples can be found in examples/Recursion.hs

IsData

class PIsData a where Source #

Laws: - If PSubtype PData a, then pdataImpl a must be pupcast. - pdataImpl . pupcast . pfromDataImpl ≡ id - pfromDataImpl . punsafeDowncast . pdataImpl ≡ id

Minimal complete definition

Nothing

Methods

pfromDataImpl :: Term s (PAsData a) -> Term s a Source #

default pfromDataImpl :: PIsData (PInner a) => Term s (PAsData a) -> Term s a Source #

pdataImpl :: Term s a -> Term s PData Source #

default pdataImpl :: PIsData (PInner a) => Term s a -> Term s PData Source #

Instances

Instances details
PIsData PBool Source # 
Instance details

Defined in Plutarch.Internal.IsData

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PBool) -> Term s PBool Source #

pdataImpl :: forall (s :: S). Term s PBool -> Term s PData Source #

PIsData PByteString Source # 
Instance details

Defined in Plutarch.Internal.IsData

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PByteString) -> Term s PByteString Source #

pdataImpl :: forall (s :: S). Term s PByteString -> Term s PData Source #

PIsData PData Source # 
Instance details

Defined in Plutarch.Internal.IsData

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PData) -> Term s PData Source #

pdataImpl :: forall (s :: S). Term s PData -> Term s PData Source #

PIsData PInteger Source # 
Instance details

Defined in Plutarch.Internal.IsData

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PInteger) -> Term s PInteger Source #

pdataImpl :: forall (s :: S). Term s PInteger -> Term s PData Source #

PIsData PUnit Source # 
Instance details

Defined in Plutarch.Internal.IsData

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PUnit) -> Term s PUnit Source #

pdataImpl :: forall (s :: S). Term s PUnit -> Term s PData Source #

PIsData PPositive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PPositive) -> Term s PPositive Source #

pdataImpl :: forall (s :: S). Term s PPositive -> Term s PData Source #

PIsData (PDataNewtype a) Source #

Since: 1.7.0

Instance details

Defined in Plutarch.Builtin

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData (PDataNewtype a)) -> Term s (PDataNewtype a) Source #

pdataImpl :: forall (s :: S). Term s (PDataNewtype a) -> Term s PData Source #

PSubtype PData a => PIsData (PBuiltinList a) Source # 
Instance details

Defined in Plutarch.Internal.IsData

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData (PBuiltinList a)) -> Term s (PBuiltinList a) Source #

pdataImpl :: forall (s :: S). Term s (PBuiltinList a) -> Term s PData Source #

PIsData (PDataRecord xs) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData (PDataRecord xs)) -> Term s (PDataRecord xs) Source #

pdataImpl :: forall (s :: S). Term s (PDataRecord xs) -> Term s PData Source #

PIsData (PDataSum defs) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData (PDataSum defs)) -> Term s (PDataSum defs) Source #

pdataImpl :: forall (s :: S). Term s (PDataSum defs) -> Term s PData Source #

PIsData (PDataRec struct) Source #

@since WIP

Instance details

Defined in Plutarch.Repr.Data

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData (PDataRec struct)) -> Term s (PDataRec struct) Source #

pdataImpl :: forall (s :: S). Term s (PDataRec struct) -> Term s PData Source #

PIsData (PDataStruct struct) Source #

@since WIP

Instance details

Defined in Plutarch.Repr.Data

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData (PDataStruct struct)) -> Term s (PDataStruct struct) Source #

pdataImpl :: forall (s :: S). Term s (PDataStruct struct) -> Term s PData Source #

PIsData (PBuiltinPair (PAsData a) (PAsData b)) Source # 
Instance details

Defined in Plutarch.Internal.IsData

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData (PBuiltinPair (PAsData a) (PAsData b))) -> Term s (PBuiltinPair (PAsData a) (PAsData b)) Source #

pdataImpl :: forall (s :: S). Term s (PBuiltinPair (PAsData a) (PAsData b)) -> Term s PData Source #

PIsData (PBuiltinPair PData PData) Source # 
Instance details

Defined in Plutarch.Internal.IsData

PIsData (PBuiltinPair PInteger (PBuiltinList PData)) Source # 
Instance details

Defined in Plutarch.Internal.IsData

PIsData (PEitherData a b) Source #

@since WIP

Instance details

Defined in Plutarch.Either

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData (PEitherData a b)) -> Term s (PEitherData a b) Source #

pdataImpl :: forall (s :: S). Term s (PEitherData a b) -> Term s PData Source #

pdata :: PIsData a => Term s a -> Term s (PAsData a) Source #

pforgetData :: forall s a. Term s (PAsData a) -> Term s PData Source #

pfromData :: PIsData a => Term s (PAsData a) -> Term s a Source #

Lifting and lowering

class PlutusType a => PLiftable (a :: S -> Type) where Source #

Indicates that the given Plutarch type has an equivalent in Haskell (and Plutus by extension), and we have the ability to move between them.

Important note

Calling methods of PLiftable directly should rarely, if ever, be a thing you do, unless defining your own instances without via-deriving helpers (below). Prefer using pconstant and plift, as these handle some of the oddities required without you having to think about them.

You should rarely, if ever, need to define PLiftable instances by hand. Whenever possible, prefer using DeriveBuiltinPLiftable, DeriveDataPLiftable, and DeriveNewtypePLiftable as they have fewer complexities and caveats. See their documentation for when to use them.

If you do want to define the methods yourself, there's a few key factors to keep in mind:

  1. You still shouldn't write every method by hand, there are helpers fromPlutarch* and toPlutarch* to cover common cases like types in Plutus universe or Scott encoding
  2. If defining toPlutarchRepr and fromPlutarchRepr you will need to define an associated PlutusRepr type, this is a Hasekll level type that is included in the Plutus default universe.
  3. If defining toPlutarch and fromPlutarch for Scott encoded type you need to set PlutusRepr PMyType = PLiftedClosed PMyType
  4. When choosing a type for AsHaskell, any value of that type must be representable in Plutarch. If you have internal invariants to maintain on the Haskell side, make sure you do so with great care.

Laws

  1. fromPlutarchRepr . toPlutarchRepr = Just
  2. fmap toPlutarchRepr . fromPlutarchRepr = Just
  3. fromPlutarch . toPlutarch = Right
  4. fmap toPlutarch . fromPlutarch = Right

Any derivations via DeriveBuiltinPLiftable, DeriveDataPLiftable, and DeriveNewtypePLiftable automatically follow these laws.

@since WIP

Associated Types

type AsHaskell a :: Type Source #

type PlutusRepr a :: Type Source #

Instances

Instances details
PLiftable PBuiltinBLS12_381_G1_Element Source # 
Instance details

Defined in Plutarch.Internal.Lift

PLiftable PBuiltinBLS12_381_G2_Element Source # 
Instance details

Defined in Plutarch.Internal.Lift

PLiftable PBuiltinBLS12_381_MlResult Source # 
Instance details

Defined in Plutarch.Internal.Lift

PLiftable PBool Source # 
Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type AsHaskell PBool Source #

type PlutusRepr PBool Source #

PLiftable PByte Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type AsHaskell PByte Source #

type PlutusRepr PByte Source #

PLiftable PByteString Source # 
Instance details

Defined in Plutarch.Internal.Lift

PLiftable PData Source # 
Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type AsHaskell PData Source #

type PlutusRepr PData Source #

PLiftable PInteger Source # 
Instance details

Defined in Plutarch.Internal.Lift

PLiftable PString Source # 
Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type AsHaskell PString Source #

type PlutusRepr PString Source #

PLiftable PUnit Source # 
Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type AsHaskell PUnit Source #

type PlutusRepr PUnit Source #

PLiftable PPositive Source # 
Instance details

Defined in Plutarch.Internal.Numeric

PLiftable PRational Source #

@since WIP

Instance details

Defined in Plutarch.Rational

PLiftable (PAsData PByteString) Source # 
Instance details

Defined in Plutarch.Internal.Lift

PLiftable (PAsData PData) Source # 
Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type AsHaskell (PAsData PData) Source #

type PlutusRepr (PAsData PData) Source #

(ToData (AsHaskell a), FromData (AsHaskell a), PIsData a) => PLiftable (PAsData a) Source # 
Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type AsHaskell (PAsData a) Source #

type PlutusRepr (PAsData a) Source #

(PLiftable a, Contains DefaultUni (PlutusRepr a)) => PLiftable (PBuiltinList a) Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type AsHaskell (PBuiltinList a) Source #

type PlutusRepr (PBuiltinList a) Source #

PLiftable a => PLiftable (PMaybe a) Source #

@since WIP

Instance details

Defined in Plutarch.Maybe

Associated Types

type AsHaskell (PMaybe a) Source #

type PlutusRepr (PMaybe a) Source #

PLiftable a => PLiftable (PMaybeSoP a) Source #

@since WIP

Instance details

Defined in Plutarch.Maybe

Associated Types

type AsHaskell (PMaybeSoP a) Source #

type PlutusRepr (PMaybeSoP a) Source #

(PLiftable a, Contains DefaultUni (PlutusRepr a), PLiftable b, Contains DefaultUni (PlutusRepr b)) => PLiftable (PBuiltinPair a b) Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type AsHaskell (PBuiltinPair a b) Source #

type PlutusRepr (PBuiltinPair a b) Source #

(PLiftable a, PLiftable b) => PLiftable (PEither a b) Source #

@since WIP

Instance details

Defined in Plutarch.Either

Associated Types

type AsHaskell (PEither a b) Source #

type PlutusRepr (PEither a b) Source #

(ToData (AsHaskell a), FromData (AsHaskell a), ToData (AsHaskell b), FromData (AsHaskell b)) => PLiftable (PEitherData a b) Source # 
Instance details

Defined in Plutarch.Either

Associated Types

type AsHaskell (PEitherData a b) Source #

type PlutusRepr (PEitherData a b) Source #

(PlutusType a, Includes DefaultUni h) => PLiftable (DeriveBuiltinPLiftable a h) Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Lift

(PlutusType a, PSubtype PData a, ToData h, FromData h) => PLiftable (DeriveDataPLiftable a h) Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Lift

(PLiftable inner, Coercible (AsHaskell inner) h) => PLiftable (DeriveNewtypePLiftable wrapper inner h) Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type AsHaskell (DeriveNewtypePLiftable wrapper inner h) Source #

type PlutusRepr (DeriveNewtypePLiftable wrapper inner h) Source #

Methods

toPlutarchRepr :: AsHaskell (DeriveNewtypePLiftable wrapper inner h) -> PlutusRepr (DeriveNewtypePLiftable wrapper inner h) Source #

toPlutarch :: forall (s :: S). AsHaskell (DeriveNewtypePLiftable wrapper inner h) -> PLifted s (DeriveNewtypePLiftable wrapper inner h) Source #

fromPlutarchRepr :: PlutusRepr (DeriveNewtypePLiftable wrapper inner h) -> Maybe (AsHaskell (DeriveNewtypePLiftable wrapper inner h)) Source #

fromPlutarch :: (forall (s :: S). PLifted s (DeriveNewtypePLiftable wrapper inner h)) -> Either LiftError (AsHaskell (DeriveNewtypePLiftable wrapper inner h)) Source #

data DeriveDataPLiftable (a :: S -> Type) (h :: Type) (s :: S) Source #

via-deriving helper, indicating that a has a Haskell-level equivalent h by way of its Data encoding, rather than by h being directly part of the Plutus default universe.

@since WIP

Instances

Instances details
(PlutusType a, PSubtype PData a, ToData h, FromData h) => PLiftable (DeriveDataPLiftable a h) Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Lift

DerivePlutusType (DeriveDataPLiftable a h) Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type DPTStrat (DeriveDataPLiftable a h) Source #

PlutusType (DeriveDataPLiftable a h) Source # 
Instance details

Defined in Plutarch.Internal.Lift

Methods

pcon' :: forall (s :: S). DeriveDataPLiftable a h s -> Term s (PInner (DeriveDataPLiftable a h)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (DeriveDataPLiftable a h)) -> (DeriveDataPLiftable a h s -> Term s b) -> Term s b Source #

Generic (DeriveDataPLiftable a h s) Source # 
Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type Rep (DeriveDataPLiftable a h s) :: Type -> Type Source #

type AsHaskell (DeriveDataPLiftable a h) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PlutusRepr (DeriveDataPLiftable a h) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type DPTStrat (DeriveDataPLiftable a h) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PContravariant' (DeriveDataPLiftable a h) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PCovariant' (DeriveDataPLiftable a h) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PInner (DeriveDataPLiftable a h) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PVariant' (DeriveDataPLiftable a h) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type Rep (DeriveDataPLiftable a h s) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type Rep (DeriveDataPLiftable a h s) = D1 ('MetaData "DeriveDataPLiftable" "Plutarch.Internal.Lift" "plutarch-1.9.0-FtN0mhIoM9oEvz7Q98pjWP" 'True) (C1 ('MetaCons "DeriveDataPLiftable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a s))))

data DeriveNewtypePLiftable (wrapper :: S -> Type) (inner :: S -> Type) (h :: Type) (s :: S) Source #

via-deriving helper, indicating that wrapper has a Haskell-level equivalent h by way of encoding of inner. It requires that AsHaskell inner has the same Haskell representation as h

@since WIP

Instances

Instances details
(PLiftable inner, Coercible (AsHaskell inner) h) => PLiftable (DeriveNewtypePLiftable wrapper inner h) Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type AsHaskell (DeriveNewtypePLiftable wrapper inner h) Source #

type PlutusRepr (DeriveNewtypePLiftable wrapper inner h) Source #

Methods

toPlutarchRepr :: AsHaskell (DeriveNewtypePLiftable wrapper inner h) -> PlutusRepr (DeriveNewtypePLiftable wrapper inner h) Source #

toPlutarch :: forall (s :: S). AsHaskell (DeriveNewtypePLiftable wrapper inner h) -> PLifted s (DeriveNewtypePLiftable wrapper inner h) Source #

fromPlutarchRepr :: PlutusRepr (DeriveNewtypePLiftable wrapper inner h) -> Maybe (AsHaskell (DeriveNewtypePLiftable wrapper inner h)) Source #

fromPlutarch :: (forall (s :: S). PLifted s (DeriveNewtypePLiftable wrapper inner h)) -> Either LiftError (AsHaskell (DeriveNewtypePLiftable wrapper inner h)) Source #

DerivePlutusType (DeriveNewtypePLiftable w i h) Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type DPTStrat (DeriveNewtypePLiftable w i h) Source #

PlutusType (DeriveNewtypePLiftable wrapper inner h) Source # 
Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type PInner (DeriveNewtypePLiftable wrapper inner h) :: PType Source #

type PCovariant' (DeriveNewtypePLiftable wrapper inner h) Source #

type PContravariant' (DeriveNewtypePLiftable wrapper inner h) Source #

type PVariant' (DeriveNewtypePLiftable wrapper inner h) Source #

Methods

pcon' :: forall (s :: S). DeriveNewtypePLiftable wrapper inner h s -> Term s (PInner (DeriveNewtypePLiftable wrapper inner h)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (DeriveNewtypePLiftable wrapper inner h)) -> (DeriveNewtypePLiftable wrapper inner h s -> Term s b) -> Term s b Source #

Generic (DeriveNewtypePLiftable wrapper inner h s) Source # 
Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type Rep (DeriveNewtypePLiftable wrapper inner h s) :: Type -> Type Source #

Methods

from :: DeriveNewtypePLiftable wrapper inner h s -> Rep (DeriveNewtypePLiftable wrapper inner h s) x Source #

to :: Rep (DeriveNewtypePLiftable wrapper inner h s) x -> DeriveNewtypePLiftable wrapper inner h s Source #

type AsHaskell (DeriveNewtypePLiftable wrapper inner h) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type AsHaskell (DeriveNewtypePLiftable wrapper inner h) = h
type PlutusRepr (DeriveNewtypePLiftable wrapper inner h) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PlutusRepr (DeriveNewtypePLiftable wrapper inner h) = PlutusRepr inner
type DPTStrat (DeriveNewtypePLiftable w i h) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PContravariant' (DeriveNewtypePLiftable wrapper inner h) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PContravariant' (DeriveNewtypePLiftable wrapper inner h) = All2 PContravariant'' (PCode (DeriveNewtypePLiftable wrapper inner h))
type PCovariant' (DeriveNewtypePLiftable wrapper inner h) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PCovariant' (DeriveNewtypePLiftable wrapper inner h) = All2 PCovariant'' (PCode (DeriveNewtypePLiftable wrapper inner h))
type PInner (DeriveNewtypePLiftable wrapper inner h) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PInner (DeriveNewtypePLiftable wrapper inner h) = DerivedPInner (DPTStrat (DeriveNewtypePLiftable wrapper inner h)) (DeriveNewtypePLiftable wrapper inner h)
type PVariant' (DeriveNewtypePLiftable wrapper inner h) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type PVariant' (DeriveNewtypePLiftable wrapper inner h) = All2 PVariant'' (PCode (DeriveNewtypePLiftable wrapper inner h))
type Rep (DeriveNewtypePLiftable wrapper inner h s) Source # 
Instance details

Defined in Plutarch.Internal.Lift

type Rep (DeriveNewtypePLiftable wrapper inner h s) = D1 ('MetaData "DeriveNewtypePLiftable" "Plutarch.Internal.Lift" "plutarch-1.9.0-FtN0mhIoM9oEvz7Q98pjWP" 'True) (C1 ('MetaCons "DeriveNewtypePLiftable" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (wrapper s))))

newtype PLifted (s :: S) (a :: S -> Type) Source #

Similar to Identity, but at the level of Plutarch. Only needed when writing manual instances of PLiftable, or if you want to use toPlutarch and fromPlutarch directly.

This is used for coercing Plutarch terms in Haskell level with `coerce :: PLifted s a -> PLifted s b` for via-deriving helpers

@since WIP

Constructors

PLifted (Term s POpaque) 

fromPlutarchUni :: forall (a :: S -> Type). (PLiftable a, DefaultUni `Includes` PlutusRepr a) => (forall s. PLifted s a) -> Either LiftError (AsHaskell a) Source #

Valid definition for fromPlutarch if PlutusRepr is in Plutus universe

@since WIP

toPlutarchUni :: forall (a :: S -> Type) (s :: S). (PLiftable a, DefaultUni `Includes` PlutusRepr a) => AsHaskell a -> PLifted s a Source #

Valid definition for toPlutarch if PlutusRepr is in Plutus universe

@since WIP

pconstant :: forall (a :: S -> Type) (s :: S). PLiftable a => AsHaskell a -> Term s a Source #

Given a Haskell-level representation of a Plutarch term, transform it into its equivalent term.

@since WIP

plift :: forall (a :: S -> Type). PLiftable a => (forall (s :: S). Term s a) -> AsHaskell a Source #

Given a closed Plutarch term, compile and evaluate it, then produce the corresponding Haskell value. If compilation or evaluation fails somehow, this will call error: if you need to 'trap' these outcomes and handle them differently somehow, use fromPlutarch.

@since WIP

Lists

type family PElemConstraint list (a :: S -> Type) :: Constraint Source #

Instances

Instances details
type PElemConstraint PBuiltinList a Source # 
Instance details

Defined in Plutarch.Internal.ListLike

type PElemConstraint PBuiltinList a = Contains DefaultUni (PlutusRepr a)
type PElemConstraint PList _1 Source # 
Instance details

Defined in Plutarch.List

type PElemConstraint PList _1 = ()

type PIsListLike list a = (PListLike list, PElemConstraint list a) Source #

'PIsListLike list a' constraints list be a PListLike with valid element type, a.

class PListLike (list :: (S -> Type) -> S -> Type) Source #

Plutarch types that behave like lists.

Minimal complete definition

pelimList, pcons, pnil

Instances

Instances details
PListLike PBuiltinList Source # 
Instance details

Defined in Plutarch.Internal.ListLike

Associated Types

type PElemConstraint PBuiltinList a Source #

Methods

pelimList :: forall (a :: S -> Type) (s :: S) (r :: PType). PElemConstraint PBuiltinList a => (Term s a -> Term s (PBuiltinList a) -> Term s r) -> Term s r -> Term s (PBuiltinList a) -> Term s r Source #

pcons :: forall (a :: S -> Type) (s :: S). PElemConstraint PBuiltinList a => Term s (a :--> (PBuiltinList a :--> PBuiltinList a)) Source #

pnil :: forall (a :: S -> Type) (s :: S). PElemConstraint PBuiltinList a => Term s (PBuiltinList a) Source #

phead :: forall (a :: S -> Type) (s :: S). PElemConstraint PBuiltinList a => Term s (PBuiltinList a :--> a) Source #

ptail :: forall (a :: S -> Type) (s :: S). PElemConstraint PBuiltinList a => Term s (PBuiltinList a :--> PBuiltinList a) Source #

pnull :: forall (a :: S -> Type) (s :: S). PElemConstraint PBuiltinList a => Term s (PBuiltinList a :--> PBool) Source #

PListLike PList Source # 
Instance details

Defined in Plutarch.List

Associated Types

type PElemConstraint PList a Source #

Methods

pelimList :: forall (a :: S -> Type) (s :: S) (r :: PType). PElemConstraint PList a => (Term s a -> Term s (PList a) -> Term s r) -> Term s r -> Term s (PList a) -> Term s r Source #

pcons :: forall (a :: S -> Type) (s :: S). PElemConstraint PList a => Term s (a :--> (PList a :--> PList a)) Source #

pnil :: forall (a :: S -> Type) (s :: S). PElemConstraint PList a => Term s (PList a) Source #

phead :: forall (a :: S -> Type) (s :: S). PElemConstraint PList a => Term s (PList a :--> a) Source #

ptail :: forall (a :: S -> Type) (s :: S). PElemConstraint PList a => Term s (PList a :--> PList a) Source #

pnull :: forall (a :: S -> Type) (s :: S). PElemConstraint PList a => Term s (PList a :--> PBool) Source #

data PList (a :: S -> Type) (s :: S) Source #

Constructors

PSCons (Term s a) (Term s (PList a)) 
PSNil 

Instances

Instances details
PListLike PList Source # 
Instance details

Defined in Plutarch.List

Associated Types

type PElemConstraint PList a Source #

Methods

pelimList :: forall (a :: S -> Type) (s :: S) (r :: PType). PElemConstraint PList a => (Term s a -> Term s (PList a) -> Term s r) -> Term s r -> Term s (PList a) -> Term s r Source #

pcons :: forall (a :: S -> Type) (s :: S). PElemConstraint PList a => Term s (a :--> (PList a :--> PList a)) Source #

pnil :: forall (a :: S -> Type) (s :: S). PElemConstraint PList a => Term s (PList a) Source #

phead :: forall (a :: S -> Type) (s :: S). PElemConstraint PList a => Term s (PList a :--> a) Source #

ptail :: forall (a :: S -> Type) (s :: S). PElemConstraint PList a => Term s (PList a :--> PList a) Source #

pnull :: forall (a :: S -> Type) (s :: S). PElemConstraint PList a => Term s (PList a :--> PBool) Source #

PEq a => PEq (PList a) Source # 
Instance details

Defined in Plutarch.List

Methods

(#==) :: forall (s :: S). Term s (PList a) -> Term s (PList a) -> Term s PBool Source #

DerivePlutusType (PList a) Source # 
Instance details

Defined in Plutarch.List

Associated Types

type DPTStrat (PList a) Source #

PlutusType (PList a) Source # 
Instance details

Defined in Plutarch.List

Associated Types

type PInner (PList a) :: PType Source #

type PCovariant' (PList a) Source #

type PContravariant' (PList a) Source #

type PVariant' (PList a) Source #

Methods

pcon' :: forall (s :: S). PList a s -> Term s (PInner (PList a)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PList a)) -> (PList a s -> Term s b) -> Term s b Source #

PShow a => PShow (PList a) Source # 
Instance details

Defined in Plutarch.List

Methods

pshow' :: forall (s :: S). Bool -> Term s (PList a) -> Term s PString Source #

Generic (PList a s) Source # 
Instance details

Defined in Plutarch.List

Associated Types

type Rep (PList a s) :: Type -> Type Source #

Methods

from :: PList a s -> Rep (PList a s) x Source #

to :: Rep (PList a s) x -> PList a s Source #

type PElemConstraint PList _1 Source # 
Instance details

Defined in Plutarch.List

type PElemConstraint PList _1 = ()
type DPTStrat (PList a) Source # 
Instance details

Defined in Plutarch.List

type PContravariant' (PList a) Source # 
Instance details

Defined in Plutarch.List

type PCovariant' (PList a) Source # 
Instance details

Defined in Plutarch.List

type PCovariant' (PList a) = All2 PCovariant'' (PCode (PList a))
type PInner (PList a) Source # 
Instance details

Defined in Plutarch.List

type PVariant' (PList a) Source # 
Instance details

Defined in Plutarch.List

type PVariant' (PList a) = All2 PVariant'' (PCode (PList a))
type Rep (PList a s) Source # 
Instance details

Defined in Plutarch.List

type Rep (PList a s) = D1 ('MetaData "PList" "Plutarch.List" "plutarch-1.9.0-FtN0mhIoM9oEvz7Q98pjWP" 'False) (C1 ('MetaCons "PSCons" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PList a)))) :+: C1 ('MetaCons "PSNil" 'PrefixI 'False) (U1 :: Type -> Type))

pelem :: (PIsListLike list a, PEq a) => Term s (a :--> (list a :--> PBool)) Source #

O(n) . Check if element is in the list

pelemAt :: PIsListLike l a => Term s (PInteger :--> (l a :--> a)) Source #

O(n) . Like Haskell level (!!) but on the Plutarch level, not infix and with arguments reversed, errors if the specified index is greater than or equal to the lists length

pfind :: PIsListLike l a => Term s ((a :--> PBool) :--> (l a :--> PMaybe a)) Source #

O(n) . like haskell level find but on plutarch level

plistEquals :: (PIsListLike list a, PEq a) => Term s (list a :--> (list a :--> PBool)) Source #

O(min(n, m)) . Check if two lists are equal.

puncons :: PIsListLike list a => Term s (list a :--> PMaybe (PPair a (list a))) Source #

Extract head and tail of the list, if list is not empty.

pzip :: (PListLike list, PElemConstraint list a, PElemConstraint list b, PElemConstraint list (PPair a b)) => Term s (list a :--> (list b :--> list (PPair a b))) Source #

O(min(n, m)) . Zip two lists together, creating pairs of the elements.

If the lists are of differing lengths, cut to the shortest.

(#!!) :: PIsListLike l a => Term s (l a) -> Term s PInteger -> Term s a Source #

O(n) . Like Haskell level (!!) but on the plutarch level

pall :: PIsListLike list a => Term s ((a :--> PBool) :--> (list a :--> PBool)) Source #

O(n) . Check that predicate holds for all elements in a list.

pany :: PIsListLike list a => Term s ((a :--> PBool) :--> (list a :--> PBool)) Source #

O(n) . Check that predicate holds for any element in a list.

pconcat :: PIsListLike list a => Term s (list a :--> (list a :--> list a)) Source #

O(n) . Concatenate two lists

Example: > pconcat # psingleton x # psingleton y == plistLiteral [x, y]

pconcat exhibits identities with empty lists such that > forall x. pconcat # pnil # x == x > forall x. pconcat # x # pnil == x

pcons :: (PListLike list, PElemConstraint list a) => Term s (a :--> (list a :--> list a)) Source #

Cons an element onto an existing list.

pdrop :: PIsListLike list a => Natural -> Term s (list a) -> Term s (list a) Source #

Drop the first n fields of a List.

The term will be statically generated as repeated applications of ptail, which will be more efficient in many circumstances.

pelimList :: (PListLike list, PElemConstraint list a) => (Term s a -> Term s (list a) -> Term s r) -> Term s r -> Term s (list a) -> Term s r Source #

Canonical eliminator for list-likes.

pfilter :: PIsListLike list a => Term s ((a :--> PBool) :--> (list a :--> list a)) Source #

O(n) . Filter elements from a list that don't match the predicate.

pfoldl :: PIsListLike list a => Term s ((b :--> (a :--> b)) :--> (b :--> (list a :--> b))) Source #

O(n) . Fold on a list left-associatively.

pfoldr :: PIsListLike list a => Term s ((a :--> (b :--> b)) :--> (b :--> (list a :--> b))) Source #

O(n) . Fold on a list right-associatively.

pfoldrLazy :: PIsListLike list a => Term s ((a :--> (PDelayed b :--> b)) :--> (b :--> (list a :--> b))) Source #

O(n) . Fold on a list right-associatively, with opportunity for short circuting.

May short circuit when given reducer function is lazy in its second argument.

phead :: (PListLike list, PElemConstraint list a) => Term s (list a :--> a) Source #

Return the first element of a list. Partial, throws an error upon encountering an empty list.

plength :: PIsListLike list a => Term s (list a :--> PInteger) Source #

O(n) . Count the number of elements in the list

pmap :: (PListLike list, PElemConstraint list a, PElemConstraint list b) => Term s ((a :--> b) :--> (list a :--> list b)) Source #

O(n) . Map a function over a list of elements

pnil :: (PListLike list, PElemConstraint list a) => Term s (list a) Source #

The empty list

pnull :: (PListLike list, PElemConstraint list a) => Term s (list a :--> PBool) Source #

O(1) . Check if a list is empty

precList :: PIsListLike list a => (Term s (list a :--> r) -> Term s a -> Term s (list a) -> Term s r) -> (Term s (list a :--> r) -> Term s r) -> Term s (list a :--> r) Source #

Like pelimList, but with a fixpoint recursion hatch.

psingleton :: PIsListLike list a => Term s (a :--> list a) Source #

O(1) . Create a singleton list from an element

ptail :: (PListLike list, PElemConstraint list a) => Term s (list a :--> list a) Source #

Take the tail of a list, meaning drop its head. Partial, throws an error upon encountering an empty list.

ptryIndex :: PIsListLike list a => Natural -> Term s (list a) -> Term s a Source #

Index a BuiltinList, throwing an error if the index is out of bounds.

pzipWith :: (PListLike list, PElemConstraint list a, PElemConstraint list b, PElemConstraint list c) => Term s ((a :--> (b :--> c)) :--> (list a :--> (list b :--> list c))) Source #

O(min(n, m)) . Zip two lists together with a passed function.

If the lists are of differing lengths, cut to the shortest.

pzipWith' :: (PListLike list, PElemConstraint list a, PElemConstraint list b, PElemConstraint list c) => (Term s a -> Term s b -> Term s c) -> Term s (list a :--> (list b :--> list c)) Source #

Like pzipWith but with Haskell-level merge function.

PlutusType

class (PInner a ~ DerivedPInner (DPTStrat a) a, PlutusTypeStrat (DPTStrat a), PlutusTypeStratConstraint (DPTStrat a) a, PlutusType a) => DerivePlutusType (a :: PType) Source #

Associated Types

type DPTStrat a :: Type Source #

type DPTStrat a = TypeError ('Text "Please specify a strategy for deriving PlutusType for type " ':<>: 'ShowType a)

Instances

Instances details
DerivePlutusType PBitString Source #

@since WIP

Instance details

Defined in Plutarch.BitString

Associated Types

type DPTStrat PBitString Source #

DerivePlutusType PBuiltinBLS12_381_G1_Element Source #

@since WIP

Instance details

Defined in Plutarch.Internal.PlutusType

DerivePlutusType PBuiltinBLS12_381_G2_Element Source #

@since WIP

Instance details

Defined in Plutarch.Internal.PlutusType

DerivePlutusType PBuiltinBLS12_381_MlResult Source #

@since WIP

Instance details

Defined in Plutarch.Internal.PlutusType

DerivePlutusType PByte Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Associated Types

type DPTStrat PByte Source #

DerivePlutusType PByteString Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Associated Types

type DPTStrat PByteString Source #

DerivePlutusType PEndianness Source #

@since WIP

Instance details

Defined in Plutarch.Internal.PlutusType

Associated Types

type DPTStrat PEndianness Source #

DerivePlutusType PLogicOpSemantics Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Associated Types

type DPTStrat PLogicOpSemantics Source #

DerivePlutusType PInteger Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Associated Types

type DPTStrat PInteger Source #

DerivePlutusType PString Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Associated Types

type DPTStrat PString Source #

DerivePlutusType PPositive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Associated Types

type DPTStrat PPositive Source #

DerivePlutusType (PList a) Source # 
Instance details

Defined in Plutarch.List

Associated Types

type DPTStrat (PList a) Source #

DerivePlutusType (PMaybe a) Source # 
Instance details

Defined in Plutarch.Maybe

Associated Types

type DPTStrat (PMaybe a) Source #

DerivePlutusType (PEither a b) Source # 
Instance details

Defined in Plutarch.Either

Associated Types

type DPTStrat (PEither a b) Source #

DerivePlutusType (DeriveBuiltinPLiftable a h) Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type DPTStrat (DeriveBuiltinPLiftable a h) Source #

DerivePlutusType (DeriveDataPLiftable a h) Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type DPTStrat (DeriveDataPLiftable a h) Source #

DerivePlutusType (PPair a b) Source # 
Instance details

Defined in Plutarch.Pair

Associated Types

type DPTStrat (PPair a b) Source #

DerivePlutusType (DeriveNewtypePLiftable w i h) Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type DPTStrat (DeriveNewtypePLiftable w i h) Source #

type PCon = PlutusType Source #

Deprecated: Use PlutusType

type PMatch = PlutusType Source #

Deprecated: Use PlutusType

class PlutusType (a :: PType) Source #

Associated Types

type PInner a :: PType Source #

Instances

Instances details
PlutusType PBitString Source # 
Instance details

Defined in Plutarch.BitString

Methods

pcon' :: forall (s :: S). PBitString s -> Term s (PInner PBitString) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PBitString) -> (PBitString s -> Term s b) -> Term s b Source #

PlutusType PBuiltinBLS12_381_G1_Element Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

PlutusType PBuiltinBLS12_381_G2_Element Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

PlutusType PBuiltinBLS12_381_MlResult Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

PlutusType PBool Source #

@since WIP

Instance details

Defined in Plutarch.Internal.PlutusType

Methods

pcon' :: forall (s :: S). PBool s -> Term s (PInner PBool) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PBool) -> (PBool s -> Term s b) -> Term s b Source #

PlutusType PByte Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Methods

pcon' :: forall (s :: S). PByte s -> Term s (PInner PByte) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PByte) -> (PByte s -> Term s b) -> Term s b Source #

PlutusType PByteString Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Methods

pcon' :: forall (s :: S). PByteString s -> Term s (PInner PByteString) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PByteString) -> (PByteString s -> Term s b) -> Term s b Source #

PlutusType PEndianness Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Methods

pcon' :: forall (s :: S). PEndianness s -> Term s (PInner PEndianness) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PEndianness) -> (PEndianness s -> Term s b) -> Term s b Source #

PlutusType PLogicOpSemantics Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Methods

pcon' :: forall (s :: S). PLogicOpSemantics s -> Term s (PInner PLogicOpSemantics) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PLogicOpSemantics) -> (PLogicOpSemantics s -> Term s b) -> Term s b Source #

PlutusType PData Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Methods

pcon' :: forall (s :: S). PData s -> Term s (PInner PData) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PData) -> (PData s -> Term s b) -> Term s b Source #

PlutusType PInteger Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Methods

pcon' :: forall (s :: S). PInteger s -> Term s (PInner PInteger) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PInteger) -> (PInteger s -> Term s b) -> Term s b Source #

PlutusType POpaque Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Methods

pcon' :: forall (s :: S). POpaque s -> Term s (PInner POpaque) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner POpaque) -> (POpaque s -> Term s b) -> Term s b Source #

PlutusType PString Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Methods

pcon' :: forall (s :: S). PString s -> Term s (PInner PString) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PString) -> (PString s -> Term s b) -> Term s b Source #

PlutusType PUnit Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Methods

pcon' :: forall (s :: S). PUnit s -> Term s (PInner PUnit) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PUnit) -> (PUnit s -> Term s b) -> Term s b Source #

PlutusType PPositive Source # 
Instance details

Defined in Plutarch.Internal.Numeric

Methods

pcon' :: forall (s :: S). PPositive s -> Term s (PInner PPositive) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PPositive) -> (PPositive s -> Term s b) -> Term s b Source #

PlutusType PRational Source # 
Instance details

Defined in Plutarch.Rational

Methods

pcon' :: forall (s :: S). PRational s -> Term s (PInner PRational) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PRational) -> (PRational s -> Term s b) -> Term s b Source #

PlutusType (PDataNewtype a) Source #

Since: 1.7.0

Instance details

Defined in Plutarch.Builtin

Methods

pcon' :: forall (s :: S). PDataNewtype a s -> Term s (PInner (PDataNewtype a)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PDataNewtype a)) -> (PDataNewtype a s -> Term s b) -> Term s b Source #

PIsData a => PlutusType (PAsData a) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Associated Types

type PInner (PAsData a) :: PType Source #

type PCovariant' (PAsData a) Source #

type PContravariant' (PAsData a) Source #

type PVariant' (PAsData a) Source #

Methods

pcon' :: forall (s :: S). PAsData a s -> Term s (PInner (PAsData a)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PAsData a)) -> (PAsData a s -> Term s b) -> Term s b Source #

Contains DefaultUni (PlutusRepr a) => PlutusType (PBuiltinList a) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Methods

pcon' :: forall (s :: S). PBuiltinList a s -> Term s (PInner (PBuiltinList a)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PBuiltinList a)) -> (PBuiltinList a s -> Term s b) -> Term s b Source #

SListI l => PlutusType (PDataRecord l) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

pcon' :: forall (s :: S). PDataRecord l s -> Term s (PInner (PDataRecord l)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PDataRecord l)) -> (PDataRecord l s -> Term s b) -> Term s b Source #

SListI defs => PlutusType (PDataSum defs) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Associated Types

type PInner (PDataSum defs) :: PType Source #

type PCovariant' (PDataSum defs) Source #

type PContravariant' (PDataSum defs) Source #

type PVariant' (PDataSum defs) Source #

Methods

pcon' :: forall (s :: S). PDataSum defs s -> Term s (PInner (PDataSum defs)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PDataSum defs)) -> (PDataSum defs s -> Term s b) -> Term s b Source #

PlutusType (PFix f) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Associated Types

type PInner (PFix f) :: PType Source #

type PCovariant' (PFix f) Source #

type PContravariant' (PFix f) Source #

type PVariant' (PFix f) Source #

Methods

pcon' :: forall (s :: S). PFix f s -> Term s (PInner (PFix f)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PFix f)) -> (PFix f s -> Term s b) -> Term s b Source #

PlutusType (PList a) Source # 
Instance details

Defined in Plutarch.List

Associated Types

type PInner (PList a) :: PType Source #

type PCovariant' (PList a) Source #

type PContravariant' (PList a) Source #

type PVariant' (PList a) Source #

Methods

pcon' :: forall (s :: S). PList a s -> Term s (PInner (PList a)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PList a)) -> (PList a s -> Term s b) -> Term s b Source #

PlutusType (PMaybe a) Source # 
Instance details

Defined in Plutarch.Maybe

Associated Types

type PInner (PMaybe a) :: PType Source #

type PCovariant' (PMaybe a) Source #

type PContravariant' (PMaybe a) Source #

type PVariant' (PMaybe a) Source #

Methods

pcon' :: forall (s :: S). PMaybe a s -> Term s (PInner (PMaybe a)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PMaybe a)) -> (PMaybe a s -> Term s b) -> Term s b Source #

PlutusType (PMaybeSoP a) Source # 
Instance details

Defined in Plutarch.Maybe

Methods

pcon' :: forall (s :: S). PMaybeSoP a s -> Term s (PInner (PMaybeSoP a)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PMaybeSoP a)) -> (PMaybeSoP a s -> Term s b) -> Term s b Source #

(Generic (a (Any :: S)), '[struct'] ~ Code (a (Any :: S)), struct ~ UnTermRec struct', All PIsData struct, SListI struct, forall (s :: S). StructSameRepr s a '[struct], RecTypePrettyError (Code (a (Any :: S)))) => PlutusType (DeriveAsDataRec a) Source #

@since WIP

Instance details

Defined in Plutarch.Repr.Data

Methods

pcon' :: forall (s :: S). DeriveAsDataRec a s -> Term s (PInner (DeriveAsDataRec a)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (DeriveAsDataRec a)) -> (DeriveAsDataRec a s -> Term s b) -> Term s b Source #

(Generic (a (Any :: S)), struct ~ UnTermStruct (a (Any :: S)), All2 PIsData struct, SListI2 struct, forall (s :: S). StructSameRepr s a struct) => PlutusType (DeriveAsDataStruct a) Source #

@since WIP

Instance details

Defined in Plutarch.Repr.Data

Methods

pcon' :: forall (s :: S). DeriveAsDataStruct a s -> Term s (PInner (DeriveAsDataStruct a)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (DeriveAsDataStruct a)) -> (DeriveAsDataStruct a s -> Term s b) -> Term s b Source #

(SListI struct, All PIsData struct) => PlutusType (PDataRec struct) Source #

@since WIP

Instance details

Defined in Plutarch.Repr.Data

Associated Types

type PInner (PDataRec struct) :: PType Source #

type PCovariant' (PDataRec struct) Source #

type PContravariant' (PDataRec struct) Source #

type PVariant' (PDataRec struct) Source #

Methods

pcon' :: forall (s :: S). PDataRec struct s -> Term s (PInner (PDataRec struct)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PDataRec struct)) -> (PDataRec struct s -> Term s b) -> Term s b Source #

(SListI2 struct, All2 PIsData struct) => PlutusType (PDataStruct struct) Source #

@since WIP

Instance details

Defined in Plutarch.Repr.Data

Associated Types

type PInner (PDataStruct struct) :: PType Source #

type PCovariant' (PDataStruct struct) Source #

type PContravariant' (PDataStruct struct) Source #

type PVariant' (PDataStruct struct) Source #

Methods

pcon' :: forall (s :: S). PDataStruct struct s -> Term s (PInner (PDataStruct struct)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PDataStruct struct)) -> (PDataStruct struct s -> Term s b) -> Term s b Source #

(pt ~ UnTermSingle (Head (Head (Code (a (Any :: S))))), forall (s :: S). H s a pt) => PlutusType (DeriveAsNewtype a) Source # 
Instance details

Defined in Plutarch.Repr.Newtype

Methods

pcon' :: forall (s :: S). DeriveAsNewtype a s -> Term s (PInner (DeriveAsNewtype a)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (DeriveAsNewtype a)) -> (DeriveAsNewtype a s -> Term s b) -> Term s b Source #

(Generic (a (Any :: S)), '[struct'] ~ Code (a (Any :: S)), struct ~ UnTermRec struct', SListI struct, forall (s :: S). StructSameRepr s a '[struct], RecTypePrettyError (Code (a (Any :: S)))) => PlutusType (DeriveAsSOPRec a) Source #

@since WIP

Instance details

Defined in Plutarch.Repr.SOP

Methods

pcon' :: forall (s :: S). DeriveAsSOPRec a s -> Term s (PInner (DeriveAsSOPRec a)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (DeriveAsSOPRec a)) -> (DeriveAsSOPRec a s -> Term s b) -> Term s b Source #

(Generic (a (Any :: S)), struct ~ UnTermStruct (a (Any :: S)), SListI2 struct, forall (s :: S). StructSameRepr s a struct, PSOPStructConstraint struct) => PlutusType (DeriveAsSOPStruct a) Source #

@since WIP

Instance details

Defined in Plutarch.Repr.SOP

Methods

pcon' :: forall (s :: S). DeriveAsSOPStruct a s -> Term s (PInner (DeriveAsSOPStruct a)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (DeriveAsSOPStruct a)) -> (DeriveAsSOPStruct a s -> Term s b) -> Term s b Source #

SListI struct => PlutusType (PSOPRec struct) Source #

@since WIP

Instance details

Defined in Plutarch.Repr.SOP

Associated Types

type PInner (PSOPRec struct) :: PType Source #

type PCovariant' (PSOPRec struct) Source #

type PContravariant' (PSOPRec struct) Source #

type PVariant' (PSOPRec struct) Source #

Methods

pcon' :: forall (s :: S). PSOPRec struct s -> Term s (PInner (PSOPRec struct)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PSOPRec struct)) -> (PSOPRec struct s -> Term s b) -> Term s b Source #

(SListI2 struct, PSOPStructConstraint struct) => PlutusType (PSOPStruct struct) Source #

@since WIP

Instance details

Defined in Plutarch.Repr.SOP

Associated Types

type PInner (PSOPStruct struct) :: PType Source #

type PCovariant' (PSOPStruct struct) Source #

type PContravariant' (PSOPStruct struct) Source #

type PVariant' (PSOPStruct struct) Source #

Methods

pcon' :: forall (s :: S). PSOPStruct struct s -> Term s (PInner (PSOPStruct struct)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PSOPStruct struct)) -> (PSOPStruct struct s -> Term s b) -> Term s b Source #

(Generic (a (Any :: S)), '[struct'] ~ Code (a (Any :: S)), struct ~ UnTermRec struct', SListI struct, forall (s :: S). StructSameRepr s a '[struct], RecTypePrettyError (Code (a (Any :: S)))) => PlutusType (DeriveAsScottRec a) Source #

@since WIP

Instance details

Defined in Plutarch.Repr.Scott

Methods

pcon' :: forall (s :: S). DeriveAsScottRec a s -> Term s (PInner (DeriveAsScottRec a)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (DeriveAsScottRec a)) -> (DeriveAsScottRec a s -> Term s b) -> Term s b Source #

(Generic (a (Any :: S)), struct ~ UnTermStruct (a (Any :: S)), SListI2 struct, forall (s :: S). StructSameRepr s a struct, PScottStructConstraint struct) => PlutusType (DeriveAsScottStruct a) Source #

@since WIP

Instance details

Defined in Plutarch.Repr.Scott

Methods

pcon' :: forall (s :: S). DeriveAsScottStruct a s -> Term s (PInner (DeriveAsScottStruct a)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (DeriveAsScottStruct a)) -> (DeriveAsScottStruct a s -> Term s b) -> Term s b Source #

SListI struct => PlutusType (PScottRec struct) Source #

@since WIP

Instance details

Defined in Plutarch.Repr.Scott

Associated Types

type PInner (PScottRec struct) :: PType Source #

type PCovariant' (PScottRec struct) Source #

type PContravariant' (PScottRec struct) Source #

type PVariant' (PScottRec struct) Source #

Methods

pcon' :: forall (s :: S). PScottRec struct s -> Term s (PInner (PScottRec struct)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PScottRec struct)) -> (PScottRec struct s -> Term s b) -> Term s b Source #

(SListI2 struct, PScottStructConstraint struct) => PlutusType (PScottStruct struct) Source #

@since WIP

Instance details

Defined in Plutarch.Repr.Scott

Associated Types

type PInner (PScottStruct struct) :: PType Source #

type PCovariant' (PScottStruct struct) Source #

type PContravariant' (PScottStruct struct) Source #

type PVariant' (PScottStruct struct) Source #

Methods

pcon' :: forall (s :: S). PScottStruct struct s -> Term s (PInner (PScottStruct struct)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PScottStruct struct)) -> (PScottStruct struct s -> Term s b) -> Term s b Source #

(forall (s :: S). TagTypeConstraints s a struct) => PlutusType (DeriveAsTag a) Source #

This derives tag-only PlutusType automatically. Resulted instances will use PInteger as underlying type, making this much more efficient than using regular DataScottSOP based encoding. As name suggests, types with no-argument constructors can use this.

Example: @@ data PFoo s = A | B | C | D | E deriving stock (GHC.Generic, Show) deriving anyclass (PEq, PIsData) deriving (PlutusType, PLiftable) via DeriveAsTag PFoo

instance SOP.Generic (PFoo s) @@

@since WIP

Instance details

Defined in Plutarch.Repr.Tag

Methods

pcon' :: forall (s :: S). DeriveAsTag a s -> Term s (PInner (DeriveAsTag a)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (DeriveAsTag a)) -> (DeriveAsTag a s -> Term s b) -> Term s b Source #

PlutusType (PTag struct) Source # 
Instance details

Defined in Plutarch.Repr.Tag

Associated Types

type PInner (PTag struct) :: PType Source #

type PCovariant' (PTag struct) Source #

type PContravariant' (PTag struct) Source #

type PVariant' (PTag struct) Source #

Methods

pcon' :: forall (s :: S). PTag struct s -> Term s (PInner (PTag struct)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PTag struct)) -> (PTag struct s -> Term s b) -> Term s b Source #

PlutusType (PBuiltinPair a b) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Methods

pcon' :: forall (s :: S). PBuiltinPair a b s -> Term s (PInner (PBuiltinPair a b)) Source #

pmatch' :: forall (s :: S) (b0 :: PType). Term s (PInner (PBuiltinPair a b)) -> (PBuiltinPair a b s -> Term s b0) -> Term s b0 Source #

PlutusType (PEither a b) Source # 
Instance details

Defined in Plutarch.Either

Associated Types

type PInner (PEither a b) :: PType Source #

type PCovariant' (PEither a b) Source #

type PContravariant' (PEither a b) Source #

type PVariant' (PEither a b) Source #

Methods

pcon' :: forall (s :: S). PEither a b s -> Term s (PInner (PEither a b)) Source #

pmatch' :: forall (s :: S) (b0 :: PType). Term s (PInner (PEither a b)) -> (PEither a b s -> Term s b0) -> Term s b0 Source #

PlutusType (PEitherData a b) Source #

@since WIP

Instance details

Defined in Plutarch.Either

Methods

pcon' :: forall (s :: S). PEitherData a b s -> Term s (PInner (PEitherData a b)) Source #

pmatch' :: forall (s :: S) (b0 :: PType). Term s (PInner (PEitherData a b)) -> (PEitherData a b s -> Term s b0) -> Term s b0 Source #

PlutusType (DeriveBuiltinPLiftable a h) Source # 
Instance details

Defined in Plutarch.Internal.Lift

Methods

pcon' :: forall (s :: S). DeriveBuiltinPLiftable a h s -> Term s (PInner (DeriveBuiltinPLiftable a h)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (DeriveBuiltinPLiftable a h)) -> (DeriveBuiltinPLiftable a h s -> Term s b) -> Term s b Source #

PlutusType (DeriveDataPLiftable a h) Source # 
Instance details

Defined in Plutarch.Internal.Lift

Methods

pcon' :: forall (s :: S). DeriveDataPLiftable a h s -> Term s (PInner (DeriveDataPLiftable a h)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (DeriveDataPLiftable a h)) -> (DeriveDataPLiftable a h s -> Term s b) -> Term s b Source #

PlutusType (PForall f) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Associated Types

type PInner (PForall f) :: PType Source #

type PCovariant' (PForall f) Source #

type PContravariant' (PForall f) Source #

type PVariant' (PForall f) Source #

Methods

pcon' :: forall (s :: S). PForall f s -> Term s (PInner (PForall f)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PForall f)) -> (PForall f s -> Term s b) -> Term s b Source #

PlutusType (PSome f) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Associated Types

type PInner (PSome f) :: PType Source #

type PCovariant' (PSome f) Source #

type PContravariant' (PSome f) Source #

type PVariant' (PSome f) Source #

Methods

pcon' :: forall (s :: S). PSome f s -> Term s (PInner (PSome f)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PSome f)) -> (PSome f s -> Term s b) -> Term s b Source #

PlutusType (PScottEncoded a r) Source # 
Instance details

Defined in Plutarch.Internal.ScottEncoding

Methods

pcon' :: forall (s :: S). PScottEncoded a r s -> Term s (PInner (PScottEncoded a r)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PScottEncoded a r)) -> (PScottEncoded a r s -> Term s b) -> Term s b Source #

PlutusType (a :--> b) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Associated Types

type PInner (a :--> b) :: PType Source #

type PCovariant' (a :--> b) Source #

type PContravariant' (a :--> b) Source #

type PVariant' (a :--> b) Source #

Methods

pcon' :: forall (s :: S). (a :--> b) s -> Term s (PInner (a :--> b)) Source #

pmatch' :: forall (s :: S) (b0 :: PType). Term s (PInner (a :--> b)) -> ((a :--> b) s -> Term s b0) -> Term s b0 Source #

PlutusType (PPair a b) Source # 
Instance details

Defined in Plutarch.Pair

Associated Types

type PInner (PPair a b) :: PType Source #

type PCovariant' (PPair a b) Source #

type PContravariant' (PPair a b) Source #

type PVariant' (PPair a b) Source #

Methods

pcon' :: forall (s :: S). PPair a b s -> Term s (PInner (PPair a b)) Source #

pmatch' :: forall (s :: S) (b0 :: PType). Term s (PInner (PPair a b)) -> (PPair a b s -> Term s b0) -> Term s b0 Source #

PlutusType (DeriveNewtypePLiftable wrapper inner h) Source # 
Instance details

Defined in Plutarch.Internal.Lift

Associated Types

type PInner (DeriveNewtypePLiftable wrapper inner h) :: PType Source #

type PCovariant' (DeriveNewtypePLiftable wrapper inner h) Source #

type PContravariant' (DeriveNewtypePLiftable wrapper inner h) Source #

type PVariant' (DeriveNewtypePLiftable wrapper inner h) Source #

Methods

pcon' :: forall (s :: S). DeriveNewtypePLiftable wrapper inner h s -> Term s (PInner (DeriveNewtypePLiftable wrapper inner h)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (DeriveNewtypePLiftable wrapper inner h)) -> (DeriveNewtypePLiftable wrapper inner h s -> Term s b) -> Term s b Source #

pcon :: PlutusType a => a s -> Term s a Source #

Construct a Plutarch Term via a Haskell datatype

pmatch :: PlutusType a => Term s a -> (a s -> Term s b) -> Term s b Source #

Pattern match over Plutarch Terms via a Haskell datatype

Numeric

data Positive Source #

@since WIP

Instances

Instances details
Arbitrary Positive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

CoArbitrary Positive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

coarbitrary :: Positive -> Gen b -> Gen b

Function Positive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

function :: (Positive -> b) -> Positive :-> b

Show Positive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Eq Positive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Ord Positive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Pretty Positive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

pretty :: Positive -> Doc ann

prettyList :: [Positive] -> Doc ann

data PPositive (s :: S) Source #

@since WIP

Instances

Instances details
PCountable PPositive Source #

@since WIP

Instance details

Defined in Plutarch.Enum

Methods

psuccessor :: forall (s :: S). Term s (PPositive :--> PPositive) Source #

psuccessorN :: forall (s :: S). Term s (PPositive :--> (PPositive :--> PPositive)) Source #

PEq PPositive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

(#==) :: forall (s :: S). Term s PPositive -> Term s PPositive -> Term s PBool Source #

PIsData PPositive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PPositive) -> Term s PPositive Source #

pdataImpl :: forall (s :: S). Term s PPositive -> Term s PData Source #

PLiftable PPositive Source # 
Instance details

Defined in Plutarch.Internal.Numeric

PAdditiveSemigroup PPositive Source #

@since WIP

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

(#+) :: forall (s :: S). Term s PPositive -> Term s PPositive -> Term s PPositive Source #

pscalePositive :: forall (s :: S). Term s (PPositive :--> (PPositive :--> PPositive)) Source #

PMultiplicativeMonoid PPositive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

pone :: forall (s :: S). Term s PPositive Source #

PMultiplicativeSemigroup PPositive Source #

@since WIP

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

(#*) :: forall (s :: S). Term s PPositive -> Term s PPositive -> Term s PPositive Source #

ppowPositive :: forall (s :: S). Term s (PPositive :--> (PPositive :--> PPositive)) Source #

POrd PPositive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

(#<=) :: forall (s :: S). Term s PPositive -> Term s PPositive -> Term s PBool Source #

(#<) :: forall (s :: S). Term s PPositive -> Term s PPositive -> Term s PBool Source #

pmax :: forall (s :: S). Term s PPositive -> Term s PPositive -> Term s PPositive Source #

pmin :: forall (s :: S). Term s PPositive -> Term s PPositive -> Term s PPositive Source #

DerivePlutusType PPositive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Associated Types

type DPTStrat PPositive Source #

PlutusType PPositive Source # 
Instance details

Defined in Plutarch.Internal.Numeric

Methods

pcon' :: forall (s :: S). PPositive s -> Term s (PInner PPositive) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PPositive) -> (PPositive s -> Term s b) -> Term s b Source #

PShow PPositive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Show

Methods

pshow' :: forall (s :: S). Bool -> Term s PPositive -> Term s PString Source #

PTryFrom PInteger PPositive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PInteger PPositive :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PInteger -> ((Term s PPositive, Reduce (PTryFromExcess PInteger PPositive s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData PPositive) Source #

@since WIP

Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData (PAsData PPositive) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData PPositive), Reduce (PTryFromExcess PData (PAsData PPositive) s)) -> Term s r) -> Term s r Source #

Generic (PPositive s) Source # 
Instance details

Defined in Plutarch.Internal.Numeric

Associated Types

type Rep (PPositive s) :: Type -> Type Source #

Methods

from :: PPositive s -> Rep (PPositive s) x Source #

to :: Rep (PPositive s) x -> PPositive s Source #

type AsHaskell PPositive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

type PlutusRepr PPositive Source # 
Instance details

Defined in Plutarch.Internal.Numeric

type DPTStrat PPositive Source # 
Instance details

Defined in Plutarch.Internal.Numeric

type PContravariant' PPositive Source # 
Instance details

Defined in Plutarch.Internal.Numeric

type PCovariant' PPositive Source # 
Instance details

Defined in Plutarch.Internal.Numeric

type PInner PPositive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

type PVariant' PPositive Source # 
Instance details

Defined in Plutarch.Internal.Numeric

type PTryFromExcess PInteger PPositive Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type PTryFromExcess PData (PAsData PPositive) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

type Rep (PPositive s) Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

type Rep (PPositive s) = D1 ('MetaData "PPositive" "Plutarch.Internal.Numeric" "plutarch-1.9.0-FtN0mhIoM9oEvz7Q98pjWP" 'True) (C1 ('MetaCons "PPositive" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s PInteger))))

class PAdditiveSemigroup (a :: S -> Type) where Source #

The addition operation.

Laws

  1. x #+ y = y #+ x (commutativity of #+)
  2. x #+ (y #+ z) = (x #+ y) #+ z (associativity of #+)

If you define a custom pscalePositive, ensure the following also hold:

  1. pscalePositive # x # pone = x
  2. (pscalePositive # x # n) #+ (pscalePositive # x # m) = pscalePositive # x # (n #+ m)
  3. pscalePositive # (pscalePositive # x # n) # m = pscalePositive # x # (n #* m)

The default implementation ensures these laws are satisfied.

@since WIP

Minimal complete definition

Nothing

Methods

(#+) :: forall (s :: S). Term s a -> Term s a -> Term s a infix 6 Source #

default (#+) :: forall (s :: S). PAdditiveSemigroup (PInner a) => Term s a -> Term s a -> Term s a Source #

pscalePositive :: forall (s :: S). Term s (a :--> (PPositive :--> a)) Source #

This defaults to exponentiation-by-squaring, which in general is the best we can do.

Instances

Instances details
PAdditiveSemigroup PBuiltinBLS12_381_G1_Element Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

PAdditiveSemigroup PBuiltinBLS12_381_G2_Element Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

PAdditiveSemigroup PInteger Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

(#+) :: forall (s :: S). Term s PInteger -> Term s PInteger -> Term s PInteger Source #

pscalePositive :: forall (s :: S). Term s (PInteger :--> (PPositive :--> PInteger)) Source #

PAdditiveSemigroup PPositive Source #

@since WIP

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

(#+) :: forall (s :: S). Term s PPositive -> Term s PPositive -> Term s PPositive Source #

pscalePositive :: forall (s :: S). Term s (PPositive :--> (PPositive :--> PPositive)) Source #

PAdditiveSemigroup PRational Source #

@since WIP

Instance details

Defined in Plutarch.Rational

Methods

(#+) :: forall (s :: S). Term s PRational -> Term s PRational -> Term s PRational Source #

pscalePositive :: forall (s :: S). Term s (PRational :--> (PPositive :--> PRational)) Source #

class PAdditiveSemigroup a => PAdditiveMonoid (a :: S -> Type) where Source #

The notion of zero, as well as a (kind of) reversal of pscalePositive, similar to floor division by positive integers.

Laws

  1. pzero #+ x = x (pzero is the identity of #+)
  2. pscalePositive # pzero # n = pzero (pzero does not scale up)

@since WIP

Methods

pzero :: forall (s :: S). Term s a Source #

Instances

Instances details
PAdditiveMonoid PBuiltinBLS12_381_G1_Element Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

pzero :: forall (s :: S). Term s PBuiltinBLS12_381_G1_Element Source #

PAdditiveMonoid PBuiltinBLS12_381_G2_Element Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

pzero :: forall (s :: S). Term s PBuiltinBLS12_381_G2_Element Source #

PAdditiveMonoid PInteger Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

pzero :: forall (s :: S). Term s PInteger Source #

PAdditiveMonoid PRational Source #

@since WIP

Instance details

Defined in Plutarch.Rational

Methods

pzero :: forall (s :: S). Term s PRational Source #

class PAdditiveMonoid a => PAdditiveGroup (a :: S -> Type) where Source #

The notion of additive inverses, and the subtraction operation.

Laws

If you define pnegate, the following laws must hold:

  1. (pnegate # x) #+ x = pzero (pnegate is an additive inverse)
  2. pnegate #$ pnegate # x = x (pnegate is self-inverting)

If you define #-, the following law must hold:

  1. x #- x = pzero

Additionally, the following 'consistency laws' must hold. Default implementations of both pnegate and #- uphold these.

  1. pnegate # x = pzero #- x
  2. x #- y = x #+ (pnegate # y)

Lastly, if you define a custom pscaleInteger, the following laws must hold:

  1. pscaleInteger # x # pzero = pzero
  2. pscaleInteger # x #$ pnegate y = pnegate #$ pscaleInteger # x # y

@since WIP

Minimal complete definition

pnegate | (#-)

Methods

pnegate :: forall (s :: S). Term s (a :--> a) Source #

(#-) :: forall (s :: S). Term s a -> Term s a -> Term s a infix 6 Source #

pscaleInteger :: forall (s :: S). Term s (a :--> (PInteger :--> a)) Source #

Instances

Instances details
PAdditiveGroup PBuiltinBLS12_381_G1_Element Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

PAdditiveGroup PBuiltinBLS12_381_G2_Element Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

PAdditiveGroup PInteger Source #

@since WIP

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

pnegate :: forall (s :: S). Term s (PInteger :--> PInteger) Source #

(#-) :: forall (s :: S). Term s PInteger -> Term s PInteger -> Term s PInteger Source #

pscaleInteger :: forall (s :: S). Term s (PInteger :--> (PInteger :--> PInteger)) Source #

PAdditiveGroup PRational Source #

@since WIP

Instance details

Defined in Plutarch.Rational

Methods

pnegate :: forall (s :: S). Term s (PRational :--> PRational) Source #

(#-) :: forall (s :: S). Term s PRational -> Term s PRational -> Term s PRational Source #

pscaleInteger :: forall (s :: S). Term s (PRational :--> (PInteger :--> PRational)) Source #

class PMultiplicativeSemigroup (a :: S -> Type) where Source #

The multiplication operation.

Laws

  1. x #* (y #* z) = (x #* y) #* z (associativity of #*)

If you define a custom ppowPositive, ensure the following also hold:

  1. ppowPositive # x # pone = x
  2. (ppowPositive # x # n) #* (ppowPositive # x # m) = pscalePositive # x # (n #+ m)
  3. ppowPositive # (ppowPositive # x # n) # m = pscalePositive # x # (n #* m)

The default implementation ensures these laws are satisfied.

Note

Unlike PAdditiveSemigroup, the multiplication operation doesn't need to be commutative. Currently, all Plutarch-provided instances are, but this need not be true for other instances.

@since WIP

Minimal complete definition

Nothing

Methods

(#*) :: forall (s :: S). Term s a -> Term s a -> Term s a infix 6 Source #

default (#*) :: forall (s :: S). PMultiplicativeSemigroup (PInner a) => Term s a -> Term s a -> Term s a Source #

ppowPositive :: forall (s :: S). Term s (a :--> (PPositive :--> a)) Source #

Instances

Instances details
PMultiplicativeSemigroup PInteger Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

(#*) :: forall (s :: S). Term s PInteger -> Term s PInteger -> Term s PInteger Source #

ppowPositive :: forall (s :: S). Term s (PInteger :--> (PPositive :--> PInteger)) Source #

PMultiplicativeSemigroup PPositive Source #

@since WIP

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

(#*) :: forall (s :: S). Term s PPositive -> Term s PPositive -> Term s PPositive Source #

ppowPositive :: forall (s :: S). Term s (PPositive :--> (PPositive :--> PPositive)) Source #

PMultiplicativeSemigroup PRational Source #

@since WIP

Instance details

Defined in Plutarch.Rational

Methods

(#*) :: forall (s :: S). Term s PRational -> Term s PRational -> Term s PRational Source #

ppowPositive :: forall (s :: S). Term s (PRational :--> (PPositive :--> PRational)) Source #

class PMultiplicativeSemigroup a => PMultiplicativeMonoid (a :: S -> Type) where Source #

The notion of one (multiplicative identity).

Laws

  1. pone #* x = x (pone is the left identity of #*)
  2. x #* pone = x (pone is the right identity of #*)

@since WIP

Methods

pone :: forall (s :: S). Term s a Source #

Instances

Instances details
PMultiplicativeMonoid PInteger Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

pone :: forall (s :: S). Term s PInteger Source #

PMultiplicativeMonoid PPositive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

pone :: forall (s :: S). Term s PPositive Source #

PMultiplicativeMonoid PRational Source #

@since WIP

Instance details

Defined in Plutarch.Rational

Methods

pone :: forall (s :: S). Term s PRational Source #

class (PAdditiveGroup a, PMultiplicativeMonoid a) => PRing (a :: S -> Type) where Source #

Laws

  1. pfromInteger 0 = pzero
  2. pfromInteger 1 = pone
  3. pfromInteger (x + y) = pfromInteger x #+ pfromInteger y
  4. pfromInteger (x * y) = pfromInteger x #* pfromInteger y

Additionally, the following 'interaction laws' must hold between the instances of PAdditiveGroup and PMultiplicativeMonoid for a:

  1. x #* (y #+ z) = (x #* y) #+ (x #* z) (#* left-distributes over #+)
  2. (y #+ z) #* x = (y #* x) #+ (z #* x) (#* right-distributes over #+)

@since WIP

Minimal complete definition

Nothing

Methods

pfromInteger :: forall (s :: S). Integer -> Term s a Source #

default pfromInteger :: forall (s :: S). PRing (PInner a) => Integer -> Term s a Source #

Instances

Instances details
PRing PInteger Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

pfromInteger :: forall (s :: S). Integer -> Term s PInteger Source #

PRing PRational Source #

@since WIP

Instance details

Defined in Plutarch.Rational

Methods

pfromInteger :: forall (s :: S). Integer -> Term s PRational Source #

class (PRing a, POrd a) => PIntegralDomain (a :: S -> Type) where Source #

Laws

Pedantry note

Technically, the requirements here are too strong: we demand an ordered ring, which integral domains don't necessarily have to be. However, in our case, our hand is forced by expected semantics: in abstract algebra, both the absolute value and the signum are real numbers (which are always totally ordered) but in our case, both must be elements of the integral domain itself. Thus, in order for the laws to make any sense, we have to ensure a total order on the integral domain. Since all of our integral domains are 'at least as big' as the integers, this doesn't pose a huge problem.

@since WIP

Minimal complete definition

Nothing

Methods

psignum :: forall (s :: S). Term s (a :--> a) Source #

default psignum :: forall (s :: S). Term s (a :--> a) Source #

pabs :: forall (s :: S). Term s (a :--> a) Source #

default pabs :: forall (s :: S). Term s (a :--> a) Source #

Instances

Instances details
PIntegralDomain PInteger Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Numeric

Methods

psignum :: forall (s :: S). Term s (PInteger :--> PInteger) Source #

pabs :: forall (s :: S). Term s (PInteger :--> PInteger) Source #

PIntegralDomain PRational Source #

@since WIP

Instance details

Defined in Plutarch.Rational

Methods

psignum :: forall (s :: S). Term s (PRational :--> PRational) Source #

pabs :: forall (s :: S). Term s (PRational :--> PRational) Source #

pquot :: forall (s :: S). Term s (PInteger :--> (PInteger :--> PInteger)) Source #

@since WIP

prem :: forall (s :: S). Term s (PInteger :--> (PInteger :--> PInteger)) Source #

@since WIP

pdiv :: forall (s :: S). Term s (PInteger :--> (PInteger :--> PInteger)) Source #

@since WIP

pmod :: forall (s :: S). Term s (PInteger :--> (PInteger :--> PInteger)) Source #

@since WIP

ppositive :: Term s (PInteger :--> PMaybe PPositive) Source #

Build a PPositive from a PInteger. Yields PNothing if argument is zero.

ptryPositive :: forall (s :: S). Term s (PInteger :--> PPositive) Source #

Partial version of PPositive. Errors if argument is zero.

@since WIP

Other

pto :: Term s a -> Term s (PInner a) Source #

Safely coerce from a Term to it's PInner representation.

pinl :: Term s a -> (Term s a -> Term s b) -> Term s b Source #

plam :: forall c. (PLamN a b s, HasCallStack) => (Term s c -> a) -> Term s (c :--> b) Source #

newtype PForall (b :: a -> PType) s Source #

Constructors

PForall (forall (x :: a). Term s (b x)) 

Instances

Instances details
PlutusType (PForall f) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Associated Types

type PInner (PForall f) :: PType Source #

type PCovariant' (PForall f) Source #

type PContravariant' (PForall f) Source #

type PVariant' (PForall f) Source #

Methods

pcon' :: forall (s :: S). PForall f s -> Term s (PInner (PForall f)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PForall f)) -> (PForall f s -> Term s b) -> Term s b Source #

type PContravariant' (PForall f) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PCovariant' (PForall f) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PInner (PForall f) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PInner (PForall f) = PForall f
type PVariant' (PForall f) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PVariant' (PForall f) = All2 PVariant'' (PCode (PForall f))

Show

class PShow t Source #

Instances

Instances details
PShow PBool Source # 
Instance details

Defined in Plutarch.Internal.Show

Methods

pshow' :: forall (s :: S). Bool -> Term s PBool -> Term s PString Source #

PShow PByteString Source # 
Instance details

Defined in Plutarch.Internal.Show

Methods

pshow' :: forall (s :: S). Bool -> Term s PByteString -> Term s PString Source #

PShow PData Source # 
Instance details

Defined in Plutarch.Internal.Show

Methods

pshow' :: forall (s :: S). Bool -> Term s PData -> Term s PString Source #

PShow PInteger Source # 
Instance details

Defined in Plutarch.Internal.Show

Methods

pshow' :: forall (s :: S). Bool -> Term s PInteger -> Term s PString Source #

PShow PString Source # 
Instance details

Defined in Plutarch.Internal.Show

Methods

pshow' :: forall (s :: S). Bool -> Term s PString -> Term s PString Source #

PShow PUnit Source # 
Instance details

Defined in Plutarch.Internal.Show

Methods

pshow' :: forall (s :: S). Bool -> Term s PUnit -> Term s PString Source #

PShow PPositive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Show

Methods

pshow' :: forall (s :: S). Bool -> Term s PPositive -> Term s PString Source #

PShow PRational Source # 
Instance details

Defined in Plutarch.Rational

Methods

pshow' :: forall (s :: S). Bool -> Term s PRational -> Term s PString Source #

(PIsData a, PShow a) => PShow (PDataNewtype a) Source #

Since: 1.7.0

Instance details

Defined in Plutarch.Builtin

Methods

pshow' :: forall (s :: S). Bool -> Term s (PDataNewtype a) -> Term s PString Source #

(PIsData a, PShow a) => PShow (PAsData a) Source # 
Instance details

Defined in Plutarch.Internal.Show

Methods

pshow' :: forall (s :: S). Bool -> Term s (PAsData a) -> Term s PString Source #

(PShow a, Contains DefaultUni (PlutusRepr a)) => PShow (PBuiltinList a) Source # 
Instance details

Defined in Plutarch.Internal.Show

Methods

pshow' :: forall (s :: S). Bool -> Term s (PBuiltinList a) -> Term s PString Source #

(All (Top :: PLabeledType -> Constraint) xs, KnownSymbol label, PIsData x, PShow x, PShow (PDataRecordShowHelper xs)) => PShow (PDataRecord ((label ':= x) ': xs)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

pshow' :: forall (s :: S). Bool -> Term s (PDataRecord ((label ':= x) ': xs)) -> Term s PString Source #

PShow (PDataRecord ('[] :: [PLabeledType])) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

pshow' :: forall (s :: S). Bool -> Term s (PDataRecord '[]) -> Term s PString Source #

(All (Top :: [PLabeledType] -> Constraint) defs, All (Compose PShow PDataRecord) defs) => PShow (PDataSum defs) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Methods

pshow' :: forall (s :: S). Bool -> Term s (PDataSum defs) -> Term s PString Source #

PShow a => PShow (PList a) Source # 
Instance details

Defined in Plutarch.List

Methods

pshow' :: forall (s :: S). Bool -> Term s (PList a) -> Term s PString Source #

PShow a => PShow (PMaybe a) Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Show

Methods

pshow' :: forall (s :: S). Bool -> Term s (PMaybe a) -> Term s PString Source #

PShow a => PShow (PMaybeSoP a) Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Show

Methods

pshow' :: forall (s :: S). Bool -> Term s (PMaybeSoP a) -> Term s PString Source #

(PShow a, PShow b) => PShow (PBuiltinPair a b) Source # 
Instance details

Defined in Plutarch.Internal.Show

Methods

pshow' :: forall (s :: S). Bool -> Term s (PBuiltinPair a b) -> Term s PString Source #

(PShow a, PShow b) => PShow (PEither a b) Source # 
Instance details

Defined in Plutarch.Either

Methods

pshow' :: forall (s :: S). Bool -> Term s (PEither a b) -> Term s PString Source #

(PIsData a, PIsData b, PShow a, PShow b) => PShow (PEitherData a b) Source #

@since WIP

Instance details

Defined in Plutarch.Either

Methods

pshow' :: forall (s :: S). Bool -> Term s (PEitherData a b) -> Term s PString Source #

(PShow a, PShow b) => PShow (PPair a b) Source # 
Instance details

Defined in Plutarch.Pair

Methods

pshow' :: forall (s :: S). Bool -> Term s (PPair a b) -> Term s PString Source #

pshow :: PShow a => Term s a -> Term s PString Source #

Return the string representation of a Plutarch value

Term and related functionality

data Term (s :: S) (a :: PType) Source #

Instances

Instances details
(IndexLabel name as ~ a, ElemOf name a as, Term s (PAsData b) ~ a, PFromDataable b c) => HasField (name :: Symbol) (HRec as) (Term s c) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal.HList

Methods

getField :: HRec as -> Term s c Source #

IsString (Term s PString) Source # 
Instance details

Defined in Plutarch.Builtin.String

Monoid (Term s PByteString) Source # 
Instance details

Defined in Plutarch.Builtin.ByteString

Monoid (Term s PString) Source # 
Instance details

Defined in Plutarch.Builtin.String

Monoid (Term s PUnit) Source # 
Instance details

Defined in Plutarch.Builtin.Unit

Semigroup (Term s PByteString) Source # 
Instance details

Defined in Plutarch.Builtin.ByteString

Semigroup (Term s PString) Source # 
Instance details

Defined in Plutarch.Builtin.String

Semigroup (Term s PUnit) Source # 
Instance details

Defined in Plutarch.Builtin.Unit

PIntegralDomain a => Num (Term s a) Source # 
Instance details

Defined in Plutarch.Internal.Numeric

Methods

(+) :: Term s a -> Term s a -> Term s a Source #

(-) :: Term s a -> Term s a -> Term s a Source #

(*) :: Term s a -> Term s a -> Term s a Source #

negate :: Term s a -> Term s a Source #

abs :: Term s a -> Term s a Source #

signum :: Term s a -> Term s a Source #

fromInteger :: Integer -> Term s a Source #

Fractional (Term s PRational) Source #

@since WIP

Instance details

Defined in Plutarch.Rational

data S Source #

type ClosedTerm (a :: PType) = forall (s :: S). Term s a Source #

  • Closed* terms with no free variables.

data PDelayed (a :: PType) (s :: S) Source #

papp :: Term s (a :--> b) -> Term s a -> Term s b Source #

Lambda Application.

pdelay :: Term s a -> Term s (PDelayed a) Source #

Plutus 'delay', used for laziness.

pforce :: Term s (PDelayed a) -> Term s a Source #

Plutus 'force', used to force evaluation of PDelayed terms.

perror :: Term s a Source #

Plutus 'error'.

When using this explicitly, it should be ensured that the containing term is delayed, avoiding premature evaluation.

plet :: Term s a -> (Term s a -> Term s b) -> Term s b Source #

Let bindings.

This is approximately a shorthand for a lambda and application:

plet v f == papp (plam f) v

But sufficiently small terms in WHNF may be inlined for efficiency.

(#) :: Term s (a :--> b) -> Term s a -> Term s b infixl 8 Source #

High precedence infixl synonym of papp, to be used like function juxtaposition. e.g.:

>>> f # x # y
f x y

(#$) :: Term s (a :--> b) -> Term s a -> Term s b infixr 0 Source #

Low precedence infixr synonym of papp, to be used like $, in combination with #. e.g.:

>>> f # x #$ g # y # z
f x (g y z)

data ((a :: PType) :--> (b :: PType)) (s :: S) infixr 0 Source #

Instances

Instances details
PlutusType (a :--> b) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

Associated Types

type PInner (a :--> b) :: PType Source #

type PCovariant' (a :--> b) Source #

type PContravariant' (a :--> b) Source #

type PVariant' (a :--> b) Source #

Methods

pcon' :: forall (s :: S). (a :--> b) s -> Term s (PInner (a :--> b)) Source #

pmatch' :: forall (s :: S) (b0 :: PType). Term s (PInner (a :--> b)) -> ((a :--> b) s -> Term s b0) -> Term s b0 Source #

(a' ~ Term s a, PLamN b' b s) => PLamN (a' -> b') (a :--> b) s Source # 
Instance details

Defined in Plutarch.Internal.PLam

Methods

plam :: forall (c :: PType). HasCallStack => (Term s c -> a' -> b') -> Term s (c :--> (a :--> b)) Source #

type PContravariant' (a :--> b) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PCovariant' (a :--> b) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PInner (a :--> b) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PInner (a :--> b) = a :--> b
type PVariant' (a :--> b) Source # 
Instance details

Defined in Plutarch.Internal.PlutusType

type PVariant' (a :--> b) = (PVariant' a, PVariant' b)

Conversion

type family PSubtype (a :: PType) (b :: PType) :: Constraint where ... Source #

Equations

PSubtype a b = (PSubtype' a b ~ 'PSubtypeRelation, PSubtypeHelper a b (PSubtype' a b)) 

class PSubtype a b => PTryFrom (a :: PType) (b :: PType) where Source #

PTryFrom a b represents a subtyping relationship between a and b, and a way to go from a to b. Laws: - (punsafeCoerce . fst) $ tcont (ptryFrom x) ≡ pure x

Minimal complete definition

Nothing

Associated Types

type PTryFromExcess a b :: PType Source #

Methods

ptryFrom' :: forall s r. Term s a -> ((Term s b, Reduce (PTryFromExcess a b s)) -> Term s r) -> Term s r Source #

default ptryFrom' :: forall s r. (PTryFrom a (PInner b), PTryFromExcess a b ~ PTryFromExcess a (PInner b)) => Term s a -> ((Term s b, Reduce (PTryFromExcess a b s)) -> Term s r) -> Term s r Source #

Instances

Instances details
PTryFrom PData PData Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData PData :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s PData, Reduce (PTryFromExcess PData PData s)) -> Term s r) -> Term s r Source #

PTryFrom PInteger PPositive Source #

@since WIP

Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PInteger PPositive :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PInteger -> ((Term s PPositive, Reduce (PTryFromExcess PInteger PPositive s)) -> Term s r) -> Term s r Source #

(PIsData a, PTryFrom PData (PAsData a)) => PTryFrom PData (PDataNewtype a) Source #

Since: 1.7.0

Instance details

Defined in Plutarch.Builtin

Associated Types

type PTryFromExcess PData (PDataNewtype a) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PDataNewtype a), Reduce (PTryFromExcess PData (PDataNewtype a) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData (PDataNewtype a)) Source #

Since: 1.7.0

Instance details

Defined in Plutarch.Builtin

Associated Types

type PTryFromExcess PData (PAsData (PDataNewtype a)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PDataNewtype a)), Reduce (PTryFromExcess PData (PAsData (PDataNewtype a)) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData PBool) Source #

Since: 1.7.0

Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData (PAsData PBool) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData PBool), Reduce (PTryFromExcess PData (PAsData PBool) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData PByteString) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData PByteString), Reduce (PTryFromExcess PData (PAsData PByteString) s)) -> Term s r) -> Term s r Source #

(PTryFrom PData (PAsData a), PIsData a) => PTryFrom PData (PAsData (PBuiltinList (PAsData a))) Source #

Recover a `PBuiltinList (PAsData a)`

Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData (PAsData (PBuiltinList (PAsData a))) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PBuiltinList (PAsData a))), Reduce (PTryFromExcess PData (PAsData (PBuiltinList (PAsData a))) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData (PBuiltinList PData)) Source #

This verifies a list to be indeed a list but doesn't recover the inner data use this instance instead of the one for `PData (PAsData (PBuiltinList (PAsData a)))` as this is O(1) instead of O(n)

Instance details

Defined in Plutarch.Internal.TryFrom

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PBuiltinList PData)), Reduce (PTryFromExcess PData (PAsData (PBuiltinList PData)) s)) -> Term s r) -> Term s r Source #

(PTryFrom PData a, a ~ PAsData a', PIsData a', PTryFrom PData b, b ~ PAsData b', PIsData b') => PTryFrom PData (PAsData (PBuiltinPair a b)) Source #

Recover a `PAsData (PBuiltinPair a b)`

Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData (PAsData (PBuiltinPair a b)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PBuiltinPair a b)), Reduce (PTryFromExcess PData (PAsData (PBuiltinPair a b)) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData PData) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData (PAsData PData) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData PData), Reduce (PTryFromExcess PData (PAsData PData) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData PInteger) Source # 
Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData (PAsData PInteger) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData PInteger), Reduce (PTryFromExcess PData (PAsData PInteger) s)) -> Term s r) -> Term s r Source #

(PTryFrom (PBuiltinList PData) (PDataRecord as), PTryFromExcess (PBuiltinList PData) (PDataRecord as) ~ HRecP ase) => PTryFrom PData (PAsData (PDataRecord as)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Associated Types

type PTryFromExcess PData (PAsData (PDataRecord as)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PDataRecord as)), Reduce (PTryFromExcess PData (PAsData (PDataRecord as)) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PDataSum ys) => PTryFrom PData (PAsData (PDataSum ys)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Associated Types

type PTryFromExcess PData (PAsData (PDataSum ys)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PDataSum ys)), Reduce (PTryFromExcess PData (PAsData (PDataSum ys)) s)) -> Term s r) -> Term s r Source #

(PTryFrom PData a, PTryFrom PData b) => PTryFrom PData (PAsData (PEitherData a b)) Source #

@since WIP

Instance details

Defined in Plutarch.Either

Associated Types

type PTryFromExcess PData (PAsData (PEitherData a b)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PEitherData a b)), Reduce (PTryFromExcess PData (PAsData (PEitherData a b)) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData PPositive) Source #

@since WIP

Instance details

Defined in Plutarch.Internal.TryFrom

Associated Types

type PTryFromExcess PData (PAsData PPositive) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData PPositive), Reduce (PTryFromExcess PData (PAsData PPositive) s)) -> Term s r) -> Term s r Source #

PTryFrom PData (PAsData PRational) Source #

NOTE: This instance produces a verified PPositive as the excess output.

Instance details

Defined in Plutarch.Rational

Associated Types

type PTryFromExcess PData (PAsData PRational) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData PRational), Reduce (PTryFromExcess PData (PAsData PRational) s)) -> Term s r) -> Term s r Source #

SumValidation 0 ys => PTryFrom PData (PDataSum ys) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Associated Types

type PTryFromExcess PData (PDataSum ys) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PDataSum ys), Reduce (PTryFromExcess PData (PDataSum ys) s)) -> Term s r) -> Term s r Source #

(PTryFrom PData a, PTryFrom PData b) => PTryFrom PData (PEitherData a b) Source #

@since WIP

Instance details

Defined in Plutarch.Either

Associated Types

type PTryFromExcess PData (PEitherData a b) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PEitherData a b), Reduce (PTryFromExcess PData (PEitherData a b) s)) -> Term s r) -> Term s r Source #

(Helper2 (PSubtype' PData pty) pty, PTryFrom (PBuiltinList PData) (PDataRecord as), PTryFromExcess (PBuiltinList PData) (PDataRecord as) ~ HRecP ase) => PTryFrom (PBuiltinList PData) (PDataRecord ((name ':= pty) ': as)) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Associated Types

type PTryFromExcess (PBuiltinList PData) (PDataRecord ((name ':= pty) ': as)) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s (PBuiltinList PData) -> ((Term s (PDataRecord ((name ':= pty) ': as)), Reduce (PTryFromExcess (PBuiltinList PData) (PDataRecord ((name ':= pty) ': as)) s)) -> Term s r) -> Term s r Source #

PTryFrom (PBuiltinList PData) (PDataRecord ('[] :: [PLabeledType])) Source # 
Instance details

Defined in Plutarch.DataRepr.Internal

Associated Types

type PTryFromExcess (PBuiltinList PData) (PDataRecord '[]) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s (PBuiltinList PData) -> ((Term s (PDataRecord '[]), Reduce (PTryFromExcess (PBuiltinList PData) (PDataRecord '[]) s)) -> Term s r) -> Term s r Source #

ptryFrom :: forall b a s r. PTryFrom a b => Term s a -> ((Term s b, Reduce (PTryFromExcess a b s)) -> Term s r) -> Term s r Source #

pupcast :: forall a b s. PSubtype a b => Term s b -> Term s a Source #

Maybe

data PMaybe (a :: S -> Type) (s :: S) Source #

Plutus Maybe type, with Scott-encoded repr

Constructors

PJust (Term s a) 
PNothing 

Instances

Instances details
PEq a => PEq (PMaybe a) Source # 
Instance details

Defined in Plutarch.Maybe

Methods

(#==) :: forall (s :: S). Term s (PMaybe a) -> Term s (PMaybe a) -> Term s PBool Source #

PLiftable a => PLiftable (PMaybe a) Source #

@since WIP

Instance details

Defined in Plutarch.Maybe

Associated Types

type AsHaskell (PMaybe a) Source #

type PlutusRepr (PMaybe a) Source #

DerivePlutusType (PMaybe a) Source # 
Instance details

Defined in Plutarch.Maybe

Associated Types

type DPTStrat (PMaybe a) Source #

PlutusType (PMaybe a) Source # 
Instance details

Defined in Plutarch.Maybe

Associated Types

type PInner (PMaybe a) :: PType Source #

type PCovariant' (PMaybe a) Source #

type PContravariant' (PMaybe a) Source #

type PVariant' (PMaybe a) Source #

Methods

pcon' :: forall (s :: S). PMaybe a s -> Term s (PInner (PMaybe a)) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PMaybe a)) -> (PMaybe a s -> Term s b) -> Term s b Source #

PShow a => PShow (PMaybe a) Source #

@since WIP

Instance details

Defined in Plutarch.Internal.Show

Methods

pshow' :: forall (s :: S). Bool -> Term s (PMaybe a) -> Term s PString Source #

Generic (PMaybe a s) Source # 
Instance details

Defined in Plutarch.Maybe

Associated Types

type Rep (PMaybe a s) :: Type -> Type Source #

Methods

from :: PMaybe a s -> Rep (PMaybe a s) x Source #

to :: Rep (PMaybe a s) x -> PMaybe a s Source #

type AsHaskell (PMaybe a) Source # 
Instance details

Defined in Plutarch.Maybe

type PlutusRepr (PMaybe a) Source # 
Instance details

Defined in Plutarch.Maybe

type DPTStrat (PMaybe a) Source # 
Instance details

Defined in Plutarch.Maybe

type PContravariant' (PMaybe a) Source # 
Instance details

Defined in Plutarch.Maybe

type PCovariant' (PMaybe a) Source # 
Instance details

Defined in Plutarch.Maybe

type PInner (PMaybe a) Source # 
Instance details

Defined in Plutarch.Maybe

type PVariant' (PMaybe a) Source # 
Instance details

Defined in Plutarch.Maybe

type PVariant' (PMaybe a) = All2 PVariant'' (PCode (PMaybe a))
type Rep (PMaybe a s) Source # 
Instance details

Defined in Plutarch.Maybe

type Rep (PMaybe a s) = D1 ('MetaData "PMaybe" "Plutarch.Maybe" "plutarch-1.9.0-FtN0mhIoM9oEvz7Q98pjWP" 'False) (C1 ('MetaCons "PJust" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s a))) :+: C1 ('MetaCons "PNothing" 'PrefixI 'False) (U1 :: Type -> Type))

Pair

data PPair (a :: PType) (b :: PType) (s :: S) Source #

Plutus encoding of Pairs.

Note: This is represented differently than BuiltinPair. It is scott-encoded.

Constructors

PPair (Term s a) (Term s b) 

Instances

Instances details
(PEq a, PEq b) => PEq (PPair a b) Source # 
Instance details

Defined in Plutarch.Pair

Methods

(#==) :: forall (s :: S). Term s (PPair a b) -> Term s (PPair a b) -> Term s PBool Source #

DerivePlutusType (PPair a b) Source # 
Instance details

Defined in Plutarch.Pair

Associated Types

type DPTStrat (PPair a b) Source #

PlutusType (PPair a b) Source # 
Instance details

Defined in Plutarch.Pair

Associated Types

type PInner (PPair a b) :: PType Source #

type PCovariant' (PPair a b) Source #

type PContravariant' (PPair a b) Source #

type PVariant' (PPair a b) Source #

Methods

pcon' :: forall (s :: S). PPair a b s -> Term s (PInner (PPair a b)) Source #

pmatch' :: forall (s :: S) (b0 :: PType). Term s (PInner (PPair a b)) -> (PPair a b s -> Term s b0) -> Term s b0 Source #

(PShow a, PShow b) => PShow (PPair a b) Source # 
Instance details

Defined in Plutarch.Pair

Methods

pshow' :: forall (s :: S). Bool -> Term s (PPair a b) -> Term s PString Source #

Generic (PPair a b s) Source # 
Instance details

Defined in Plutarch.Pair

Associated Types

type Rep (PPair a b s) :: Type -> Type Source #

Methods

from :: PPair a b s -> Rep (PPair a b s) x Source #

to :: Rep (PPair a b s) x -> PPair a b s Source #

type DPTStrat (PPair a b) Source # 
Instance details

Defined in Plutarch.Pair

type PContravariant' (PPair a b) Source # 
Instance details

Defined in Plutarch.Pair

type PCovariant' (PPair a b) Source # 
Instance details

Defined in Plutarch.Pair

type PCovariant' (PPair a b) = All2 PCovariant'' (PCode (PPair a b))
type PInner (PPair a b) Source # 
Instance details

Defined in Plutarch.Pair

type PInner (PPair a b) = DerivedPInner (DPTStrat (PPair a b)) (PPair a b)
type PVariant' (PPair a b) Source # 
Instance details

Defined in Plutarch.Pair

type PVariant' (PPair a b) = All2 PVariant'' (PCode (PPair a b))
type Rep (PPair a b s) Source # 
Instance details

Defined in Plutarch.Pair

type Rep (PPair a b s) = D1 ('MetaData "PPair" "Plutarch.Pair" "plutarch-1.9.0-FtN0mhIoM9oEvz7Q98pjWP" 'False) (C1 ('MetaCons "PPair" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s a)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s b))))

Rational

data PRational s Source #

A Scott-encoded rational number, with a guaranteed positive denominator (and thus, a canonical form).

Note

This is not the Plutarch equivalent of a Plutus Rational; for this, you want PRationalData from plutarch-ledger-api. PRational is designed to optimize for computation: if you want to do any serious work with rational numbers that isn't just passing them around, you want to use (or convert to) PRational.

Constructors

PRational (Term s PInteger) (Term s PPositive) 

Instances

Instances details
PEq PRational Source # 
Instance details

Defined in Plutarch.Rational

Methods

(#==) :: forall (s :: S). Term s PRational -> Term s PRational -> Term s PBool Source #

PLiftable PRational Source #

@since WIP

Instance details

Defined in Plutarch.Rational

PAdditiveGroup PRational Source #

@since WIP

Instance details

Defined in Plutarch.Rational

Methods

pnegate :: forall (s :: S). Term s (PRational :--> PRational) Source #

(#-) :: forall (s :: S). Term s PRational -> Term s PRational -> Term s PRational Source #

pscaleInteger :: forall (s :: S). Term s (PRational :--> (PInteger :--> PRational)) Source #

PAdditiveMonoid PRational Source #

@since WIP

Instance details

Defined in Plutarch.Rational

Methods

pzero :: forall (s :: S). Term s PRational Source #

PAdditiveSemigroup PRational Source #

@since WIP

Instance details

Defined in Plutarch.Rational

Methods

(#+) :: forall (s :: S). Term s PRational -> Term s PRational -> Term s PRational Source #

pscalePositive :: forall (s :: S). Term s (PRational :--> (PPositive :--> PRational)) Source #

PIntegralDomain PRational Source #

@since WIP

Instance details

Defined in Plutarch.Rational

Methods

psignum :: forall (s :: S). Term s (PRational :--> PRational) Source #

pabs :: forall (s :: S). Term s (PRational :--> PRational) Source #

PMultiplicativeMonoid PRational Source #

@since WIP

Instance details

Defined in Plutarch.Rational

Methods

pone :: forall (s :: S). Term s PRational Source #

PMultiplicativeSemigroup PRational Source #

@since WIP

Instance details

Defined in Plutarch.Rational

Methods

(#*) :: forall (s :: S). Term s PRational -> Term s PRational -> Term s PRational Source #

ppowPositive :: forall (s :: S). Term s (PRational :--> (PPositive :--> PRational)) Source #

PRing PRational Source #

@since WIP

Instance details

Defined in Plutarch.Rational

Methods

pfromInteger :: forall (s :: S). Integer -> Term s PRational Source #

POrd PRational Source # 
Instance details

Defined in Plutarch.Rational

Methods

(#<=) :: forall (s :: S). Term s PRational -> Term s PRational -> Term s PBool Source #

(#<) :: forall (s :: S). Term s PRational -> Term s PRational -> Term s PBool Source #

pmax :: forall (s :: S). Term s PRational -> Term s PRational -> Term s PRational Source #

pmin :: forall (s :: S). Term s PRational -> Term s PRational -> Term s PRational Source #

PlutusType PRational Source # 
Instance details

Defined in Plutarch.Rational

Methods

pcon' :: forall (s :: S). PRational s -> Term s (PInner PRational) Source #

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PRational) -> (PRational s -> Term s b) -> Term s b Source #

PShow PRational Source # 
Instance details

Defined in Plutarch.Rational

Methods

pshow' :: forall (s :: S). Bool -> Term s PRational -> Term s PString Source #

PTryFrom PData (PAsData PRational) Source #

NOTE: This instance produces a verified PPositive as the excess output.

Instance details

Defined in Plutarch.Rational

Associated Types

type PTryFromExcess PData (PAsData PRational) :: PType Source #

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData PRational), Reduce (PTryFromExcess PData (PAsData PRational) s)) -> Term s r) -> Term s r Source #

Generic (PRational s) Source # 
Instance details

Defined in Plutarch.Rational

Associated Types

type Rep (PRational s) :: Type -> Type Source #

Methods

from :: PRational s -> Rep (PRational s) x Source #

to :: Rep (PRational s) x -> PRational s Source #

Generic (PRational s) Source # 
Instance details

Defined in Plutarch.Rational

Associated Types

type Code (PRational s) :: [[Type]]

Methods

from :: PRational s -> Rep (PRational s)

to :: Rep (PRational s) -> PRational s

Fractional (Term s PRational) Source #

@since WIP

Instance details

Defined in Plutarch.Rational

type AsHaskell PRational Source # 
Instance details

Defined in Plutarch.Rational

type AsHaskell PRational = Rational
type PlutusRepr PRational Source # 
Instance details

Defined in Plutarch.Rational

type PContravariant' PRational Source # 
Instance details

Defined in Plutarch.Rational

type PCovariant' PRational Source # 
Instance details

Defined in Plutarch.Rational

type PInner PRational Source # 
Instance details

Defined in Plutarch.Rational

type PVariant' PRational Source # 
Instance details

Defined in Plutarch.Rational

type PTryFromExcess PData (PAsData PRational) Source # 
Instance details

Defined in Plutarch.Rational

type Rep (PRational s) Source # 
Instance details

Defined in Plutarch.Rational

type Rep (PRational s) = D1 ('MetaData "PRational" "Plutarch.Rational" "plutarch-1.9.0-FtN0mhIoM9oEvz7Q98pjWP" 'False) (C1 ('MetaCons "PRational" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s PInteger)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s PPositive))))
type Code (PRational s) Source # 
Instance details

Defined in Plutarch.Rational

type Code (PRational s) = GCode (PRational s)

TermCont

newtype TermCont :: forall (r :: PType). S -> Type -> Type where Source #

Constructors

TermCont 

Fields

Instances

Instances details
MonadFail (TermCont s) Source # 
Instance details

Defined in Plutarch.Internal.TermCont

Methods

fail :: String -> TermCont s a Source #

Applicative (TermCont s) Source # 
Instance details

Defined in Plutarch.Internal.TermCont

Methods

pure :: a -> TermCont s a Source #

(<*>) :: TermCont s (a -> b) -> TermCont s a -> TermCont s b Source #

liftA2 :: (a -> b -> c) -> TermCont s a -> TermCont s b -> TermCont s c Source #

(*>) :: TermCont s a -> TermCont s b -> TermCont s b Source #

(<*) :: TermCont s a -> TermCont s b -> TermCont s a Source #

Functor (TermCont s) Source # 
Instance details

Defined in Plutarch.Internal.TermCont

Methods

fmap :: (a -> b) -> TermCont s a -> TermCont s b Source #

(<$) :: a -> TermCont s b -> TermCont s a Source #

Monad (TermCont s) Source # 
Instance details

Defined in Plutarch.Internal.TermCont

Methods

(>>=) :: TermCont s a -> (a -> TermCont s b) -> TermCont s b Source #

(>>) :: TermCont s a -> TermCont s b -> TermCont s b Source #

return :: a -> TermCont s a Source #

pguardC :: Term s PString -> Term s PBool -> TermCont s () Source #

Trace a message and raise error if cond is false. Otherwise, continue.

Example ===

onlyAllow42 :: Term s (PInteger :--> PUnit)
onlyAllow42 = plam $ i -> unTermCont $ do
  pguardC "expected 42" $ i #== 42
  pure $ pconstant ()

pguardC' :: Term s a -> Term s PBool -> TermCont @a s () Source #

Stop computation and return given term if cond is false. Otherwise, continue.

Example ===

is42 :: Term s (PInteger :--> PBool)
is42 = plam $ i -> unTermCont $ do
  pguardC' (pconstant False) $ i #== 42
  pure $ pconstant True

pletC :: Term s a -> TermCont s (Term s a) Source #

Like plet but works in a TermCont monad

pletFieldsC :: forall fs a s b ps bs. (PDataFields a, ps ~ PFields a, bs ~ Bindings ps fs, BindFields ps bs) => Term s a -> TermCont @b s (HRec (BoundTerms ps bs s)) Source #

Like pletFields but works in a TermCont monad.

pmatchC :: PlutusType a => Term s a -> TermCont s (a s) Source #

Like pmatch but works in a TermCont monad

ptraceC :: Term s PString -> TermCont s () Source #

Like ptrace but works in a TermCont monad.

Example ===

foo :: Term s PUnit
foo = unTermCont $ do
  ptraceC "returning unit!"
  pure $ pconstant ()

ptryFromC :: forall b r a s. PTryFrom a b => Term s a -> TermCont @r s (Term s b, Reduce (PTryFromExcess a b s)) Source #

TermCont producing version of ptryFrom.

unTermCont :: TermCont @a s (Term s a) -> Term s a Source #

tcont :: ((a -> Term s r) -> Term s r) -> TermCont @r s a Source #

Tracing

ptrace :: forall (a :: S -> Type) (s :: S). Term s PString -> Term s a -> Term s a Source #

Deprecated: Use ptraceInfo

Backward compatibility synonym for ptraceInfo.

Since: 1.6.0

ptraceDebug :: forall (a :: S -> Type) (s :: S). Term s PString -> Term s a -> Term s a Source #

Trace the given message at the debug level before evaluating the given argument.

Since: 1.6.0

ptraceDebugError :: forall (a :: S -> Type) (s :: S). Term s PString -> Term s a Source #

Trace the given message at the debug level, then terminate with perror.

Since: 1.6.0

ptraceDebugIfFalse :: forall (s :: S). Term s PString -> Term s PBool -> Term s PBool Source #

Trace the given message at the debug level if the argument is false.

Since: 1.6.0

ptraceDebugIfTrue :: forall (s :: S). Term s PString -> Term s PBool -> Term s PBool Source #

Trace the given message at the debug level if the argument is true.

Since: 1.6.0

ptraceDebugShowId :: forall (a :: S -> Type) (s :: S). PShow a => Term s a -> Term s a Source #

Like Haskell's traceShowId but for Plutarch, at the debug level.

Since: 1.6.0

ptraceError :: forall (a :: S -> Type) (s :: S). Term s PString -> Term s a Source #

Deprecated: Use ptraceInfoError

Synonym for ptraceInfoError.

Since: 1.6.0

ptraceIfFalse :: forall (s :: S). Term s PString -> Term s PBool -> Term s PBool Source #

Deprecated: Use ptraceInfoIfFalse

Synonym for ptraceInfoIfFalse.

Since: 1.6.0

ptraceInfo :: forall (a :: S -> Type) (s :: S). Term s PString -> Term s a -> Term s a Source #

Trace the given message at the info level before evaluating the given argument.

Since: 1.6.0

ptraceInfoError :: forall (a :: S -> Type) (s :: S). Term s PString -> Term s a Source #

Trace the given message at the info level, then terminate with perror.

Since: 1.6.0

ptraceInfoIfFalse :: forall (s :: S). Term s PString -> Term s PBool -> Term s PBool Source #

Trace the given message at the info level if the argument is false.

Since: 1.6.0

ptraceInfoIfTrue :: forall (s :: S). Term s PString -> Term s PBool -> Term s PBool Source #

Trace the given message at the info level if the argument is true.

Since: 1.6.0

ptraceInfoShowId :: forall (a :: S -> Type) (s :: S). PShow a => Term s a -> Term s a Source #

Like Haskell's traceShowId but for Plutarch, at the info level.

Since: 1.6.0

ptraceShowId :: forall (a :: S -> Type) (s :: S). PShow a => Term s a -> Term s a Source #

Deprecated: Use ptraceInfoShowId

Synonym for ptraceInfoShowId.

Since: 1.6.0