plutarch-ledger-api-3.2.1
Safe HaskellSafe-Inferred
LanguageHaskell2010

Plutarch.LedgerApi.V2

Synopsis

Contexts

data PScriptPurpose (s :: S) Source #

Since: 3.1.1

Constructors

PMinting (Term s (PDataRecord '["_0" ':= PCurrencySymbol])) 
PSpending (Term s (PDataRecord '["_0" ':= PTxOutRef])) 
PRewarding (Term s (PDataRecord '["_0" ':= PStakingCredential])) 
PCertifying (Term s (PDataRecord '["_0" ':= PDCert])) 

Instances

Instances details
PIsData PScriptPurpose Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V1.Contexts

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PScriptPurpose) -> Term s PScriptPurpose

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

PEq PScriptPurpose Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V1.Contexts

Methods

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

PLiftable PScriptPurpose Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Contexts

Associated Types

type AsHaskell PScriptPurpose

type PlutusRepr PScriptPurpose

Methods

toPlutarchRepr :: AsHaskell PScriptPurpose -> PlutusRepr PScriptPurpose

toPlutarch :: forall (s :: S). AsHaskell PScriptPurpose -> PLifted s PScriptPurpose

fromPlutarchRepr :: PlutusRepr PScriptPurpose -> Maybe (AsHaskell PScriptPurpose)

fromPlutarch :: (forall (s :: S). PLifted s PScriptPurpose) -> Either LiftError (AsHaskell PScriptPurpose)

DerivePlutusType PScriptPurpose Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V1.Contexts

Associated Types

type DPTStrat PScriptPurpose

PlutusType PScriptPurpose Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Contexts

Associated Types

type PInner PScriptPurpose :: PType

type PCovariant' PScriptPurpose

type PContravariant' PScriptPurpose

type PVariant' PScriptPurpose

Methods

pcon' :: forall (s :: S). PScriptPurpose s -> Term s (PInner PScriptPurpose)

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PScriptPurpose) -> (PScriptPurpose s -> Term s b) -> Term s b

PShow PScriptPurpose Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V1.Contexts

Methods

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

PTryFrom PData PScriptPurpose Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Contexts

Associated Types

type PTryFromExcess PData PScriptPurpose :: PType

Methods

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

PTryFrom PData (PAsData PScriptPurpose) Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V1.Contexts

Associated Types

type PTryFromExcess PData (PAsData PScriptPurpose) :: PType

Methods

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

Generic (PScriptPurpose s) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Contexts

Associated Types

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

type AsHaskell PScriptPurpose Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.V1.Contexts

type AsHaskell PScriptPurpose = AsHaskell (DeriveDataPLiftable PScriptPurpose ScriptPurpose)
type PlutusRepr PScriptPurpose Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Contexts

type PlutusRepr PScriptPurpose = PlutusRepr (DeriveDataPLiftable PScriptPurpose ScriptPurpose)
type DPTStrat PScriptPurpose Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Contexts

type DPTStrat PScriptPurpose = PlutusTypeData
type PContravariant' PScriptPurpose Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Contexts

type PContravariant' PScriptPurpose = All2 PContravariant'' (PCode PScriptPurpose)
type PCovariant' PScriptPurpose Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Contexts

type PCovariant' PScriptPurpose = All2 PCovariant'' (PCode PScriptPurpose)
type PInner PScriptPurpose Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V1.Contexts

type PInner PScriptPurpose = DerivedPInner (DPTStrat PScriptPurpose) PScriptPurpose
type PVariant' PScriptPurpose Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Contexts

type PVariant' PScriptPurpose = All2 PVariant'' (PCode PScriptPurpose)
type PTryFromExcess PData PScriptPurpose Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V1.Contexts

type PTryFromExcess PData PScriptPurpose = PTryFromExcess PData (PInner PScriptPurpose)
type PTryFromExcess PData (PAsData PScriptPurpose) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Contexts

type PTryFromExcess PData (PAsData PScriptPurpose) = PTryFromExcess PData (PInner (PAsData PScriptPurpose))
type Rep (PScriptPurpose s) Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V1.Contexts

type Rep (PScriptPurpose s) = D1 ('MetaData "PScriptPurpose" "Plutarch.LedgerApi.V1.Contexts" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'False) ((C1 ('MetaCons "PMinting" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["_0" ':= PCurrencySymbol])))) :+: C1 ('MetaCons "PSpending" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["_0" ':= PTxOutRef]))))) :+: (C1 ('MetaCons "PRewarding" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["_0" ':= PStakingCredential])))) :+: C1 ('MetaCons "PCertifying" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["_0" ':= PDCert]))))))

newtype PScriptContext (s :: S) Source #

Since: 3.1.1

Constructors

PScriptContext (Term s (PDataRecord '["txInfo" ':= PTxInfo, "purpose" ':= PScriptPurpose])) 

Instances

Instances details
PIsData PScriptContext Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PScriptContext) -> Term s PScriptContext

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

PDataFields PScriptContext Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

Associated Types

type PFields PScriptContext :: [PLabeledType]

Methods

ptoFields :: forall (s :: S). Term s PScriptContext -> Term s (PDataRecord (PFields PScriptContext))

PEq PScriptContext Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

Methods

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

PLiftable PScriptContext Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

Associated Types

type AsHaskell PScriptContext

type PlutusRepr PScriptContext

Methods

toPlutarchRepr :: AsHaskell PScriptContext -> PlutusRepr PScriptContext

toPlutarch :: forall (s :: S). AsHaskell PScriptContext -> PLifted s PScriptContext

fromPlutarchRepr :: PlutusRepr PScriptContext -> Maybe (AsHaskell PScriptContext)

fromPlutarch :: (forall (s :: S). PLifted s PScriptContext) -> Either LiftError (AsHaskell PScriptContext)

DerivePlutusType PScriptContext Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

Associated Types

type DPTStrat PScriptContext

PlutusType PScriptContext Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

Associated Types

type PInner PScriptContext :: PType

type PCovariant' PScriptContext

type PContravariant' PScriptContext

type PVariant' PScriptContext

Methods

pcon' :: forall (s :: S). PScriptContext s -> Term s (PInner PScriptContext)

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PScriptContext) -> (PScriptContext s -> Term s b) -> Term s b

PShow PScriptContext Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

Methods

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

PTryFrom PData PScriptContext Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

Associated Types

type PTryFromExcess PData PScriptContext :: PType

Methods

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

PTryFrom PData (PAsData PScriptContext) Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

Associated Types

type PTryFromExcess PData (PAsData PScriptContext) :: PType

Methods

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

Generic (PScriptContext s) Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

Associated Types

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

type PFields PScriptContext Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

type PFields PScriptContext = Helper (PInner PScriptContext)
type AsHaskell PScriptContext Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.V2

type AsHaskell PScriptContext = AsHaskell (DeriveDataPLiftable PScriptContext ScriptContext)
type PlutusRepr PScriptContext Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

type PlutusRepr PScriptContext = PlutusRepr (DeriveDataPLiftable PScriptContext ScriptContext)
type DPTStrat PScriptContext Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

type DPTStrat PScriptContext = PlutusTypeData
type PContravariant' PScriptContext Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

type PContravariant' PScriptContext = All2 PContravariant'' (PCode PScriptContext)
type PCovariant' PScriptContext Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

type PCovariant' PScriptContext = All2 PCovariant'' (PCode PScriptContext)
type PInner PScriptContext Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

type PInner PScriptContext = DerivedPInner (DPTStrat PScriptContext) PScriptContext
type PVariant' PScriptContext Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

type PVariant' PScriptContext = All2 PVariant'' (PCode PScriptContext)
type PTryFromExcess PData PScriptContext Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

type PTryFromExcess PData PScriptContext = PTryFromExcess PData (PInner PScriptContext)
type PTryFromExcess PData (PAsData PScriptContext) Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

type PTryFromExcess PData (PAsData PScriptContext) = PTryFromExcess PData (PInner (PAsData PScriptContext))
type Rep (PScriptContext s) Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

type Rep (PScriptContext s) = D1 ('MetaData "PScriptContext" "Plutarch.LedgerApi.V2" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PScriptContext" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["txInfo" ':= PTxInfo, "purpose" ':= PScriptPurpose])))))

Certificates

data PDCert (s :: S) Source #

Since: 3.1.1

Constructors

PDCertDelegRegKey (Term s (PDataRecord '["_0" ':= PStakingCredential])) 
PDCertDelegDeRegKey (Term s (PDataRecord '["_0" ':= PStakingCredential])) 
PDCertDelegDelegate (Term s (PDataRecord '["_0" ':= PStakingCredential, "_1" ':= PPubKeyHash])) 
PDCertPoolRegister (Term s (PDataRecord '["_0" ':= PPubKeyHash, "_1" ':= PPubKeyHash])) 
PDCertPoolRetire (Term s (PDataRecord '["_0" ':= PPubKeyHash, "_1" ':= PInteger])) 
PDCertGenesis (Term s (PDataRecord '[])) 
PDCertMir (Term s (PDataRecord '[])) 

Instances

Instances details
PIsData PDCert Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V1.DCert

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PDCert) -> Term s PDCert

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

PEq PDCert Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V1.DCert

Methods

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

PLiftable PDCert Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.DCert

Associated Types

type AsHaskell PDCert

type PlutusRepr PDCert

Methods

toPlutarchRepr :: AsHaskell PDCert -> PlutusRepr PDCert

toPlutarch :: forall (s :: S). AsHaskell PDCert -> PLifted s PDCert

fromPlutarchRepr :: PlutusRepr PDCert -> Maybe (AsHaskell PDCert)

fromPlutarch :: (forall (s :: S). PLifted s PDCert) -> Either LiftError (AsHaskell PDCert)

DerivePlutusType PDCert Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V1.DCert

Associated Types

type DPTStrat PDCert

PlutusType PDCert Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.DCert

Associated Types

type PInner PDCert :: PType

type PCovariant' PDCert

type PContravariant' PDCert

type PVariant' PDCert

Methods

pcon' :: forall (s :: S). PDCert s -> Term s (PInner PDCert)

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PDCert) -> (PDCert s -> Term s b) -> Term s b

PShow PDCert Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V1.DCert

Methods

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

PTryFrom PData PDCert Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.DCert

Associated Types

type PTryFromExcess PData PDCert :: PType

Methods

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

PTryFrom PData (PAsData PDCert) Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.DCert

Associated Types

type PTryFromExcess PData (PAsData PDCert) :: PType

Methods

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

Generic (PDCert s) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.DCert

Associated Types

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

Methods

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

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

type AsHaskell PDCert Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.V1.DCert

type AsHaskell PDCert = AsHaskell (DeriveDataPLiftable PDCert DCert)
type PlutusRepr PDCert Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.DCert

type PlutusRepr PDCert = PlutusRepr (DeriveDataPLiftable PDCert DCert)
type DPTStrat PDCert Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.DCert

type DPTStrat PDCert = PlutusTypeData
type PContravariant' PDCert Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.DCert

type PContravariant' PDCert = All2 PContravariant'' (PCode PDCert)
type PCovariant' PDCert Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.DCert

type PCovariant' PDCert = All2 PCovariant'' (PCode PDCert)
type PInner PDCert Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V1.DCert

type PInner PDCert = DerivedPInner (DPTStrat PDCert) PDCert
type PVariant' PDCert Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.DCert

type PVariant' PDCert = All2 PVariant'' (PCode PDCert)
type PTryFromExcess PData PDCert Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V1.DCert

type PTryFromExcess PData PDCert = PTryFromExcess PData (PInner PDCert)
type PTryFromExcess PData (PAsData PDCert) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.DCert

type PTryFromExcess PData (PAsData PDCert) = PTryFromExcess PData (PInner (PAsData PDCert))
type Rep (PDCert s) Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V1.DCert

type Rep (PDCert s) = D1 ('MetaData "PDCert" "Plutarch.LedgerApi.V1.DCert" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'False) ((C1 ('MetaCons "PDCertDelegRegKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["_0" ':= PStakingCredential])))) :+: (C1 ('MetaCons "PDCertDelegDeRegKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["_0" ':= PStakingCredential])))) :+: C1 ('MetaCons "PDCertDelegDelegate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["_0" ':= PStakingCredential, "_1" ':= PPubKeyHash])))))) :+: ((C1 ('MetaCons "PDCertPoolRegister" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["_0" ':= PPubKeyHash, "_1" ':= PPubKeyHash])))) :+: C1 ('MetaCons "PDCertPoolRetire" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["_0" ':= PPubKeyHash, "_1" ':= PInteger]))))) :+: (C1 ('MetaCons "PDCertGenesis" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord ('[] :: [PLabeledType]))))) :+: C1 ('MetaCons "PDCertMir" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord ('[] :: [PLabeledType]))))))))

Credentials

data PCredential (s :: S) Source #

Since: 2.0.0

Constructors

PPubKeyCredential (Term s (PDataRecord '["_0" ':= PPubKeyHash])) 
PScriptCredential (Term s (PDataRecord '["_0" ':= PScriptHash])) 

Instances

Instances details
PIsData PCredential Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Credential

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PCredential) -> Term s PCredential

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

PEq PCredential Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Credential

Methods

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

PLiftable PCredential Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Credential

Associated Types

type AsHaskell PCredential

type PlutusRepr PCredential

Methods

toPlutarchRepr :: AsHaskell PCredential -> PlutusRepr PCredential

toPlutarch :: forall (s :: S). AsHaskell PCredential -> PLifted s PCredential

fromPlutarchRepr :: PlutusRepr PCredential -> Maybe (AsHaskell PCredential)

fromPlutarch :: (forall (s :: S). PLifted s PCredential) -> Either LiftError (AsHaskell PCredential)

POrd PCredential Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Credential

Methods

pmax :: forall (s :: S). Term s PCredential -> Term s PCredential -> Term s PCredential

pmin :: forall (s :: S). Term s PCredential -> Term s PCredential -> Term s PCredential

PPartialOrd PCredential Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Credential

Methods

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

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

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

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

DerivePlutusType PCredential Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Credential

Associated Types

type DPTStrat PCredential

PlutusType PCredential Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Credential

Associated Types

type PInner PCredential :: PType

type PCovariant' PCredential

type PContravariant' PCredential

type PVariant' PCredential

Methods

pcon' :: forall (s :: S). PCredential s -> Term s (PInner PCredential)

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PCredential) -> (PCredential s -> Term s b) -> Term s b

PShow PCredential Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Credential

Methods

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

PTryFrom PData PCredential Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Credential

Associated Types

type PTryFromExcess PData PCredential :: PType

Methods

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

PTryFrom PData (PAsData PCredential) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Credential

Associated Types

type PTryFromExcess PData (PAsData PCredential) :: PType

Methods

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

Generic (PCredential s) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Credential

Associated Types

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

type AsHaskell PCredential Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.V1.Credential

type AsHaskell PCredential = AsHaskell (DeriveDataPLiftable PCredential Credential)
type PlutusRepr PCredential Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Credential

type PlutusRepr PCredential = PlutusRepr (DeriveDataPLiftable PCredential Credential)
type DPTStrat PCredential Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Credential

type DPTStrat PCredential = PlutusTypeData
type PContravariant' PCredential Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Credential

type PContravariant' PCredential = All2 PContravariant'' (PCode PCredential)
type PCovariant' PCredential Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Credential

type PCovariant' PCredential = All2 PCovariant'' (PCode PCredential)
type PInner PCredential Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Credential

type PInner PCredential = DerivedPInner (DPTStrat PCredential) PCredential
type PVariant' PCredential Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Credential

type PVariant' PCredential = All2 PVariant'' (PCode PCredential)
type PTryFromExcess PData PCredential Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Credential

type PTryFromExcess PData PCredential = PTryFromExcess PData (PInner PCredential)
type PTryFromExcess PData (PAsData PCredential) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Credential

type PTryFromExcess PData (PAsData PCredential) = PTryFromExcess PData (PInner (PAsData PCredential))
type Rep (PCredential s) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Credential

type Rep (PCredential s) = D1 ('MetaData "PCredential" "Plutarch.LedgerApi.V1.Credential" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'False) (C1 ('MetaCons "PPubKeyCredential" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["_0" ':= PPubKeyHash])))) :+: C1 ('MetaCons "PScriptCredential" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["_0" ':= PScriptHash])))))

data PStakingCredential (s :: S) Source #

Since: 2.0.0

Constructors

PStakingHash (Term s (PDataRecord '["_0" ':= PCredential])) 
PStakingPtr (Term s (PDataRecord '["_0" ':= PInteger, "_1" ':= PInteger, "_2" ':= PInteger])) 

Instances

