cardano-api
Safe HaskellNone
LanguageHaskell2010

Cardano.Api.Experimental

Description

This module provides an experimental library interface intended to replace the existing API. It is subject to significant changes. Please, use it with caution.

Synopsis

Creating transactions

For details and an example of creating a transaction using the experimental API, see the Cardano.Api.Experimental.Tx documentation.

Contents

Transaction-related

data UnsignedTx era Source #

A transaction that can contain everything except key witnesses.

Constructors

EraTx (LedgerEra era) => UnsignedTx (Tx (LedgerEra era)) 

Instances

Instances details
HasTypeProxy era => HasTypeProxy (UnsignedTx era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx

Associated Types

data AsType (UnsignedTx era) 
Instance details

Defined in Cardano.Api.Experimental.Tx

(HasTypeProxy era, EraTx (LedgerEra era)) => SerialiseAsRawBytes (UnsignedTx era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx

Show (UnsignedTx era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx

Eq (UnsignedTx era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx

Methods

(==) :: UnsignedTx era -> UnsignedTx era -> Bool Source #

(/=) :: UnsignedTx era -> UnsignedTx era -> Bool Source #

data AsType (UnsignedTx era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx

data SignedTx era Source #

A transaction that has been witnesssed

Constructors

EraTx (LedgerEra era) => SignedTx (Tx (LedgerEra era)) 

Instances

Instances details
HasTypeProxy era => HasTypeProxy (SignedTx era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx

Associated Types

data AsType (SignedTx era) 
Instance details

Defined in Cardano.Api.Experimental.Tx

data AsType (SignedTx era) = AsSignedTx (AsType era)
(HasTypeProxy era, EraTx (LedgerEra era)) => SerialiseAsRawBytes (SignedTx era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx

Show (SignedTx era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx

Eq (SignedTx era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx

Methods

(==) :: SignedTx era -> SignedTx era -> Bool Source #

(/=) :: SignedTx era -> SignedTx era -> Bool Source #

data AsType (SignedTx era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx

data AsType (SignedTx era) = AsSignedTx (AsType era)

Transaction fee related

estimateBalancedTxBody Source #

Arguments

:: HasCallStack 
=> Era era 
-> TxBodyContent BuildTx era 
-> PParams (LedgerEra era) 
-> Set PoolId

The set of registered stake pools, being unregistered in this transaction.

-> Map StakeCredential Coin

A map of all deposits for stake credentials that are being unregistered in this transaction.

-> Map (Credential 'DRepRole) Coin

A map of all deposits for DRep credentials that are being unregistered in this transaction.

-> Map (PlutusPurpose AsIx (LedgerEra era)) ExecutionUnits

Plutus script execution units.

-> Coin

Total potential collateral amount.

-> Int

The number of key witnesses to be added to the transaction.

-> Int

The number of Byron key witnesses to be added to the transaction.

-> Int

The size of all reference scripts in bytes.

-> AddressInEra era

Change address.

-> Value

Total value of UTXOs being spent.

-> Either (TxFeeEstimationError era) (BalancedTxBody era) 

Use when you do not have access to the UTxOs you intend to spend

Era-related

data BabbageEra Source #

A type used as a tag to distinguish the Babbage era.

Instances

Instances details
IsCardanoEra BabbageEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Core

IsAllegraBasedEra BabbageEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Eon.AllegraEraOnwards

IsAlonzoBasedEra BabbageEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Eon.AlonzoEraOnwards

IsBabbageBasedEra BabbageEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Eon.BabbageEraOnwards

IsMaryBasedEra BabbageEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Eon.MaryEraOnwards

IsShelleyBasedEra BabbageEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Eon.ShelleyBasedEra

HasTypeProxy BabbageEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Core

Associated Types

data AsType BabbageEra 
Instance details

Defined in Cardano.Api.Era.Internal.Core

HasScriptLanguageInEra PlutusScriptV1 BabbageEra Source # 
Instance details

Defined in Cardano.Api.Plutus.Internal.Script

HasScriptLanguageInEra PlutusScriptV2 BabbageEra Source # 
Instance details

Defined in Cardano.Api.Plutus.Internal.Script

ToAlonzoScript PlutusScriptV1 BabbageEra Source # 
Instance details

Defined in Cardano.Api.Plutus.Internal.Script

ToAlonzoScript PlutusScriptV2 BabbageEra Source # 
Instance details

Defined in Cardano.Api.Plutus.Internal.Script

data AsType BabbageEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Core

data ConwayEra Source #

A type used as a tag to distinguish the Conway era.

Instances

Instances details
IsCardanoEra ConwayEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Core

IsAllegraBasedEra ConwayEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Eon.AllegraEraOnwards

IsAlonzoBasedEra ConwayEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Eon.AlonzoEraOnwards

IsBabbageBasedEra ConwayEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Eon.BabbageEraOnwards

IsConwayBasedEra ConwayEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Eon.ConwayEraOnwards

IsMaryBasedEra ConwayEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Eon.MaryEraOnwards

IsShelleyBasedEra ConwayEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Eon.ShelleyBasedEra

IsEra ConwayEra Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

HasTypeProxy ConwayEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Core

Associated Types

data AsType ConwayEra 
Instance details

Defined in Cardano.Api.Era.Internal.Core

HasScriptLanguageInEra PlutusScriptV1 ConwayEra Source # 
Instance details

Defined in Cardano.Api.Plutus.Internal.Script

HasScriptLanguageInEra PlutusScriptV2 ConwayEra Source # 
Instance details

Defined in Cardano.Api.Plutus.Internal.Script

HasScriptLanguageInEra PlutusScriptV3 ConwayEra Source # 
Instance details

Defined in Cardano.Api.Plutus.Internal.Script

ToAlonzoScript PlutusScriptV1 ConwayEra Source # 
Instance details

Defined in Cardano.Api.Plutus.Internal.Script

ToAlonzoScript PlutusScriptV2 ConwayEra Source # 
Instance details

Defined in Cardano.Api.Plutus.Internal.Script

ToAlonzoScript PlutusScriptV3 ConwayEra Source # 
Instance details

Defined in Cardano.Api.Plutus.Internal.Script

data AsType ConwayEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Core

data Era era where Source #

Represents the latest Cardano blockchain eras, including the one currently on mainnet and the upcoming one.

After a hard fork takes place, the era on mainnet before the hard fork is deprecated and, after a deprecation period, removed from cardano-api. During the deprecation period, cardano-api users should update their codebase to the new mainnet era.

Constructors

ConwayEra :: Era ConwayEra

The currently active era on the Cardano mainnet.

DijkstraEra :: Era DijkstraEra 

Instances

Instances details
Eon Era Source #

A temporary compatibility instance for easier conversion between the experimental and old APIs.

Instance details

Defined in Cardano.Api.Experimental.Era

Methods

inEonForEra :: a -> (Era era -> a) -> CardanoEra era -> a Source #

ToCardanoEra Era Source #

A temporary compatibility instance for easier conversion between the experimental and old APIs.

Instance details

Defined in Cardano.Api.Experimental.Era

Methods

toCardanoEra :: Era era -> CardanoEra era Source #

TestEquality Era Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Methods

testEquality :: Era a -> Era b -> Maybe (a :~: b) Source #

Convert ConwayEraOnwards Era Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Methods

convert :: ConwayEraOnwards era -> Era era Source #

Convert Era CardanoEra Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Methods

convert :: Era era -> CardanoEra era Source #

Convert Era AlonzoEraOnwards Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Methods

convert :: Era era -> AlonzoEraOnwards era Source #

Convert Era BabbageEraOnwards Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Methods

convert :: Era era -> BabbageEraOnwards era Source #

Convert Era ConwayEraOnwards Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Methods

convert :: Era era -> ConwayEraOnwards era Source #

Convert Era MaryEraOnwards Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Methods

convert :: Era era -> MaryEraOnwards era Source #

Convert Era ShelleyBasedEra Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Methods

convert :: Era era -> ShelleyBasedEra era Source #

ToJSON (Era era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Methods

toJSON :: Era era -> Value #

toEncoding :: Era era -> Encoding #

toJSONList :: [Era era] -> Value #

toEncodingList :: [Era era] -> Encoding #

omitField :: Era era -> Bool #

Show (Era era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Methods

showsPrec :: Int -> Era era -> ShowS Source #

show :: Era era -> String Source #

showList :: [Era era] -> ShowS Source #

Eq (Era era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Methods

(==) :: Era era -> Era era -> Bool Source #

(/=) :: Era era -> Era era -> Bool Source #

Pretty (Era era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Methods

pretty :: Era era -> Doc ann #

prettyList :: [Era era] -> Doc ann #

FromJSON (Some Era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Methods

parseJSON :: Value -> Parser (Some Era) #

parseJSONList :: Value -> Parser [Some Era] #

omittedField :: Maybe (Some Era) #

ToJSON (Some Era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Methods

toJSON :: Some Era -> Value #

toEncoding :: Some Era -> Encoding #

toJSONList :: [Some Era] -> Value #

toEncodingList :: [Some Era] -> Encoding #

omitField :: Some Era -> Bool #

Bounded (Some Era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Enum (Some Era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Show (Some Era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Eq (Some Era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Methods

(==) :: Some Era -> Some Era -> Bool Source #

(/=) :: Some Era -> Some Era -> Bool Source #

Ord (Some Era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Pretty (Some Era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Methods

pretty :: Some Era -> Doc ann #

prettyList :: [Some Era] -> Doc ann #

class IsEra era where Source #

Type class interface for the Era type.

Methods

useEra :: Era era Source #

Instances

Instances details
IsEra ConwayEra Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

IsEra DijkstraEra Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

data Some (f :: k -> Type) where Source #

An existential wrapper for types of kind k -> Type. It can hold any era, for example, Some Era. The era witness can be brought back into scope, for example, using this pattern:

anyEra = Some ConwayEra
-- then later in the code
Some era <- pure anyEra
obtainCommonConstraints era foo

Constructors

Some :: forall {k} (f :: k -> Type) (a :: k). (Typeable a, Typeable (f a)) => f a -> Some f 

Instances

Instances details
FromJSON (Some Era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Methods

parseJSON :: Value -> Parser (Some Era) #

parseJSONList :: Value -> Parser [Some Era] #

omittedField :: Maybe (Some Era) #

ToJSON (Some Era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Methods

toJSON :: Some Era -> Value #

toEncoding :: Some Era -> Encoding #

toJSONList :: [Some Era] -> Value #

toEncodingList :: [Some Era] -> Encoding #

omitField :: Some Era -> Bool #

Bounded (Some Era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Enum (Some Era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Show (Some Era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Eq (Some Era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Methods

(==) :: Some Era -> Some Era -> Bool Source #

(/=) :: Some Era -> Some Era -> Bool Source #

Ord (Some Era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Pretty (Some Era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Methods

pretty :: Some Era -> Doc ann #

prettyList :: [Some Era] -> Doc ann #

type family LedgerEra era = (r :: Type) | r -> era where ... Source #

Users typically interact with the latest features on the mainnet or experiment with features from the upcoming era. Therefore, protocol versions are limited to the current mainnet era and the next (upcoming) era.

newtype DeprecatedEra era Source #

Constructors

DeprecatedEra (ShelleyBasedEra era) 

Instances

Instances details
Error (DeprecatedEra era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Methods

prettyError :: DeprecatedEra era -> Doc ann Source #

Show (DeprecatedEra era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Pretty (DeprecatedEra era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Era

Methods

pretty :: DeprecatedEra era -> Doc ann #

prettyList :: [DeprecatedEra era] -> Doc ann #

eraToSbe :: Era era -> ShelleyBasedEra era Source #

Deprecated: Use convert instead.

How to deprecate an era:

  1. Add the DEPRECATED pragma to the era type tag and constructor at the same time:
{-# DEPRECATED BabbageEra "BabbageEra no longer supported, use ConwayEra" #-}
data BabbageEra
  1. Update the Haddock documentation for the constructor of the deprecated era, mentioning the deprecation.
data Era era where
  {-# DEPRECATED BabbageEra "BabbageEra no longer supported, use ConwayEra" #-}
  BabbageEra :: Era BabbageEra
  -- | The era currently active on Cardano's mainnet.
  ConwayEra :: Era ConwayEra
  1. Add a new IsEra instance and update the deprecated era instance to produce a compile-time error:
instance TypeError ('Text "IsEra BabbageEra: Deprecated. Update to ConwayEra") => IsEra BabbageEra where
  useEra = error "unreachable"

instance IsEra ConwayEra where
  useEra = ConwayEra

eraToBabbageEraOnwards :: Era era -> BabbageEraOnwards era Source #

Deprecated: Use convert instead.

Witness related

data AnyWitness era where Source #

Here we consider three types of witnesses in Cardano: * key witnesses * simple script witnesses * Plutus script witnesses

Note that AnyKeyWitnessPlaceholder does not contain the actual key witness. This is because key witnesses are provided in the signing stage of the transaction. However we need this constuctor to index the witnessable things correctly when plutus scripts are being used within the transaction. AnyWitness is solely used to contruct the transaction body.

Constructors

AnyKeyWitnessPlaceholder :: forall era. AnyWitness era 
AnySimpleScriptWitness :: forall era. SimpleScriptOrReferenceInput era -> AnyWitness era 
AnyPlutusScriptWitness :: forall (lang :: Language) (purpose :: PlutusScriptPurpose) era. PlutusScriptWitness lang purpose era -> AnyWitness era 

Instances

Instances details
Show (AnyWitness era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx.Internal.AnyWitness

data PlutusScriptWitness (lang :: Language) (purpose :: PlutusScriptPurpose) era where Source #

This is a Plutus script witness. It possesses: 1. The plutus script or reference input 2. The script redeemer 3. The execution units 4. Potentially a script datum. See the PlutusScriptDatum type family for more details.

Note that Plutus script witnesses do not exist on their own. They must witness something and a redeemer pointer must be constucted to point to the thing being witnessed. See IndexedPlutusScriptWitness for more details.

Constructors

PlutusScriptWitness :: forall (lang :: Language) era (purpose :: PlutusScriptPurpose). SLanguage lang -> PlutusScriptOrReferenceInput lang era -> PlutusScriptDatum lang purpose -> ScriptRedeemer -> ExecutionUnits -> PlutusScriptWitness lang purpose era 

Instances

Instances details
Show (PlutusScriptWitness lang purpose era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Plutus.Internal.ScriptWitness

Methods

showsPrec :: Int -> PlutusScriptWitness lang purpose era -> ShowS Source #

show :: PlutusScriptWitness lang purpose era -> String Source #

showList :: [PlutusScriptWitness lang purpose era] -> ShowS Source #

data TxScriptWitnessRequirements era Source #

This type collects all the requirements for script witnesses in a transaction.

Instances

Instances details
Monoid (TxScriptWitnessRequirements AlonzoEra) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx.Internal.TxScriptWitnessRequirements

Monoid (TxScriptWitnessRequirements BabbageEra) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx.Internal.TxScriptWitnessRequirements

Monoid (TxScriptWitnessRequirements ConwayEra) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx.Internal.TxScriptWitnessRequirements

Monoid (TxScriptWitnessRequirements DijkstraEra) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx.Internal.TxScriptWitnessRequirements

Semigroup (TxScriptWitnessRequirements AlonzoEra) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx.Internal.TxScriptWitnessRequirements

Semigroup (TxScriptWitnessRequirements BabbageEra) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx.Internal.TxScriptWitnessRequirements

Semigroup (TxScriptWitnessRequirements ConwayEra) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx.Internal.TxScriptWitnessRequirements

Semigroup (TxScriptWitnessRequirements DijkstraEra) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx.Internal.TxScriptWitnessRequirements

data Witnessable (thing :: WitnessableItem) era where Source #

These are all of the "things" a plutus script can witness. We include the relevant type class constraint to avoid boilerplate when creating the PlutusPurpose in the toPlutusScriptPurpose.

Constructors

WitTxIn :: forall era. AlonzoEraScript era => TxIn -> Witnessable 'TxInItem era 
WitTxCert :: forall era. (EraTxCert era, AlonzoEraScript era) => TxCert era -> StakeCredential -> Witnessable 'CertItem era 
WitMint :: forall era. AlonzoEraScript era => PolicyId -> PolicyAssets -> Witnessable 'MintItem era 
WitWithdrawal :: forall era. AlonzoEraScript era => StakeAddress -> Coin -> Witnessable 'WithdrawalItem era 
WitVote :: forall era. ConwayEraScript era => Voter -> Witnessable 'VoterItem era 
WitProposal :: forall era. (ConwayEraScript era, EraPParams era) => ProposalProcedure era -> Witnessable 'ProposalItem era 

Instances

Instances details
Show (Witnessable thing era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Plutus.Internal.IndexedPlutusScriptWitness

Methods

showsPrec :: Int -> Witnessable thing era -> ShowS Source #

show :: Witnessable thing era -> String Source #

showList :: [Witnessable thing era] -> ShowS Source #

Eq (Witnessable thing era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Plutus.Internal.IndexedPlutusScriptWitness

Methods

(==) :: Witnessable thing era -> Witnessable thing era -> Bool Source #

(/=) :: Witnessable thing era -> Witnessable thing era -> Bool Source #

Simple script related

data SimpleScript era where Source #

A simple script in a particular era. We leverage ledger's Cardano.Api.Experimental.ErasraScript type class methods to work with the script.

Constructors

SimpleScript :: forall era. EraScript era => NativeScript era -> SimpleScript era 

Instances

Instances details
Show (SimpleScript era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Simple.Script

Eq (SimpleScript era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Simple.Script

Plutus related

data PlutusScriptInEra (lang :: Language) era where Source #

A Plutus script in a particular era. Why PlutusRunnable? Mainly for deserialization benefits. The deserialization of this type looks at the major protocol version and the script language to determine if indeed the script is runnable. This is a dramatic improvement over the old api which essentially read a ByteString and hoped for the best. Any failures due to malformed/invalid scripts were caught upon transaction submission or running the script when attempting to predict the necessary execution units.

Where do we get the major protocol version from? In order to access the major protocol version we pass in an era type parameter which can be translated to the major protocol version.

Where do we get the script language from? The serialized version of PlutusRunnable encodes the script language. See `DecCBOR (PlutusRunnable l)` in cardano-ledger for more details.

Constructors

PlutusScriptInEra :: forall (lang :: Language) era. PlutusRunnable lang -> PlutusScriptInEra lang era 

Instances

Instances details
Show (PlutusScriptInEra lang era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Plutus.Internal.Script

Eq (PlutusScriptInEra lang era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Plutus.Internal.Script

Methods

(==) :: PlutusScriptInEra lang era -> PlutusScriptInEra lang era -> Bool Source #

(/=) :: PlutusScriptInEra lang era -> PlutusScriptInEra lang era -> Bool Source #

data PlutusScriptOrReferenceInput (lang :: Language) era Source #

You can provide the plutus script directly in the transaction or a reference input that points to the script in the UTxO. Using a reference script saves space in your transaction.

data IndexedPlutusScriptWitness (witnessable :: WitnessableItem) (lang :: Language) (purpose :: PlutusScriptPurpose) era where Source #

A Plutus script witness along the thing it is witnessing and the index of that thing. E.g transaction input, certificate, withdrawal, minting policy, etc. A Plutus script witness only makes sense in the context of what it is witnessing and the index of the thing it is witnessing.

Constructors

IndexedPlutusScriptWitness :: forall era (witnessable :: WitnessableItem) (lang :: Language) (purpose :: PlutusScriptPurpose). AlonzoEraScript era => Witnessable witnessable era -> PlutusPurpose AsIx era -> PlutusScriptWitness lang purpose era -> IndexedPlutusScriptWitness witnessable lang purpose era 

Instances

Instances details
Show (IndexedPlutusScriptWitness witnessable lang purpose era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Plutus.Internal.IndexedPlutusScriptWitness

Methods

showsPrec :: Int -> IndexedPlutusScriptWitness witnessable lang purpose era -> ShowS Source #

show :: IndexedPlutusScriptWitness witnessable lang purpose era -> String Source #

showList :: [IndexedPlutusScriptWitness witnessable lang purpose era] -> ShowS Source #

data PlutusScriptPurpose Source #

Every Plutus script has a purpose that indicates what that script is witnessing.

Constructors

SpendingScript

Witnesses a transaction input

MintingScript

Witnesses a minting policy

WithdrawingScript

Witnesses a withdrawal

CertifyingScript

Witnesses a certificate

ProposingScript

Witnesses a proposal

VotingScript

Witnesses a vote

data PlutusScriptDatum (lang :: Language) (purpose :: PlutusScriptPurpose) where Source #

Constructors

SpendingScriptDatum :: forall (lang :: Language). PlutusScriptDatumF lang 'SpendingScript -> PlutusScriptDatum lang 'SpendingScript 
InlineDatum :: forall (lang :: Language) (purpose :: PlutusScriptPurpose). PlutusScriptDatum lang purpose 
NoScriptDatum :: forall (lang :: Language) (purpose :: PlutusScriptPurpose). PlutusScriptDatum lang purpose 

Instances

Instances details
Show (PlutusScriptDatum lang purpose) Source # 
Instance details

Defined in Cardano.Api.Experimental.Plutus.Internal.ScriptWitness

Methods

showsPrec :: Int -> PlutusScriptDatum lang purpose -> ShowS Source #

show :: PlutusScriptDatum lang purpose -> String Source #

showList :: [PlutusScriptDatum lang purpose] -> ShowS Source #

Certificate related

data Certificate era where Source #

Constructors

Certificate :: forall era. EraTxCert era => TxCert era -> Certificate era 

Instances

Instances details
Typeable era => HasTypeProxy (Certificate era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx.Internal.Certificate.Type

Associated Types

data AsType (Certificate era) 
Instance details

Defined in Cardano.Api.Experimental.Tx.Internal.Certificate.Type

(Typeable ledgerera, EraTxCert ledgerera) => SerialiseAsCBOR (Certificate ledgerera) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx.Internal.Certificate.Type

(Typeable ledgerera, EraTxCert ledgerera) => HasTextEnvelope (Certificate ledgerera) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx.Internal.Certificate.Type

Show (Certificate era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx.Internal.Certificate.Type

Eq (Certificate era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx.Internal.Certificate.Type

Methods

(==) :: Certificate era -> Certificate era -> Bool Source #

(/=) :: Certificate era -> Certificate era -> Bool Source #

Ord (Certificate era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx.Internal.Certificate.Type

data AsType (Certificate era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx.Internal.Certificate.Type

Registering stake address and delegating

Registering stake pools

Governance related certificates

Data family instances

data family AsType t Source #

A family of singleton types used in this API to indicate which type to use where it would otherwise be ambiguous or merely unclear.

Values of this type are passed to deserialisation functions for example.

Instances

Instances details
data AsType ByteString Source # 
Instance details

Defined in Cardano.Api.HasTypeProxy

data AsType AddressAny Source # 
Instance details

Defined in Cardano.Api.Address

data AsType ByronAddr Source # 
Instance details

Defined in Cardano.Api.Address

data AsType ShelleyAddr Source # 
Instance details

Defined in Cardano.Api.Address

data AsType StakeAddress Source # 
Instance details

Defined in Cardano.Api.Address

data AsType BlockHeader Source # 
Instance details

Defined in Cardano.Api.Block

data AsType ByronKey Source # 
Instance details

Defined in Cardano.Api.Byron.Internal.Key

data AsType ByronKeyLegacy Source # 
Instance details

Defined in Cardano.Api.Byron.Internal.Key

data AsType ByronUpdateProposal Source # 
Instance details

Defined in Cardano.Api.Byron.Internal.Proposal

data AsType ByronVote Source # 
Instance details

Defined in Cardano.Api.Byron.Internal.Proposal

data AsType DRepMetadata Source # 
Instance details

Defined in Cardano.Api.Certificate.Internal.DRepMetadata

data AsType OperationalCertificate Source # 
Instance details

Defined in Cardano.Api.Certificate.Internal.OperationalCertificate

data AsType OperationalCertificateIssueCounter Source # 
Instance details

Defined in Cardano.Api.Certificate.Internal.OperationalCertificate

data AsType StakePoolMetadata Source # 
Instance details

Defined in Cardano.Api.Certificate.Internal.StakePoolMetadata

data AsType AllegraEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Core

data AsType AlonzoEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Core

data AsType BabbageEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Core

data AsType ByronEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Core

data AsType ConwayEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Core

data AsType DijkstraEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Core

data AsType MaryEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Core

data AsType ShelleyEra Source # 
Instance details

Defined in Cardano.Api.Era.Internal.Core

data AsType GovernancePoll Source # 
Instance details

Defined in Cardano.Api.Governance.Internal.Poll

data AsType GovernancePollAnswer Source # 
Instance details

Defined in Cardano.Api.Governance.Internal.Poll

data AsType CommitteeColdExtendedKey Source # 
Instance details

Defined in Cardano.Api.Key.Internal

data AsType CommitteeColdKey Source # 
Instance details

Defined in Cardano.Api.Key.Internal

data AsType CommitteeHotExtendedKey Source # 
Instance details

Defined in Cardano.Api.Key.Internal

data AsType CommitteeHotKey Source # 
Instance details

Defined in Cardano.Api.Key.Internal

data AsType DRepExtendedKey Source # 
Instance details

Defined in Cardano.Api.Key.Internal

data AsType DRepKey Source # 
Instance details

Defined in Cardano.Api.Key.Internal

data AsType GenesisDelegateExtendedKey Source # 
Instance details

Defined in Cardano.Api.Key.Internal

data AsType GenesisDelegateKey Source # 
Instance details

Defined in Cardano.Api.Key.Internal

data AsType GenesisExtendedKey Source # 
Instance details

Defined in Cardano.Api.Key.Internal

data AsType GenesisKey Source # 
Instance details

Defined in Cardano.Api.Key.Internal

data AsType GenesisUTxOKey Source # 
Instance details

Defined in Cardano.Api.Key.Internal

data AsType PaymentExtendedKey Source # 
Instance details

Defined in Cardano.Api.Key.Internal

data AsType PaymentKey Source # 
Instance details

Defined in Cardano.Api.Key.Internal

data AsType StakeExtendedKey Source # 
Instance details

Defined in Cardano.Api.Key.Internal

data AsType StakeKey Source # 
Instance details

Defined in Cardano.Api.Key.Internal

data AsType StakePoolExtendedKey Source # 
Instance details

Defined in Cardano.Api.Key.Internal

data AsType StakePoolKey Source # 
Instance details

Defined in Cardano.Api.Key.Internal

data AsType KesKey Source # 
Instance details

Defined in Cardano.Api.Key.Internal.Praos

data AsType VrfKey Source # 
Instance details

Defined in Cardano.Api.Key.Internal.Praos

data AsType PlutusScriptV1 Source # 
Instance details

Defined in Cardano.Api.Plutus.Internal.Script

data AsType PlutusScriptV2 Source # 
Instance details

Defined in Cardano.Api.Plutus.Internal.Script

data AsType PlutusScriptV3 Source # 
Instance details

Defined in Cardano.Api.Plutus.Internal.Script

data AsType PlutusScriptV4 Source # 
Instance details

Defined in Cardano.Api.Plutus.Internal.Script

data AsType ScriptHash Source # 
Instance details

Defined in Cardano.Api.Plutus.Internal.Script

data AsType ScriptInAnyLang Source # 
Instance details

Defined in Cardano.Api.Plutus.Internal.Script

data AsType SimpleScript' Source # 
Instance details

Defined in Cardano.Api.Plutus.Internal.Script

data AsType HashableScriptData Source # 
Instance details

Defined in Cardano.Api.Plutus.Internal.ScriptData

data AsType ScriptData Source # 
Instance details

Defined in Cardano.Api.Plutus.Internal.ScriptData

data AsType PraosNonce Source # 
Instance details

Defined in Cardano.Api.ProtocolParameters

data AsType UpdateProposal Source # 
Instance details

Defined in Cardano.Api.ProtocolParameters

data AsType EraHistory Source # 
Instance details

Defined in Cardano.Api.Query.Internal.Type.QueryInMode

data AsType TextEnvelope Source # 
Instance details

Defined in Cardano.Api.Serialise.TextEnvelope.Internal

data AsType TxId Source # 
Instance details

Defined in Cardano.Api.Tx.Internal.TxIn

data AsType TxMetadata Source # 
Instance details

Defined in Cardano.Api.Tx.Internal.TxMetadata

data AsType AssetName Source # 
Instance details

Defined in Cardano.Api.Value.Internal

data AsType PolicyId Source # 
Instance details

Defined in Cardano.Api.Value.Internal

data AsType GovActionId Source # 
Instance details

Defined in Cardano.Api.Internal.Orphans.Serialisation

data AsType GovActionIx Source # 
Instance details

Defined in Cardano.Api.Internal.Orphans.Serialisation

data AsType Term Source # 
Instance details

Defined in Cardano.Api.Serialise.Cbor.Canonical

data AsType Word16 Source # 
Instance details

Defined in Cardano.Api.HasTypeProxy

data AsType Word8 Source # 
Instance details

Defined in Cardano.Api.HasTypeProxy

data AsType (Address addrtype) Source # 
Instance details

Defined in Cardano.Api.Address

data AsType (Address addrtype) = AsAddress (AsType addrtype)
data AsType (AddressInEra era) Source # 
Instance details

Defined in Cardano.Api.Address

data AsType (Certificate era) Source # 
Instance details

Defined in Cardano.Api.Certificate.Internal

data AsType (SignedTx era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx

data AsType (SignedTx era) = AsSignedTx (AsType era)
data AsType (UnsignedTx era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx

data AsType (Certificate era) Source # 
Instance details

Defined in Cardano.Api.Experimental.Tx.Internal.Certificate.Type

data AsType (Proposal era) Source # 
Instance details

Defined in Cardano.Api.Governance.Internal.Action.ProposalProcedure

data AsType (VotingProcedure era) Source # 
Instance details

Defined in Cardano.Api.Governance.Internal.Action.VotingProcedure

data AsType (VotingProcedures era) Source # 
Instance details

Defined in Cardano.Api.Governance.Internal.Action.VotingProcedure

data AsType (Hash a) Source # 
Instance details

Defined in Cardano.Api.Hash

data AsType (Hash a) = AsHash (AsType a)
data AsType (SigningKey a) Source # 
Instance details

Defined in Cardano.Api.Key.Internal.Class

data AsType (VerificationKey a) Source # 
Instance details

Defined in Cardano.Api.Key.Internal.Class

data AsType (PlutusScript lang) Source # 
Instance details

Defined in Cardano.Api.Plutus.Internal.Script

data AsType (Script lang) Source # 
Instance details

Defined in Cardano.Api.Plutus.Internal.Script

data AsType (Script lang) = AsScript (AsType lang)
data AsType (ScriptInEra era) Source # 
Instance details

Defined in Cardano.Api.Plutus.Internal.Script

data AsType (KeyWitness era) Source # 
Instance details

Defined in Cardano.Api.Tx.Internal.Sign

data AsType (Tx era) Source # 
Instance details

Defined in Cardano.Api.Tx.Internal.Sign

data AsType (Tx era) = AsTx (AsType era)
data AsType (TxBody era) Source # 
Instance details

Defined in Cardano.Api.Tx.Internal.Sign

data AsType (TxBody era) = AsTxBody (AsType era)
data AsType (Credential 'ColdCommitteeRole) Source # 
Instance details

Defined in Cardano.Api.Internal.Orphans.Serialisation

data AsType (Credential 'DRepRole) Source # 
Instance details

Defined in Cardano.Api.Internal.Orphans.Serialisation

data AsType (Credential 'HotCommitteeRole) Source # 
Instance details

Defined in Cardano.Api.Internal.Orphans.Serialisation

data AsType (PlutusScriptInEra era lang) Source # 
Instance details

Defined in Cardano.Api.Plutus.Internal.Script

data AsType (TxOut ctx era) Source # 
Instance details

Defined in Cardano.Api.Tx.Internal.Output

data AsType (TxOut ctx era) = AsTxOut (AsType era)

Internal

getAnyWitnessRedeemerPointerMap :: forall era (witnessable :: WitnessableItem). AlonzoEraOnwards era -> [(Witnessable witnessable (ShelleyLedgerEra era), AnyWitness (ShelleyLedgerEra era))] -> Redeemers (ShelleyLedgerEra era) Source #

The transaction's redeemer pointer map allows the ledger to connect a redeemer and execution unit pairing to the relevant script. The ledger basically reconstructs the indicies (redeemer pointers) of this map can then look up the relevant execution units/redeemer pairing. NB: the redeemer pointer has been renamed to 'PlutusPurpose AsIndex' in the ledger.

toPlutusScriptPurpose :: forall (thing :: WitnessableItem) era. Word32 -> Witnessable thing era -> PlutusPurpose AsIx era Source #

To reduce boilerplate, we reuse the PlutusPurpose type from `cardano-ledger`. This type is utilized in constructing the redeemer pointers map, which links the redeemer and execution units with the entity being witnessed. The map is indexed by the redeemer pointer.

A natural question arises: How do Plutus scripts determine which execution units and redeemer are paired with them? The ledger constructs a redeemer pointer for every Plutus script, and this pointer corresponds to the one in the transaction's redeemer pointers map. For more details, refer to collectPlutusScriptsWithContext in `cardano-ledger`.

Legacy

legacyWitnessConversion :: forall era (witnessable :: WitnessableItem) ctx. AlonzoEraOnwards era -> [(Witnessable witnessable (ShelleyLedgerEra era), BuildTxWith BuildTx (Witness ctx era))] -> Either DecoderError [(Witnessable witnessable (ShelleyLedgerEra era), AnyWitness (ShelleyLedgerEra era))] Source #

When it comes to using plutus scripts we need to provide the following to the tx:

  1. The redeemer pointer map
  2. The set of plutus languages in use
  3. The set of plutus scripts in use (present in the t)
  4. The datum map