Safe Haskell | Safe-Inferred |
---|---|
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 ∷ !(ShelleyPParams era)
- sgGenDelegs ∷ !(Map (KeyHash 'Genesis (Crypto era)) (GenDelegPair (Crypto era)))
- sgInitialFunds ∷ ListMap (Addr (Crypto era)) Coin
- sgStaking ∷ ShelleyGenesisStaking (Crypto era)
- shelleyGenesisDefaults ∷ ShelleyGenesis crypto
- class (Eq (VerificationKey keyrole), Show (VerificationKey keyrole), SerialiseAsRawBytes (Hash keyrole), HasTextEnvelope (VerificationKey keyrole), HasTextEnvelope (SigningKey keyrole)) ⇒ Key keyrole where
- data VerificationKey keyrole ∷ Type
- data SigningKey keyrole ∷ Type
- getVerificationKey ∷ SigningKey keyrole → VerificationKey keyrole
- deterministicSigningKey ∷ AsType keyrole → Seed → SigningKey keyrole
- deterministicSigningKeySeedSize ∷ AsType keyrole → Word
- verificationKeyHash ∷ VerificationKey keyrole → Hash keyrole
- 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 ⇒ EraTxBody (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) (ReferenceScript 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 → MaryValue StandardCrypto
- fromMaryValue ∷ MaryValue StandardCrypto → Value
- calcMinimumDeposit ∷ Value → Lovelace → Lovelace
- signArbitraryBytesKes ∷ SigningKey KesKey → Period → ByteString → SignedKES (KES StandardCrypto) ByteString
- 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 ⇒ LedgerSupportsProtocol (ShelleyBlock (TPraos StandardCrypto) (ShelleyEra StandardCrypto)) ⇒ ConsensusMode mode → block → BlockInMode mode
- toConsensusBlock ∷ ConsensusBlockForMode mode ~ block ⇒ LedgerSupportsProtocol (ShelleyBlock (TPraos StandardCrypto) (ShelleyEra StandardCrypto)) ⇒ 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 ∷ Maybe 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
- protocolParamUTxOCostPerByte ∷ Maybe Lovelace
- checkProtocolParameters ∷ ∀ era. IsCardanoEra era ⇒ ShelleyBasedEra era → ProtocolParameters → Either ProtocolParametersError ()
- data ProtocolParametersError
- fromShelleyBasedScript ∷ ShelleyBasedEra era → Script (ShelleyLedgerEra era) → ScriptInEra era
- toShelleyScript ∷ ScriptInEra era → Script (ShelleyLedgerEra era)
- toShelleyMultiSig ∷ SimpleScript → Either MultiSigError (MultiSig StandardCrypto)
- fromShelleyMultiSig ∷ MultiSig StandardCrypto → SimpleScript
- toAllegraTimelock ∷ SimpleScript → Timelock StandardCrypto
- fromAllegraTimelock ∷ Timelock StandardCrypto → SimpleScript
- toShelleyScriptHash ∷ ScriptHash → ScriptHash StandardCrypto
- fromShelleyScriptHash ∷ ScriptHash StandardCrypto → ScriptHash
- data PlutusScript lang where
- data PlutusScriptOrReferenceInput lang
- = PScript (PlutusScript lang)
- | PReferenceScript TxIn (Maybe ScriptHash)
- data SimpleScriptOrReferenceInput lang
- toPlutusData ∷ ScriptData → Data
- fromPlutusData ∷ Data → ScriptData
- toAlonzoData ∷ HashableScriptData → Data ledgerera
- fromAlonzoData ∷ Data ledgerera → HashableScriptData
- toAlonzoPrices ∷ ExecutionUnitPrices → Maybe Prices
- fromAlonzoPrices ∷ Prices → ExecutionUnitPrices
- toAlonzoExUnits ∷ ExecutionUnits → ExUnits
- fromAlonzoExUnits ∷ ExUnits → ExecutionUnits
- toAlonzoRdmrPtr ∷ ScriptWitnessIndex → RdmrPtr
- fromAlonzoRdmrPtr ∷ RdmrPtr → ScriptWitnessIndex
- scriptDataFromJsonDetailedSchema ∷ Value → Either ScriptDataJsonSchemaError HashableScriptData
- scriptDataToJsonDetailedSchema ∷ HashableScriptData → Value
- calculateExecutionUnitsLovelace ∷ ExecutionUnitPrices → ExecutionUnits → Maybe Lovelace
- data ReferenceScript era where
- data ReferenceTxInsScriptsInlineDatumsSupportedInEra era where
- refInsScriptsAndInlineDatsSupportedInEra ∷ CardanoEra era → Maybe (ReferenceTxInsScriptsInlineDatumsSupportedInEra era)
- refScriptToShelleyScript ∷ CardanoEra era → ReferenceScript era → StrictMaybe (Script (ShelleyLedgerEra era))
- 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 slot tx txid txerr query m = LocalNodeClientProtocols (LocalChainSyncClient block point tip m) (Maybe (LocalTxSubmissionClient tx txerr m ())) (Maybe (LocalStateQueryClient block point query m ())) (Maybe (LocalTxMonitorClient txid tx slot 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 (ConsensusProtocol era)))
- decodeProtocolState ∷ FromCBOR (ChainDepState (ConsensusProtocol era)) ⇒ ProtocolState era → Either (ByteString, DecoderError) (ChainDepState (ConsensusProtocol era))
- newtype SerialisedDebugLedgerState era = SerialisedDebugLedgerState (Serialised (NewEpochState (ShelleyLedgerEra era)))
- newtype CurrentEpochState era = CurrentEpochState (EpochState (ShelleyLedgerEra era))
- newtype SerialisedCurrentEpochState era = SerialisedCurrentEpochState (Serialised (EpochState (ShelleyLedgerEra era)))
- decodeCurrentEpochState ∷ ∀ era. (Era (ShelleyLedgerEra era), HashAnnotated (TxBody (ShelleyLedgerEra era)) EraIndependentTxBody (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 PoolState era = PoolState (PState (Crypto (ShelleyLedgerEra era)))
- newtype SerialisedPoolState era = SerialisedPoolState (Serialised (PState (Crypto (ShelleyLedgerEra era))))
- decodePoolState ∷ ∀ era. FromCBOR (PState (Crypto (ShelleyLedgerEra era))) ⇒ SerialisedPoolState era → Either DecoderError (PoolState era)
- newtype PoolDistribution era = PoolDistribution {
- unPoolDistr ∷ PoolDistr (Crypto (ShelleyLedgerEra era))
- newtype SerialisedPoolDistribution era = SerialisedPoolDistribution (Serialised (PoolDistr (Crypto (ShelleyLedgerEra era))))
- decodePoolDistribution ∷ ∀ era. FromCBOR (PoolDistr (Crypto (ShelleyLedgerEra era))) ⇒ SerialisedPoolDistribution era → Either DecoderError (PoolDistribution era)
- newtype StakeSnapshot era = StakeSnapshot (StakeSnapshots (Crypto (ShelleyLedgerEra era)))
- newtype SerialisedStakeSnapshots era = SerialisedStakeSnapshots (Serialised (StakeSnapshots (Crypto (ShelleyLedgerEra era))))
- decodeStakeSnapshot ∷ ∀ era. FromCBOR (StakeSnapshots (Crypto (ShelleyLedgerEra era))) ⇒ SerialisedStakeSnapshots era → Either DecoderError (StakeSnapshot era)
- newtype UTxO era = UTxO {}
- data AcquiringFailure
- newtype SystemStart = SystemStart {}
- data LeadershipError
- = LeaderErrDecodeLedgerStateFailure
- | LeaderErrDecodeProtocolStateFailure (ByteString, DecoderError)
- | LeaderErrDecodeProtocolEpochStateFailure DecoderError
- | LeaderErrGenesisSlot
- | LeaderErrStakePoolHasNoStake PoolId
- | LeaderErrStakeDistribUnstable SlotNo SlotNo SlotNo SlotNo
- | LeaderErrSlotRangeCalculationFailure Text
- | LeaderErrCandidateNonceStillEvolving
- currentEpochEligibleLeadershipSlots ∷ ∀ era ledgerera. ShelleyLedgerEra era ~ ledgerera ⇒ Era ledgerera ⇒ PraosProtocolSupportsNode (ConsensusProtocol era) ⇒ HasField "_d" (PParams ledgerera) UnitInterval ⇒ FromCBOR (ChainDepState (ConsensusProtocol era)) ⇒ ShelleyBasedEra era → ShelleyGenesis StandardShelley → EpochInfo (Either Text) → BundledProtocolParameters era → ProtocolState era → PoolId → SigningKey VrfKey → SerialisedPoolDistribution era → EpochNo → Either LeadershipError (Set SlotNo)
- nextEpochEligibleLeadershipSlots ∷ ∀ era. (HasField "_d" (PParams (ShelleyLedgerEra era)) UnitInterval, HashAnnotated (TxBody (ShelleyLedgerEra era)) EraIndependentTxBody (Crypto (ShelleyLedgerEra era))) ⇒ Era (ShelleyLedgerEra era) ⇒ Share (TxOut (ShelleyLedgerEra era)) ~ Interns (Credential 'Staking (Crypto (ShelleyLedgerEra era))) ⇒ FromCBOR (ChainDepState (ConsensusProtocol era)) ⇒ PraosProtocolSupportsNode (ConsensusProtocol era) ⇒ ShelleyBasedEra era → ShelleyGenesis StandardShelley → SerialisedCurrentEpochState era → ProtocolState era → PoolId → SigningKey VrfKey → BundledProtocolParameters era → EpochInfo (Either Text) → (ChainTip, EpochNo) → Either LeadershipError (Set SlotNo)
- shelleyPayAddrToPlutusPubKHash ∷ Address ShelleyAddr → Maybe PubKeyHash
- toConsensusGenTx ∷ ConsensusBlockForMode mode ~ block ⇒ TxInMode mode → GenTx block
- fromAlonzoCostModels ∷ CostModels → Map AnyPlutusScriptVersion CostModel
- toShelleyNetwork ∷ NetworkId → Network
- fromShelleyPParams ∷ ShelleyPParams 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.
Cryptographic key interface
class (Eq (VerificationKey keyrole), Show (VerificationKey keyrole), SerialiseAsRawBytes (Hash keyrole), HasTextEnvelope (VerificationKey keyrole), HasTextEnvelope (SigningKey keyrole)) ⇒ Key keyrole where Source #
An interface for cryptographic keys used for signatures with a SigningKey
and a VerificationKey
key.
This interface does not provide actual signing or verifying functions since this API is concerned with the management of keys: generating and serialising.
Associated Types
data VerificationKey keyrole ∷ Type Source #
The type of cryptographic verification key, for each key role.
data SigningKey keyrole ∷ Type Source #
The type of cryptographic signing key, for each key role.
Methods
getVerificationKey ∷ SigningKey keyrole → VerificationKey keyrole Source #
Get the corresponding verification key from a signing key.
deterministicSigningKey ∷ AsType keyrole → Seed → SigningKey keyrole Source #
Generate a SigningKey
deterministically, given a Seed
. The
required size of the seed is given by deterministicSigningKeySeedSize
.
deterministicSigningKeySeedSize ∷ AsType keyrole → Word Source #
verificationKeyHash ∷ VerificationKey keyrole → Hash keyrole Source #
Instances
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
Show PaymentCredential Source # | |
Defined in Cardano.Api.Address | |
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 # |
data StakeAddress where Source #
Constructors
StakeAddress ∷ Network → StakeCredential StandardCrypto → StakeAddress |
Instances
data StakeAddressReference Source #
Constructors
StakeAddressByValue StakeCredential | |
StakeAddressByPointer StakeAddressPointer | |
NoStakeAddress |
Instances
Show StakeAddressReference Source # | |
Defined in Cardano.Api.Address | |
Eq StakeAddressReference Source # | |
Defined in Cardano.Api.Address Methods (==) ∷ StakeAddressReference → StakeAddressReference → Bool Source # (/=) ∷ StakeAddressReference → StakeAddressReference → Bool Source # |
data StakeCredential Source #
Constructors
StakeCredentialByKey (Hash StakeKey) | |
StakeCredentialByScript ScriptHash |
Instances
ToJSON StakeCredential Source # | |
Defined in Cardano.Api.Address Methods toJSON ∷ StakeCredential → Value # toEncoding ∷ StakeCredential → Encoding # toJSONList ∷ [StakeCredential] → Value # toEncodingList ∷ [StakeCredential] → Encoding # | |
Show StakeCredential Source # | |
Defined in Cardano.Api.Address | |
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 # |
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
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 # | |
Eq (TxBody era) Source # | |
data AsType (TxBody era) Source # | |
Defined in Cardano.Api.TxBody |
Constructors
TxId (Hash StandardCrypto EraIndependentTxBody) |
Instances
FromJSON TxId Source # | |
Defined in Cardano.Api.TxIn | |
FromJSONKey TxId Source # | |
Defined in Cardano.Api.TxIn | |
ToJSON TxId Source # | |
Defined in Cardano.Api.TxIn Methods toEncoding ∷ TxId → Encoding # toJSONList ∷ [TxId] → Value # toEncodingList ∷ [TxId] → Encoding # | |
ToJSONKey TxId Source # | |
Defined in Cardano.Api.TxIn | |
IsString TxId Source # | |
Defined in Cardano.Api.TxIn Methods fromString ∷ String → TxId Source # | |
Show TxId Source # | |
HasTypeProxy TxId Source # | |
SerialiseAsRawBytes TxId Source # | |
Defined in Cardano.Api.TxIn | |
Eq TxId Source # | |
Ord TxId Source # | |
data AsType TxId Source # | |
Defined in Cardano.Api.TxIn |
toShelleyTxId ∷ TxId → TxId StandardCrypto Source #
fromShelleyTxId ∷ TxId StandardCrypto → TxId Source #
getTxIdShelley ∷ Crypto (ShelleyLedgerEra era) ~ StandardCrypto ⇒ EraTxBody (ShelleyLedgerEra era) ⇒ ShelleyBasedEra era → TxBody (ShelleyLedgerEra era) → TxId Source #
Instances
FromJSON TxIn Source # | |
Defined in Cardano.Api.TxIn | |
FromJSONKey TxIn Source # | |
Defined in Cardano.Api.TxIn | |
ToJSON TxIn Source # | |
Defined in Cardano.Api.TxIn Methods toEncoding ∷ TxIn → Encoding # toJSONList ∷ [TxIn] → Value # toEncodingList ∷ [TxIn] → Encoding # | |
ToJSONKey TxIn Source # | |
Defined in Cardano.Api.TxIn | |
Show TxIn Source # | |
Eq TxIn Source # | |
Ord TxIn Source # | |
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) (ReferenceScript era) |
Instances
EraCast (TxOut ctx) Source # | |
Defined in Cardano.Api.TxBody Methods eraCast ∷ (IsCardanoEra fromEra, IsCardanoEra toEra) ⇒ CardanoEra toEra → TxOut ctx fromEra → Either EraCastError (TxOut ctx toEra) Source # | |
IsShelleyBasedEra era ⇒ FromJSON (TxOut CtxTx era) Source # | |
Defined in Cardano.Api.TxBody | |
IsShelleyBasedEra era ⇒ FromJSON (TxOut CtxUTxO 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 # | |
Show (TxOut ctx era) Source # | |
Eq (TxOut ctx era) Source # | |
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
FromJSON TxIx Source # | |
Defined in Cardano.Api.TxIn | |
ToJSON TxIx Source # | |
Defined in Cardano.Api.TxIn Methods toEncoding ∷ TxIx → Encoding # toJSONList ∷ [TxIx] → Value # toEncodingList ∷ [TxIx] → Encoding # | |
Enum TxIx Source # | |
Defined in Cardano.Api.TxIn | |
Show TxIx Source # | |
Eq TxIx Source # | |
Ord TxIx Source # | |
Instances
toShelleyLovelace ∷ Lovelace → Coin Source #
fromShelleyLovelace ∷ Coin → Lovelace Source #
toMaryValue ∷ Value → MaryValue StandardCrypto Source #
fromMaryValue ∷ MaryValue 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
Arbitrary signing
signArbitraryBytesKes Source #
Arguments
∷ SigningKey KesKey | |
→ Period | Desired Kes period |
→ ByteString | Message to sign |
→ SignedKES (KES StandardCrypto) ByteString |
Signing transactions
Creating transaction witnesses one by one, or all in one go.
Constructors
ShelleyTx ∷ ShelleyBasedEra era → Tx (ShelleyLedgerEra era) → Tx era |
Instances
Show (InAnyCardanoEra Tx) Source # | |
Defined in Cardano.Api.Tx | |
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 # | |
Eq (InAnyCardanoEra Tx) Source # | |
Defined in Cardano.Api.Tx Methods (==) ∷ InAnyCardanoEra Tx → InAnyCardanoEra Tx → Bool Source # (/=) ∷ InAnyCardanoEra Tx → InAnyCardanoEra Tx → Bool Source # | |
Eq (Tx era) 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 ⇒ LedgerSupportsProtocol (ShelleyBlock (TPraos StandardCrypto) (ShelleyEra StandardCrypto)) ⇒ ConsensusMode mode → block → BlockInMode mode Source #
toConsensusBlock ∷ ConsensusBlockForMode mode ~ block ⇒ LedgerSupportsProtocol (ShelleyBlock (TPraos StandardCrypto) (ShelleyEra StandardCrypto)) ⇒ 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
fromShelleyBasedScript ∷ ShelleyBasedEra era → Script (ShelleyLedgerEra era) → ScriptInEra era Source #
toShelleyScript ∷ ScriptInEra era → Script (ShelleyLedgerEra era) Source #
toShelleyMultiSig ∷ SimpleScript → Either MultiSigError (MultiSig StandardCrypto) Source #
Conversion for the MultiSig
language used by the Shelley era.
fromShelleyMultiSig ∷ MultiSig StandardCrypto → SimpleScript Source #
Conversion for the MultiSig
language used by the Shelley era.
toAllegraTimelock ∷ SimpleScript → Timelock StandardCrypto Source #
Conversion for the Timelock
language that is shared between the
Allegra and Mary eras.
fromAllegraTimelock ∷ Timelock StandardCrypto → SimpleScript 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
data PlutusScriptOrReferenceInput lang Source #
Scripts can now exist in the UTxO at a transaction output. We can reference these scripts via specification of a reference transaction input in order to witness spending inputs, withdrawals, certificates or to mint tokens. This datatype encapsulates this concept.
Constructors
PScript (PlutusScript lang) | |
PReferenceScript TxIn (Maybe ScriptHash) |
Instances
Show (PlutusScriptOrReferenceInput lang) Source # | |
Defined in Cardano.Api.Script | |
Eq (PlutusScriptOrReferenceInput lang) Source # | |
Defined in Cardano.Api.Script Methods (==) ∷ PlutusScriptOrReferenceInput lang → PlutusScriptOrReferenceInput lang → Bool Source # (/=) ∷ PlutusScriptOrReferenceInput lang → PlutusScriptOrReferenceInput lang → Bool Source # |
data SimpleScriptOrReferenceInput lang Source #
Constructors
SScript SimpleScript | |
SReferenceScript TxIn (Maybe ScriptHash) |
Instances
Show (SimpleScriptOrReferenceInput lang) Source # | |
Defined in Cardano.Api.Script | |
Eq (SimpleScriptOrReferenceInput lang) Source # | |
Defined in Cardano.Api.Script Methods (==) ∷ SimpleScriptOrReferenceInput lang → SimpleScriptOrReferenceInput lang → Bool Source # (/=) ∷ SimpleScriptOrReferenceInput lang → SimpleScriptOrReferenceInput lang → Bool Source # |
toPlutusData ∷ ScriptData → Data Source #
fromPlutusData ∷ Data → ScriptData Source #
toAlonzoData ∷ HashableScriptData → Data ledgerera Source #
fromAlonzoData ∷ Data ledgerera → HashableScriptData 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 #
scriptDataFromJsonDetailedSchema ∷ Value → Either ScriptDataJsonSchemaError HashableScriptData Source #
Reference Scripts
data ReferenceScript era where Source #
A reference scripts is a script that can exist at a transaction output. This greatly reduces the size of transactions that use scripts as the script no longer has to be added to the transaction, they can now be referenced via a transaction output.
Constructors
ReferenceScript ∷ ReferenceTxInsScriptsInlineDatumsSupportedInEra era → ScriptInAnyLang → ReferenceScript era | |
ReferenceScriptNone ∷ ReferenceScript era |
Instances
EraCast ReferenceScript Source # | |
Defined in Cardano.Api.Script Methods eraCast ∷ (IsCardanoEra fromEra, IsCardanoEra toEra) ⇒ CardanoEra toEra → ReferenceScript fromEra → Either EraCastError (ReferenceScript toEra) Source # | |
IsCardanoEra era ⇒ FromJSON (ReferenceScript era) Source # | |
Defined in Cardano.Api.Script Methods parseJSON ∷ Value → Parser (ReferenceScript era) # parseJSONList ∷ Value → Parser [ReferenceScript era] # | |
IsCardanoEra era ⇒ ToJSON (ReferenceScript era) Source # | |
Defined in Cardano.Api.Script Methods toJSON ∷ ReferenceScript era → Value # toEncoding ∷ ReferenceScript era → Encoding # toJSONList ∷ [ReferenceScript era] → Value # toEncodingList ∷ [ReferenceScript era] → Encoding # | |
Show (ReferenceScript era) Source # | |
Defined in Cardano.Api.Script | |
Eq (ReferenceScript era) Source # | |
Defined in Cardano.Api.Script Methods (==) ∷ ReferenceScript era → ReferenceScript era → Bool Source # (/=) ∷ ReferenceScript era → ReferenceScript era → Bool Source # |
data ReferenceTxInsScriptsInlineDatumsSupportedInEra era where Source #
Constructors
Instances
refInsScriptsAndInlineDatsSupportedInEra ∷ CardanoEra era → Maybe (ReferenceTxInsScriptsInlineDatumsSupportedInEra era) Source #
refScriptToShelleyScript ∷ CardanoEra era → ReferenceScript era → StrictMaybe (Script (ShelleyLedgerEra era)) Source #
Certificates
data Certificate Source #
Constructors
Instances
Show Certificate Source # | |
Defined in Cardano.Api.Certificate | |
HasTypeProxy Certificate Source # | |
Defined in Cardano.Api.Certificate Associated Types data AsType Certificate Source # Methods proxyToAsType ∷ Proxy Certificate → AsType Certificate Source # | |
SerialiseAsCBOR Certificate Source # | |
Defined in Cardano.Api.Certificate Methods serialiseToCBOR ∷ Certificate → ByteString Source # deserialiseFromCBOR ∷ AsType Certificate → ByteString → Either DecoderError |