| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
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
- data UnsignedTx era = EraTx (LedgerEra era) => UnsignedTx (Tx (LedgerEra era))
- newtype UnsignedTxError = UnsignedTxError TxBodyError
- data SignedTx era = EraTx (LedgerEra era) => SignedTx (Tx (LedgerEra era))
- makeUnsignedTx :: Era era -> TxBodyContent BuildTx era -> Either TxBodyError (UnsignedTx era)
- makeKeyWitness :: Era era -> UnsignedTx era -> ShelleyWitnessSigningKey -> WitVKey 'Witness
- signTx :: Era era -> [BootstrapWitness] -> [WitVKey 'Witness] -> UnsignedTx era -> SignedTx era
- convertTxBodyToUnsignedTx :: HasCallStack => ShelleyBasedEra era -> TxBody era -> UnsignedTx era
- type EraCommonConstraints era = (AllegraEraScript (LedgerEra era), AlonzoEraTx (LedgerEra era), BabbageEraPParams (LedgerEra era), BabbageEraTxBody (LedgerEra era), ConwayEraTxBody (LedgerEra era), ConwayEraTxCert (LedgerEra era), Era (LedgerEra era), EraScript (LedgerEra era), EraTx (LedgerEra era), EraTxCert (LedgerEra era), EraTxOut (LedgerEra era), EraUTxO (LedgerEra era), FromCBOR (ChainDepState (ConsensusProtocol era)), NativeScript (LedgerEra era) ~ Timelock (LedgerEra era), PraosProtocolSupportsNode (ConsensusProtocol era), ShelleyLedgerEra era ~ LedgerEra era, ToJSON (ChainDepState (ConsensusProtocol era)), HashAnnotated (TxBody (LedgerEra era)) EraIndependentTxBody, IsCardanoEra era, IsShelleyBasedEra era, IsEra era)
- obtainCommonConstraints :: Era era -> (EraCommonConstraints era => a) -> a
- hashTxBody :: HashAnnotated (TxBody era) EraIndependentTxBody => TxBody era -> Hash HASH EraIndependentTxBody
- evaluateTransactionExecutionUnitsShelley :: ShelleyBasedEra era -> SystemStart -> LedgerEpochInfo -> LedgerProtocolParameters era -> UTxO era -> Tx (ShelleyLedgerEra era) -> Map ScriptWitnessIndex (Either ScriptExecutionError (EvalTxExecutionUnitsLog, ExecutionUnits))
- data AnchorDataFromCertificateError = InvalidPoolMetadataHashError Url ByteString
- getAnchorDataFromCertificate :: Era era -> Certificate (LedgerEra era) -> Either AnchorDataFromCertificateError (Maybe Anchor)
- mkTxCertificates :: IsEra era => [(Certificate (ShelleyLedgerEra era), AnyWitness (LedgerEra era))] -> TxCertificates BuildTx era
- estimateBalancedTxBody :: HasCallStack => Era era -> TxBodyContent BuildTx era -> PParams (LedgerEra era) -> Set PoolId -> Map StakeCredential Coin -> Map (Credential 'DRepRole) Coin -> Map (PlutusPurpose AsIx (LedgerEra era)) ExecutionUnits -> Coin -> Int -> Int -> Int -> AddressInEra era -> Value -> Either (TxFeeEstimationError era) (BalancedTxBody era)
- data BabbageEra
- data ConwayEra
- data Era era where
- class IsEra era where
- data Some (f :: k -> Type) where
- type family LedgerEra era = (r :: Type) | r -> era where ...
- newtype DeprecatedEra era = DeprecatedEra (ShelleyBasedEra era)
- eraToSbe :: Era era -> ShelleyBasedEra era
- eraToBabbageEraOnwards :: Era era -> BabbageEraOnwards era
- sbeToEra :: MonadError (DeprecatedEra era) m => ShelleyBasedEra era -> m (Era era)
- data AnyWitness era where
- 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
- data PlutusScriptWitness (lang :: Language) (purpose :: PlutusScriptPurpose) era where
- PlutusScriptWitness :: forall (lang :: Language) era (purpose :: PlutusScriptPurpose). SLanguage lang -> PlutusScriptOrReferenceInput lang era -> PlutusScriptDatum lang purpose -> ScriptRedeemer -> ExecutionUnits -> PlutusScriptWitness lang purpose era
- data TxScriptWitnessRequirements era = TxScriptWitnessRequirements (Set Language) [Script era] (TxDats era) (Redeemers era)
- data Witnessable (thing :: WitnessableItem) era where
- 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
- data WitnessableItem
- data SimpleScript era where
- SimpleScript :: forall era. EraScript era => NativeScript era -> SimpleScript era
- data SimpleScriptOrReferenceInput era
- = SScript (SimpleScript era)
- | SReferenceScript TxIn
- data PlutusScriptInEra (lang :: Language) era where
- PlutusScriptInEra :: forall (lang :: Language) era. PlutusRunnable lang -> PlutusScriptInEra lang era
- data PlutusScriptOrReferenceInput (lang :: Language) era
- = PScript (PlutusScriptInEra lang era)
- | PReferenceScript TxIn
- data IndexedPlutusScriptWitness (witnessable :: WitnessableItem) (lang :: Language) (purpose :: PlutusScriptPurpose) era where
- 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
- data PlutusScriptPurpose
- data PlutusScriptDatum (lang :: Language) (purpose :: PlutusScriptPurpose) where
- 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
- data NoScriptDatum = NoScriptDatumAllowed
- data Certificate era where
- Certificate :: forall era. EraTxCert era => TxCert era -> Certificate era
- makeStakeAddressDelegationCertificate :: IsEra era => StakeCredential -> Delegatee era -> Certificate (LedgerEra era)
- makeStakeAddressRegistrationCertificate :: IsEra era => StakeCredential -> Coin -> Certificate (LedgerEra era)
- makeStakeAddressUnregistrationCertificate :: IsEra era => StakeCredential -> Coin -> Certificate (LedgerEra era)
- makeStakePoolRegistrationCertificate :: IsEra era => PoolParams -> Certificate (LedgerEra era)
- makeStakePoolRetirementCertificate :: IsShelleyBasedEra era => Hash StakePoolKey -> EpochNo -> Certificate (ShelleyLedgerEra era)
- makeCommitteeColdkeyResignationCertificate :: IsEra era => Credential 'ColdCommitteeRole -> Maybe Anchor -> Certificate (LedgerEra era)
- makeCommitteeHotKeyAuthorizationCertificate :: IsEra era => Credential 'ColdCommitteeRole -> Credential 'HotCommitteeRole -> Certificate (LedgerEra era)
- makeDrepRegistrationCertificate :: IsEra era => Credential 'DRepRole -> Coin -> Maybe Anchor -> Certificate (LedgerEra era)
- makeDrepUnregistrationCertificate :: IsEra era => Credential 'DRepRole -> Coin -> Certificate (LedgerEra era)
- makeDrepUpdateCertificate :: IsEra era => Credential 'DRepRole -> Maybe Anchor -> Certificate (LedgerEra era)
- makeStakeAddressAndDRepDelegationCertificate :: IsEra era => StakeCredential -> Delegatee -> Coin -> Certificate (LedgerEra era)
- data family AsType t
- getAnyWitnessRedeemerPointerMap :: forall era (witnessable :: WitnessableItem). AlonzoEraOnwards era -> [(Witnessable witnessable (ShelleyLedgerEra era), AnyWitness (ShelleyLedgerEra era))] -> Redeemers (ShelleyLedgerEra era)
- toPlutusScriptPurpose :: forall (thing :: WitnessableItem) era. Word32 -> Witnessable thing era -> PlutusPurpose AsIx era
- 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))]
- toPlutusSLanguage :: PlutusScriptVersion lang -> SLanguage (ToLedgerPlutusLanguage lang)
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
| HasTypeProxy era => HasTypeProxy (UnsignedTx era) Source # | |||||
Defined in Cardano.Api.Experimental.Tx Associated Types
Methods proxyToAsType :: Proxy (UnsignedTx era) -> AsType (UnsignedTx era) Source # | |||||
| (HasTypeProxy era, EraTx (LedgerEra era)) => SerialiseAsRawBytes (UnsignedTx era) Source # | |||||
Defined in Cardano.Api.Experimental.Tx Methods serialiseToRawBytes :: UnsignedTx era -> ByteString Source # deserialiseFromRawBytes :: AsType (UnsignedTx era) -> ByteString -> Either SerialiseAsRawBytesError (UnsignedTx era) Source # | |||||
| Show (UnsignedTx era) Source # | |||||
Defined in Cardano.Api.Experimental.Tx | |||||
| Eq (UnsignedTx era) Source # | |||||
Defined in Cardano.Api.Experimental.Tx Methods (==) :: UnsignedTx era -> UnsignedTx era -> Bool Source # (/=) :: UnsignedTx era -> UnsignedTx era -> Bool Source # | |||||
| data AsType (UnsignedTx era) Source # | |||||
Defined in Cardano.Api.Experimental.Tx | |||||
newtype UnsignedTxError Source #
Constructors
| UnsignedTxError TxBodyError |
A transaction that has been witnesssed
Instances
| HasTypeProxy era => HasTypeProxy (SignedTx era) Source # | |||||
Defined in Cardano.Api.Experimental.Tx Associated Types
| |||||
| (HasTypeProxy era, EraTx (LedgerEra era)) => SerialiseAsRawBytes (SignedTx era) Source # | |||||
Defined in Cardano.Api.Experimental.Tx Methods serialiseToRawBytes :: SignedTx era -> ByteString Source # deserialiseFromRawBytes :: AsType (SignedTx era) -> ByteString -> Either SerialiseAsRawBytesError (SignedTx era) Source # | |||||
| Show (SignedTx era) Source # | |||||
| Eq (SignedTx era) Source # | |||||
| data AsType (SignedTx era) Source # | |||||
Defined in Cardano.Api.Experimental.Tx | |||||
makeUnsignedTx :: Era era -> TxBodyContent BuildTx era -> Either TxBodyError (UnsignedTx era) Source #
makeKeyWitness :: Era era -> UnsignedTx era -> ShelleyWitnessSigningKey -> WitVKey 'Witness Source #
signTx :: Era era -> [BootstrapWitness] -> [WitVKey 'Witness] -> UnsignedTx era -> SignedTx era Source #
convertTxBodyToUnsignedTx :: HasCallStack => ShelleyBasedEra era -> TxBody era -> UnsignedTx era Source #
type EraCommonConstraints era = (AllegraEraScript (LedgerEra era), AlonzoEraTx (LedgerEra era), BabbageEraPParams (LedgerEra era), BabbageEraTxBody (LedgerEra era), ConwayEraTxBody (LedgerEra era), ConwayEraTxCert (LedgerEra era), Era (LedgerEra era), EraScript (LedgerEra era), EraTx (LedgerEra era), EraTxCert (LedgerEra era), EraTxOut (LedgerEra era), EraUTxO (LedgerEra era), FromCBOR (ChainDepState (ConsensusProtocol era)), NativeScript (LedgerEra era) ~ Timelock (LedgerEra era), PraosProtocolSupportsNode (ConsensusProtocol era), ShelleyLedgerEra era ~ LedgerEra era, ToJSON (ChainDepState (ConsensusProtocol era)), HashAnnotated (TxBody (LedgerEra era)) EraIndependentTxBody, IsCardanoEra era, IsShelleyBasedEra era, IsEra era) Source #
obtainCommonConstraints :: Era era -> (EraCommonConstraints era => a) -> a Source #
hashTxBody :: HashAnnotated (TxBody era) EraIndependentTxBody => TxBody era -> Hash HASH EraIndependentTxBody Source #
evaluateTransactionExecutionUnitsShelley :: ShelleyBasedEra era -> SystemStart -> LedgerEpochInfo -> LedgerProtocolParameters era -> UTxO era -> Tx (ShelleyLedgerEra era) -> Map ScriptWitnessIndex (Either ScriptExecutionError (EvalTxExecutionUnitsLog, ExecutionUnits)) Source #
data AnchorDataFromCertificateError Source #
Constructors
| InvalidPoolMetadataHashError Url ByteString |
getAnchorDataFromCertificate :: Era era -> Certificate (LedgerEra era) -> Either AnchorDataFromCertificateError (Maybe Anchor) Source #
mkTxCertificates :: IsEra era => [(Certificate (ShelleyLedgerEra era), AnyWitness (LedgerEra era))] -> TxCertificates BuildTx era Source #
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
A type used as a tag to distinguish the Conway era.
Instances
| IsCardanoEra ConwayEra Source # | |||||
Defined in Cardano.Api.Era.Internal.Core Methods | |||||
| IsAllegraBasedEra ConwayEra Source # | |||||
Defined in Cardano.Api.Era.Internal.Eon.AllegraEraOnwards Methods | |||||
| IsAlonzoBasedEra ConwayEra Source # | |||||
Defined in Cardano.Api.Era.Internal.Eon.AlonzoEraOnwards Methods | |||||
| IsBabbageBasedEra ConwayEra Source # | |||||
Defined in Cardano.Api.Era.Internal.Eon.BabbageEraOnwards Methods | |||||
| IsConwayBasedEra ConwayEra Source # | |||||
Defined in Cardano.Api.Era.Internal.Eon.ConwayEraOnwards Methods | |||||
| IsMaryBasedEra ConwayEra Source # | |||||
Defined in Cardano.Api.Era.Internal.Eon.MaryEraOnwards Methods | |||||
| IsShelleyBasedEra ConwayEra Source # | |||||
Defined in Cardano.Api.Era.Internal.Eon.ShelleyBasedEra Methods | |||||
| IsEra ConwayEra Source # | |||||
| HasTypeProxy ConwayEra Source # | |||||
Defined in Cardano.Api.Era.Internal.Core Associated Types
| |||||
| HasScriptLanguageInEra PlutusScriptV1 ConwayEra Source # | |||||
Defined in Cardano.Api.Plutus.Internal.Script | |||||
| HasScriptLanguageInEra PlutusScriptV2 ConwayEra Source # | |||||
Defined in Cardano.Api.Plutus.Internal.Script | |||||
| HasScriptLanguageInEra PlutusScriptV3 ConwayEra Source # | |||||
Defined in Cardano.Api.Plutus.Internal.Script | |||||
| ToAlonzoScript PlutusScriptV1 ConwayEra Source # | |||||
Defined in Cardano.Api.Plutus.Internal.Script Methods toLedgerScript :: PlutusScript PlutusScriptV1 -> AlonzoScript (ShelleyLedgerEra ConwayEra) Source # | |||||
| ToAlonzoScript PlutusScriptV2 ConwayEra Source # | |||||
Defined in Cardano.Api.Plutus.Internal.Script Methods toLedgerScript :: PlutusScript PlutusScriptV2 -> AlonzoScript (ShelleyLedgerEra ConwayEra) Source # | |||||
| ToAlonzoScript PlutusScriptV3 ConwayEra Source # | |||||
Defined in Cardano.Api.Plutus.Internal.Script Methods toLedgerScript :: PlutusScript PlutusScriptV3 -> AlonzoScript (ShelleyLedgerEra ConwayEra) Source # | |||||
| data AsType ConwayEra Source # | |||||
Defined in Cardano.Api.Era.Internal.Core | |||||
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
| Eon Era Source # | A temporary compatibility instance for easier conversion between the experimental and old APIs. |
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. |
Defined in Cardano.Api.Experimental.Era Methods toCardanoEra :: Era era -> CardanoEra era Source # | |
| TestEquality Era Source # | |
Defined in Cardano.Api.Experimental.Era | |
| Convert ConwayEraOnwards Era Source # | |
Defined in Cardano.Api.Experimental.Era Methods convert :: ConwayEraOnwards era -> Era era Source # | |
| Convert Era CardanoEra Source # | |
Defined in Cardano.Api.Experimental.Era Methods convert :: Era era -> CardanoEra era Source # | |
| Convert Era AlonzoEraOnwards Source # | |
Defined in Cardano.Api.Experimental.Era Methods convert :: Era era -> AlonzoEraOnwards era Source # | |
| Convert Era BabbageEraOnwards Source # | |
Defined in Cardano.Api.Experimental.Era Methods convert :: Era era -> BabbageEraOnwards era Source # | |
| Convert Era ConwayEraOnwards Source # | |
Defined in Cardano.Api.Experimental.Era Methods convert :: Era era -> ConwayEraOnwards era Source # | |
| Convert Era MaryEraOnwards Source # | |
Defined in Cardano.Api.Experimental.Era Methods convert :: Era era -> MaryEraOnwards era Source # | |
| Convert Era ShelleyBasedEra Source # | |
Defined in Cardano.Api.Experimental.Era Methods convert :: Era era -> ShelleyBasedEra era Source # | |
| ToJSON (Era era) Source # | |
Defined in Cardano.Api.Experimental.Era | |
| Show (Era era) Source # | |
| Eq (Era era) Source # | |
| Pretty (Era era) Source # | |
Defined in Cardano.Api.Experimental.Era | |
| FromJSON (Some Era) Source # | |
Defined in Cardano.Api.Experimental.Era | |
| ToJSON (Some Era) Source # | |
| Bounded (Some Era) Source # | |
| Enum (Some Era) Source # | |
Defined in Cardano.Api.Experimental.Era Methods succ :: Some Era -> Some Era Source # pred :: Some Era -> Some Era Source # toEnum :: Int -> Some Era Source # fromEnum :: Some Era -> Int Source # enumFrom :: Some Era -> [Some Era] Source # enumFromThen :: Some Era -> Some Era -> [Some Era] Source # enumFromTo :: Some Era -> Some Era -> [Some Era] Source # enumFromThenTo :: Some Era -> Some Era -> Some Era -> [Some Era] Source # | |
| Show (Some Era) Source # | |
| Eq (Some Era) Source # | |
| Ord (Some Era) Source # | |
Defined in Cardano.Api.Experimental.Era | |
| Pretty (Some Era) Source # | |
class IsEra era where Source #
Type class interface for the Era type.
Instances
| IsEra ConwayEra Source # | |
| IsEra DijkstraEra Source # | |
Defined in Cardano.Api.Experimental.Era Methods useEra :: Era DijkstraEra Source # | |
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
| FromJSON (Some Era) Source # | |
Defined in Cardano.Api.Experimental.Era | |
| ToJSON (Some Era) Source # | |
| Bounded (Some Era) Source # | |
| Enum (Some Era) Source # | |
Defined in Cardano.Api.Experimental.Era Methods succ :: Some Era -> Some Era Source # pred :: Some Era -> Some Era Source # toEnum :: Int -> Some Era Source # fromEnum :: Some Era -> Int Source # enumFrom :: Some Era -> [Some Era] Source # enumFromThen :: Some Era -> Some Era -> [Some Era] Source # enumFromTo :: Some Era -> Some Era -> [Some Era] Source # enumFromThenTo :: Some Era -> Some Era -> Some Era -> [Some Era] Source # | |
| Show (Some Era) Source # | |
| Eq (Some Era) Source # | |
| Ord (Some Era) Source # | |
Defined in Cardano.Api.Experimental.Era | |
| Pretty (Some Era) Source # | |
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.
Equations
| LedgerEra ConwayEra = ConwayEra | |
| LedgerEra DijkstraEra = DijkstraEra |
newtype DeprecatedEra era Source #
Constructors
| DeprecatedEra (ShelleyBasedEra era) |
Instances
| Error (DeprecatedEra era) Source # | |
Defined in Cardano.Api.Experimental.Era Methods prettyError :: DeprecatedEra era -> Doc ann Source # | |
| Show (DeprecatedEra era) Source # | |
Defined in Cardano.Api.Experimental.Era | |
| Pretty (DeprecatedEra era) Source # | |
Defined in Cardano.Api.Experimental.Era | |
eraToSbe :: Era era -> ShelleyBasedEra era Source #
Deprecated: Use convert instead.
How to deprecate an era:
- 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
- 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
- Add a new
IsErainstance 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.
sbeToEra :: MonadError (DeprecatedEra era) m => ShelleyBasedEra era -> m (Era era) Source #
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
| Show (AnyWitness era) Source # | |
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
| Show (PlutusScriptWitness lang purpose era) Source # | |
data TxScriptWitnessRequirements era Source #
This type collects all the requirements for script witnesses in a transaction.
Instances
| Monoid (TxScriptWitnessRequirements AlonzoEra) Source # | |
Defined in Cardano.Api.Experimental.Tx.Internal.TxScriptWitnessRequirements Methods mempty :: TxScriptWitnessRequirements AlonzoEra Source # mappend :: TxScriptWitnessRequirements AlonzoEra -> TxScriptWitnessRequirements AlonzoEra -> TxScriptWitnessRequirements AlonzoEra Source # mconcat :: [TxScriptWitnessRequirements AlonzoEra] -> TxScriptWitnessRequirements AlonzoEra Source # | |
| Monoid (TxScriptWitnessRequirements BabbageEra) Source # | |
Defined in Cardano.Api.Experimental.Tx.Internal.TxScriptWitnessRequirements Methods mempty :: TxScriptWitnessRequirements BabbageEra Source # mappend :: TxScriptWitnessRequirements BabbageEra -> TxScriptWitnessRequirements BabbageEra -> TxScriptWitnessRequirements BabbageEra Source # mconcat :: [TxScriptWitnessRequirements BabbageEra] -> TxScriptWitnessRequirements BabbageEra Source # | |
| Monoid (TxScriptWitnessRequirements ConwayEra) Source # | |
Defined in Cardano.Api.Experimental.Tx.Internal.TxScriptWitnessRequirements Methods mempty :: TxScriptWitnessRequirements ConwayEra Source # mappend :: TxScriptWitnessRequirements ConwayEra -> TxScriptWitnessRequirements ConwayEra -> TxScriptWitnessRequirements ConwayEra Source # mconcat :: [TxScriptWitnessRequirements ConwayEra] -> TxScriptWitnessRequirements ConwayEra Source # | |
| Monoid (TxScriptWitnessRequirements DijkstraEra) Source # | |
Defined in Cardano.Api.Experimental.Tx.Internal.TxScriptWitnessRequirements Methods mempty :: TxScriptWitnessRequirements DijkstraEra Source # mappend :: TxScriptWitnessRequirements DijkstraEra -> TxScriptWitnessRequirements DijkstraEra -> TxScriptWitnessRequirements DijkstraEra Source # mconcat :: [TxScriptWitnessRequirements DijkstraEra] -> TxScriptWitnessRequirements DijkstraEra Source # | |
| Semigroup (TxScriptWitnessRequirements AlonzoEra) Source # | |
Defined in Cardano.Api.Experimental.Tx.Internal.TxScriptWitnessRequirements Methods (<>) :: TxScriptWitnessRequirements AlonzoEra -> TxScriptWitnessRequirements AlonzoEra -> TxScriptWitnessRequirements AlonzoEra Source # sconcat :: NonEmpty (TxScriptWitnessRequirements AlonzoEra) -> TxScriptWitnessRequirements AlonzoEra Source # stimes :: Integral b => b -> TxScriptWitnessRequirements AlonzoEra -> TxScriptWitnessRequirements AlonzoEra Source # | |
| Semigroup (TxScriptWitnessRequirements BabbageEra) Source # | |
Defined in Cardano.Api.Experimental.Tx.Internal.TxScriptWitnessRequirements Methods (<>) :: TxScriptWitnessRequirements BabbageEra -> TxScriptWitnessRequirements BabbageEra -> TxScriptWitnessRequirements BabbageEra Source # sconcat :: NonEmpty (TxScriptWitnessRequirements BabbageEra) -> TxScriptWitnessRequirements BabbageEra Source # stimes :: Integral b => b -> TxScriptWitnessRequirements BabbageEra -> TxScriptWitnessRequirements BabbageEra Source # | |
| Semigroup (TxScriptWitnessRequirements ConwayEra) Source # | |
Defined in Cardano.Api.Experimental.Tx.Internal.TxScriptWitnessRequirements Methods (<>) :: TxScriptWitnessRequirements ConwayEra -> TxScriptWitnessRequirements ConwayEra -> TxScriptWitnessRequirements ConwayEra Source # sconcat :: NonEmpty (TxScriptWitnessRequirements ConwayEra) -> TxScriptWitnessRequirements ConwayEra Source # stimes :: Integral b => b -> TxScriptWitnessRequirements ConwayEra -> TxScriptWitnessRequirements ConwayEra Source # | |
| Semigroup (TxScriptWitnessRequirements DijkstraEra) Source # | |
Defined in Cardano.Api.Experimental.Tx.Internal.TxScriptWitnessRequirements Methods (<>) :: TxScriptWitnessRequirements DijkstraEra -> TxScriptWitnessRequirements DijkstraEra -> TxScriptWitnessRequirements DijkstraEra Source # sconcat :: NonEmpty (TxScriptWitnessRequirements DijkstraEra) -> TxScriptWitnessRequirements DijkstraEra Source # stimes :: Integral b => b -> TxScriptWitnessRequirements DijkstraEra -> TxScriptWitnessRequirements DijkstraEra Source # | |
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
| Show (Witnessable thing era) Source # | |
| Eq (Witnessable thing era) Source # | |
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 # | |
data WitnessableItem Source #
Constructors
| TxInItem | |
| CertItem | |
| MintItem | |
| WithdrawalItem | |
| VoterItem | |
| ProposalItem |
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
| Show (SimpleScript era) Source # | |
Defined in Cardano.Api.Experimental.Simple.Script | |
| Eq (SimpleScript era) Source # | |
Defined in Cardano.Api.Experimental.Simple.Script Methods (==) :: SimpleScript era -> SimpleScript era -> Bool Source # (/=) :: SimpleScript era -> SimpleScript era -> Bool Source # | |
data SimpleScriptOrReferenceInput era Source #
Constructors
| SScript (SimpleScript era) | |
| SReferenceScript TxIn |
Instances
| Show (SimpleScriptOrReferenceInput era) Source # | |
Defined in Cardano.Api.Experimental.Simple.Script | |
| Eq (SimpleScriptOrReferenceInput era) Source # | |
Defined in Cardano.Api.Experimental.Simple.Script Methods (==) :: SimpleScriptOrReferenceInput era -> SimpleScriptOrReferenceInput era -> Bool Source # (/=) :: SimpleScriptOrReferenceInput era -> SimpleScriptOrReferenceInput era -> Bool Source # | |
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
| Show (PlutusScriptInEra lang era) Source # | |
| Eq (PlutusScriptInEra lang era) Source # | |
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.
Constructors
| PScript (PlutusScriptInEra lang era) | |
| PReferenceScript TxIn |
Instances
| Show (PlutusScriptOrReferenceInput lang era) Source # | |
| Eq (PlutusScriptOrReferenceInput lang era) Source # | |
Defined in Cardano.Api.Experimental.Plutus.Internal.Script Methods (==) :: PlutusScriptOrReferenceInput lang era -> PlutusScriptOrReferenceInput lang era -> Bool Source # (/=) :: PlutusScriptOrReferenceInput lang era -> PlutusScriptOrReferenceInput lang era -> Bool Source # | |
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
| Show (IndexedPlutusScriptWitness witnessable lang purpose era) 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
| Show (PlutusScriptDatum lang purpose) Source # | |
data NoScriptDatum Source #
Constructors
| NoScriptDatumAllowed |
Instances
Certificate related
data Certificate era where Source #
Constructors
| Certificate :: forall era. EraTxCert era => TxCert era -> Certificate era |
Instances
| Typeable era => HasTypeProxy (Certificate era) Source # | |||||
Defined in Cardano.Api.Experimental.Tx.Internal.Certificate.Type Associated Types
Methods proxyToAsType :: Proxy (Certificate era) -> AsType (Certificate era) Source # | |||||
| (Typeable ledgerera, EraTxCert ledgerera) => SerialiseAsCBOR (Certificate ledgerera) Source # | |||||
Defined in Cardano.Api.Experimental.Tx.Internal.Certificate.Type Methods serialiseToCBOR :: Certificate ledgerera -> ByteString Source # deserialiseFromCBOR :: AsType (Certificate ledgerera) -> ByteString -> Either DecoderError (Certificate ledgerera) Source # | |||||
| (Typeable ledgerera, EraTxCert ledgerera) => HasTextEnvelope (Certificate ledgerera) Source # | |||||
Defined in Cardano.Api.Experimental.Tx.Internal.Certificate.Type Methods textEnvelopeType :: AsType (Certificate ledgerera) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: Certificate ledgerera -> TextEnvelopeDescr Source # | |||||
| Show (Certificate era) Source # | |||||
| Eq (Certificate era) Source # | |||||
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 # | |||||
Defined in Cardano.Api.Experimental.Tx.Internal.Certificate.Type Methods compare :: Certificate era -> Certificate era -> Ordering Source # (<) :: Certificate era -> Certificate era -> Bool Source # (<=) :: Certificate era -> Certificate era -> Bool Source # (>) :: Certificate era -> Certificate era -> Bool Source # (>=) :: Certificate era -> Certificate era -> Bool Source # max :: Certificate era -> Certificate era -> Certificate era Source # min :: Certificate era -> Certificate era -> Certificate era Source # | |||||
| data AsType (Certificate era) Source # | |||||
Registering stake address and delegating
makeStakeAddressDelegationCertificate :: IsEra era => StakeCredential -> Delegatee era -> Certificate (LedgerEra era) Source #
makeStakeAddressRegistrationCertificate :: IsEra era => StakeCredential -> Coin -> Certificate (LedgerEra era) Source #
makeStakeAddressUnregistrationCertificate :: IsEra era => StakeCredential -> Coin -> Certificate (LedgerEra era) Source #
Registering stake pools
makeStakePoolRegistrationCertificate :: IsEra era => PoolParams -> Certificate (LedgerEra era) Source #
makeStakePoolRetirementCertificate :: IsShelleyBasedEra era => Hash StakePoolKey -> EpochNo -> Certificate (ShelleyLedgerEra era) Source #
Governance related certificates
makeCommitteeColdkeyResignationCertificate :: IsEra era => Credential 'ColdCommitteeRole -> Maybe Anchor -> Certificate (LedgerEra era) Source #
makeCommitteeHotKeyAuthorizationCertificate :: IsEra era => Credential 'ColdCommitteeRole -> Credential 'HotCommitteeRole -> Certificate (LedgerEra era) Source #
makeDrepRegistrationCertificate :: IsEra era => Credential 'DRepRole -> Coin -> Maybe Anchor -> Certificate (LedgerEra era) Source #
makeDrepUnregistrationCertificate :: IsEra era => Credential 'DRepRole -> Coin -> Certificate (LedgerEra era) Source #
makeDrepUpdateCertificate :: IsEra era => Credential 'DRepRole -> Maybe Anchor -> Certificate (LedgerEra era) Source #
makeStakeAddressAndDRepDelegationCertificate :: IsEra era => StakeCredential -> Delegatee -> Coin -> Certificate (LedgerEra era) Source #
Data family instances
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
| data AsType ByteString Source # | |
Defined in Cardano.Api.HasTypeProxy | |
| data AsType AddressAny Source # | |
Defined in Cardano.Api.Address | |
| data AsType ByronAddr Source # | |
Defined in Cardano.Api.Address | |
| data AsType ShelleyAddr Source # | |
Defined in Cardano.Api.Address | |
| data AsType StakeAddress Source # | |
Defined in Cardano.Api.Address | |
| data AsType BlockHeader Source # | |
Defined in Cardano.Api.Block | |
| data AsType ByronKey Source # | |
Defined in Cardano.Api.Byron.Internal.Key | |
| data AsType ByronKeyLegacy Source # | |
Defined in Cardano.Api.Byron.Internal.Key | |
| data AsType ByronUpdateProposal Source # | |
Defined in Cardano.Api.Byron.Internal.Proposal | |
| data AsType ByronVote Source # | |
Defined in Cardano.Api.Byron.Internal.Proposal | |
| data AsType DRepMetadata Source # | |
| data AsType OperationalCertificate Source # | |
| data AsType OperationalCertificateIssueCounter Source # | |
| data AsType StakePoolMetadata Source # | |
| data AsType AllegraEra Source # | |
Defined in Cardano.Api.Era.Internal.Core | |
| data AsType AlonzoEra Source # | |
Defined in Cardano.Api.Era.Internal.Core | |
| data AsType BabbageEra Source # | |
Defined in Cardano.Api.Era.Internal.Core | |
| data AsType ByronEra Source # | |
Defined in Cardano.Api.Era.Internal.Core | |
| data AsType ConwayEra Source # | |
Defined in Cardano.Api.Era.Internal.Core | |
| data AsType DijkstraEra Source # | |
Defined in Cardano.Api.Era.Internal.Core | |
| data AsType MaryEra Source # | |
Defined in Cardano.Api.Era.Internal.Core | |
| data AsType ShelleyEra Source # | |
Defined in Cardano.Api.Era.Internal.Core | |
| data AsType GovernancePoll Source # | |
Defined in Cardano.Api.Governance.Internal.Poll | |
| data AsType GovernancePollAnswer Source # | |
Defined in Cardano.Api.Governance.Internal.Poll | |
| data AsType CommitteeColdExtendedKey Source # | |
Defined in Cardano.Api.Key.Internal | |
| data AsType CommitteeColdKey Source # | |
Defined in Cardano.Api.Key.Internal | |
| data AsType CommitteeHotExtendedKey Source # | |
Defined in Cardano.Api.Key.Internal | |
| data AsType CommitteeHotKey Source # | |
Defined in Cardano.Api.Key.Internal | |
| data AsType DRepExtendedKey Source # | |
Defined in Cardano.Api.Key.Internal | |
| data AsType DRepKey Source # | |
Defined in Cardano.Api.Key.Internal | |
| data AsType GenesisDelegateExtendedKey Source # | |
Defined in Cardano.Api.Key.Internal | |
| data AsType GenesisDelegateKey Source # | |
Defined in Cardano.Api.Key.Internal | |
| data AsType GenesisExtendedKey Source # | |
Defined in Cardano.Api.Key.Internal | |
| data AsType GenesisKey Source # | |
Defined in Cardano.Api.Key.Internal | |
| data AsType GenesisUTxOKey Source # | |
Defined in Cardano.Api.Key.Internal | |
| data AsType PaymentExtendedKey Source # | |
Defined in Cardano.Api.Key.Internal | |
| data AsType PaymentKey Source # | |
Defined in Cardano.Api.Key.Internal | |
| data AsType StakeExtendedKey Source # | |
Defined in Cardano.Api.Key.Internal | |
| data AsType StakeKey Source # | |
Defined in Cardano.Api.Key.Internal | |
| data AsType StakePoolExtendedKey Source # | |
Defined in Cardano.Api.Key.Internal | |
| data AsType StakePoolKey Source # | |
Defined in Cardano.Api.Key.Internal | |
| data AsType KesKey Source # | |
Defined in Cardano.Api.Key.Internal.Praos | |
| data AsType VrfKey Source # | |
Defined in Cardano.Api.Key.Internal.Praos | |
| data AsType PlutusScriptV1 Source # | |
Defined in Cardano.Api.Plutus.Internal.Script | |
| data AsType PlutusScriptV2 Source # | |
Defined in Cardano.Api.Plutus.Internal.Script | |
| data AsType PlutusScriptV3 Source # | |
Defined in Cardano.Api.Plutus.Internal.Script | |
| data AsType PlutusScriptV4 Source # | |
Defined in Cardano.Api.Plutus.Internal.Script | |
| data AsType ScriptHash Source # | |
Defined in Cardano.Api.Plutus.Internal.Script | |
| data AsType ScriptInAnyLang Source # | |
Defined in Cardano.Api.Plutus.Internal.Script | |
| data AsType SimpleScript' Source # | |
Defined in Cardano.Api.Plutus.Internal.Script | |
| data AsType HashableScriptData Source # | |
Defined in Cardano.Api.Plutus.Internal.ScriptData | |
| data AsType ScriptData Source # | |
Defined in Cardano.Api.Plutus.Internal.ScriptData | |
| data AsType PraosNonce Source # | |
Defined in Cardano.Api.ProtocolParameters | |
| data AsType UpdateProposal Source # | |
Defined in Cardano.Api.ProtocolParameters | |
| data AsType EraHistory Source # | |
Defined in Cardano.Api.Query.Internal.Type.QueryInMode | |
| data AsType TextEnvelope Source # | |
Defined in Cardano.Api.Serialise.TextEnvelope.Internal | |
| data AsType TxId Source # | |
Defined in Cardano.Api.Tx.Internal.TxIn | |
| data AsType TxMetadata Source # | |
Defined in Cardano.Api.Tx.Internal.TxMetadata | |
| data AsType AssetName Source # | |
Defined in Cardano.Api.Value.Internal | |
| data AsType PolicyId Source # | |
Defined in Cardano.Api.Value.Internal | |
| data AsType GovActionId Source # | |
Defined in Cardano.Api.Internal.Orphans.Serialisation | |
| data AsType GovActionIx Source # | |
Defined in Cardano.Api.Internal.Orphans.Serialisation | |
| data AsType Term Source # | |
Defined in Cardano.Api.Serialise.Cbor.Canonical | |
| data AsType Word16 Source # | |
Defined in Cardano.Api.HasTypeProxy | |
| data AsType Word8 Source # | |
Defined in Cardano.Api.HasTypeProxy | |
| data AsType (Address addrtype) Source # | |
Defined in Cardano.Api.Address | |
| data AsType (AddressInEra era) Source # | |
Defined in Cardano.Api.Address | |
| data AsType (Certificate era) Source # | |
Defined in Cardano.Api.Certificate.Internal | |
| data AsType (SignedTx era) Source # | |
Defined in Cardano.Api.Experimental.Tx | |
| data AsType (UnsignedTx era) Source # | |
Defined in Cardano.Api.Experimental.Tx | |
| data AsType (Certificate era) Source # | |
| data AsType (Proposal era) Source # | |
| data AsType (VotingProcedure era) Source # | |
| data AsType (VotingProcedures era) Source # | |
| data AsType (Hash a) Source # | |
Defined in Cardano.Api.Hash | |
| data AsType (SigningKey a) Source # | |
Defined in Cardano.Api.Key.Internal.Class | |
| data AsType (VerificationKey a) Source # | |
Defined in Cardano.Api.Key.Internal.Class | |
| data AsType (PlutusScript lang) Source # | |
Defined in Cardano.Api.Plutus.Internal.Script | |
| data AsType (Script lang) Source # | |
Defined in Cardano.Api.Plutus.Internal.Script | |
| data AsType (ScriptInEra era) Source # | |
Defined in Cardano.Api.Plutus.Internal.Script | |
| data AsType (KeyWitness era) Source # | |
Defined in Cardano.Api.Tx.Internal.Sign | |
| data AsType (Tx era) Source # | |
Defined in Cardano.Api.Tx.Internal.Sign | |
| data AsType (TxBody era) Source # | |
Defined in Cardano.Api.Tx.Internal.Sign | |
| data AsType (Credential 'ColdCommitteeRole) Source # | |
Defined in Cardano.Api.Internal.Orphans.Serialisation | |
| data AsType (Credential 'DRepRole) Source # | |
Defined in Cardano.Api.Internal.Orphans.Serialisation | |
| data AsType (Credential 'HotCommitteeRole) Source # | |
Defined in Cardano.Api.Internal.Orphans.Serialisation | |
| data AsType (PlutusScriptInEra era lang) Source # | |
Defined in Cardano.Api.Plutus.Internal.Script | |
| data AsType (TxOut ctx era) Source # | |
Defined in Cardano.Api.Tx.Internal.Output | |
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:
- The redeemer pointer map
- The set of plutus languages in use
- The set of plutus scripts in use (present in the t)
- The datum map
toPlutusSLanguage :: PlutusScriptVersion lang -> SLanguage (ToLedgerPlutusLanguage lang) Source #