Safe Haskell | None |
---|---|
Language | Haskell2010 |
Cardano.Api.Shelley
Description
This module provides a library interface that is intended to be the complete API for Shelley covering everything, including exposing constructors for the lower level types.
Synopsis
- module Cardano.Api
- data ShelleyGenesis era = ShelleyGenesis {
- sgSystemStart ∷ !UTCTime
- sgNetworkMagic ∷ !Word32
- sgNetworkId ∷ !Network
- sgActiveSlotsCoeff ∷ !PositiveUnitInterval
- sgSecurityParam ∷ !Word64
- sgEpochLength ∷ !EpochSize
- sgSlotsPerKESPeriod ∷ !Word64
- sgMaxKESEvolutions ∷ !Word64
- sgSlotLength ∷ !NominalDiffTime
- sgUpdateQuorum ∷ !Word64
- sgMaxLovelaceSupply ∷ !Word64
- sgProtocolParams ∷ !(PParams era)
- sgGenDelegs ∷ !(Map (KeyHash 'Genesis (Crypto era)) (GenDelegPair (Crypto era)))
- sgInitialFunds ∷ !(Map (Addr (Crypto era)) Coin)
- sgStaking ∷ !(ShelleyGenesisStaking (Crypto era))
- shelleyGenesisDefaults ∷ ShelleyGenesis crypto
- alonzoGenesisDefaults ∷ AlonzoGenesis
- data family Hash keyrole ∷ Type
- data Address addrtype where
- ShelleyAddress ∷ Network → PaymentCredential StandardCrypto → StakeReference StandardCrypto → Address ShelleyAddr
- toShelleyAddr ∷ AddressInEra era → Addr StandardCrypto
- fromShelleyAddr ∷ ShelleyBasedEra era → Addr StandardCrypto → AddressInEra era
- fromShelleyAddrIsSbe ∷ IsShelleyBasedEra era ⇒ Addr StandardCrypto → AddressInEra era
- fromShelleyAddrToAny ∷ Addr StandardCrypto → AddressAny
- toShelleyStakeCredential ∷ StakeCredential → StakeCredential StandardCrypto
- fromShelleyStakeCredential ∷ StakeCredential StandardCrypto → StakeCredential
- data NetworkId
- data PaymentCredential
- data StakeAddress where
- StakeAddress ∷ Network → StakeCredential StandardCrypto → StakeAddress
- data StakeAddressReference
- data StakeCredential
- toShelleyStakeAddr ∷ StakeAddress → RewardAcnt StandardCrypto
- fromShelleyStakeAddr ∷ RewardAcnt StandardCrypto → StakeAddress
- fromShelleyStakeReference ∷ StakeReference StandardCrypto → StakeAddressReference
- fromShelleyPaymentCredential ∷ PaymentCredential StandardCrypto → PaymentCredential
- data TxBody era where
- ShelleyTxBody ∷ ShelleyBasedEra era → TxBody (ShelleyLedgerEra era) → [Script (ShelleyLedgerEra era)] → TxBodyScriptData era → Maybe (AuxiliaryData (ShelleyLedgerEra era)) → TxScriptValidity era → TxBody era
- newtype TxId = TxId (Hash StandardCrypto EraIndependentTxBody)
- toShelleyTxId ∷ TxId → TxId StandardCrypto
- fromShelleyTxId ∷ TxId StandardCrypto → TxId
- getTxIdShelley ∷ Crypto (ShelleyLedgerEra era) ~ StandardCrypto ⇒ UsesTxBody (ShelleyLedgerEra era) ⇒ ShelleyBasedEra era → TxBody (ShelleyLedgerEra era) → TxId
- data TxIn = TxIn TxId TxIx
- toShelleyTxIn ∷ TxIn → TxIn StandardCrypto
- fromShelleyTxIn ∷ TxIn StandardCrypto → TxIn
- data TxOut ctx era = TxOut (AddressInEra era) (TxOutValue era) (TxOutDatum ctx era)
- toShelleyTxOut ∷ ∀ era ledgerera. ShelleyLedgerEra era ~ ledgerera ⇒ ShelleyBasedEra era → TxOut CtxUTxO era → TxOut ledgerera
- fromShelleyTxOut ∷ ShelleyLedgerEra era ~ ledgerera ⇒ ShelleyBasedEra era → TxOut ledgerera → TxOut ctx era
- newtype TxIx = TxIx Word
- newtype Lovelace = Lovelace Integer
- toShelleyLovelace ∷ Lovelace → Coin
- fromShelleyLovelace ∷ Coin → Lovelace
- toMaryValue ∷ Value → Value StandardCrypto
- fromMaryValue ∷ Value StandardCrypto → Value
- calcMinimumDeposit ∷ Value → Lovelace → Lovelace
- data Tx era where
- ShelleyTx ∷ ShelleyBasedEra era → Tx (ShelleyLedgerEra era) → Tx era
- data KeyWitness era where
- ShelleyBootstrapWitness ∷ ShelleyBasedEra era → BootstrapWitness StandardCrypto → KeyWitness era
- ShelleyKeyWitness ∷ ShelleyBasedEra era → WitVKey Witness StandardCrypto → KeyWitness era
- data ShelleyWitnessSigningKey
- = WitnessPaymentKey (SigningKey PaymentKey)
- | WitnessPaymentExtendedKey (SigningKey PaymentExtendedKey)
- | WitnessStakeKey (SigningKey StakeKey)
- | WitnessStakeExtendedKey (SigningKey StakeExtendedKey)
- | WitnessStakePoolKey (SigningKey StakePoolKey)
- | WitnessGenesisKey (SigningKey GenesisKey)
- | WitnessGenesisExtendedKey (SigningKey GenesisExtendedKey)
- | WitnessGenesisDelegateKey (SigningKey GenesisDelegateKey)
- | WitnessGenesisDelegateExtendedKey (SigningKey GenesisDelegateExtendedKey)
- data ShelleySigningKey
- = ShelleyNormalSigningKey (SignKeyDSIGN StandardCrypto)
- | ShelleyExtendedSigningKey XPrv
- getShelleyKeyWitnessVerificationKey ∷ ShelleySigningKey → VKey Witness StandardCrypto
- getTxBodyAndWitnesses ∷ Tx era → (TxBody era, [KeyWitness era])
- makeShelleySignature ∷ SignableRepresentation tosign ⇒ tosign → ShelleySigningKey → SignedDSIGN StandardCrypto tosign
- toShelleySigningKey ∷ ShelleyWitnessSigningKey → ShelleySigningKey
- fromConsensusBlock ∷ ConsensusBlockForMode mode ~ block ⇒ ConsensusMode mode → block → BlockInMode mode
- toConsensusBlock ∷ ConsensusBlockForMode mode ~ block ⇒ BlockInMode mode → block
- fromConsensusTip ∷ ConsensusBlockForMode mode ~ block ⇒ ConsensusMode mode → Tip block → ChainTip
- fromConsensusPointInMode ∷ ConsensusMode mode → Point (ConsensusBlockForMode mode) → ChainPoint
- toConsensusPointInMode ∷ ConsensusMode mode → ChainPoint → Point (ConsensusBlockForMode mode)
- toConsensusPointHF ∷ HeaderHash block ~ OneEraHash xs ⇒ ChainPoint → Point block
- toShelleyMetadata ∷ Map Word64 TxMetadataValue → Map Word64 Metadatum
- fromShelleyMetadata ∷ Map Word64 Metadatum → Map Word64 TxMetadataValue
- toShelleyMetadatum ∷ TxMetadataValue → Metadatum
- fromShelleyMetadatum ∷ Metadatum → TxMetadataValue
- data ProtocolParameters = ProtocolParameters {
- protocolParamProtocolVersion ∷ (Natural, Natural)
- protocolParamDecentralization ∷ Rational
- protocolParamExtraPraosEntropy ∷ Maybe PraosNonce
- protocolParamMaxBlockHeaderSize ∷ Natural
- protocolParamMaxBlockBodySize ∷ Natural
- protocolParamMaxTxSize ∷ Natural
- protocolParamTxFeeFixed ∷ Natural
- protocolParamTxFeePerByte ∷ Natural
- protocolParamMinUTxOValue ∷ Maybe Lovelace
- protocolParamStakeAddressDeposit ∷ Lovelace
- protocolParamStakePoolDeposit ∷ Lovelace
- protocolParamMinPoolCost ∷ Lovelace
- protocolParamPoolRetireMaxEpoch ∷ EpochNo
- protocolParamStakePoolTargetNum ∷ Natural
- protocolParamPoolPledgeInfluence ∷ Rational
- protocolParamMonetaryExpansion ∷ Rational
- protocolParamTreasuryCut ∷ Rational
- protocolParamUTxOCostPerWord ∷ Maybe Lovelace
- protocolParamCostModels ∷ Map AnyPlutusScriptVersion CostModel
- protocolParamPrices ∷ Maybe ExecutionUnitPrices
- protocolParamMaxTxExUnits ∷ Maybe ExecutionUnits
- protocolParamMaxBlockExUnits ∷ Maybe ExecutionUnits
- protocolParamMaxValueSize ∷ Maybe Natural
- protocolParamCollateralPercent ∷ Maybe Natural
- protocolParamMaxCollateralInputs ∷ Maybe Natural
- checkProtocolParameters ∷ ∀ era. IsCardanoEra era ⇒ ShelleyBasedEra era → ProtocolParameters → Either ProtocolParametersError ()
- data ProtocolParametersError
- toShelleyScript ∷ ScriptInEra era → Script (ShelleyLedgerEra era)
- toShelleyMultiSig ∷ SimpleScript SimpleScriptV1 → MultiSig StandardCrypto
- fromShelleyMultiSig ∷ MultiSig StandardCrypto → SimpleScript lang
- toAllegraTimelock ∷ ∀ lang. SimpleScript lang → Timelock StandardCrypto
- fromAllegraTimelock ∷ TimeLocksSupported lang → Timelock StandardCrypto → SimpleScript lang
- toShelleyScriptHash ∷ ScriptHash → ScriptHash StandardCrypto
- fromShelleyScriptHash ∷ ScriptHash StandardCrypto → ScriptHash
- data PlutusScript lang where
- toPlutusData ∷ ScriptData → Data
- fromPlutusData ∷ Data → ScriptData
- toAlonzoData ∷ ScriptData → Data ledgerera
- fromAlonzoData ∷ Data ledgerera → ScriptData
- toAlonzoPrices ∷ ExecutionUnitPrices → Maybe Prices
- fromAlonzoPrices ∷ Prices → ExecutionUnitPrices
- toAlonzoExUnits ∷ ExecutionUnits → ExUnits
- fromAlonzoExUnits ∷ ExUnits → ExecutionUnits
- toAlonzoRdmrPtr ∷ ScriptWitnessIndex → RdmrPtr
- fromAlonzoRdmrPtr ∷ RdmrPtr → ScriptWitnessIndex
- scriptDataFromJsonDetailedSchema ∷ Value → Either ScriptDataJsonSchemaError ScriptData
- scriptDataToJsonDetailedSchema ∷ ScriptData → Value
- calculateExecutionUnitsLovelace ∷ ExecutionUnitPrices → ExecutionUnits → Maybe Lovelace
- data Certificate
- = StakeAddressRegistrationCertificate StakeCredential
- | StakeAddressDeregistrationCertificate StakeCredential
- | StakeAddressDelegationCertificate StakeCredential PoolId
- | StakePoolRegistrationCertificate StakePoolParameters
- | StakePoolRetirementCertificate PoolId EpochNo
- | GenesisKeyDelegationCertificate (Hash GenesisKey) (Hash GenesisDelegateKey) (Hash VrfKey)
- | MIRCertificate MIRPot MIRTarget
- toShelleyCertificate ∷ Certificate → DCert StandardCrypto
- fromShelleyCertificate ∷ DCert StandardCrypto → Certificate
- data OperationalCertificate = OperationalCertificate !(OCert StandardCrypto) !(VerificationKey StakePoolKey)
- data OperationalCertificateIssueCounter = OperationalCertificateIssueCounter {}
- data OperationalCertIssueError = OperationalCertKeyMismatch (VerificationKey StakePoolKey) (VerificationKey StakePoolKey)
- data StakePoolMetadata = StakePoolMetadata !Text !Text !Text !Text
- stakePoolName ∷ StakePoolMetadata → Text
- stakePoolDescription ∷ StakePoolMetadata → Text
- stakePoolTicker ∷ StakePoolMetadata → Text
- stakePoolHomepage ∷ StakePoolMetadata → Text
- data StakePoolMetadataReference = StakePoolMetadataReference Text (Hash StakePoolMetadata)
- stakePoolMetadataURL ∷ StakePoolMetadataReference → Text
- stakePoolMetadataHash ∷ StakePoolMetadataReference → Hash StakePoolMetadata
- data StakePoolParameters = StakePoolParameters PoolId (Hash VrfKey) Lovelace Rational StakeAddress Lovelace [Hash StakeKey] [StakePoolRelay] (Maybe StakePoolMetadataReference)
- stakePoolId ∷ StakePoolParameters → PoolId
- stakePoolVRF ∷ StakePoolParameters → Hash VrfKey
- stakePoolCost ∷ StakePoolParameters → Lovelace
- stakePoolMargin ∷ StakePoolParameters → Rational
- stakePoolRewardAccount ∷ StakePoolParameters → StakeAddress
- stakePoolPledge ∷ StakePoolParameters → Lovelace
- stakePoolOwners ∷ StakePoolParameters → [Hash StakeKey]
- stakePoolRelays ∷ StakePoolParameters → [StakePoolRelay]
- stakePoolMetadata ∷ StakePoolParameters → Maybe StakePoolMetadataReference
- data StakePoolRelay
- = StakePoolRelayIp (Maybe IPv4) (Maybe IPv6) (Maybe PortNumber)
- | StakePoolRelayDnsARecord ByteString (Maybe PortNumber)
- | StakePoolRelayDnsSrvRecord ByteString
- newtype EpochNo = EpochNo {}
- data StakePoolKey
- type PoolId = Hash StakePoolKey
- data KesKey
- newtype KESPeriod = KESPeriod {}
- data VrfKey
- data LocalNodeConnectInfo mode = LocalNodeConnectInfo (ConsensusModeParams mode) NetworkId FilePath
- data ShelleyMode
- data ConsensusMode mode where
- data LocalNodeClientProtocols block point tip tx txerr query m = LocalNodeClientProtocols (LocalChainSyncClient block point tip m) (Maybe (LocalTxSubmissionClient tx txerr m ())) (Maybe (LocalStateQueryClient block point query m ()))
- type family ShelleyLedgerEra era where ...
- data DebugLedgerState era where
- DebugLedgerState ∷ ShelleyLedgerEra era ~ ledgerera ⇒ NewEpochState ledgerera → DebugLedgerState era
- decodeDebugLedgerState ∷ ∀ era. FromCBOR (DebugLedgerState era) ⇒ SerialisedDebugLedgerState era → Either ByteString (DebugLedgerState era)
- newtype ProtocolState era = ProtocolState (Serialised (ChainDepState (Crypto (ShelleyLedgerEra era))))
- decodeProtocolState ∷ ProtocolState era → Either ByteString (ChainDepState StandardCrypto)
- newtype SerialisedDebugLedgerState era = SerialisedDebugLedgerState (Serialised (NewEpochState (ShelleyLedgerEra era)))
- newtype SerialisedCurrentEpochState era = SerialisedCurrentEpochState (Serialised (EpochState (ShelleyLedgerEra era)))
- decodeCurrentEpochState ∷ ∀ era. Era (ShelleyLedgerEra era) ⇒ Share (TxOut (ShelleyLedgerEra era)) ~ Interns (Credential 'Staking (Crypto (ShelleyLedgerEra era))) ⇒ FromSharedCBOR (TxOut (ShelleyLedgerEra era)) ⇒ Share (TxOut (ShelleyLedgerEra era)) ~ Interns (Credential 'Staking (Crypto (ShelleyLedgerEra era))) ⇒ FromCBOR (PParams (ShelleyLedgerEra era)) ⇒ FromCBOR (Value (ShelleyLedgerEra era)) ⇒ FromCBOR (State (EraRule "PPUP" (ShelleyLedgerEra era))) ⇒ SerialisedCurrentEpochState era → Either DecoderError (CurrentEpochState era)
- newtype UTxO era = UTxO {}
- data LeadershipError
- = LeaderErrDecodeLedgerStateFailure
- | LeaderErrDecodeProtocolStateFailure
- | LeaderErrDecodeProtocolEpochStateFailure DecoderError
- | LeaderErrGenesisSlot
- | LeaderErrStakePoolHasNoStake PoolId
- | LeaderErrStakeDistribUnstable SlotNo SlotNo SlotNo SlotNo
- | LeaderErrSlotRangeCalculationFailure Text
- | LeaderErrCandidateNonceStillEvolving
- currentEpochEligibleLeadershipSlots ∷ ShelleyLedgerEra era ~ ledgerera ⇒ Era ledgerera ⇒ HasField "_d" (PParams ledgerera) UnitInterval ⇒ Signable (VRF (Crypto ledgerera)) Seed ⇒ Share (TxOut (ShelleyLedgerEra era)) ~ Interns (Credential 'Staking (Crypto (ShelleyLedgerEra era))) ⇒ Crypto ledgerera ~ StandardCrypto ⇒ ShelleyBasedEra era → ShelleyGenesis StandardShelley → EpochInfo (Either Text) → ProtocolParameters → ProtocolState era → PoolId → SigningKey VrfKey → SerialisedCurrentEpochState era → EpochNo → Either LeadershipError (Set SlotNo)
- nextEpochEligibleLeadershipSlots ∷ HasField "_d" (PParams (ShelleyLedgerEra era)) UnitInterval ⇒ Era (ShelleyLedgerEra era) ⇒ Share (TxOut (ShelleyLedgerEra era)) ~ Interns (Credential 'Staking (Crypto (ShelleyLedgerEra era))) ⇒ ShelleyBasedEra era → ShelleyGenesis StandardShelley → SerialisedCurrentEpochState era → ProtocolState era → PoolId → SigningKey VrfKey → ProtocolParameters → EpochInfo (Either Text) → (ChainTip, EpochNo) → Either LeadershipError (Set SlotNo)
- shelleyPayAddrToPlutusPubKHash ∷ Address ShelleyAddr → Maybe PubKeyHash
- toShelleyNetwork ∷ NetworkId → Network
- fromShelleyPParams ∷ PParams ledgerera → ProtocolParameters
Documentation
module Cardano.Api
Genesis
data ShelleyGenesis era #
Constructors
ShelleyGenesis | |
Fields
|
Instances
shelleyGenesisDefaults ∷ ShelleyGenesis crypto Source #
Some reasonable starting defaults for constructing a ShelleyGenesis
.
You must override at least the following fields for this to be useful:
sgSystemStart
the time of the first blocksgNetworkMagic
to a suitable testnet or mainnet network magic number.sgGenDelegs
to have some initial nodessgInitialFunds
to have any money in the systemsgMaxLovelaceSupply
must be at least the sum of thesgInitialFunds
but more if you want to allow for rewards.
alonzoGenesisDefaults ∷ AlonzoGenesis Source #
Reasonable starting defaults for constructing an AlonzoGenesis
.
Cryptographic key interface
Hashes
data family Hash keyrole ∷ Type Source #
Instances
Payment addresses
Constructing and inspecting Shelley payment addresses
data Address addrtype where Source #
Addresses are used as locations where assets live. The address determines the rights needed to spend assets at the address: in particular holding some signing key or being able to satisfy the conditions of a script.
There are currently two types of address:
- Byron addresses, which use the type tag
ByronAddr
; and - Shelley addresses, which use the type tag
ShelleyAddr
. Notably, Shelley addresses support scripts and stake delegation.
The address type is subtly from the ledger era in which each
address type is valid: while Byron addresses are the only choice in the
Byron era, the Shelley era and all subsequent eras support both Byron and
Shelley addresses. The Address
type param only says the type of the address
(either Byron or Shelley). The AddressInEra
type connects the address type
with the era in which it is supported.
Constructors
ShelleyAddress ∷ Network → PaymentCredential StandardCrypto → StakeReference StandardCrypto → Address ShelleyAddr | Shelley addresses allow delegation. Shelley addresses were introduced in Shelley era and are thus supported from the Shelley era onwards |
Instances
toShelleyAddr ∷ AddressInEra era → Addr StandardCrypto Source #
fromShelleyAddr ∷ ShelleyBasedEra era → Addr StandardCrypto → AddressInEra era Source #
fromShelleyAddrIsSbe ∷ IsShelleyBasedEra era ⇒ Addr StandardCrypto → AddressInEra era Source #
fromShelleyAddrToAny ∷ Addr StandardCrypto → AddressAny Source #
toShelleyStakeCredential ∷ StakeCredential → StakeCredential StandardCrypto Source #
fromShelleyStakeCredential ∷ StakeCredential StandardCrypto → StakeCredential Source #
Stake addresses
data PaymentCredential Source #
Constructors
PaymentCredentialByKey (Hash PaymentKey) | |
PaymentCredentialByScript ScriptHash |
Instances
Eq PaymentCredential Source # | |
Defined in Cardano.Api.Address Methods (==) ∷ PaymentCredential → PaymentCredential → Bool Source # (/=) ∷ PaymentCredential → PaymentCredential → Bool Source # | |
Ord PaymentCredential Source # | |
Defined in Cardano.Api.Address Methods compare ∷ PaymentCredential → PaymentCredential → Ordering Source # (<) ∷ PaymentCredential → PaymentCredential → Bool Source # (<=) ∷ PaymentCredential → PaymentCredential → Bool Source # (>) ∷ PaymentCredential → PaymentCredential → Bool Source # (>=) ∷ PaymentCredential → PaymentCredential → Bool Source # max ∷ PaymentCredential → PaymentCredential → PaymentCredential Source # min ∷ PaymentCredential → PaymentCredential → PaymentCredential Source # | |
Show PaymentCredential Source # | |
Defined in Cardano.Api.Address |
data StakeAddress where Source #
Constructors
StakeAddress ∷ Network → StakeCredential StandardCrypto → StakeAddress |
Instances
data StakeAddressReference Source #
Constructors
StakeAddressByValue StakeCredential | |
StakeAddressByPointer StakeAddressPointer | |
NoStakeAddress |
Instances
Eq StakeAddressReference Source # | |
Defined in Cardano.Api.Address Methods (==) ∷ StakeAddressReference → StakeAddressReference → Bool Source # (/=) ∷ StakeAddressReference → StakeAddressReference → Bool Source # | |
Show StakeAddressReference Source # | |
Defined in Cardano.Api.Address |
data StakeCredential Source #
Constructors
StakeCredentialByKey (Hash StakeKey) | |
StakeCredentialByScript ScriptHash |
Instances
Eq StakeCredential Source # | |
Defined in Cardano.Api.Address Methods | |
Ord StakeCredential Source # | |
Defined in Cardano.Api.Address Methods compare ∷ StakeCredential → StakeCredential → Ordering Source # (<) ∷ StakeCredential → StakeCredential → Bool Source # (<=) ∷ StakeCredential → StakeCredential → Bool Source # (>) ∷ StakeCredential → StakeCredential → Bool Source # (>=) ∷ StakeCredential → StakeCredential → Bool Source # max ∷ StakeCredential → StakeCredential → StakeCredential Source # min ∷ StakeCredential → StakeCredential → StakeCredential Source # | |
Show StakeCredential Source # | |
Defined in Cardano.Api.Address |
toShelleyStakeAddr ∷ StakeAddress → RewardAcnt StandardCrypto Source #
fromShelleyStakeAddr ∷ RewardAcnt StandardCrypto → StakeAddress Source #
fromShelleyStakeReference ∷ StakeReference StandardCrypto → StakeAddressReference Source #
fromShelleyPaymentCredential ∷ PaymentCredential StandardCrypto → PaymentCredential Source #
Building transactions
Constructing and inspecting transactions
data TxBody era where Source #
Constructors
ShelleyTxBody | |
Fields
|
Instances
Eq (TxBody era) Source # | |
Show (TxBody era) Source # | |
HasTypeProxy era ⇒ HasTypeProxy (TxBody era) Source # | |
IsCardanoEra era ⇒ SerialiseAsCBOR (TxBody era) Source # | |
Defined in Cardano.Api.TxBody Methods serialiseToCBOR ∷ TxBody era → ByteString Source # deserialiseFromCBOR ∷ AsType (TxBody era) → ByteString → Either DecoderError (TxBody era) Source # | |
IsCardanoEra era ⇒ HasTextEnvelope (TxBody era) Source # | |
Defined in Cardano.Api.TxBody Methods textEnvelopeType ∷ AsType (TxBody era) → TextEnvelopeType Source # textEnvelopeDefaultDescr ∷ TxBody era → TextEnvelopeDescr Source # | |
data AsType (TxBody era) Source # | |
Defined in Cardano.Api.TxBody |
Constructors
TxId (Hash StandardCrypto EraIndependentTxBody) |
Instances
Eq TxId Source # | |
Ord TxId Source # | |
Show TxId Source # | |
IsString TxId Source # | |
Defined in Cardano.Api.TxBody Methods fromString ∷ String → TxId Source # | |
FromJSON TxId Source # | |
Defined in Cardano.Api.TxBody | |
ToJSON TxId Source # | |
Defined in Cardano.Api.TxBody Methods toEncoding ∷ TxId → Encoding # toJSONList ∷ [TxId] → Value # toEncodingList ∷ [TxId] → Encoding # | |
FromJSONKey TxId Source # | |
Defined in Cardano.Api.TxBody | |
ToJSONKey TxId Source # | |
Defined in Cardano.Api.TxBody | |
HasTypeProxy TxId Source # | |
SerialiseAsRawBytes TxId Source # | |
Defined in Cardano.Api.TxBody Methods serialiseToRawBytes ∷ TxId → ByteString Source # deserialiseFromRawBytes ∷ AsType TxId → ByteString → Maybe TxId Source # | |
data AsType TxId Source # | |
Defined in Cardano.Api.TxBody |
toShelleyTxId ∷ TxId → TxId StandardCrypto Source #
fromShelleyTxId ∷ TxId StandardCrypto → TxId Source #
getTxIdShelley ∷ Crypto (ShelleyLedgerEra era) ~ StandardCrypto ⇒ UsesTxBody (ShelleyLedgerEra era) ⇒ ShelleyBasedEra era → TxBody (ShelleyLedgerEra era) → TxId Source #
Instances
Eq TxIn Source # | |
Ord TxIn Source # | |
Show TxIn Source # | |
FromJSON TxIn Source # | |
Defined in Cardano.Api.TxBody | |
ToJSON TxIn Source # | |
Defined in Cardano.Api.TxBody Methods toEncoding ∷ TxIn → Encoding # toJSONList ∷ [TxIn] → Value # toEncodingList ∷ [TxIn] → Encoding # | |
FromJSONKey TxIn Source # | |
Defined in Cardano.Api.TxBody | |
ToJSONKey TxIn Source # | |
Defined in Cardano.Api.TxBody |
toShelleyTxIn ∷ TxIn → TxIn StandardCrypto Source #
This function may overflow on the transaction index. Call sites must ensure that all uses of this function are appropriately guarded.
fromShelleyTxIn ∷ TxIn StandardCrypto → TxIn Source #
Constructors
TxOut (AddressInEra era) (TxOutValue era) (TxOutDatum ctx era) |
Instances
Eq (TxOut ctx era) Source # | |
Show (TxOut ctx era) Source # | |
(IsShelleyBasedEra era, IsCardanoEra era) ⇒ FromJSON (TxOut CtxUTxO era) Source # | |
Defined in Cardano.Api.TxBody | |
(IsShelleyBasedEra era, IsCardanoEra era) ⇒ FromJSON (TxOut CtxTx era) Source # | |
Defined in Cardano.Api.TxBody | |
IsCardanoEra era ⇒ ToJSON (TxOut ctx era) Source # | |
Defined in Cardano.Api.TxBody Methods toJSON ∷ TxOut ctx era → Value # toEncoding ∷ TxOut ctx era → Encoding # toJSONList ∷ [TxOut ctx era] → Value # toEncodingList ∷ [TxOut ctx era] → Encoding # |
toShelleyTxOut ∷ ∀ era ledgerera. ShelleyLedgerEra era ~ ledgerera ⇒ ShelleyBasedEra era → TxOut CtxUTxO era → TxOut ledgerera Source #
fromShelleyTxOut ∷ ShelleyLedgerEra era ~ ledgerera ⇒ ShelleyBasedEra era → TxOut ledgerera → TxOut ctx era Source #
Instances
Enum TxIx Source # | |
Defined in Cardano.Api.TxBody | |
Eq TxIx Source # | |
Ord TxIx Source # | |
Show TxIx Source # | |
FromJSON TxIx Source # | |
Defined in Cardano.Api.TxBody | |
ToJSON TxIx Source # | |
Defined in Cardano.Api.TxBody Methods toEncoding ∷ TxIx → Encoding # toJSONList ∷ [TxIx] → Value # toEncodingList ∷ [TxIx] → Encoding # |
Instances
Enum Lovelace Source # | |
Defined in Cardano.Api.Value Methods succ ∷ Lovelace → Lovelace Source # pred ∷ Lovelace → Lovelace Source # toEnum ∷ Int → Lovelace Source # fromEnum ∷ Lovelace → Int Source # enumFrom ∷ Lovelace → [Lovelace] Source # enumFromThen ∷ Lovelace → Lovelace → [Lovelace] Source # enumFromTo ∷ Lovelace → Lovelace → [Lovelace] Source # enumFromThenTo ∷ Lovelace → Lovelace → Lovelace → [Lovelace] Source # | |
Eq Lovelace Source # | |
Num Lovelace Source # | |
Defined in Cardano.Api.Value | |
Ord Lovelace Source # | |
Show Lovelace Source # | |
Semigroup Lovelace Source # | |
Monoid Lovelace Source # | |
FromJSON Lovelace Source # | |
Defined in Cardano.Api.Value | |
ToJSON Lovelace Source # | |
Defined in Cardano.Api.Value Methods toEncoding ∷ Lovelace → Encoding # toJSONList ∷ [Lovelace] → Value # toEncodingList ∷ [Lovelace] → Encoding # | |
FromCBOR Lovelace Source # | |
ToCBOR Lovelace Source # | |
toShelleyLovelace ∷ Lovelace → Coin Source #
fromShelleyLovelace ∷ Coin → Lovelace Source #
toMaryValue ∷ Value → Value StandardCrypto Source #
fromMaryValue ∷ Value StandardCrypto → Value Source #
calcMinimumDeposit ∷ Value → Lovelace → Lovelace Source #
Calculate cost of making a UTxO entry for a given Value
and
mininimum UTxO value derived from the ProtocolParameters
Signing transactions
Creating transaction witnesses one by one, or all in one go.
Constructors
ShelleyTx ∷ ShelleyBasedEra era → Tx (ShelleyLedgerEra era) → Tx era |
Instances
Eq (Tx era) Source # | |
Show (Tx era) Source # | |
HasTypeProxy era ⇒ HasTypeProxy (Tx era) Source # | |
IsCardanoEra era ⇒ SerialiseAsCBOR (Tx era) Source # | |
Defined in Cardano.Api.Tx Methods serialiseToCBOR ∷ Tx era → ByteString Source # deserialiseFromCBOR ∷ AsType (Tx era) → ByteString → Either DecoderError (Tx era) Source # | |
IsCardanoEra era ⇒ HasTextEnvelope (Tx era) Source # | |
Defined in Cardano.Api.Tx Methods textEnvelopeType ∷ AsType (Tx era) → TextEnvelopeType Source # textEnvelopeDefaultDescr ∷ Tx era → TextEnvelopeDescr Source # | |
data AsType (Tx era) Source # | |
Defined in Cardano.Api.Tx |
Incremental signing and separate witnesses
data KeyWitness era where Source #
Constructors
ShelleyBootstrapWitness ∷ ShelleyBasedEra era → BootstrapWitness StandardCrypto → KeyWitness era | |
ShelleyKeyWitness ∷ ShelleyBasedEra era → WitVKey Witness StandardCrypto → KeyWitness era |
Instances
data ShelleyWitnessSigningKey Source #
Constructors
data ShelleySigningKey Source #
We support making key witnesses with both normal and extended signing keys.
Constructors
ShelleyNormalSigningKey (SignKeyDSIGN StandardCrypto) | A normal ed25519 signing key |
ShelleyExtendedSigningKey XPrv | An extended ed25519 signing key |
getShelleyKeyWitnessVerificationKey ∷ ShelleySigningKey → VKey Witness StandardCrypto Source #
getTxBodyAndWitnesses ∷ Tx era → (TxBody era, [KeyWitness era]) Source #
makeShelleySignature ∷ SignableRepresentation tosign ⇒ tosign → ShelleySigningKey → SignedDSIGN StandardCrypto tosign Source #
Blocks
fromConsensusBlock ∷ ConsensusBlockForMode mode ~ block ⇒ ConsensusMode mode → block → BlockInMode mode Source #
toConsensusBlock ∷ ConsensusBlockForMode mode ~ block ⇒ BlockInMode mode → block Source #
fromConsensusTip ∷ ConsensusBlockForMode mode ~ block ⇒ ConsensusMode mode → Tip block → ChainTip Source #
fromConsensusPointInMode ∷ ConsensusMode mode → Point (ConsensusBlockForMode mode) → ChainPoint Source #
toConsensusPointInMode ∷ ConsensusMode mode → ChainPoint → Point (ConsensusBlockForMode mode) Source #
toConsensusPointHF ∷ HeaderHash block ~ OneEraHash xs ⇒ ChainPoint → Point block Source #
Convert a Point
for multi-era block type
Transaction metadata
Embedding additional structured data within transactions.
toShelleyMetadata ∷ Map Word64 TxMetadataValue → Map Word64 Metadatum Source #
fromShelleyMetadata ∷ Map Word64 Metadatum → Map Word64 TxMetadataValue Source #
toShelleyMetadatum ∷ TxMetadataValue → Metadatum Source #
fromShelleyMetadatum ∷ Metadatum → TxMetadataValue Source #
Protocol parameters
data ProtocolParameters Source #
The values of the set of updatable protocol parameters. At any particular point on the chain there is a current set of parameters in use.
These parameters can be updated (at epoch boundaries) via an
UpdateProposal
, which contains a ProtocolParametersUpdate
.
The ProtocolParametersUpdate
is essentially a diff for the
ProtocolParameters
.
There are also parameters fixed in the Genesis file. See GenesisParameters
.
Constructors
ProtocolParameters | |
Fields
|
Instances
checkProtocolParameters ∷ ∀ era. IsCardanoEra era ⇒ ShelleyBasedEra era → ProtocolParameters → Either ProtocolParametersError () Source #
data ProtocolParametersError Source #
Constructors
PParamsErrorMissingMinUTxoValue AnyCardanoEra | |
PParamsErrorMissingAlonzoProtocolParameter |
Instances
Show ProtocolParametersError Source # | |
Defined in Cardano.Api.ProtocolParameters | |
Error ProtocolParametersError Source # | |
Defined in Cardano.Api.ProtocolParameters Methods |
Scripts
toShelleyScript ∷ ScriptInEra era → Script (ShelleyLedgerEra era) Source #
toShelleyMultiSig ∷ SimpleScript SimpleScriptV1 → MultiSig StandardCrypto Source #
Conversion for the MultiSig
language used by the Shelley era.
fromShelleyMultiSig ∷ MultiSig StandardCrypto → SimpleScript lang Source #
Conversion for the MultiSig
language used by the Shelley era.
toAllegraTimelock ∷ ∀ lang. SimpleScript lang → Timelock StandardCrypto Source #
Conversion for the Timelock
language that is shared between the
Allegra and Mary eras.
fromAllegraTimelock ∷ TimeLocksSupported lang → Timelock StandardCrypto → SimpleScript lang Source #
Conversion for the Timelock
language that is shared between the
Allegra and Mary eras.
toShelleyScriptHash ∷ ScriptHash → ScriptHash StandardCrypto Source #
fromShelleyScriptHash ∷ ScriptHash StandardCrypto → ScriptHash Source #
data PlutusScript lang where Source #
Plutus scripts.
Note that Plutus scripts have a binary serialisation but no JSON serialisation.
Constructors
PlutusScriptSerialised ∷ ShortByteString → PlutusScript lang |
Instances
toPlutusData ∷ ScriptData → Data Source #
fromPlutusData ∷ Data → ScriptData Source #
toAlonzoData ∷ ScriptData → Data ledgerera Source #
fromAlonzoData ∷ Data ledgerera → ScriptData Source #
toAlonzoPrices ∷ ExecutionUnitPrices → Maybe Prices Source #
fromAlonzoPrices ∷ Prices → ExecutionUnitPrices Source #
toAlonzoExUnits ∷ ExecutionUnits → ExUnits Source #
fromAlonzoExUnits ∷ ExUnits → ExecutionUnits Source #
toAlonzoRdmrPtr ∷ ScriptWitnessIndex → RdmrPtr Source #
fromAlonzoRdmrPtr ∷ RdmrPtr → ScriptWitnessIndex Source #
scriptDataToJsonDetailedSchema ∷ ScriptData → Value Source #
Certificates
data Certificate Source #
Constructors
Instances
toShelleyCertificate ∷ Certificate → DCert StandardCrypto Source #
fromShelleyCertificate ∷ DCert StandardCrypto → Certificate Source #
Operational certificates
data OperationalCertificate Source #
Constructors
OperationalCertificate !(OCert StandardCrypto) !(VerificationKey StakePoolKey) |
Instances
data OperationalCertificateIssueCounter Source #
Constructors
OperationalCertificateIssueCounter | |
Fields |
Instances
Eq OperationalCertificateIssueCounter Source # | |
Show OperationalCertificateIssueCounter Source # | |
FromCBOR OperationalCertificateIssueCounter Source # | |
Defined in Cardano.Api.OperationalCertificate Methods fromCBOR ∷ Decoder s OperationalCertificateIssueCounter # | |
ToCBOR OperationalCertificateIssueCounter Source # | |
Defined in Cardano.Api.OperationalCertificate Methods toCBOR ∷ OperationalCertificateIssueCounter → Encoding # encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy OperationalCertificateIssueCounter → Size # encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [OperationalCertificateIssueCounter] → Size # | |
HasTypeProxy OperationalCertificateIssueCounter Source # | |
Defined in Cardano.Api.OperationalCertificate Associated Types | |
SerialiseAsCBOR OperationalCertificateIssueCounter Source # | |
HasTextEnvelope OperationalCertificateIssueCounter Source # | |
data AsType OperationalCertificateIssueCounter Source # | |
data OperationalCertIssueError Source #
Constructors
OperationalCertKeyMismatch (VerificationKey StakePoolKey) (VerificationKey StakePoolKey) | The stake pool verification key expected for the
Order: pool vkey expected, pool skey supplied |
Instances
Show OperationalCertIssueError Source # | |
Defined in Cardano.Api.OperationalCertificate | |
Error OperationalCertIssueError Source # | |
Defined in Cardano.Api.OperationalCertificate Methods |
Stake Pool
data StakePoolMetadata Source #
A representation of the required fields for off-chain stake pool metadata.
Constructors
StakePoolMetadata !Text !Text !Text !Text |
Instances
stakePoolName ∷ StakePoolMetadata → Text Source #
A name of up to 50 characters.
stakePoolDescription ∷ StakePoolMetadata → Text Source #
A description of up to 255 characters.
stakePoolTicker ∷ StakePoolMetadata → Text Source #
A ticker of 3-5 characters, for a compact display of stake pools in a wallet.
stakePoolHomepage ∷ StakePoolMetadata → Text Source #
A URL to a homepage with additional information about the pool. n.b. the spec does not specify a character limit for this field.
data StakePoolMetadataReference Source #
Constructors
StakePoolMetadataReference Text (Hash StakePoolMetadata) |
Instances
Eq StakePoolMetadataReference Source # | |
Defined in Cardano.Api.Certificate | |
Show StakePoolMetadataReference Source # | |
Defined in Cardano.Api.Certificate |
data StakePoolParameters Source #
Constructors
StakePoolParameters PoolId (Hash VrfKey) Lovelace Rational StakeAddress Lovelace [Hash StakeKey] [StakePoolRelay] (Maybe StakePoolMetadataReference) |
Instances
Eq StakePoolParameters Source # | |
Defined in Cardano.Api.Certificate Methods (==) ∷ StakePoolParameters → StakePoolParameters → Bool Source # (/=) ∷ StakePoolParameters → StakePoolParameters → Bool Source # | |
Show StakePoolParameters Source # | |
Defined in Cardano.Api.Certificate |
data StakePoolRelay Source #
Constructors
StakePoolRelayIp (Maybe IPv4) (Maybe IPv6) (Maybe PortNumber) | One or both of IPv4 & IPv6 |
StakePoolRelayDnsARecord ByteString (Maybe PortNumber) | An DNS name pointing to a |
StakePoolRelayDnsSrvRecord ByteString | A DNS name pointing to a |
Instances
Eq StakePoolRelay Source # | |
Defined in Cardano.Api.Certificate Methods (==) ∷ StakePoolRelay → StakePoolRelay → Bool Source # (/=) ∷ StakePoolRelay → StakePoolRelay → Bool Source # | |
Show StakePoolRelay Source # | |
Defined in Cardano.Api.Certificate |
Instances
Stake pool operator's keys
data StakePoolKey Source #
Instances
HasTypeProxy StakePoolKey Source # | |
Defined in Cardano.Api.KeysShelley Associated Types data AsType StakePoolKey Source # Methods proxyToAsType ∷ Proxy StakePoolKey → AsType StakePoolKey Source # | |
Key StakePoolKey Source # | |
Defined in Cardano.Api.KeysShelley |