ytxp-plutarch-0.1.0: Control scripts, types, and utilities for the YTxP architecture
Safe HaskellSafe-Inferred
LanguageHaskell2010

Cardano.YTxP.Control.Yielding

Description

Add note on orphan instances. We want to have the haskell types come from the shared SDK so that other onchain implementations can reuse those same types. This however, forces us to declare orphan instances for haskell -> plutarch conversion

Synopsis

Documentation

getAuthorisedScriptHash :: forall (s :: S). Term s (PCurrencySymbol :--> (PBuiltinList (PAsData PTxInInfo) :--> (PYieldingRedeemer :--> PScriptHash))) Source #

Given a list of reference inputs and a Yielding Redeemer, dig out the authorised script hash by:

  • Indexing the reference inputs according to the redeemer
  • Checking the fetched reference input for the correct AuthorisedScriptsSTCS
  • Returning the AuthorisedScriptHash

data PAuthorisedScriptPurpose (s :: S) Source #

Constructors

PMinting 
PSpending 
PRewarding 

Instances

Instances details
PEq PAuthorisedScriptPurpose Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

Methods

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

PIsData PAuthorisedScriptPurpose Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

Methods

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

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

DerivePlutusType PAuthorisedScriptPurpose Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

Associated Types

type DPTStrat PAuthorisedScriptPurpose

PlutusType PAuthorisedScriptPurpose Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

Associated Types

type PInner PAuthorisedScriptPurpose :: PType

type PCovariant' PAuthorisedScriptPurpose

type PContravariant' PAuthorisedScriptPurpose

type PVariant' PAuthorisedScriptPurpose

Methods

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

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

PUnsafeLiftDecl PAuthorisedScriptPurpose Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

Associated Types

type PLifted PAuthorisedScriptPurpose = (r :: Type)

PTryFrom PData (PAsData PAuthorisedScriptPurpose) Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

Associated Types

type PTryFromExcess PData (PAsData PAuthorisedScriptPurpose) :: PType

Methods

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

Bounded (PAuthorisedScriptPurpose s) Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

Enum (PAuthorisedScriptPurpose s) Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

Generic (PAuthorisedScriptPurpose s) Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

Associated Types

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

type DPTStrat PAuthorisedScriptPurpose Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

type PContravariant' PAuthorisedScriptPurpose Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

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

Defined in Cardano.YTxP.Control.Yielding

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

Defined in Cardano.YTxP.Control.Yielding

type PVariant' PAuthorisedScriptPurpose Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

type PVariant' PAuthorisedScriptPurpose = All2 PVariant'' (PCode PAuthorisedScriptPurpose)
type PLifted PAuthorisedScriptPurpose Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

type PLifted PAuthorisedScriptPurpose = AuthorisedScriptPurpose
type PTryFromExcess PData (PAsData PAuthorisedScriptPurpose) Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

type PTryFromExcess PData (PAsData PAuthorisedScriptPurpose) = PTryFromExcess PData (PInner (PAsData PAuthorisedScriptPurpose))
type Rep (PAuthorisedScriptPurpose s) Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

type Rep (PAuthorisedScriptPurpose s) = D1 ('MetaData "PAuthorisedScriptPurpose" "Cardano.YTxP.Control.Yielding" "ytxp-plutarch-0.1.0-B6ap1x8UFi7IOd7qlOwhiu" 'False) (C1 ('MetaCons "PMinting" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PSpending" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PRewarding" 'PrefixI 'False) (U1 :: Type -> Type)))

data PYieldingRedeemer (s :: S) Source #

Instances

Instances details
PIsData PYieldingRedeemer Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

Methods

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

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

PDataFields PYieldingRedeemer Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

Associated Types

type PFields PYieldingRedeemer :: [PLabeledType]

Methods

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

DerivePlutusType PYieldingRedeemer Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

Associated Types

type DPTStrat PYieldingRedeemer

PlutusType PYieldingRedeemer Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

Associated Types

type PInner PYieldingRedeemer :: PType

type PCovariant' PYieldingRedeemer

type PContravariant' PYieldingRedeemer

type PVariant' PYieldingRedeemer

Methods

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

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

PUnsafeLiftDecl PYieldingRedeemer Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

Associated Types

type PLifted PYieldingRedeemer = (r :: Type)

PTryFrom PData (PAsData PYieldingRedeemer) Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

Associated Types

type PTryFromExcess PData (PAsData PYieldingRedeemer) :: PType

Methods

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

Generic (PYieldingRedeemer s) Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

Associated Types

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

type PFields PYieldingRedeemer Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

type PFields PYieldingRedeemer = Helper (PInner PYieldingRedeemer)
type DPTStrat PYieldingRedeemer Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

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

Defined in Cardano.YTxP.Control.Yielding

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

Defined in Cardano.YTxP.Control.Yielding

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

Defined in Cardano.YTxP.Control.Yielding

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

Defined in Cardano.YTxP.Control.Yielding

type PVariant' PYieldingRedeemer = All2 PVariant'' (PCode PYieldingRedeemer)
type PLifted PYieldingRedeemer Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

type PLifted PYieldingRedeemer = YieldingRedeemer
type PTryFromExcess PData (PAsData PYieldingRedeemer) Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

type PTryFromExcess PData (PAsData PYieldingRedeemer) = PTryFromExcess PData (PInner (PAsData PYieldingRedeemer))
type Rep (PYieldingRedeemer s) Source # 
Instance details

Defined in Cardano.YTxP.Control.Yielding

Orphan instances

PConstantDecl AuthorisedScriptIndex Source # 
Instance details

Associated Types

type PConstantRepr AuthorisedScriptIndex

type PConstanted AuthorisedScriptIndex :: PType

Methods

pconstantToRepr :: AuthorisedScriptIndex -> PConstantRepr AuthorisedScriptIndex

pconstantFromRepr :: PConstantRepr AuthorisedScriptIndex -> Maybe AuthorisedScriptIndex

PConstantDecl AuthorisedScriptProofIndex Source # 
Instance details

Associated Types

type PConstantRepr AuthorisedScriptProofIndex

type PConstanted AuthorisedScriptProofIndex :: PType

Methods

pconstantToRepr :: AuthorisedScriptProofIndex -> PConstantRepr AuthorisedScriptProofIndex

pconstantFromRepr :: PConstantRepr AuthorisedScriptProofIndex -> Maybe AuthorisedScriptProofIndex

PConstantDecl AuthorisedScriptPurpose Source # 
Instance details

Associated Types

type PConstantRepr AuthorisedScriptPurpose

type PConstanted AuthorisedScriptPurpose :: PType

Methods

pconstantToRepr :: AuthorisedScriptPurpose -> PConstantRepr AuthorisedScriptPurpose

pconstantFromRepr :: PConstantRepr AuthorisedScriptPurpose -> Maybe AuthorisedScriptPurpose

PConstantDecl YieldingRedeemer Source # 
Instance details

Associated Types

type PConstantRepr YieldingRedeemer

type PConstanted YieldingRedeemer :: PType

Methods

pconstantToRepr :: YieldingRedeemer -> PConstantRepr YieldingRedeemer

pconstantFromRepr :: PConstantRepr YieldingRedeemer -> Maybe YieldingRedeemer