Instances details
PIsData PStakingCredential Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Credential

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PStakingCredential) -> Term s PStakingCredential

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

PEq PStakingCredential Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Credential

Methods

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

PLiftable PStakingCredential Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Credential

Associated Types

type AsHaskell PStakingCredential

type PlutusRepr PStakingCredential

Methods

toPlutarchRepr :: AsHaskell PStakingCredential -> PlutusRepr PStakingCredential

toPlutarch :: forall (s :: S). AsHaskell PStakingCredential -> PLifted s PStakingCredential

fromPlutarchRepr :: PlutusRepr PStakingCredential -> Maybe (AsHaskell PStakingCredential)

fromPlutarch :: (forall (s :: S). PLifted s PStakingCredential) -> Either LiftError (AsHaskell PStakingCredential)

POrd PStakingCredential Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Credential

Methods

pmax :: forall (s :: S). Term s PStakingCredential -> Term s PStakingCredential -> Term s PStakingCredential

pmin :: forall (s :: S). Term s PStakingCredential -> Term s PStakingCredential -> Term s PStakingCredential

PPartialOrd PStakingCredential Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Credential

Methods

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

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

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

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

DerivePlutusType PStakingCredential Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Credential

Associated Types

type DPTStrat PStakingCredential

PlutusType PStakingCredential Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Credential

Associated Types

type PInner PStakingCredential :: PType

type PCovariant' PStakingCredential

type PContravariant' PStakingCredential

type PVariant' PStakingCredential

Methods

pcon' :: forall (s :: S). PStakingCredential s -> Term s (PInner PStakingCredential)

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PStakingCredential) -> (PStakingCredential s -> Term s b) -> Term s b

PShow PStakingCredential Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Credential

Methods

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

PTryFrom PData PStakingCredential Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Credential

Associated Types

type PTryFromExcess PData PStakingCredential :: PType

Methods

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

PTryFrom PData (PAsData PStakingCredential) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Credential

Associated Types

type PTryFromExcess PData (PAsData PStakingCredential) :: PType

Methods

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

Generic (PStakingCredential s) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Credential

Associated Types

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

type AsHaskell PStakingCredential Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.V1.Credential

type AsHaskell PStakingCredential = AsHaskell (DeriveDataPLiftable PStakingCredential StakingCredential)
type PlutusRepr PStakingCredential Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Credential

type PlutusRepr PStakingCredential = PlutusRepr (DeriveDataPLiftable PStakingCredential StakingCredential)
type DPTStrat PStakingCredential Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Credential

type DPTStrat PStakingCredential = PlutusTypeData
type PContravariant' PStakingCredential Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Credential

type PContravariant' PStakingCredential = All2 PContravariant'' (PCode PStakingCredential)
type PCovariant' PStakingCredential Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Credential

type PCovariant' PStakingCredential = All2 PCovariant'' (PCode PStakingCredential)
type PInner PStakingCredential Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Credential

type PInner PStakingCredential = DerivedPInner (DPTStrat PStakingCredential) PStakingCredential
type PVariant' PStakingCredential Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Credential

type PVariant' PStakingCredential = All2 PVariant'' (PCode PStakingCredential)
type PTryFromExcess PData PStakingCredential Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Credential

type PTryFromExcess PData PStakingCredential = PTryFromExcess PData (PInner PStakingCredential)
type PTryFromExcess PData (PAsData PStakingCredential) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Credential

type PTryFromExcess PData (PAsData PStakingCredential) = PTryFromExcess PData (PInner (PAsData PStakingCredential))
type Rep (PStakingCredential s) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Credential

type Rep (PStakingCredential s) = D1 ('MetaData "PStakingCredential" "Plutarch.LedgerApi.V1.Credential" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'False) (C1 ('MetaCons "PStakingHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["_0" ':= PCredential])))) :+: C1 ('MetaCons "PStakingPtr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["_0" ':= PInteger, "_1" ':= PInteger, "_2" ':= PInteger])))))

Value

newtype PValue (keys :: KeyGuarantees) (amounts :: AmountGuarantees) (s :: S) Source #

Since: 2.0.0

Constructors

PValue (Term s (PMap keys PCurrencySymbol (PMap keys PTokenName PInteger))) 

Instances

Instances details
PTryFrom PData (PAsData (PValue 'Sorted 'NoGuarantees)) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type PTryFromExcess PData (PAsData (PValue 'Sorted 'NoGuarantees)) :: PType

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PValue 'Sorted 'NoGuarantees)), Reduce (PTryFromExcess PData (PAsData (PValue 'Sorted 'NoGuarantees)) s)) -> Term s r) -> Term s r

PTryFrom PData (PAsData (PValue 'Sorted 'NonZero)) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type PTryFromExcess PData (PAsData (PValue 'Sorted 'NonZero)) :: PType

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PValue 'Sorted 'NonZero)), Reduce (PTryFromExcess PData (PAsData (PValue 'Sorted 'NonZero)) s)) -> Term s r) -> Term s r

PTryFrom PData (PAsData (PValue 'Sorted 'Positive)) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type PTryFromExcess PData (PAsData (PValue 'Sorted 'Positive)) :: PType

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PValue 'Sorted 'Positive)), Reduce (PTryFromExcess PData (PAsData (PValue 'Sorted 'Positive)) s)) -> Term s r) -> Term s r

PTryFrom PData (PAsData (PValue 'Unsorted 'NoGuarantees)) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type PTryFromExcess PData (PAsData (PValue 'Unsorted 'NoGuarantees)) :: PType

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PValue 'Unsorted 'NoGuarantees)), Reduce (PTryFromExcess PData (PAsData (PValue 'Unsorted 'NoGuarantees)) s)) -> Term s r) -> Term s r

PTryFrom PData (PAsData (PValue 'Unsorted 'NonZero)) Source #

Since: 2.1.1

Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type PTryFromExcess PData (PAsData (PValue 'Unsorted 'NonZero)) :: PType

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PValue 'Unsorted 'NonZero)), Reduce (PTryFromExcess PData (PAsData (PValue 'Unsorted 'NonZero)) s)) -> Term s r) -> Term s r

PTryFrom PData (PAsData (PValue 'Unsorted 'Positive)) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type PTryFromExcess PData (PAsData (PValue 'Unsorted 'Positive)) :: PType

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PValue 'Unsorted 'Positive)), Reduce (PTryFromExcess PData (PAsData (PValue 'Unsorted 'Positive)) s)) -> Term s r) -> Term s r

Semigroup (Term s (PValue 'Sorted normalization)) => Monoid (Term s (PValue 'Sorted normalization)) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

mempty :: Term s (PValue 'Sorted normalization) Source #

mappend :: Term s (PValue 'Sorted normalization) -> Term s (PValue 'Sorted normalization) -> Term s (PValue 'Sorted normalization) Source #

mconcat :: [Term s (PValue 'Sorted normalization)] -> Term s (PValue 'Sorted normalization) Source #

Semigroup (Term s (PValue 'Sorted 'NoGuarantees)) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Semigroup (Term s (PValue 'Sorted 'NonZero)) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

(<>) :: Term s (PValue 'Sorted 'NonZero) -> Term s (PValue 'Sorted 'NonZero) -> Term s (PValue 'Sorted 'NonZero) Source #

sconcat :: NonEmpty (Term s (PValue 'Sorted 'NonZero)) -> Term s (PValue 'Sorted 'NonZero) Source #

stimes :: Integral b => b -> Term s (PValue 'Sorted 'NonZero) -> Term s (PValue 'Sorted 'NonZero) Source #

Semigroup (Term s (PValue 'Sorted 'Positive)) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

(<>) :: Term s (PValue 'Sorted 'Positive) -> Term s (PValue 'Sorted 'Positive) -> Term s (PValue 'Sorted 'Positive) Source #

sconcat :: NonEmpty (Term s (PValue 'Sorted 'Positive)) -> Term s (PValue 'Sorted 'Positive) Source #

stimes :: Integral b => b -> Term s (PValue 'Sorted 'Positive) -> Term s (PValue 'Sorted 'Positive) Source #

PIsData (PValue keys amounts) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData (PValue keys amounts)) -> Term s (PValue keys amounts)

pdataImpl :: forall (s :: S). Term s (PValue keys amounts) -> Term s PData

PEq (PValue 'Sorted 'NoGuarantees) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

(#==) :: forall (s :: S). Term s (PValue 'Sorted 'NoGuarantees) -> Term s (PValue 'Sorted 'NoGuarantees) -> Term s PBool

PEq (PValue 'Sorted 'NonZero) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

(#==) :: forall (s :: S). Term s (PValue 'Sorted 'NonZero) -> Term s (PValue 'Sorted 'NonZero) -> Term s PBool

PEq (PValue 'Sorted 'Positive) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

(#==) :: forall (s :: S). Term s (PValue 'Sorted 'Positive) -> Term s (PValue 'Sorted 'Positive) -> Term s PBool

PLiftable (PValue 'Unsorted 'NoGuarantees) Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type AsHaskell (PValue 'Unsorted 'NoGuarantees)

type PlutusRepr (PValue 'Unsorted 'NoGuarantees)

Methods

toPlutarchRepr :: AsHaskell (PValue 'Unsorted 'NoGuarantees) -> PlutusRepr (PValue 'Unsorted 'NoGuarantees)

toPlutarch :: forall (s :: S). AsHaskell (PValue 'Unsorted 'NoGuarantees) -> PLifted s (PValue 'Unsorted 'NoGuarantees)

fromPlutarchRepr :: PlutusRepr (PValue 'Unsorted 'NoGuarantees) -> Maybe (AsHaskell (PValue 'Unsorted 'NoGuarantees))

fromPlutarch :: (forall (s :: S). PLifted s (PValue 'Unsorted 'NoGuarantees)) -> Either LiftError (AsHaskell (PValue 'Unsorted 'NoGuarantees))

PPartialOrd (PValue 'Sorted 'NonZero) Source #

Partial ordering implementation for sorted PValue with NonZero amounts.

Use pcheckBinRel if AmountGuarantees is NoGuarantees.

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

(#<=) :: forall (s :: S). Term s (PValue 'Sorted 'NonZero) -> Term s (PValue 'Sorted 'NonZero) -> Term s PBool

(#<) :: forall (s :: S). Term s (PValue 'Sorted 'NonZero) -> Term s (PValue 'Sorted 'NonZero) -> Term s PBool

(#>=) :: forall (s :: S). Term s (PValue 'Sorted 'NonZero) -> Term s (PValue 'Sorted 'NonZero) -> Term s PBool

(#>) :: forall (s :: S). Term s (PValue 'Sorted 'NonZero) -> Term s (PValue 'Sorted 'NonZero) -> Term s PBool

PPartialOrd (PValue 'Sorted 'Positive) Source #

Partial ordering implementation for sorted PValue with Positive amounts.

Use pcheckBinRel if AmountGuarantees is NoGuarantees.

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

(#<=) :: forall (s :: S). Term s (PValue 'Sorted 'Positive) -> Term s (PValue 'Sorted 'Positive) -> Term s PBool

(#<) :: forall (s :: S). Term s (PValue 'Sorted 'Positive) -> Term s (PValue 'Sorted 'Positive) -> Term s PBool

(#>=) :: forall (s :: S). Term s (PValue 'Sorted 'Positive) -> Term s (PValue 'Sorted 'Positive) -> Term s PBool

(#>) :: forall (s :: S). Term s (PValue 'Sorted 'Positive) -> Term s (PValue 'Sorted 'Positive) -> Term s PBool

DerivePlutusType (PValue keys amounts) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type DPTStrat (PValue keys amounts)

PlutusType (PValue keys amounts) Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type PInner (PValue keys amounts) :: PType

type PCovariant' (PValue keys amounts)

type PContravariant' (PValue keys amounts)

type PVariant' (PValue keys amounts)

Methods

pcon' :: forall (s :: S). PValue keys amounts s -> Term s (PInner (PValue keys amounts))

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PValue keys amounts)) -> (PValue keys amounts s -> Term s b) -> Term s b

PShow (PValue keys amounts) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

pshow' :: forall (s :: S). Bool -> Term s (PValue keys amounts) -> Term s PString

Semigroup (Term s (PValue 'Sorted 'NoGuarantees)) => Group (Term s (PValue 'Sorted 'NoGuarantees)) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

inv :: Term s (PValue 'Sorted 'NoGuarantees) -> Term s (PValue 'Sorted 'NoGuarantees)

Semigroup (Term s (PValue 'Sorted 'NonZero)) => Group (Term s (PValue 'Sorted 'NonZero)) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

inv :: Term s (PValue 'Sorted 'NonZero) -> Term s (PValue 'Sorted 'NonZero)

Semigroup (Term s (PValue 'Sorted normalization)) => Monoid (Term s (PValue 'Sorted normalization)) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

mempty :: Term s (PValue 'Sorted normalization)

Semigroup (Term s (PValue 'Sorted 'NoGuarantees)) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

(<>) :: Term s (PValue 'Sorted 'NoGuarantees) -> Term s (PValue 'Sorted 'NoGuarantees) -> Term s (PValue 'Sorted 'NoGuarantees)

Semigroup (Term s (PValue 'Sorted 'NonZero)) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

(<>) :: Term s (PValue 'Sorted 'NonZero) -> Term s (PValue 'Sorted 'NonZero) -> Term s (PValue 'Sorted 'NonZero)

Semigroup (Term s (PValue 'Sorted 'Positive)) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

(<>) :: Term s (PValue 'Sorted 'Positive) -> Term s (PValue 'Sorted 'Positive) -> Term s (PValue 'Sorted 'Positive)

Generic (PValue keys amounts s) Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type Rep (PValue keys amounts s) :: Type -> Type Source #

Methods

from :: PValue keys amounts s -> Rep (PValue keys amounts s) x Source #

to :: Rep (PValue keys amounts s) x -> PValue keys amounts s Source #

type PTryFromExcess PData (PAsData (PValue 'Sorted 'NoGuarantees)) Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type PTryFromExcess PData (PAsData (PValue 'Sorted 'NoGuarantees)) = PTryFromExcess PData (PInner (PAsData (PValue 'Sorted 'NoGuarantees)))
type PTryFromExcess PData (PAsData (PValue 'Sorted 'NonZero)) Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type PTryFromExcess PData (PAsData (PValue 'Sorted 'NonZero)) = Mret (PValue 'Sorted 'NonZero)
type PTryFromExcess PData (PAsData (PValue 'Sorted 'Positive)) Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type PTryFromExcess PData (PAsData (PValue 'Sorted 'Positive)) = Mret (PValue 'Sorted 'Positive)
type PTryFromExcess PData (PAsData (PValue 'Unsorted 'NoGuarantees)) Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type PTryFromExcess PData (PAsData (PValue 'Unsorted 'NoGuarantees)) = PTryFromExcess PData (PInner (PAsData (PValue 'Unsorted 'NoGuarantees)))
type PTryFromExcess PData (PAsData (PValue 'Unsorted 'NonZero)) Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type PTryFromExcess PData (PAsData (PValue 'Unsorted 'NonZero)) = Mret (PValue 'Unsorted 'NonZero)
type PTryFromExcess PData (PAsData (PValue 'Unsorted 'Positive)) Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type PTryFromExcess PData (PAsData (PValue 'Unsorted 'Positive)) = Mret (PValue 'Unsorted 'Positive)
type AsHaskell (PValue 'Unsorted 'NoGuarantees) Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.Value

type AsHaskell (PValue 'Unsorted 'NoGuarantees) = AsHaskell (DeriveNewtypePLiftable (PValue 'Unsorted 'NoGuarantees) (PMap 'Unsorted PCurrencySymbol (PMap 'Unsorted PTokenName PInteger)) Value)
type PlutusRepr (PValue 'Unsorted 'NoGuarantees) Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type PlutusRepr (PValue 'Unsorted 'NoGuarantees) = PlutusRepr (DeriveNewtypePLiftable (PValue 'Unsorted 'NoGuarantees) (PMap 'Unsorted PCurrencySymbol (PMap 'Unsorted PTokenName PInteger)) Value)
type DPTStrat (PValue keys amounts) Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type DPTStrat (PValue keys amounts) = PlutusTypeNewtype
type PContravariant' (PValue keys amounts) Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type PContravariant' (PValue keys amounts) = All2 PContravariant'' (PCode (PValue keys amounts))
type PCovariant' (PValue keys amounts) Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type PCovariant' (PValue keys amounts) = All2 PCovariant'' (PCode (PValue keys amounts))
type PInner (PValue keys amounts) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

type PInner (PValue keys amounts) = DerivedPInner (DPTStrat (PValue keys amounts)) (PValue keys amounts)
type PVariant' (PValue keys amounts) Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type PVariant' (PValue keys amounts) = All2 PVariant'' (PCode (PValue keys amounts))
type Rep (PValue keys amounts s) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

type Rep (PValue keys amounts s) = D1 ('MetaData "PValue" "Plutarch.LedgerApi.Value" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PMap keys PCurrencySymbol (PMap keys PTokenName PInteger))))))

data AmountGuarantees Source #

Since: 2.0.0

Constructors

NoGuarantees 
NonZero 
Positive 

newtype PLovelace (s :: S) Source #

Since: 2.2.0

Constructors

PLovelace (Term s (PDataNewtype PInteger)) 

Instances

Instances details
PIsData PLovelace Source #

Since: 2.2.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PLovelace) -> Term s PLovelace

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

PEq PLovelace Source #

Since: 2.2.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

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

PLiftable PLovelace Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type AsHaskell PLovelace

type PlutusRepr PLovelace

Methods

toPlutarchRepr :: AsHaskell PLovelace -> PlutusRepr PLovelace

toPlutarch :: forall (s :: S). AsHaskell PLovelace -> PLifted s PLovelace

fromPlutarchRepr :: PlutusRepr PLovelace -> Maybe (AsHaskell PLovelace)

fromPlutarch :: (forall (s :: S). PLifted s PLovelace) -> Either LiftError (AsHaskell PLovelace)

PPartialOrd PLovelace Source #

Since: 2.2.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

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

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

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

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

DerivePlutusType PLovelace Source #

Since: 2.2.0

Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type DPTStrat PLovelace

PlutusType PLovelace Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type PInner PLovelace :: PType

type PCovariant' PLovelace

type PContravariant' PLovelace

type PVariant' PLovelace

Methods

pcon' :: forall (s :: S). PLovelace s -> Term s (PInner PLovelace)

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PLovelace) -> (PLovelace s -> Term s b) -> Term s b

PShow PLovelace Source #

Since: 2.2.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

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

PTryFrom PData PLovelace Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type PTryFromExcess PData PLovelace :: PType

Methods

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

PTryFrom PData (PAsData PLovelace) Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type PTryFromExcess PData (PAsData PLovelace) :: PType

Methods

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

Generic (PLovelace s) Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

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

Methods

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

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

type AsHaskell PLovelace Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.Value

type AsHaskell PLovelace = AsHaskell (DeriveDataPLiftable PLovelace Lovelace)
type PlutusRepr PLovelace Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type PlutusRepr PLovelace = PlutusRepr (DeriveDataPLiftable PLovelace Lovelace)
type DPTStrat PLovelace Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type DPTStrat PLovelace = PlutusTypeNewtype
type PContravariant' PLovelace Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type PContravariant' PLovelace = All2 PContravariant'' (PCode PLovelace)
type PCovariant' PLovelace Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type PCovariant' PLovelace = All2 PCovariant'' (PCode PLovelace)
type PInner PLovelace Source #

Since: 2.2.0

Instance details

Defined in Plutarch.LedgerApi.Value

type PInner PLovelace = DerivedPInner (DPTStrat PLovelace) PLovelace
type PVariant' PLovelace Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type PVariant' PLovelace = All2 PVariant'' (PCode PLovelace)
type PTryFromExcess PData PLovelace Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.Value

type PTryFromExcess PData PLovelace = PTryFromExcess PData (PInner PLovelace)
type PTryFromExcess PData (PAsData PLovelace) Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type PTryFromExcess PData (PAsData PLovelace) = PTryFromExcess PData (PInner (PAsData PLovelace))
type Rep (PLovelace s) Source #

Since: 2.2.0

Instance details

Defined in Plutarch.LedgerApi.Value

type Rep (PLovelace s) = D1 ('MetaData "PLovelace" "Plutarch.LedgerApi.Value" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PLovelace" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataNewtype PInteger)))))

newtype PTokenName (s :: S) Source #

Since: 2.0.0

Constructors

PTokenName (Term s (PDataNewtype PByteString)) 

Instances

Instances details
PIsData PTokenName Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PTokenName) -> Term s PTokenName

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

PEq PTokenName Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

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

PLiftable PTokenName Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type AsHaskell PTokenName

type PlutusRepr PTokenName

Methods

toPlutarchRepr :: AsHaskell PTokenName -> PlutusRepr PTokenName

toPlutarch :: forall (s :: S). AsHaskell PTokenName -> PLifted s PTokenName

fromPlutarchRepr :: PlutusRepr PTokenName -> Maybe (AsHaskell PTokenName)

fromPlutarch :: (forall (s :: S). PLifted s PTokenName) -> Either LiftError (AsHaskell PTokenName)

POrd PTokenName Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

pmax :: forall (s :: S). Term s PTokenName -> Term s PTokenName -> Term s PTokenName

pmin :: forall (s :: S). Term s PTokenName -> Term s PTokenName -> Term s PTokenName

PPartialOrd PTokenName Source #

@wsince 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

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

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

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

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

DerivePlutusType PTokenName Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type DPTStrat PTokenName

PlutusType PTokenName Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type PInner PTokenName :: PType

type PCovariant' PTokenName

type PContravariant' PTokenName

type PVariant' PTokenName

Methods

pcon' :: forall (s :: S). PTokenName s -> Term s (PInner PTokenName)

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PTokenName) -> (PTokenName s -> Term s b) -> Term s b

PShow PTokenName Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

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

PTryFrom PData PTokenName Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type PTryFromExcess PData PTokenName :: PType

Methods

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

PTryFrom PData (PAsData PTokenName) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type PTryFromExcess PData (PAsData PTokenName) :: PType

Methods

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

Generic (PTokenName s) Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

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

Methods

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

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

type AsHaskell PTokenName Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.Value

type AsHaskell PTokenName = AsHaskell (DeriveDataPLiftable PTokenName TokenName)
type PlutusRepr PTokenName Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type PlutusRepr PTokenName = PlutusRepr (DeriveDataPLiftable PTokenName TokenName)
type DPTStrat PTokenName Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type DPTStrat PTokenName = PlutusTypeNewtype
type PContravariant' PTokenName Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type PContravariant' PTokenName = All2 PContravariant'' (PCode PTokenName)
type PCovariant' PTokenName Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type PCovariant' PTokenName = All2 PCovariant'' (PCode PTokenName)
type PInner PTokenName Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

type PInner PTokenName = DerivedPInner (DPTStrat PTokenName) PTokenName
type PVariant' PTokenName Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

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

Defined in Plutarch.LedgerApi.Value

type PTryFromExcess PData PTokenName = Mret PTokenName
type PTryFromExcess PData (PAsData PTokenName) Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type PTryFromExcess PData (PAsData PTokenName) = Mret PTokenName
type Rep (PTokenName s) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

type Rep (PTokenName s) = D1 ('MetaData "PTokenName" "Plutarch.LedgerApi.Value" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PTokenName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataNewtype PByteString)))))

newtype PCurrencySymbol (s :: S) Source #

Since: 2.0.0

Constructors

PCurrencySymbol (Term s (PDataNewtype PByteString)) 

Instances

Instances details
PIsData PCurrencySymbol Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PCurrencySymbol) -> Term s PCurrencySymbol

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

PEq PCurrencySymbol Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

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

PLiftable PCurrencySymbol Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type AsHaskell PCurrencySymbol

type PlutusRepr PCurrencySymbol

Methods

toPlutarchRepr :: AsHaskell PCurrencySymbol -> PlutusRepr PCurrencySymbol

toPlutarch :: forall (s :: S). AsHaskell PCurrencySymbol -> PLifted s PCurrencySymbol

fromPlutarchRepr :: PlutusRepr PCurrencySymbol -> Maybe (AsHaskell PCurrencySymbol)

fromPlutarch :: (forall (s :: S). PLifted s PCurrencySymbol) -> Either LiftError (AsHaskell PCurrencySymbol)

POrd PCurrencySymbol Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

pmax :: forall (s :: S). Term s PCurrencySymbol -> Term s PCurrencySymbol -> Term s PCurrencySymbol

pmin :: forall (s :: S). Term s PCurrencySymbol -> Term s PCurrencySymbol -> Term s PCurrencySymbol

PPartialOrd PCurrencySymbol Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

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

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

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

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

DerivePlutusType PCurrencySymbol Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type DPTStrat PCurrencySymbol

PlutusType PCurrencySymbol Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type PInner PCurrencySymbol :: PType

type PCovariant' PCurrencySymbol

type PContravariant' PCurrencySymbol

type PVariant' PCurrencySymbol

Methods

pcon' :: forall (s :: S). PCurrencySymbol s -> Term s (PInner PCurrencySymbol)

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PCurrencySymbol) -> (PCurrencySymbol s -> Term s b) -> Term s b

PShow PCurrencySymbol Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Methods

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

PTryFrom PData PCurrencySymbol Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type PTryFromExcess PData PCurrencySymbol :: PType

Methods

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

PTryFrom PData (PAsData PCurrencySymbol) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

type PTryFromExcess PData (PAsData PCurrencySymbol) :: PType

Methods

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

Generic (PCurrencySymbol s) Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

Associated Types

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

type AsHaskell PCurrencySymbol Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.Value

type AsHaskell PCurrencySymbol = AsHaskell (DeriveDataPLiftable PCurrencySymbol CurrencySymbol)
type PlutusRepr PCurrencySymbol Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type PlutusRepr PCurrencySymbol = PlutusRepr (DeriveDataPLiftable PCurrencySymbol CurrencySymbol)
type DPTStrat PCurrencySymbol Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type DPTStrat PCurrencySymbol = PlutusTypeNewtype
type PContravariant' PCurrencySymbol Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type PContravariant' PCurrencySymbol = All2 PContravariant'' (PCode PCurrencySymbol)
type PCovariant' PCurrencySymbol Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type PCovariant' PCurrencySymbol = All2 PCovariant'' (PCode PCurrencySymbol)
type PInner PCurrencySymbol Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

type PInner PCurrencySymbol = DerivedPInner (DPTStrat PCurrencySymbol) PCurrencySymbol
type PVariant' PCurrencySymbol Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

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

Defined in Plutarch.LedgerApi.Value

type PTryFromExcess PData PCurrencySymbol = Mret PCurrencySymbol
type PTryFromExcess PData (PAsData PCurrencySymbol) Source # 
Instance details

Defined in Plutarch.LedgerApi.Value

type PTryFromExcess PData (PAsData PCurrencySymbol) = Mret PCurrencySymbol
type Rep (PCurrencySymbol s) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Value

type Rep (PCurrencySymbol s) = D1 ('MetaData "PCurrencySymbol" "Plutarch.LedgerApi.Value" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PCurrencySymbol" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataNewtype PByteString)))))

Time

newtype PPosixTime (s :: S) Source #

Since: 2.0.0

Constructors

PPosixTime (Term s (PDataNewtype PInteger)) 

Instances

Instances details
PIsData PPosixTime Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Time

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PPosixTime) -> Term s PPosixTime

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

PCountable PPosixTime Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.V1.Time

Methods

psuccessor :: forall (s :: S). Term s (PPosixTime :--> PPosixTime)

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

PEnumerable PPosixTime Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.V1.Time

Methods

ppredecessor :: forall (s :: S). Term s (PPosixTime :--> PPosixTime)

ppredecessorN :: forall (s :: S). Term s (PPositive :--> (PPosixTime :--> PPosixTime))

PIntegral PPosixTime Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Time

Methods

pdiv :: forall (s :: S). Term s (PPosixTime :--> (PPosixTime :--> PPosixTime))

pmod :: forall (s :: S). Term s (PPosixTime :--> (PPosixTime :--> PPosixTime))

pquot :: forall (s :: S). Term s (PPosixTime :--> (PPosixTime :--> PPosixTime))

prem :: forall (s :: S). Term s (PPosixTime :--> (PPosixTime :--> PPosixTime))

PEq PPosixTime Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Time

Methods

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

PLiftable PPosixTime Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Time

Associated Types

type AsHaskell PPosixTime

type PlutusRepr PPosixTime

Methods

toPlutarchRepr :: AsHaskell PPosixTime -> PlutusRepr PPosixTime

toPlutarch :: forall (s :: S). AsHaskell PPosixTime -> PLifted s PPosixTime

fromPlutarchRepr :: PlutusRepr PPosixTime -> Maybe (AsHaskell PPosixTime)

fromPlutarch :: (forall (s :: S). PLifted s PPosixTime) -> Either LiftError (AsHaskell PPosixTime)

POrd PPosixTime Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Time

Methods

pmax :: forall (s :: S). Term s PPosixTime -> Term s PPosixTime -> Term s PPosixTime

pmin :: forall (s :: S). Term s PPosixTime -> Term s PPosixTime -> Term s PPosixTime

PPartialOrd PPosixTime Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Time

Methods

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

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

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

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

DerivePlutusType PPosixTime Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Time

Associated Types

type DPTStrat PPosixTime

PlutusType PPosixTime Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Time

Associated Types

type PInner PPosixTime :: PType

type PCovariant' PPosixTime

type PContravariant' PPosixTime

type PVariant' PPosixTime

Methods

pcon' :: forall (s :: S). PPosixTime s -> Term s (PInner PPosixTime)

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PPosixTime) -> (PPosixTime s -> Term s b) -> Term s b

PNum PPosixTime Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Time

Methods

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

(#-) :: forall (s :: S). Term s PPosixTime -> Term s PPosixTime -> Term s PPosixTime

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

pnegate :: forall (s :: S). Term s (PPosixTime :--> PPosixTime)

pabs :: forall (s :: S). Term s (PPosixTime :--> PPosixTime)

psignum :: forall (s :: S). Term s (PPosixTime :--> PPosixTime)

pfromInteger :: forall (s :: S). Integer -> Term s PPosixTime

PShow PPosixTime Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Time

Methods

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

PTryFrom PData PPosixTime Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.Time

Associated Types

type PTryFromExcess PData PPosixTime :: PType

Methods

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

PTryFrom PData (PAsData PPosixTime) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Time

Associated Types

type PTryFromExcess PData (PAsData PPosixTime) :: PType

Methods

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

Generic (PPosixTime s) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Time

Associated Types

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

Methods

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

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

type AsHaskell PPosixTime Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.V1.Time

type AsHaskell PPosixTime = AsHaskell (DeriveDataPLiftable PPosixTime POSIXTime)
type PlutusRepr PPosixTime Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Time

type PlutusRepr PPosixTime = PlutusRepr (DeriveDataPLiftable PPosixTime POSIXTime)
type DPTStrat PPosixTime Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Time

type DPTStrat PPosixTime = PlutusTypeNewtype
type PContravariant' PPosixTime Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Time

type PContravariant' PPosixTime = All2 PContravariant'' (PCode PPosixTime)
type PCovariant' PPosixTime Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Time

type PCovariant' PPosixTime = All2 PCovariant'' (PCode PPosixTime)
type PInner PPosixTime Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Time

type PInner PPosixTime = DerivedPInner (DPTStrat PPosixTime) PPosixTime
type PVariant' PPosixTime Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Time

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

Defined in Plutarch.LedgerApi.V1.Time

type PTryFromExcess PData PPosixTime = Mret PPosixTime
type PTryFromExcess PData (PAsData PPosixTime) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Time

type PTryFromExcess PData (PAsData PPosixTime) = Mret PPosixTime
type Rep (PPosixTime s) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Time

type Rep (PPosixTime s) = D1 ('MetaData "PPosixTime" "Plutarch.LedgerApi.V1.Time" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PPosixTime" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataNewtype PInteger)))))

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

Construct a PPosixTime from a PInteger. Same as using the constructor, but a lot shorter.

@since WIP

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

Unwrap a PPosixTime to get a PInteger. Same as using pmatch, but a lot shorter. Also unwraps the Data encoding.

@since WIP

Intervals

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

Since: 2.0.0

Constructors

PNegInf (Term s (PDataRecord '[])) 
PFinite (Term s (PDataRecord '["_0" ':= a])) 
PPosInf (Term s (PDataRecord '[])) 

Instances

Instances details
PTryFrom PData a => PTryFrom PData (PAsData (PExtended a)) Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Associated Types

type PTryFromExcess PData (PAsData (PExtended a)) :: PType

Methods

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

PTryFrom PData a => PTryFrom PData (PExtended a) Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Associated Types

type PTryFromExcess PData (PExtended a) :: PType

Methods

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

PIsData (PExtended a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData (PExtended a)) -> Term s (PExtended a)

pdataImpl :: forall (s :: S). Term s (PExtended a) -> Term s PData

PEq (PExtended a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Methods

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

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

Defined in Plutarch.LedgerApi.Interval

Associated Types

type AsHaskell (PExtended a)

type PlutusRepr (PExtended a)

Methods

toPlutarchRepr :: AsHaskell (PExtended a) -> PlutusRepr (PExtended a)

toPlutarch :: forall (s :: S). AsHaskell (PExtended a) -> PLifted s (PExtended a)

fromPlutarchRepr :: PlutusRepr (PExtended a) -> Maybe (AsHaskell (PExtended a))

fromPlutarch :: (forall (s :: S). PLifted s (PExtended a)) -> Either LiftError (AsHaskell (PExtended a))

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

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Methods

pmax :: forall (s :: S). Term s (PExtended a) -> Term s (PExtended a) -> Term s (PExtended a)

pmin :: forall (s :: S). Term s (PExtended a) -> Term s (PExtended a) -> Term s (PExtended a)

(POrd a, PIsData a) => PPartialOrd (PExtended a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Methods

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

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

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

(#>) :: forall (s :: S). Term s (PExtended a) -> Term s (PExtended a) -> Term s PBool

DerivePlutusType (PExtended a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Associated Types

type DPTStrat (PExtended a)

PlutusType (PExtended a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

Associated Types

type PInner (PExtended a) :: PType

type PCovariant' (PExtended a)

type PContravariant' (PExtended a)

type PVariant' (PExtended a)

Methods

pcon' :: forall (s :: S). PExtended a s -> Term s (PInner (PExtended a))

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

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

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Methods

pshow' :: forall (s :: S). Bool -> Term s (PExtended a) -> Term s PString

Generic (PExtended a s) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

Associated Types

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

Methods

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

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

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

Defined in Plutarch.LedgerApi.Interval

type PTryFromExcess PData (PAsData (PExtended a)) = PTryFromExcess PData (PInner (PAsData (PExtended a)))
type PTryFromExcess PData (PExtended a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

type PTryFromExcess PData (PExtended a) = PTryFromExcess PData (PInner (PExtended a))
type AsHaskell (PExtended a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

type AsHaskell (PExtended a) = AsHaskell (DeriveDataPLiftable (PExtended a) (Extended (AsHaskell a)))
type PlutusRepr (PExtended a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

type PlutusRepr (PExtended a) = PlutusRepr (DeriveDataPLiftable (PExtended a) (Extended (AsHaskell a)))
type DPTStrat (PExtended a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

type DPTStrat (PExtended a) = PlutusTypeData
type PContravariant' (PExtended a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

type PContravariant' (PExtended a) = All2 PContravariant'' (PCode (PExtended a))
type PCovariant' (PExtended a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

type PCovariant' (PExtended a) = All2 PCovariant'' (PCode (PExtended a))
type PInner (PExtended a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

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

Defined in Plutarch.LedgerApi.Interval

type PVariant' (PExtended a) = All2 PVariant'' (PCode (PExtended a))
type Rep (PExtended a s) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

type Rep (PExtended a s) = D1 ('MetaData "PExtended" "Plutarch.LedgerApi.Interval" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'False) (C1 ('MetaCons "PNegInf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord ('[] :: [PLabeledType]))))) :+: (C1 ('MetaCons "PFinite" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["_0" ':= a])))) :+: C1 ('MetaCons "PPosInf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord ('[] :: [PLabeledType])))))))

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

Since: 2.0.0

Constructors

PLowerBound (Term s (PDataRecord '["_0" ':= PExtended a, "_1" ':= PBool])) 

Instances

Instances details
PTryFrom PData a => PTryFrom PData (PAsData (PLowerBound a)) Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Associated Types

type PTryFromExcess PData (PAsData (PLowerBound a)) :: PType

Methods

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

PTryFrom PData a => PTryFrom PData (PLowerBound a) Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Associated Types

type PTryFromExcess PData (PLowerBound a) :: PType

Methods

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

PIsData (PLowerBound a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData (PLowerBound a)) -> Term s (PLowerBound a)

pdataImpl :: forall (s :: S). Term s (PLowerBound a) -> Term s PData

PDataFields (PLowerBound a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

Associated Types

type PFields (PLowerBound a) :: [PLabeledType]

Methods

ptoFields :: forall (s :: S). Term s (PLowerBound a) -> Term s (PDataRecord (PFields (PLowerBound a)))

(PIsData a, PCountable a) => PEq (PLowerBound a) Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.Interval

Methods

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

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

Defined in Plutarch.LedgerApi.Interval

Associated Types

type AsHaskell (PLowerBound a)

type PlutusRepr (PLowerBound a)

Methods

toPlutarchRepr :: AsHaskell (PLowerBound a) -> PlutusRepr (PLowerBound a)

toPlutarch :: forall (s :: S). AsHaskell (PLowerBound a) -> PLifted s (PLowerBound a)

fromPlutarchRepr :: PlutusRepr (PLowerBound a) -> Maybe (AsHaskell (PLowerBound a))

fromPlutarch :: (forall (s :: S). PLifted s (PLowerBound a)) -> Either LiftError (AsHaskell (PLowerBound a))

(PIsData a, PCountable a) => POrd (PLowerBound a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Methods

pmax :: forall (s :: S). Term s (PLowerBound a) -> Term s (PLowerBound a) -> Term s (PLowerBound a)

pmin :: forall (s :: S). Term s (PLowerBound a) -> Term s (PLowerBound a) -> Term s (PLowerBound a)

(PIsData a, PCountable a) => PPartialOrd (PLowerBound a) Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.Interval

Methods

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

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

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

(#>) :: forall (s :: S). Term s (PLowerBound a) -> Term s (PLowerBound a) -> Term s PBool

DerivePlutusType (PLowerBound a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Associated Types

type DPTStrat (PLowerBound a)

PlutusType (PLowerBound a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

Associated Types

type PInner (PLowerBound a) :: PType

type PCovariant' (PLowerBound a)

type PContravariant' (PLowerBound a)

type PVariant' (PLowerBound a)

Methods

pcon' :: forall (s :: S). PLowerBound a s -> Term s (PInner (PLowerBound a))

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

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

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Methods

pshow' :: forall (s :: S). Bool -> Term s (PLowerBound a) -> Term s PString

Generic (PLowerBound a s) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

Associated Types

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

Methods

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

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

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

Defined in Plutarch.LedgerApi.Interval

type PTryFromExcess PData (PAsData (PLowerBound a)) = PTryFromExcess PData (PInner (PAsData (PLowerBound a)))
type PTryFromExcess PData (PLowerBound a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

type PTryFromExcess PData (PLowerBound a) = PTryFromExcess PData (PInner (PLowerBound a))
type PFields (PLowerBound a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

type PFields (PLowerBound a) = Helper (PInner (PLowerBound a))
type AsHaskell (PLowerBound a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

type AsHaskell (PLowerBound a) = AsHaskell (DeriveDataPLiftable (PLowerBound a) (LowerBound (AsHaskell a)))
type PlutusRepr (PLowerBound a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

type PlutusRepr (PLowerBound a) = PlutusRepr (DeriveDataPLiftable (PLowerBound a) (LowerBound (AsHaskell a)))
type DPTStrat (PLowerBound a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

type DPTStrat (PLowerBound a) = PlutusTypeData
type PContravariant' (PLowerBound a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

type PContravariant' (PLowerBound a) = All2 PContravariant'' (PCode (PLowerBound a))
type PCovariant' (PLowerBound a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

type PCovariant' (PLowerBound a) = All2 PCovariant'' (PCode (PLowerBound a))
type PInner (PLowerBound a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

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

Defined in Plutarch.LedgerApi.Interval

type PVariant' (PLowerBound a) = All2 PVariant'' (PCode (PLowerBound a))
type Rep (PLowerBound a s) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

type Rep (PLowerBound a s) = D1 ('MetaData "PLowerBound" "Plutarch.LedgerApi.Interval" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PLowerBound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["_0" ':= PExtended a, "_1" ':= PBool])))))

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

Since: 2.0.0

Constructors

PUpperBound (Term s (PDataRecord '["_0" ':= PExtended a, "_1" ':= PBool])) 

Instances

Instances details
PTryFrom PData a => PTryFrom PData (PAsData (PUpperBound a)) Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Associated Types

type PTryFromExcess PData (PAsData (PUpperBound a)) :: PType

Methods

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

PTryFrom PData a => PTryFrom PData (PUpperBound a) Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Associated Types

type PTryFromExcess PData (PUpperBound a) :: PType

Methods

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

PIsData (PUpperBound a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData (PUpperBound a)) -> Term s (PUpperBound a)

pdataImpl :: forall (s :: S). Term s (PUpperBound a) -> Term s PData

PDataFields (PUpperBound a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

Associated Types

type PFields (PUpperBound a) :: [PLabeledType]

Methods

ptoFields :: forall (s :: S). Term s (PUpperBound a) -> Term s (PDataRecord (PFields (PUpperBound a)))

(PIsData a, PEnumerable a) => PEq (PUpperBound a) Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.Interval

Methods

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

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

Defined in Plutarch.LedgerApi.Interval

Associated Types

type AsHaskell (PUpperBound a)

type PlutusRepr (PUpperBound a)

Methods

toPlutarchRepr :: AsHaskell (PUpperBound a) -> PlutusRepr (PUpperBound a)

toPlutarch :: forall (s :: S). AsHaskell (PUpperBound a) -> PLifted s (PUpperBound a)

fromPlutarchRepr :: PlutusRepr (PUpperBound a) -> Maybe (AsHaskell (PUpperBound a))

fromPlutarch :: (forall (s :: S). PLifted s (PUpperBound a)) -> Either LiftError (AsHaskell (PUpperBound a))

(PIsData a, PEnumerable a) => POrd (PUpperBound a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Methods

pmax :: forall (s :: S). Term s (PUpperBound a) -> Term s (PUpperBound a) -> Term s (PUpperBound a)

pmin :: forall (s :: S). Term s (PUpperBound a) -> Term s (PUpperBound a) -> Term s (PUpperBound a)

(PIsData a, PEnumerable a) => PPartialOrd (PUpperBound a) Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.Interval

Methods

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

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

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

(#>) :: forall (s :: S). Term s (PUpperBound a) -> Term s (PUpperBound a) -> Term s PBool

DerivePlutusType (PUpperBound a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Associated Types

type DPTStrat (PUpperBound a)

PlutusType (PUpperBound a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

Associated Types

type PInner (PUpperBound a) :: PType

type PCovariant' (PUpperBound a)

type PContravariant' (PUpperBound a)

type PVariant' (PUpperBound a)

Methods

pcon' :: forall (s :: S). PUpperBound a s -> Term s (PInner (PUpperBound a))

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

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

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Methods

pshow' :: forall (s :: S). Bool -> Term s (PUpperBound a) -> Term s PString

Generic (PUpperBound a s) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

Associated Types

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

Methods

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

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

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

Defined in Plutarch.LedgerApi.Interval

type PTryFromExcess PData (PAsData (PUpperBound a)) = PTryFromExcess PData (PInner (PAsData (PUpperBound a)))
type PTryFromExcess PData (PUpperBound a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

type PTryFromExcess PData (PUpperBound a) = PTryFromExcess PData (PInner (PUpperBound a))
type PFields (PUpperBound a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

type PFields (PUpperBound a) = Helper (PInner (PUpperBound a))
type AsHaskell (PUpperBound a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

type AsHaskell (PUpperBound a) = AsHaskell (DeriveDataPLiftable (PUpperBound a) (UpperBound (AsHaskell a)))
type PlutusRepr (PUpperBound a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

type PlutusRepr (PUpperBound a) = PlutusRepr (DeriveDataPLiftable (PUpperBound a) (UpperBound (AsHaskell a)))
type DPTStrat (PUpperBound a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

type DPTStrat (PUpperBound a) = PlutusTypeData
type PContravariant' (PUpperBound a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

type PContravariant' (PUpperBound a) = All2 PContravariant'' (PCode (PUpperBound a))
type PCovariant' (PUpperBound a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

type PCovariant' (PUpperBound a) = All2 PCovariant'' (PCode (PUpperBound a))
type PInner (PUpperBound a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

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

Defined in Plutarch.LedgerApi.Interval

type PVariant' (PUpperBound a) = All2 PVariant'' (PCode (PUpperBound a))
type Rep (PUpperBound a s) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

type Rep (PUpperBound a s) = D1 ('MetaData "PUpperBound" "Plutarch.LedgerApi.Interval" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PUpperBound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["_0" ':= PExtended a, "_1" ':= PBool])))))

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

Since: 2.0.0

Constructors

PInterval (Term s (PDataRecord '["from" ':= PLowerBound a, "to" ':= PUpperBound a])) 

Instances

Instances details
PTryFrom PData a => PTryFrom PData (PAsData (PInterval a)) Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Associated Types

type PTryFromExcess PData (PAsData (PInterval a)) :: PType

Methods

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

PTryFrom PData a => PTryFrom PData (PInterval a) Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Associated Types

type PTryFromExcess PData (PInterval a) :: PType

Methods

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

PIsData (PInterval a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData (PInterval a)) -> Term s (PInterval a)

pdataImpl :: forall (s :: S). Term s (PInterval a) -> Term s PData

PDataFields (PInterval a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

Associated Types

type PFields (PInterval a) :: [PLabeledType]

Methods

ptoFields :: forall (s :: S). Term s (PInterval a) -> Term s (PDataRecord (PFields (PInterval a)))

PEq (PInterval a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Methods

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

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

Defined in Plutarch.LedgerApi.Interval

Associated Types

type AsHaskell (PInterval a)

type PlutusRepr (PInterval a)

Methods

toPlutarchRepr :: AsHaskell (PInterval a) -> PlutusRepr (PInterval a)

toPlutarch :: forall (s :: S). AsHaskell (PInterval a) -> PLifted s (PInterval a)

fromPlutarchRepr :: PlutusRepr (PInterval a) -> Maybe (AsHaskell (PInterval a))

fromPlutarch :: (forall (s :: S). PLifted s (PInterval a)) -> Either LiftError (AsHaskell (PInterval a))

(PIsData a, PEnumerable a) => POrd (PInterval a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Methods

pmax :: forall (s :: S). Term s (PInterval a) -> Term s (PInterval a) -> Term s (PInterval a)

pmin :: forall (s :: S). Term s (PInterval a) -> Term s (PInterval a) -> Term s (PInterval a)

(PIsData a, PEnumerable a) => PPartialOrd (PInterval a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Methods

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

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

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

(#>) :: forall (s :: S). Term s (PInterval a) -> Term s (PInterval a) -> Term s PBool

DerivePlutusType (PInterval a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Associated Types

type DPTStrat (PInterval a)

PlutusType (PInterval a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

Associated Types

type PInner (PInterval a) :: PType

type PCovariant' (PInterval a)

type PContravariant' (PInterval a)

type PVariant' (PInterval a)

Methods

pcon' :: forall (s :: S). PInterval a s -> Term s (PInner (PInterval a))

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

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

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

Methods

pshow' :: forall (s :: S). Bool -> Term s (PInterval a) -> Term s PString

Generic (PInterval a s) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

Associated Types

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

Methods

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

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

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

Defined in Plutarch.LedgerApi.Interval

type PTryFromExcess PData (PAsData (PInterval a)) = PTryFromExcess PData (PInner (PAsData (PInterval a)))
type PTryFromExcess PData (PInterval a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

type PTryFromExcess PData (PInterval a) = PTryFromExcess PData (PInner (PInterval a))
type PFields (PInterval a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

type PFields (PInterval a) = Helper (PInner (PInterval a))
type AsHaskell (PInterval a) Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.Interval

type AsHaskell (PInterval a) = AsHaskell (DeriveDataPLiftable (PInterval a) (Interval (AsHaskell a)))
type PlutusRepr (PInterval a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

type PlutusRepr (PInterval a) = PlutusRepr (DeriveDataPLiftable (PInterval a) (Interval (AsHaskell a)))
type DPTStrat (PInterval a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

type DPTStrat (PInterval a) = PlutusTypeData
type PContravariant' (PInterval a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

type PContravariant' (PInterval a) = All2 PContravariant'' (PCode (PInterval a))
type PCovariant' (PInterval a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Interval

type PCovariant' (PInterval a) = All2 PCovariant'' (PCode (PInterval a))
type PInner (PInterval a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

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

Defined in Plutarch.LedgerApi.Interval

type PVariant' (PInterval a) = All2 PVariant'' (PCode (PInterval a))
type Rep (PInterval a s) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Interval

type Rep (PInterval a s) = D1 ('MetaData "PInterval" "Plutarch.LedgerApi.Interval" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PInterval" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["from" ':= PLowerBound a, "to" ':= PUpperBound a])))))

Script stuff

newtype PDatum (s :: S) Source #

Since: 2.0.0

Constructors

PDatum (Term s PData) 

Instances

Instances details
PIsData PDatum Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PDatum) -> Term s PDatum

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

PEq PDatum Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Methods

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

PLiftable PDatum Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type AsHaskell PDatum

type PlutusRepr PDatum

Methods

toPlutarchRepr :: AsHaskell PDatum -> PlutusRepr PDatum

toPlutarch :: forall (s :: S). AsHaskell PDatum -> PLifted s PDatum

fromPlutarchRepr :: PlutusRepr PDatum -> Maybe (AsHaskell PDatum)

fromPlutarch :: (forall (s :: S). PLifted s PDatum) -> Either LiftError (AsHaskell PDatum)

DerivePlutusType PDatum Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type DPTStrat PDatum

PlutusType PDatum Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type PInner PDatum :: PType

type PCovariant' PDatum

type PContravariant' PDatum

type PVariant' PDatum

Methods

pcon' :: forall (s :: S). PDatum s -> Term s (PInner PDatum)

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PDatum) -> (PDatum s -> Term s b) -> Term s b

PShow PDatum Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Methods

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

PTryFrom PData PDatum Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type PTryFromExcess PData PDatum :: PType

Methods

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

PTryFrom PData (PAsData PDatum) Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type PTryFromExcess PData (PAsData PDatum) :: PType

Methods

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

Generic (PDatum s) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

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

Methods

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

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

type AsHaskell PDatum Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type AsHaskell PDatum = AsHaskell (DeriveDataPLiftable PDatum Datum)
type PlutusRepr PDatum Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PlutusRepr PDatum = PlutusRepr (DeriveDataPLiftable PDatum Datum)
type DPTStrat PDatum Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type DPTStrat PDatum = PlutusTypeNewtype
type PContravariant' PDatum Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PContravariant' PDatum = All2 PContravariant'' (PCode PDatum)
type PCovariant' PDatum Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PCovariant' PDatum = All2 PCovariant'' (PCode PDatum)
type PInner PDatum Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PInner PDatum = DerivedPInner (DPTStrat PDatum) PDatum
type PVariant' PDatum Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PVariant' PDatum = All2 PVariant'' (PCode PDatum)
type PTryFromExcess PData PDatum Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PTryFromExcess PData PDatum = PTryFromExcess PData (PInner PDatum)
type PTryFromExcess PData (PAsData PDatum) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PTryFromExcess PData (PAsData PDatum) = PTryFromExcess PData (PInner (PAsData PDatum))
type Rep (PDatum s) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type Rep (PDatum s) = D1 ('MetaData "PDatum" "Plutarch.LedgerApi.V1.Scripts" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PDatum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s PData))))

newtype PRedeemer (s :: S) Source #

Since: 2.0.0

Constructors

PRedeemer (Term s PData) 

Instances

Instances details
PIsData PRedeemer Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PRedeemer) -> Term s PRedeemer

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

PEq PRedeemer Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Methods

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

PLiftable PRedeemer Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type AsHaskell PRedeemer

type PlutusRepr PRedeemer

Methods

toPlutarchRepr :: AsHaskell PRedeemer -> PlutusRepr PRedeemer

toPlutarch :: forall (s :: S). AsHaskell PRedeemer -> PLifted s PRedeemer

fromPlutarchRepr :: PlutusRepr PRedeemer -> Maybe (AsHaskell PRedeemer)

fromPlutarch :: (forall (s :: S). PLifted s PRedeemer) -> Either LiftError (AsHaskell PRedeemer)

DerivePlutusType PRedeemer Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type DPTStrat PRedeemer

PlutusType PRedeemer Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type PInner PRedeemer :: PType

type PCovariant' PRedeemer

type PContravariant' PRedeemer

type PVariant' PRedeemer

Methods

pcon' :: forall (s :: S). PRedeemer s -> Term s (PInner PRedeemer)

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PRedeemer) -> (PRedeemer s -> Term s b) -> Term s b

PShow PRedeemer Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Methods

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

PTryFrom PData PRedeemer Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type PTryFromExcess PData PRedeemer :: PType

Methods

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

PTryFrom PData (PAsData PRedeemer) Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type PTryFromExcess PData (PAsData PRedeemer) :: PType

Methods

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

Generic (PRedeemer s) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

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

Methods

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

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

type AsHaskell PRedeemer Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type AsHaskell PRedeemer = AsHaskell (DeriveDataPLiftable PRedeemer Redeemer)
type PlutusRepr PRedeemer Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PlutusRepr PRedeemer = PlutusRepr (DeriveDataPLiftable PRedeemer Redeemer)
type DPTStrat PRedeemer Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type DPTStrat PRedeemer = PlutusTypeNewtype
type PContravariant' PRedeemer Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PContravariant' PRedeemer = All2 PContravariant'' (PCode PRedeemer)
type PCovariant' PRedeemer Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PCovariant' PRedeemer = All2 PCovariant'' (PCode PRedeemer)
type PInner PRedeemer Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PInner PRedeemer = DerivedPInner (DPTStrat PRedeemer) PRedeemer
type PVariant' PRedeemer Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PVariant' PRedeemer = All2 PVariant'' (PCode PRedeemer)
type PTryFromExcess PData PRedeemer Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PTryFromExcess PData PRedeemer = PTryFromExcess PData (PInner PRedeemer)
type PTryFromExcess PData (PAsData PRedeemer) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PTryFromExcess PData (PAsData PRedeemer) = PTryFromExcess PData (PInner (PAsData PRedeemer))
type Rep (PRedeemer s) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type Rep (PRedeemer s) = D1 ('MetaData "PRedeemer" "Plutarch.LedgerApi.V1.Scripts" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PRedeemer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s PData))))

newtype PDatumHash (s :: S) Source #

Since: 2.0.0

Constructors

PDatumHash (Term s (PDataNewtype PByteString)) 

Instances

Instances details
PIsData PDatumHash Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PDatumHash) -> Term s PDatumHash

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

PEq PDatumHash Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Methods

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

PLiftable PDatumHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type AsHaskell PDatumHash

type PlutusRepr PDatumHash

Methods

toPlutarchRepr :: AsHaskell PDatumHash -> PlutusRepr PDatumHash

toPlutarch :: forall (s :: S). AsHaskell PDatumHash -> PLifted s PDatumHash

fromPlutarchRepr :: PlutusRepr PDatumHash -> Maybe (AsHaskell PDatumHash)

fromPlutarch :: (forall (s :: S). PLifted s PDatumHash) -> Either LiftError (AsHaskell PDatumHash)

POrd PDatumHash Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Methods

pmax :: forall (s :: S). Term s PDatumHash -> Term s PDatumHash -> Term s PDatumHash

pmin :: forall (s :: S). Term s PDatumHash -> Term s PDatumHash -> Term s PDatumHash

PPartialOrd PDatumHash Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Methods

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

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

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

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

DerivePlutusType PDatumHash Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type DPTStrat PDatumHash

PlutusType PDatumHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type PInner PDatumHash :: PType

type PCovariant' PDatumHash

type PContravariant' PDatumHash

type PVariant' PDatumHash

Methods

pcon' :: forall (s :: S). PDatumHash s -> Term s (PInner PDatumHash)

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PDatumHash) -> (PDatumHash s -> Term s b) -> Term s b

PShow PDatumHash Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Methods

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

PTryFrom PData PDatumHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type PTryFromExcess PData PDatumHash :: PType

Methods

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

PTryFrom PData (PAsData PDatumHash) Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type PTryFromExcess PData (PAsData PDatumHash) :: PType

Methods

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

Generic (PDatumHash s) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

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

Methods

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

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

type AsHaskell PDatumHash Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type AsHaskell PDatumHash = AsHaskell (DeriveDataPLiftable PDatumHash DatumHash)
type PlutusRepr PDatumHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PlutusRepr PDatumHash = PlutusRepr (DeriveDataPLiftable PDatumHash DatumHash)
type DPTStrat PDatumHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type DPTStrat PDatumHash = PlutusTypeNewtype
type PContravariant' PDatumHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PContravariant' PDatumHash = All2 PContravariant'' (PCode PDatumHash)
type PCovariant' PDatumHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PCovariant' PDatumHash = All2 PCovariant'' (PCode PDatumHash)
type PInner PDatumHash Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PInner PDatumHash = DerivedPInner (DPTStrat PDatumHash) PDatumHash
type PVariant' PDatumHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PVariant' PDatumHash = All2 PVariant'' (PCode PDatumHash)
type PTryFromExcess PData PDatumHash Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PTryFromExcess PData PDatumHash = PTryFromExcess PData (PInner PDatumHash)
type PTryFromExcess PData (PAsData PDatumHash) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PTryFromExcess PData (PAsData PDatumHash) = PTryFromExcess PData (PInner (PAsData PDatumHash))
type Rep (PDatumHash s) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type Rep (PDatumHash s) = D1 ('MetaData "PDatumHash" "Plutarch.LedgerApi.V1.Scripts" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PDatumHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataNewtype PByteString)))))

newtype PRedeemerHash (s :: S) Source #

Since: 2.0.0

Constructors

PRedeemerHash (Term s (PDataNewtype PByteString)) 

Instances

Instances details
PIsData PRedeemerHash Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PRedeemerHash) -> Term s PRedeemerHash

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

PEq PRedeemerHash Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Methods

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

PLiftable PRedeemerHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type AsHaskell PRedeemerHash

type PlutusRepr PRedeemerHash

Methods

toPlutarchRepr :: AsHaskell PRedeemerHash -> PlutusRepr PRedeemerHash

toPlutarch :: forall (s :: S). AsHaskell PRedeemerHash -> PLifted s PRedeemerHash

fromPlutarchRepr :: PlutusRepr PRedeemerHash -> Maybe (AsHaskell PRedeemerHash)

fromPlutarch :: (forall (s :: S). PLifted s PRedeemerHash) -> Either LiftError (AsHaskell PRedeemerHash)

POrd PRedeemerHash Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Methods

pmax :: forall (s :: S). Term s PRedeemerHash -> Term s PRedeemerHash -> Term s PRedeemerHash

pmin :: forall (s :: S). Term s PRedeemerHash -> Term s PRedeemerHash -> Term s PRedeemerHash

PPartialOrd PRedeemerHash Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Methods

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

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

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

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

DerivePlutusType PRedeemerHash Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type DPTStrat PRedeemerHash

PlutusType PRedeemerHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type PInner PRedeemerHash :: PType

type PCovariant' PRedeemerHash

type PContravariant' PRedeemerHash

type PVariant' PRedeemerHash

Methods

pcon' :: forall (s :: S). PRedeemerHash s -> Term s (PInner PRedeemerHash)

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PRedeemerHash) -> (PRedeemerHash s -> Term s b) -> Term s b

PShow PRedeemerHash Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Methods

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

PTryFrom PData PRedeemerHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type PTryFromExcess PData PRedeemerHash :: PType

Methods

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

PTryFrom PData (PAsData PRedeemerHash) Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type PTryFromExcess PData (PAsData PRedeemerHash) :: PType

Methods

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

Generic (PRedeemerHash s) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

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

type AsHaskell PRedeemerHash Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type AsHaskell PRedeemerHash = AsHaskell (DeriveDataPLiftable PRedeemerHash RedeemerHash)
type PlutusRepr PRedeemerHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PlutusRepr PRedeemerHash = PlutusRepr (DeriveDataPLiftable PRedeemerHash RedeemerHash)
type DPTStrat PRedeemerHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type DPTStrat PRedeemerHash = PlutusTypeNewtype
type PContravariant' PRedeemerHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PContravariant' PRedeemerHash = All2 PContravariant'' (PCode PRedeemerHash)
type PCovariant' PRedeemerHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PCovariant' PRedeemerHash = All2 PCovariant'' (PCode PRedeemerHash)
type PInner PRedeemerHash Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PInner PRedeemerHash = DerivedPInner (DPTStrat PRedeemerHash) PRedeemerHash
type PVariant' PRedeemerHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PVariant' PRedeemerHash = All2 PVariant'' (PCode PRedeemerHash)
type PTryFromExcess PData PRedeemerHash Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PTryFromExcess PData PRedeemerHash = PTryFromExcess PData (PInner PRedeemerHash)
type PTryFromExcess PData (PAsData PRedeemerHash) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PTryFromExcess PData (PAsData PRedeemerHash) = PTryFromExcess PData (PInner (PAsData PRedeemerHash))
type Rep (PRedeemerHash s) Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type Rep (PRedeemerHash s) = D1 ('MetaData "PRedeemerHash" "Plutarch.LedgerApi.V1.Scripts" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PRedeemerHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataNewtype PByteString)))))

newtype PScriptHash (s :: S) Source #

Since: 2.0.0

Constructors

PScriptHash (Term s (PDataNewtype PByteString)) 

Instances

Instances details
PIsData PScriptHash Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PScriptHash) -> Term s PScriptHash

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

PEq PScriptHash Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Methods

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

PLiftable PScriptHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type AsHaskell PScriptHash

type PlutusRepr PScriptHash

Methods

toPlutarchRepr :: AsHaskell PScriptHash -> PlutusRepr PScriptHash

toPlutarch :: forall (s :: S). AsHaskell PScriptHash -> PLifted s PScriptHash

fromPlutarchRepr :: PlutusRepr PScriptHash -> Maybe (AsHaskell PScriptHash)

fromPlutarch :: (forall (s :: S). PLifted s PScriptHash) -> Either LiftError (AsHaskell PScriptHash)

POrd PScriptHash Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Methods

pmax :: forall (s :: S). Term s PScriptHash -> Term s PScriptHash -> Term s PScriptHash

pmin :: forall (s :: S). Term s PScriptHash -> Term s PScriptHash -> Term s PScriptHash

PPartialOrd PScriptHash Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Methods

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

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

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

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

DerivePlutusType PScriptHash Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type DPTStrat PScriptHash

PlutusType PScriptHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type PInner PScriptHash :: PType

type PCovariant' PScriptHash

type PContravariant' PScriptHash

type PVariant' PScriptHash

Methods

pcon' :: forall (s :: S). PScriptHash s -> Term s (PInner PScriptHash)

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PScriptHash) -> (PScriptHash s -> Term s b) -> Term s b

PShow PScriptHash Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Methods

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

PTryFrom PData PScriptHash Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type PTryFromExcess PData PScriptHash :: PType

Methods

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

PTryFrom PData (PAsData PScriptHash) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

type PTryFromExcess PData (PAsData PScriptHash) :: PType

Methods

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

Generic (PScriptHash s) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

Associated Types

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

type AsHaskell PScriptHash Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type AsHaskell PScriptHash = AsHaskell (DeriveDataPLiftable PScriptHash ScriptHash)
type PlutusRepr PScriptHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PlutusRepr PScriptHash = PlutusRepr (DeriveDataPLiftable PScriptHash ScriptHash)
type DPTStrat PScriptHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type DPTStrat PScriptHash = PlutusTypeNewtype
type PContravariant' PScriptHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PContravariant' PScriptHash = All2 PContravariant'' (PCode PScriptHash)
type PCovariant' PScriptHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PCovariant' PScriptHash = All2 PCovariant'' (PCode PScriptHash)
type PInner PScriptHash Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PInner PScriptHash = DerivedPInner (DPTStrat PScriptHash) PScriptHash
type PVariant' PScriptHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

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

Defined in Plutarch.LedgerApi.V1.Scripts

type PTryFromExcess PData PScriptHash = Mret PScriptHash
type PTryFromExcess PData (PAsData PScriptHash) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type PTryFromExcess PData (PAsData PScriptHash) = Mret PScriptHash
type Rep (PScriptHash s) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Scripts

type Rep (PScriptHash s) = D1 ('MetaData "PScriptHash" "Plutarch.LedgerApi.V1.Scripts" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PScriptHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataNewtype PByteString)))))

Transactions

newtype PAddress (s :: S) Source #

Since: 2.0.0

Constructors

PAddress (Term s (PDataRecord '["credential" ':= PCredential, "stakingCredential" ':= PMaybeData PStakingCredential])) 

Instances

Instances details
PIsData PAddress Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Address

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PAddress) -> Term s PAddress

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

PDataFields PAddress Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Address

Associated Types

type PFields PAddress :: [PLabeledType]

Methods

ptoFields :: forall (s :: S). Term s PAddress -> Term s (PDataRecord (PFields PAddress))

PEq PAddress Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Address

Methods

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

PLiftable PAddress Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Address

Associated Types

type AsHaskell PAddress

type PlutusRepr PAddress

Methods

toPlutarchRepr :: AsHaskell PAddress -> PlutusRepr PAddress

toPlutarch :: forall (s :: S). AsHaskell PAddress -> PLifted s PAddress

fromPlutarchRepr :: PlutusRepr PAddress -> Maybe (AsHaskell PAddress)

fromPlutarch :: (forall (s :: S). PLifted s PAddress) -> Either LiftError (AsHaskell PAddress)

POrd PAddress Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Address

Methods

pmax :: forall (s :: S). Term s PAddress -> Term s PAddress -> Term s PAddress

pmin :: forall (s :: S). Term s PAddress -> Term s PAddress -> Term s PAddress

PPartialOrd PAddress Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Address

Methods

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

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

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

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

DerivePlutusType PAddress Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Address

Associated Types

type DPTStrat PAddress

PlutusType PAddress Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Address

Associated Types

type PInner PAddress :: PType

type PCovariant' PAddress

type PContravariant' PAddress

type PVariant' PAddress

Methods

pcon' :: forall (s :: S). PAddress s -> Term s (PInner PAddress)

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PAddress) -> (PAddress s -> Term s b) -> Term s b

PShow PAddress Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Address

Methods

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

PTryFrom PData PAddress Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Address

Associated Types

type PTryFromExcess PData PAddress :: PType

Methods

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

PTryFrom PData (PAsData PAddress) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Address

Associated Types

type PTryFromExcess PData (PAsData PAddress) :: PType

Methods

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

Generic (PAddress s) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Address

Associated Types

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

Methods

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

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

type PFields PAddress Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Address

type PFields PAddress = Helper (PInner PAddress)
type AsHaskell PAddress Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.V1.Address

type AsHaskell PAddress = AsHaskell (DeriveDataPLiftable PAddress Address)
type PlutusRepr PAddress Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Address

type PlutusRepr PAddress = PlutusRepr (DeriveDataPLiftable PAddress Address)
type DPTStrat PAddress Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Address

type DPTStrat PAddress = PlutusTypeData
type PContravariant' PAddress Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Address

type PContravariant' PAddress = All2 PContravariant'' (PCode PAddress)
type PCovariant' PAddress Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Address

type PCovariant' PAddress = All2 PCovariant'' (PCode PAddress)
type PInner PAddress Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Address

type PInner PAddress = DerivedPInner (DPTStrat PAddress) PAddress
type PVariant' PAddress Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Address

type PVariant' PAddress = All2 PVariant'' (PCode PAddress)
type PTryFromExcess PData PAddress Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Address

type PTryFromExcess PData PAddress = PTryFromExcess PData (PInner PAddress)
type PTryFromExcess PData (PAsData PAddress) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Address

type PTryFromExcess PData (PAsData PAddress) = PTryFromExcess PData (PInner (PAsData PAddress))
type Rep (PAddress s) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Address

type Rep (PAddress s) = D1 ('MetaData "PAddress" "Plutarch.LedgerApi.V1.Address" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PAddress" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["credential" ':= PCredential, "stakingCredential" ':= PMaybeData PStakingCredential])))))

newtype PPubKeyHash (s :: S) Source #

Since: 2.0.0

Constructors

PPubKeyHash (Term s (PDataNewtype PByteString)) 

Instances

Instances details
PIsData PPubKeyHash Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Crypto

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PPubKeyHash) -> Term s PPubKeyHash

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

PEq PPubKeyHash Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Crypto

Methods

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

PLiftable PPubKeyHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Crypto

Associated Types

type AsHaskell PPubKeyHash

type PlutusRepr PPubKeyHash

Methods

toPlutarchRepr :: AsHaskell PPubKeyHash -> PlutusRepr PPubKeyHash

toPlutarch :: forall (s :: S). AsHaskell PPubKeyHash -> PLifted s PPubKeyHash

fromPlutarchRepr :: PlutusRepr PPubKeyHash -> Maybe (AsHaskell PPubKeyHash)

fromPlutarch :: (forall (s :: S). PLifted s PPubKeyHash) -> Either LiftError (AsHaskell PPubKeyHash)

POrd PPubKeyHash Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Crypto

Methods

pmax :: forall (s :: S). Term s PPubKeyHash -> Term s PPubKeyHash -> Term s PPubKeyHash

pmin :: forall (s :: S). Term s PPubKeyHash -> Term s PPubKeyHash -> Term s PPubKeyHash

PPartialOrd PPubKeyHash Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Crypto

Methods

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

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

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

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

DerivePlutusType PPubKeyHash Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Crypto

Associated Types

type DPTStrat PPubKeyHash

PlutusType PPubKeyHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Crypto

Associated Types

type PInner PPubKeyHash :: PType

type PCovariant' PPubKeyHash

type PContravariant' PPubKeyHash

type PVariant' PPubKeyHash

Methods

pcon' :: forall (s :: S). PPubKeyHash s -> Term s (PInner PPubKeyHash)

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PPubKeyHash) -> (PPubKeyHash s -> Term s b) -> Term s b

PShow PPubKeyHash Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Crypto

Methods

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

PTryFrom PData PPubKeyHash Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.Crypto

Associated Types

type PTryFromExcess PData PPubKeyHash :: PType

Methods

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

PTryFrom PData (PAsData PPubKeyHash) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Crypto

Associated Types

type PTryFromExcess PData (PAsData PPubKeyHash) :: PType

Methods

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

Generic (PPubKeyHash s) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Crypto

Associated Types

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

type AsHaskell PPubKeyHash Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.V1.Crypto

type AsHaskell PPubKeyHash = AsHaskell (DeriveDataPLiftable PPubKeyHash PubKeyHash)
type PlutusRepr PPubKeyHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Crypto

type PlutusRepr PPubKeyHash = PlutusRepr (DeriveDataPLiftable PPubKeyHash PubKeyHash)
type DPTStrat PPubKeyHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Crypto

type DPTStrat PPubKeyHash = PlutusTypeNewtype
type PContravariant' PPubKeyHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Crypto

type PContravariant' PPubKeyHash = All2 PContravariant'' (PCode PPubKeyHash)
type PCovariant' PPubKeyHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Crypto

type PCovariant' PPubKeyHash = All2 PCovariant'' (PCode PPubKeyHash)
type PInner PPubKeyHash Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Crypto

type PInner PPubKeyHash = DerivedPInner (DPTStrat PPubKeyHash) PPubKeyHash
type PVariant' PPubKeyHash Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Crypto

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

Defined in Plutarch.LedgerApi.V1.Crypto

type PTryFromExcess PData PPubKeyHash = Mret PPubKeyHash
type PTryFromExcess PData (PAsData PPubKeyHash) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Crypto

type PTryFromExcess PData (PAsData PPubKeyHash) = Mret PPubKeyHash
type Rep (PPubKeyHash s) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Crypto

type Rep (PPubKeyHash s) = D1 ('MetaData "PPubKeyHash" "Plutarch.LedgerApi.V1.Crypto" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PPubKeyHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataNewtype PByteString)))))

newtype PTxId (s :: S) Source #

Hashed with BLAKE2b-256.

Since: 3.1.0

Constructors

PTxId (Term s (PDataRecord '["_0" ':= PByteString])) 

Instances

Instances details
PIsData PTxId Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Tx

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PTxId) -> Term s PTxId

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

PEq PTxId Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Tx

Methods

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

PLiftable PTxId Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Tx

Associated Types

type AsHaskell PTxId

type PlutusRepr PTxId

Methods

toPlutarchRepr :: AsHaskell PTxId -> PlutusRepr PTxId

toPlutarch :: forall (s :: S). AsHaskell PTxId -> PLifted s PTxId

fromPlutarchRepr :: PlutusRepr PTxId -> Maybe (AsHaskell PTxId)

fromPlutarch :: (forall (s :: S). PLifted s PTxId) -> Either LiftError (AsHaskell PTxId)

POrd PTxId Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Tx

Methods

pmax :: forall (s :: S). Term s PTxId -> Term s PTxId -> Term s PTxId

pmin :: forall (s :: S). Term s PTxId -> Term s PTxId -> Term s PTxId

PPartialOrd PTxId Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Tx

Methods

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

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

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

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

DerivePlutusType PTxId Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.Tx

Associated Types

type DPTStrat PTxId

PlutusType PTxId Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Tx

Associated Types

type PInner PTxId :: PType

type PCovariant' PTxId

type PContravariant' PTxId

type PVariant' PTxId

Methods

pcon' :: forall (s :: S). PTxId s -> Term s (PInner PTxId)

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PTxId) -> (PTxId s -> Term s b) -> Term s b

PShow PTxId Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Tx

Methods

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

PTryFrom PData PTxId Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.Tx

Associated Types

type PTryFromExcess PData PTxId :: PType

Methods

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

PTryFrom PData (PAsData PTxId) Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.Tx

Associated Types

type PTryFromExcess PData (PAsData PTxId) :: PType

Methods

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

Generic (PTxId s) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Tx

Associated Types

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

Methods

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

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

type AsHaskell PTxId Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.V1.Tx

type AsHaskell PTxId = AsHaskell (DeriveDataPLiftable PTxId TxId)
type PlutusRepr PTxId Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Tx

type PlutusRepr PTxId = PlutusRepr (DeriveDataPLiftable PTxId TxId)
type DPTStrat PTxId Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Tx

type DPTStrat PTxId = PlutusTypeData
type PContravariant' PTxId Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Tx

type PContravariant' PTxId = All2 PContravariant'' (PCode PTxId)
type PCovariant' PTxId Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Tx

type PCovariant' PTxId = All2 PCovariant'' (PCode PTxId)
type PInner PTxId Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Tx

type PInner PTxId = DerivedPInner (DPTStrat PTxId) PTxId
type PVariant' PTxId Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Tx

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

Defined in Plutarch.LedgerApi.V1.Tx

type PTryFromExcess PData PTxId = Mret PTxId
type PTryFromExcess PData (PAsData PTxId) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Tx

type PTryFromExcess PData (PAsData PTxId) = Mret PTxId
type Rep (PTxId s) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Tx

type Rep (PTxId s) = D1 ('MetaData "PTxId" "Plutarch.LedgerApi.V1.Tx" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PTxId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["_0" ':= PByteString])))))

newtype PTxInfo (s :: S) Source #

Since: 3.1.1

Constructors

PTxInfo (Term s (PDataRecord '["inputs" ':= PBuiltinList (PAsData PTxInInfo), "referenceInputs" ':= PBuiltinList (PAsData PTxInInfo), "outputs" ':= PBuiltinList (PAsData PTxOut), "fee" ':= PValue 'Sorted 'Positive, "mint" ':= PValue 'Sorted 'NoGuarantees, "dcert" ':= PBuiltinList (PAsData PDCert), "wdrl" ':= PMap 'Unsorted PStakingCredential PInteger, "validRange" ':= PInterval PPosixTime, "signatories" ':= PBuiltinList (PAsData PPubKeyHash), "redeemers" ':= PMap 'Unsorted PScriptPurpose PRedeemer, "data" ':= PMap 'Unsorted PDatumHash PDatum, "id" ':= PTxId])) 

Instances

Instances details
PIsData PTxInfo Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PTxInfo) -> Term s PTxInfo

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

PDataFields PTxInfo Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

Associated Types

type PFields PTxInfo :: [PLabeledType]

Methods

ptoFields :: forall (s :: S). Term s PTxInfo -> Term s (PDataRecord (PFields PTxInfo))

PEq PTxInfo Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

Methods

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

PLiftable PTxInfo Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

Associated Types

type AsHaskell PTxInfo

type PlutusRepr PTxInfo

Methods

toPlutarchRepr :: AsHaskell PTxInfo -> PlutusRepr PTxInfo

toPlutarch :: forall (s :: S). AsHaskell PTxInfo -> PLifted s PTxInfo

fromPlutarchRepr :: PlutusRepr PTxInfo -> Maybe (AsHaskell PTxInfo)

fromPlutarch :: (forall (s :: S). PLifted s PTxInfo) -> Either LiftError (AsHaskell PTxInfo)

DerivePlutusType PTxInfo Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

Associated Types

type DPTStrat PTxInfo

PlutusType PTxInfo Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

Associated Types

type PInner PTxInfo :: PType

type PCovariant' PTxInfo

type PContravariant' PTxInfo

type PVariant' PTxInfo

Methods

pcon' :: forall (s :: S). PTxInfo s -> Term s (PInner PTxInfo)

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PTxInfo) -> (PTxInfo s -> Term s b) -> Term s b

PShow PTxInfo Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

Methods

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

PTryFrom PData PTxInfo Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

Associated Types

type PTryFromExcess PData PTxInfo :: PType

Methods

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

PTryFrom PData (PAsData PTxInfo) Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

Associated Types

type PTryFromExcess PData (PAsData PTxInfo) :: PType

Methods

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

Generic (PTxInfo s) Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

Associated Types

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

Methods

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

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

type PFields PTxInfo Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

type PFields PTxInfo = Helper (PInner PTxInfo)
type AsHaskell PTxInfo Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.V2

type AsHaskell PTxInfo = AsHaskell (DeriveDataPLiftable PTxInfo TxInfo)
type PlutusRepr PTxInfo Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

type PlutusRepr PTxInfo = PlutusRepr (DeriveDataPLiftable PTxInfo TxInfo)
type DPTStrat PTxInfo Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

type DPTStrat PTxInfo = PlutusTypeData
type PContravariant' PTxInfo Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

type PContravariant' PTxInfo = All2 PContravariant'' (PCode PTxInfo)
type PCovariant' PTxInfo Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

type PCovariant' PTxInfo = All2 PCovariant'' (PCode PTxInfo)
type PInner PTxInfo Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

type PInner PTxInfo = DerivedPInner (DPTStrat PTxInfo) PTxInfo
type PVariant' PTxInfo Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

type PVariant' PTxInfo = All2 PVariant'' (PCode PTxInfo)
type PTryFromExcess PData PTxInfo Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

type PTryFromExcess PData PTxInfo = PTryFromExcess PData (PInner PTxInfo)
type PTryFromExcess PData (PAsData PTxInfo) Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

type PTryFromExcess PData (PAsData PTxInfo) = PTryFromExcess PData (PInner (PAsData PTxInfo))
type Rep (PTxInfo s) Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

type Rep (PTxInfo s) = D1 ('MetaData "PTxInfo" "Plutarch.LedgerApi.V2" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PTxInfo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["inputs" ':= PBuiltinList (PAsData PTxInInfo), "referenceInputs" ':= PBuiltinList (PAsData PTxInInfo), "outputs" ':= PBuiltinList (PAsData PTxOut), "fee" ':= PValue 'Sorted 'Positive, "mint" ':= PValue 'Sorted 'NoGuarantees, "dcert" ':= PBuiltinList (PAsData PDCert), "wdrl" ':= PMap 'Unsorted PStakingCredential PInteger, "validRange" ':= PInterval PPosixTime, "signatories" ':= PBuiltinList (PAsData PPubKeyHash), "redeemers" ':= PMap 'Unsorted PScriptPurpose PRedeemer, "data" ':= PMap 'Unsorted PDatumHash PDatum, "id" ':= PTxId])))))

newtype PTxOut (s :: S) Source #

Since: 2.0.0

Constructors

PTxOut (Term s (PDataRecord '["address" ':= PAddress, "value" ':= PValue 'Sorted 'Positive, "datum" ':= POutputDatum, "referenceScript" ':= PMaybeData PScriptHash])) 

Instances

Instances details
PIsData PTxOut Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V2.Tx

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PTxOut) -> Term s PTxOut

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

PDataFields PTxOut Source # 
Instance details

Defined in Plutarch.LedgerApi.V2.Tx

Associated Types

type PFields PTxOut :: [PLabeledType]

Methods

ptoFields :: forall (s :: S). Term s PTxOut -> Term s (PDataRecord (PFields PTxOut))

PEq PTxOut Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V2.Tx

Methods

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

PLiftable PTxOut Source # 
Instance details

Defined in Plutarch.LedgerApi.V2.Tx

Associated Types

type AsHaskell PTxOut

type PlutusRepr PTxOut

Methods

toPlutarchRepr :: AsHaskell PTxOut -> PlutusRepr PTxOut

toPlutarch :: forall (s :: S). AsHaskell PTxOut -> PLifted s PTxOut

fromPlutarchRepr :: PlutusRepr PTxOut -> Maybe (AsHaskell PTxOut)

fromPlutarch :: (forall (s :: S). PLifted s PTxOut) -> Either LiftError (AsHaskell PTxOut)

DerivePlutusType PTxOut Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V2.Tx

Associated Types

type DPTStrat PTxOut

PlutusType PTxOut Source # 
Instance details

Defined in Plutarch.LedgerApi.V2.Tx

Associated Types

type PInner PTxOut :: PType

type PCovariant' PTxOut

type PContravariant' PTxOut

type PVariant' PTxOut

Methods

pcon' :: forall (s :: S). PTxOut s -> Term s (PInner PTxOut)

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PTxOut) -> (PTxOut s -> Term s b) -> Term s b

PShow PTxOut Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V2.Tx

Methods

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

PTryFrom PData PTxOut Source # 
Instance details

Defined in Plutarch.LedgerApi.V2.Tx

Associated Types

type PTryFromExcess PData PTxOut :: PType

Methods

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

PTryFrom PData (PAsData PTxOut) Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V2.Tx

Associated Types

type PTryFromExcess PData (PAsData PTxOut) :: PType

Methods

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

Generic (PTxOut s) Source # 
Instance details

Defined in Plutarch.LedgerApi.V2.Tx

Associated Types

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

Methods

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

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

type PFields PTxOut Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V2.Tx

type PFields PTxOut = Helper (PInner PTxOut)
type AsHaskell PTxOut Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.V2.Tx

type AsHaskell PTxOut = AsHaskell (DeriveDataPLiftable PTxOut TxOut)
type PlutusRepr PTxOut Source # 
Instance details

Defined in Plutarch.LedgerApi.V2.Tx

type PlutusRepr PTxOut = PlutusRepr (DeriveDataPLiftable PTxOut TxOut)
type DPTStrat PTxOut Source # 
Instance details

Defined in Plutarch.LedgerApi.V2.Tx

type DPTStrat PTxOut = PlutusTypeData
type PContravariant' PTxOut Source # 
Instance details

Defined in Plutarch.LedgerApi.V2.Tx

type PContravariant' PTxOut = All2 PContravariant'' (PCode PTxOut)
type PCovariant' PTxOut Source # 
Instance details

Defined in Plutarch.LedgerApi.V2.Tx

type PCovariant' PTxOut = All2 PCovariant'' (PCode PTxOut)
type PInner PTxOut Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V2.Tx

type PInner PTxOut = DerivedPInner (DPTStrat PTxOut) PTxOut
type PVariant' PTxOut Source # 
Instance details

Defined in Plutarch.LedgerApi.V2.Tx

type PVariant' PTxOut = All2 PVariant'' (PCode PTxOut)
type PTryFromExcess PData PTxOut Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V2.Tx

type PTryFromExcess PData PTxOut = PTryFromExcess PData (PInner PTxOut)
type PTryFromExcess PData (PAsData PTxOut) Source # 
Instance details

Defined in Plutarch.LedgerApi.V2.Tx

type PTryFromExcess PData (PAsData PTxOut) = PTryFromExcess PData (PInner (PAsData PTxOut))
type Rep (PTxOut s) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V2.Tx

type Rep (PTxOut s) = D1 ('MetaData "PTxOut" "Plutarch.LedgerApi.V2.Tx" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PTxOut" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["address" ':= PAddress, "value" ':= PValue 'Sorted 'Positive, "datum" ':= POutputDatum, "referenceScript" ':= PMaybeData PScriptHash])))))

newtype PTxOutRef (s :: S) Source #

Reference to a transaction output, with an index referencing which exact output we mean.

Since: 2.0.0

Constructors

PTxOutRef (Term s (PDataRecord '["id" ':= PTxId, "idx" ':= PInteger])) 

Instances

Instances details
PIsData PTxOutRef Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Tx

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PTxOutRef) -> Term s PTxOutRef

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

PDataFields PTxOutRef Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Tx

Associated Types

type PFields PTxOutRef :: [PLabeledType]

Methods

ptoFields :: forall (s :: S). Term s PTxOutRef -> Term s (PDataRecord (PFields PTxOutRef))

PEq PTxOutRef Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Tx

Methods

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

PLiftable PTxOutRef Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Tx

Associated Types

type AsHaskell PTxOutRef

type PlutusRepr PTxOutRef

Methods

toPlutarchRepr :: AsHaskell PTxOutRef -> PlutusRepr PTxOutRef

toPlutarch :: forall (s :: S). AsHaskell PTxOutRef -> PLifted s PTxOutRef

fromPlutarchRepr :: PlutusRepr PTxOutRef -> Maybe (AsHaskell PTxOutRef)

fromPlutarch :: (forall (s :: S). PLifted s PTxOutRef) -> Either LiftError (AsHaskell PTxOutRef)

POrd PTxOutRef Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Tx

Methods

pmax :: forall (s :: S). Term s PTxOutRef -> Term s PTxOutRef -> Term s PTxOutRef

pmin :: forall (s :: S). Term s PTxOutRef -> Term s PTxOutRef -> Term s PTxOutRef

PPartialOrd PTxOutRef Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Tx

Methods

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

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

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

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

DerivePlutusType PTxOutRef Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Tx

Associated Types

type DPTStrat PTxOutRef

PlutusType PTxOutRef Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Tx

Associated Types

type PInner PTxOutRef :: PType

type PCovariant' PTxOutRef

type PContravariant' PTxOutRef

type PVariant' PTxOutRef

Methods

pcon' :: forall (s :: S). PTxOutRef s -> Term s (PInner PTxOutRef)

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PTxOutRef) -> (PTxOutRef s -> Term s b) -> Term s b

PShow PTxOutRef Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Tx

Methods

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

PTryFrom PData PTxOutRef Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Tx

Associated Types

type PTryFromExcess PData PTxOutRef :: PType

Methods

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

PTryFrom PData (PAsData PTxOutRef) Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V1.Tx

Associated Types

type PTryFromExcess PData (PAsData PTxOutRef) :: PType

Methods

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

Generic (PTxOutRef s) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Tx

Associated Types

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

Methods

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

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

type PFields PTxOutRef Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Tx

type PFields PTxOutRef = Helper (PInner PTxOutRef)
type AsHaskell PTxOutRef Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.V1.Tx

type AsHaskell PTxOutRef = AsHaskell (DeriveDataPLiftable PTxOutRef TxOutRef)
type PlutusRepr PTxOutRef Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Tx

type PlutusRepr PTxOutRef = PlutusRepr (DeriveDataPLiftable PTxOutRef TxOutRef)
type DPTStrat PTxOutRef Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Tx

type DPTStrat PTxOutRef = PlutusTypeData
type PContravariant' PTxOutRef Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Tx

type PContravariant' PTxOutRef = All2 PContravariant'' (PCode PTxOutRef)
type PCovariant' PTxOutRef Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Tx

type PCovariant' PTxOutRef = All2 PCovariant'' (PCode PTxOutRef)
type PInner PTxOutRef Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Tx

type PInner PTxOutRef = DerivedPInner (DPTStrat PTxOutRef) PTxOutRef
type PVariant' PTxOutRef Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Tx

type PVariant' PTxOutRef = All2 PVariant'' (PCode PTxOutRef)
type PTryFromExcess PData PTxOutRef Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Tx

type PTryFromExcess PData PTxOutRef = PTryFromExcess PData (PInner PTxOutRef)
type PTryFromExcess PData (PAsData PTxOutRef) Source # 
Instance details

Defined in Plutarch.LedgerApi.V1.Tx

type PTryFromExcess PData (PAsData PTxOutRef) = PTryFromExcess PData (PInner (PAsData PTxOutRef))
type Rep (PTxOutRef s) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V1.Tx

type Rep (PTxOutRef s) = D1 ('MetaData "PTxOutRef" "Plutarch.LedgerApi.V1.Tx" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PTxOutRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["id" ':= PTxId, "idx" ':= PInteger])))))

newtype PTxInInfo (s :: S) Source #

Since: 3.1.1

Constructors

PTxInInfo (Term s (PDataRecord '["outRef" ':= PTxOutRef, "resolved" ':= PTxOut])) 

Instances

Instances details
PIsData PTxInInfo Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PTxInInfo) -> Term s PTxInInfo

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

PDataFields PTxInInfo Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

Associated Types

type PFields PTxInInfo :: [PLabeledType]

Methods

ptoFields :: forall (s :: S). Term s PTxInInfo -> Term s (PDataRecord (PFields PTxInInfo))

PEq PTxInInfo Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

Methods

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

PLiftable PTxInInfo Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

Associated Types

type AsHaskell PTxInInfo

type PlutusRepr PTxInInfo

Methods

toPlutarchRepr :: AsHaskell PTxInInfo -> PlutusRepr PTxInInfo

toPlutarch :: forall (s :: S). AsHaskell PTxInInfo -> PLifted s PTxInInfo

fromPlutarchRepr :: PlutusRepr PTxInInfo -> Maybe (AsHaskell PTxInInfo)

fromPlutarch :: (forall (s :: S). PLifted s PTxInInfo) -> Either LiftError (AsHaskell PTxInInfo)

DerivePlutusType PTxInInfo Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

Associated Types

type DPTStrat PTxInInfo

PlutusType PTxInInfo Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

Associated Types

type PInner PTxInInfo :: PType

type PCovariant' PTxInInfo

type PContravariant' PTxInInfo

type PVariant' PTxInInfo

Methods

pcon' :: forall (s :: S). PTxInInfo s -> Term s (PInner PTxInInfo)

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PTxInInfo) -> (PTxInInfo s -> Term s b) -> Term s b

PShow PTxInInfo Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

Methods

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

PTryFrom PData PTxInInfo Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

Associated Types

type PTryFromExcess PData PTxInInfo :: PType

Methods

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

PTryFrom PData (PAsData PTxInInfo) Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

Associated Types

type PTryFromExcess PData (PAsData PTxInInfo) :: PType

Methods

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

Generic (PTxInInfo s) Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

Associated Types

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

Methods

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

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

type PFields PTxInInfo Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

type PFields PTxInInfo = Helper (PInner PTxInInfo)
type AsHaskell PTxInInfo Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.V2

type AsHaskell PTxInInfo = AsHaskell (DeriveDataPLiftable PTxInInfo TxInInfo)
type PlutusRepr PTxInInfo Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

type PlutusRepr PTxInInfo = PlutusRepr (DeriveDataPLiftable PTxInInfo TxInInfo)
type DPTStrat PTxInInfo Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

type DPTStrat PTxInInfo = PlutusTypeData
type PContravariant' PTxInInfo Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

type PContravariant' PTxInInfo = All2 PContravariant'' (PCode PTxInInfo)
type PCovariant' PTxInInfo Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

type PCovariant' PTxInInfo = All2 PCovariant'' (PCode PTxInInfo)
type PInner PTxInInfo Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

type PInner PTxInInfo = DerivedPInner (DPTStrat PTxInInfo) PTxInInfo
type PVariant' PTxInInfo Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

type PVariant' PTxInInfo = All2 PVariant'' (PCode PTxInInfo)
type PTryFromExcess PData PTxInInfo Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

type PTryFromExcess PData PTxInInfo = PTryFromExcess PData (PInner PTxInInfo)
type PTryFromExcess PData (PAsData PTxInInfo) Source # 
Instance details

Defined in Plutarch.LedgerApi.V2

type PTryFromExcess PData (PAsData PTxInInfo) = PTryFromExcess PData (PInner (PAsData PTxInInfo))
type Rep (PTxInInfo s) Source #

Since: 3.1.1

Instance details

Defined in Plutarch.LedgerApi.V2

type Rep (PTxInInfo s) = D1 ('MetaData "PTxInInfo" "Plutarch.LedgerApi.V2" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PTxInInfo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["outRef" ':= PTxOutRef, "resolved" ':= PTxOut])))))

data POutputDatum (s :: S) Source #

Since: 2.0.0

Constructors

PNoOutputDatum (Term s (PDataRecord '[])) 
POutputDatumHash (Term s (PDataRecord '["datumHash" ':= PDatumHash])) 
POutputDatum (Term s (PDataRecord '["outputDatum" ':= PDatum]))

Inline datum as per CIP-0032

Instances

Instances details
PIsData POutputDatum Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V2.Tx

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData POutputDatum) -> Term s POutputDatum

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

PEq POutputDatum Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V2.Tx

Methods

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

PLiftable POutputDatum Source # 
Instance details

Defined in Plutarch.LedgerApi.V2.Tx

Associated Types

type AsHaskell POutputDatum

type PlutusRepr POutputDatum

Methods

toPlutarchRepr :: AsHaskell POutputDatum -> PlutusRepr POutputDatum

toPlutarch :: forall (s :: S). AsHaskell POutputDatum -> PLifted s POutputDatum

fromPlutarchRepr :: PlutusRepr POutputDatum -> Maybe (AsHaskell POutputDatum)

fromPlutarch :: (forall (s :: S). PLifted s POutputDatum) -> Either LiftError (AsHaskell POutputDatum)

DerivePlutusType POutputDatum Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V2.Tx

Associated Types

type DPTStrat POutputDatum

PlutusType POutputDatum Source # 
Instance details

Defined in Plutarch.LedgerApi.V2.Tx

Associated Types

type PInner POutputDatum :: PType

type PCovariant' POutputDatum

type PContravariant' POutputDatum

type PVariant' POutputDatum

Methods

pcon' :: forall (s :: S). POutputDatum s -> Term s (PInner POutputDatum)

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner POutputDatum) -> (POutputDatum s -> Term s b) -> Term s b

PShow POutputDatum Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V2.Tx

Methods

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

PTryFrom PData POutputDatum Source # 
Instance details

Defined in Plutarch.LedgerApi.V2.Tx

Associated Types

type PTryFromExcess PData POutputDatum :: PType

Methods

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

PTryFrom PData (PAsData POutputDatum) Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V2.Tx

Associated Types

type PTryFromExcess PData (PAsData POutputDatum) :: PType

Methods

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

Generic (POutputDatum s) Source # 
Instance details

Defined in Plutarch.LedgerApi.V2.Tx

Associated Types

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

type AsHaskell POutputDatum Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.V2.Tx

type AsHaskell POutputDatum = AsHaskell (DeriveDataPLiftable POutputDatum OutputDatum)
type PlutusRepr POutputDatum Source # 
Instance details

Defined in Plutarch.LedgerApi.V2.Tx

type PlutusRepr POutputDatum = PlutusRepr (DeriveDataPLiftable POutputDatum OutputDatum)
type DPTStrat POutputDatum Source # 
Instance details

Defined in Plutarch.LedgerApi.V2.Tx

type DPTStrat POutputDatum = PlutusTypeData
type PContravariant' POutputDatum Source # 
Instance details

Defined in Plutarch.LedgerApi.V2.Tx

type PContravariant' POutputDatum = All2 PContravariant'' (PCode POutputDatum)
type PCovariant' POutputDatum Source # 
Instance details

Defined in Plutarch.LedgerApi.V2.Tx

type PCovariant' POutputDatum = All2 PCovariant'' (PCode POutputDatum)
type PInner POutputDatum Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V2.Tx

type PInner POutputDatum = DerivedPInner (DPTStrat POutputDatum) POutputDatum
type PVariant' POutputDatum Source # 
Instance details

Defined in Plutarch.LedgerApi.V2.Tx

type PVariant' POutputDatum = All2 PVariant'' (PCode POutputDatum)
type PTryFromExcess PData POutputDatum Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.V2.Tx

type PTryFromExcess PData POutputDatum = PTryFromExcess PData (PInner POutputDatum)
type PTryFromExcess PData (PAsData POutputDatum) Source # 
Instance details

Defined in Plutarch.LedgerApi.V2.Tx

type PTryFromExcess PData (PAsData POutputDatum) = PTryFromExcess PData (PInner (PAsData POutputDatum))
type Rep (POutputDatum s) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.V2.Tx

type Rep (POutputDatum s) = D1 ('MetaData "POutputDatum" "Plutarch.LedgerApi.V2.Tx" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'False) (C1 ('MetaCons "PNoOutputDatum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord ('[] :: [PLabeledType]))))) :+: (C1 ('MetaCons "POutputDatumHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["datumHash" ':= PDatumHash])))) :+: C1 ('MetaCons "POutputDatum" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["outputDatum" ':= PDatum]))))))

Helpers

newtype PMap (keysort :: KeyGuarantees) (k :: S -> Type) (v :: S -> Type) (s :: S) Source #

Since: 2.0.0

Constructors

PMap (Term s (PBuiltinList (PBuiltinPair (PAsData k) (PAsData v)))) 

Instances

Instances details
(POrd k, PIsData k, PTryFrom PData (PAsData k), PTryFrom PData (PAsData v)) => PTryFrom PData (PAsData (PMap 'Sorted k v)) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.AssocMap

Associated Types

type PTryFromExcess PData (PAsData (PMap 'Sorted k v)) :: PType

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PMap 'Sorted k v)), Reduce (PTryFromExcess PData (PAsData (PMap 'Sorted k v)) s)) -> Term s r) -> Term s r

(PTryFrom PData (PAsData k), PTryFrom PData (PAsData v)) => PTryFrom PData (PAsData (PMap 'Unsorted k v)) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.AssocMap

Associated Types

type PTryFromExcess PData (PAsData (PMap 'Unsorted k v)) :: PType

Methods

ptryFrom' :: forall (s :: S) (r :: PType). Term s PData -> ((Term s (PAsData (PMap 'Unsorted k v)), Reduce (PTryFromExcess PData (PAsData (PMap 'Unsorted k v)) s)) -> Term s r) -> Term s r

PIsData (PMap keysort k v) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.AssocMap

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData (PMap keysort k v)) -> Term s (PMap keysort k v)

pdataImpl :: forall (s :: S). Term s (PMap keysort k v) -> Term s PData

PEq (PMap 'Sorted k v) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.AssocMap

Methods

(#==) :: forall (s :: S). Term s (PMap 'Sorted k v) -> Term s (PMap 'Sorted k v) -> Term s PBool

(ToData (AsHaskell k), ToData (AsHaskell v), FromData (AsHaskell k), FromData (AsHaskell v)) => PLiftable (PMap 'Unsorted k v) Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.AssocMap

Associated Types

type AsHaskell (PMap 'Unsorted k v)

type PlutusRepr (PMap 'Unsorted k v)

Methods

toPlutarchRepr :: AsHaskell (PMap 'Unsorted k v) -> PlutusRepr (PMap 'Unsorted k v)

toPlutarch :: forall (s :: S). AsHaskell (PMap 'Unsorted k v) -> PLifted s (PMap 'Unsorted k v)

fromPlutarchRepr :: PlutusRepr (PMap 'Unsorted k v) -> Maybe (AsHaskell (PMap 'Unsorted k v))

fromPlutarch :: (forall (s :: S). PLifted s (PMap 'Unsorted k v)) -> Either LiftError (AsHaskell (PMap 'Unsorted k v))

DerivePlutusType (PMap keysort k v) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.AssocMap

Associated Types

type DPTStrat (PMap keysort k v)

PlutusType (PMap keysort k v) Source # 
Instance details

Defined in Plutarch.LedgerApi.AssocMap

Associated Types

type PInner (PMap keysort k v) :: PType

type PCovariant' (PMap keysort k v)

type PContravariant' (PMap keysort k v)

type PVariant' (PMap keysort k v)

Methods

pcon' :: forall (s :: S). PMap keysort k v s -> Term s (PInner (PMap keysort k v))

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner (PMap keysort k v)) -> (PMap keysort k v s -> Term s b) -> Term s b

(PIsData k, PIsData v, PShow k, PShow v) => PShow (PMap keysort k v) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.AssocMap

Methods

pshow' :: forall (s :: S). Bool -> Term s (PMap keysort k v) -> Term s PString

Generic (PMap keysort k v s) Source # 
Instance details

Defined in Plutarch.LedgerApi.AssocMap

Associated Types

type Rep (PMap keysort k v s) :: Type -> Type Source #

Methods

from :: PMap keysort k v s -> Rep (PMap keysort k v s) x Source #

to :: Rep (PMap keysort k v s) x -> PMap keysort k v s Source #

type PTryFromExcess PData (PAsData (PMap 'Sorted k v)) Source # 
Instance details

Defined in Plutarch.LedgerApi.AssocMap

type PTryFromExcess PData (PAsData (PMap 'Sorted k v)) = Mret (PMap 'Sorted k v)
type PTryFromExcess PData (PAsData (PMap 'Unsorted k v)) Source # 
Instance details

Defined in Plutarch.LedgerApi.AssocMap

type PTryFromExcess PData (PAsData (PMap 'Unsorted k v)) = Mret (PMap 'Unsorted k v)
type AsHaskell (PMap 'Unsorted k v) Source # 
Instance details

Defined in Plutarch.LedgerApi.AssocMap

type AsHaskell (PMap 'Unsorted k v) = Map (AsHaskell k) (AsHaskell v)
type PlutusRepr (PMap 'Unsorted k v) Source # 
Instance details

Defined in Plutarch.LedgerApi.AssocMap

type PlutusRepr (PMap 'Unsorted k v) = [(Data, Data)]
type DPTStrat (PMap keysort k v) Source # 
Instance details

Defined in Plutarch.LedgerApi.AssocMap

type DPTStrat (PMap keysort k v) = PlutusTypeNewtype
type PContravariant' (PMap keysort k v) Source # 
Instance details

Defined in Plutarch.LedgerApi.AssocMap

type PContravariant' (PMap keysort k v) = All2 PContravariant'' (PCode (PMap keysort k v))
type PCovariant' (PMap keysort k v) Source # 
Instance details

Defined in Plutarch.LedgerApi.AssocMap

type PCovariant' (PMap keysort k v) = All2 PCovariant'' (PCode (PMap keysort k v))
type PInner (PMap keysort k v) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.AssocMap

type PInner (PMap keysort k v) = DerivedPInner (DPTStrat (PMap keysort k v)) (PMap keysort k v)
type PVariant' (PMap keysort k v) Source # 
Instance details

Defined in Plutarch.LedgerApi.AssocMap

type PVariant' (PMap keysort k v) = All2 PVariant'' (PCode (PMap keysort k v))
type Rep (PMap keysort k v s) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.AssocMap

type Rep (PMap keysort k v s) = D1 ('MetaData "PMap" "Plutarch.LedgerApi.AssocMap" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PMap" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PBuiltinList (PBuiltinPair (PAsData k) (PAsData v)))))))

data KeyGuarantees Source #

Since: 2.0.0

Constructors

Sorted 
Unsorted 

Utilities

Types

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

@since WIP

Constructors

PDJust (Term s (PAsData a)) 
PDNothing 

Instances

Instances details
PTryFrom PData a => PTryFrom PData (PAsData (PMaybeData a)) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Utils

Associated Types

type PTryFromExcess PData (PAsData (PMaybeData a)) :: PType

Methods

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

PTryFrom PData a => PTryFrom PData (PMaybeData a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Utils

Associated Types

type PTryFromExcess PData (PMaybeData a) :: PType

Methods

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

PIsData (PMaybeData a) Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.Utils

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData (PMaybeData a)) -> Term s (PMaybeData a)

pdataImpl :: forall (s :: S). Term s (PMaybeData a) -> Term s PData

PEq (PMaybeData a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Utils

Methods

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

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

Defined in Plutarch.LedgerApi.Utils

Associated Types

type AsHaskell (PMaybeData a)

type PlutusRepr (PMaybeData a)

Methods

toPlutarchRepr :: AsHaskell (PMaybeData a) -> PlutusRepr (PMaybeData a)

toPlutarch :: forall (s :: S). AsHaskell (PMaybeData a) -> PLifted s (PMaybeData a)

fromPlutarchRepr :: PlutusRepr (PMaybeData a) -> Maybe (AsHaskell (PMaybeData a))

fromPlutarch :: (forall (s :: S). PLifted s (PMaybeData a)) -> Either LiftError (AsHaskell (PMaybeData a))

(PIsData a, PPartialOrd a) => POrd (PMaybeData a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Utils

Methods

pmax :: forall (s :: S). Term s (PMaybeData a) -> Term s (PMaybeData a) -> Term s (PMaybeData a)

pmin :: forall (s :: S). Term s (PMaybeData a) -> Term s (PMaybeData a) -> Term s (PMaybeData a)

(PIsData a, PPartialOrd a) => PPartialOrd (PMaybeData a) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Utils

Methods

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

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

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

(#>) :: forall (s :: S). Term s (PMaybeData a) -> Term s (PMaybeData a) -> Term s PBool

PlutusType (PMaybeData a) Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.Utils

Associated Types

type PInner (PMaybeData a) :: PType

type PCovariant' (PMaybeData a)

type PContravariant' (PMaybeData a)

type PVariant' (PMaybeData a)

Methods

pcon' :: forall (s :: S). PMaybeData a s -> Term s (PInner (PMaybeData a))

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

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

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Utils

Methods

pshow' :: forall (s :: S). Bool -> Term s (PMaybeData a) -> Term s PString

Generic (PMaybeData a s) Source # 
Instance details

Defined in Plutarch.LedgerApi.Utils

Associated Types

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

Methods

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

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

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

Defined in Plutarch.LedgerApi.Utils

type PTryFromExcess PData (PAsData (PMaybeData a)) = PTryFromExcess PData (PInner (PAsData (PMaybeData a)))
type PTryFromExcess PData (PMaybeData a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Utils

type PTryFromExcess PData (PMaybeData a) = PTryFromExcess PData (PInner (PMaybeData a))
type AsHaskell (PMaybeData a) Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.Utils

type AsHaskell (PMaybeData a) = AsHaskell (DeriveDataPLiftable (PMaybeData a) (Maybe (AsHaskell a)))
type PlutusRepr (PMaybeData a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Utils

type PlutusRepr (PMaybeData a) = PlutusRepr (DeriveDataPLiftable (PMaybeData a) (Maybe (AsHaskell a)))
type PContravariant' (PMaybeData a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Utils

type PContravariant' (PMaybeData a) = All2 PContravariant'' (PCode (PMaybeData a))
type PCovariant' (PMaybeData a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Utils

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

Defined in Plutarch.LedgerApi.Utils

type PInner (PMaybeData a) = PData
type PVariant' (PMaybeData a) Source # 
Instance details

Defined in Plutarch.LedgerApi.Utils

type PVariant' (PMaybeData a) = All2 PVariant'' (PCode (PMaybeData a))
type Rep (PMaybeData a s) Source #

Since: 2.0.0

Instance details

Defined in Plutarch.LedgerApi.Utils

type Rep (PMaybeData a s) = D1 ('MetaData "PMaybeData" "Plutarch.LedgerApi.Utils" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'False) (C1 ('MetaCons "PDJust" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PAsData a)))) :+: C1 ('MetaCons "PDNothing" 'PrefixI 'False) (U1 :: Type -> Type))

newtype PRationalData s Source #

A Rational type that corresponds to the data encoding used by Rational.

Since: 3.1.0

Constructors

PRationalData (Term s (PDataRecord '["numerator" ':= PInteger, "denominator" ':= PPositive])) 

Instances

Instances details
PIsData PRationalData Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.Utils

Methods

pfromDataImpl :: forall (s :: S). Term s (PAsData PRationalData) -> Term s PRationalData

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

PDataFields PRationalData Source # 
Instance details

Defined in Plutarch.LedgerApi.Utils

Associated Types

type PFields PRationalData :: [PLabeledType]

Methods

ptoFields :: forall (s :: S). Term s PRationalData -> Term s (PDataRecord (PFields PRationalData))

PEq PRationalData Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.Utils

Methods

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

PLiftable PRationalData Source # 
Instance details

Defined in Plutarch.LedgerApi.Utils

Associated Types

type AsHaskell PRationalData

type PlutusRepr PRationalData

Methods

toPlutarchRepr :: AsHaskell PRationalData -> PlutusRepr PRationalData

toPlutarch :: forall (s :: S). AsHaskell PRationalData -> PLifted s PRationalData

fromPlutarchRepr :: PlutusRepr PRationalData -> Maybe (AsHaskell PRationalData)

fromPlutarch :: (forall (s :: S). PLifted s PRationalData) -> Either LiftError (AsHaskell PRationalData)

POrd PRationalData Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.Utils

Methods

pmax :: forall (s :: S). Term s PRationalData -> Term s PRationalData -> Term s PRationalData

pmin :: forall (s :: S). Term s PRationalData -> Term s PRationalData -> Term s PRationalData

PPartialOrd PRationalData Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.Utils

Methods

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

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

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

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

DerivePlutusType PRationalData Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.Utils

Associated Types

type DPTStrat PRationalData

PlutusType PRationalData Source # 
Instance details

Defined in Plutarch.LedgerApi.Utils

Associated Types

type PInner PRationalData :: PType

type PCovariant' PRationalData

type PContravariant' PRationalData

type PVariant' PRationalData

Methods

pcon' :: forall (s :: S). PRationalData s -> Term s (PInner PRationalData)

pmatch' :: forall (s :: S) (b :: PType). Term s (PInner PRationalData) -> (PRationalData s -> Term s b) -> Term s b

PShow PRationalData Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.Utils

Methods

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

PTryFrom PData PRationalData Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.Utils

Associated Types

type PTryFromExcess PData PRationalData :: PType

Methods

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

PTryFrom PData (PAsData PRationalData) Source #

This instance produces a verified positive denominator as the excess output.

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.Utils

Associated Types

type PTryFromExcess PData (PAsData PRationalData) :: PType

Methods

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

Generic (PRationalData s) Source # 
Instance details

Defined in Plutarch.LedgerApi.Utils

Associated Types

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

type PFields PRationalData Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.Utils

type PFields PRationalData = Helper (PInner PRationalData)
type AsHaskell PRationalData Source #

@since WIP

Instance details

Defined in Plutarch.LedgerApi.Utils

type AsHaskell PRationalData = AsHaskell (DeriveDataPLiftable PRationalData Rational)
type PlutusRepr PRationalData Source # 
Instance details

Defined in Plutarch.LedgerApi.Utils

type PlutusRepr PRationalData = PlutusRepr (DeriveDataPLiftable PRationalData Rational)
type DPTStrat PRationalData Source # 
Instance details

Defined in Plutarch.LedgerApi.Utils

type DPTStrat PRationalData = PlutusTypeData
type PContravariant' PRationalData Source # 
Instance details

Defined in Plutarch.LedgerApi.Utils

type PContravariant' PRationalData = All2 PContravariant'' (PCode PRationalData)
type PCovariant' PRationalData Source # 
Instance details

Defined in Plutarch.LedgerApi.Utils

type PCovariant' PRationalData = All2 PCovariant'' (PCode PRationalData)
type PInner PRationalData Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.Utils

type PInner PRationalData = DerivedPInner (DPTStrat PRationalData) PRationalData
type PVariant' PRationalData Source # 
Instance details

Defined in Plutarch.LedgerApi.Utils

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

Defined in Plutarch.LedgerApi.Utils

type PTryFromExcess PData PRationalData = Mret PPositive
type PTryFromExcess PData (PAsData PRationalData) Source # 
Instance details

Defined in Plutarch.LedgerApi.Utils

type PTryFromExcess PData (PAsData PRationalData) = Mret PPositive
type Rep (PRationalData s) Source #

Since: 3.1.0

Instance details

Defined in Plutarch.LedgerApi.Utils

type Rep (PRationalData s) = D1 ('MetaData "PRationalData" "Plutarch.LedgerApi.Utils" "plutarch-ledger-api-3.2.1-6pZLN6XlvMZ4r7ZEuopoAx" 'True) (C1 ('MetaCons "PRationalData" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Term s (PDataRecord '["numerator" ':= PInteger, "denominator" ':= PPositive])))))

Utilities

pfromDJust :: forall (a :: S -> Type) (s :: S). PIsData a => Term s (PMaybeData a :--> a) Source #

Extracts the element out of a PDJust and throws an error if its argument is PDNothing.

Since: 2.1.1

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

Yield PTrue if a given PMaybeData is of the form PDJust _.

Since: 2.1.1

pmaybeData :: forall (a :: S -> Type) (b :: S -> Type) (s :: S). PIsData a => Term s (b :--> ((a :--> b) :--> (PMaybeData a :--> b))) Source #

Special version of pmaybe that works with PMaybeData.

Since: 2.1.1

pdjust :: forall (a :: S -> Type) (s :: S). PIsData a => Term s (a :--> PMaybeData a) Source #

Construct a PDJust value.

Since: 2.1.1

pdnothing :: forall (a :: S -> Type) (s :: S). Term s (PMaybeData a) Source #

Construct a PDNothing value.

Since: 2.1.1

pmaybeToMaybeData :: forall (a :: S -> Type) (s :: S). PIsData a => Term s (PMaybe a :--> PMaybeData a) Source #

Construct a PMaybeData given a PMaybe. Could be useful if you want to "lift" from PMaybe to Maybe.

Since: 2.1.1

passertPDJust :: forall (a :: S -> Type) (s :: S). PIsData a => Term s (PString :--> (PMaybeData a :--> a)) Source #

Extract the value stored in a PMaybeData container. If there's no value, throw an error with the given message.

Since: 2.1.1

prationalFromData :: ClosedTerm (PRationalData :--> PRational) Source #

Since: 3.1.0