Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
-
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
- 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
- = Mainnet
- | Testnet ! NetworkMagic
- data PaymentCredential
- data StakeAddress where
- 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) ( ReferenceScript era)
- toShelleyTxOut :: forall 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
- 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 :: forall 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 :: forall lang. SimpleScript lang -> Timelock StandardCrypto
- fromAllegraTimelock :: TimeLocksSupported lang -> Timelock StandardCrypto -> SimpleScript lang
- toShelleyScriptHash :: ScriptHash -> ScriptHash StandardCrypto
- fromShelleyScriptHash :: ScriptHash StandardCrypto -> ScriptHash
-
data
PlutusScript
lang
where
- PlutusScriptSerialised :: ShortByteString -> PlutusScript lang
-
data
PlutusScriptOrReferenceInput
lang
- = PScript ( PlutusScript lang)
- | PReferenceScript TxIn ( Maybe ScriptHash )
-
data
SimpleScriptOrReferenceInput
lang
- = SScript ( SimpleScript lang)
- | SReferenceScript TxIn ( Maybe ScriptHash )
- 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 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
{
- opCertIssueCount :: ! Word64
- opCertIssueColdKey :: !( VerificationKey StakePoolKey )
- 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
{
- unKESPeriod :: Word
- 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 :: forall 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 SerialisedCurrentEpochState era = SerialisedCurrentEpochState ( Serialised ( EpochState ( ShelleyLedgerEra era)))
- decodeCurrentEpochState :: forall 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 AcquiringFailure
- newtype SystemStart = SystemStart { }
-
data
LeadershipError
- = LeaderErrDecodeLedgerStateFailure
- | LeaderErrDecodeProtocolStateFailure ( ByteString , DecoderError )
- | LeaderErrDecodeProtocolEpochStateFailure DecoderError
- | LeaderErrGenesisSlot
- | LeaderErrStakePoolHasNoStake PoolId
- | LeaderErrStakeDistribUnstable SlotNo SlotNo SlotNo SlotNo
- | LeaderErrSlotRangeCalculationFailure Text
- | LeaderErrCandidateNonceStillEvolving
- currentEpochEligibleLeadershipSlots :: forall era ledgerera. ShelleyLedgerEra era ~ ledgerera => Era ledgerera => PraosProtocolSupportsNode ( ConsensusProtocol era) => HasField "_d" ( PParams ledgerera) UnitInterval => Share ( TxOut ( ShelleyLedgerEra era)) ~ Interns ( Credential ' Staking ( Crypto ( ShelleyLedgerEra era))) => FromCBOR ( ChainDepState ( ConsensusProtocol era)) => ShelleyBasedEra era -> ShelleyGenesis StandardShelley -> EpochInfo ( Either Text ) -> ProtocolParameters -> ProtocolState era -> PoolId -> SigningKey VrfKey -> SerialisedCurrentEpochState era -> EpochNo -> Either LeadershipError ( Set SlotNo )
- nextEpochEligibleLeadershipSlots :: forall era. HasField "_d" ( PParams ( ShelleyLedgerEra era)) UnitInterval => 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 -> ProtocolParameters -> 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 :: PParams ledgerera -> ProtocolParameters
Documentation
module Cardano.Api
Genesis
data ShelleyGenesis era Source #
Shelley genesis information
Note that this is needed only for a pure Shelley network, hence it being defined here rather than in its own module. In mainnet, Shelley will transition naturally from Byron, and thus will never have its own genesis information.
ShelleyGenesis | |
|
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 block -
sgNetworkMagic
to a suitable testnet or mainnet network magic number. -
sgGenDelegs
to have some initial nodes -
sgInitialFunds
to have any money in the system -
sgMaxLovelaceSupply
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.
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.
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.
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 #
Stake addresses
data PaymentCredential Source #
Instances
Eq PaymentCredential Source # | |
Defined in Cardano.Api.Address (==) :: PaymentCredential -> PaymentCredential -> Bool Source # (/=) :: PaymentCredential -> PaymentCredential -> Bool Source # |
|
Ord PaymentCredential Source # | |
Defined in Cardano.Api.Address 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 #
Instances
data StakeAddressReference Source #
Instances
Eq StakeAddressReference Source # | |
Defined in Cardano.Api.Address (==) :: StakeAddressReference -> StakeAddressReference -> Bool Source # (/=) :: StakeAddressReference -> StakeAddressReference -> Bool Source # |
|
Show StakeAddressReference Source # | |
Defined in Cardano.Api.Address |
data StakeCredential Source #
Instances
Building transactions
Constructing and inspecting transactions
data TxBody era where Source #
ShelleyTxBody | |
|
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 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 textEnvelopeType :: AsType ( TxBody era) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: TxBody era -> TextEnvelopeDescr Source # |
|
data AsType ( TxBody era) Source # | |
Defined in Cardano.Api.TxBody |
Instances
Eq TxId Source # | |
Ord TxId Source # | |
Show TxId Source # | |
IsString TxId Source # | |
Defined in Cardano.Api.TxIn fromString :: String -> TxId Source # |
|
ToJSON TxId Source # | |
ToJSONKey TxId Source # | |
Defined in Cardano.Api.TxIn |
|
FromJSON TxId Source # | |
FromJSONKey TxId Source # | |
Defined in Cardano.Api.TxIn |
|
HasTypeProxy TxId Source # | |
SerialiseAsRawBytes TxId Source # | |
Defined in Cardano.Api.TxIn serialiseToRawBytes :: TxId -> ByteString Source # deserialiseFromRawBytes :: AsType TxId -> ByteString -> Maybe 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 => UsesTxBody ( ShelleyLedgerEra era) => ShelleyBasedEra era -> TxBody ( ShelleyLedgerEra era) -> TxId 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 #
TxOut ( AddressInEra era) ( TxOutValue era) ( TxOutDatum ctx era) ( ReferenceScript era) |
Instances
EraCast ( TxOut ctx) Source # | |
Defined in Cardano.Api.TxBody eraCast :: ( IsCardanoEra fromEra, IsCardanoEra toEra) => CardanoEra toEra -> TxOut ctx fromEra -> Either EraCastError ( TxOut ctx toEra) Source # |
|
Eq ( TxOut ctx era) Source # | |
Show ( TxOut ctx era) Source # | |
IsCardanoEra era => ToJSON ( TxOut ctx era) Source # | |
( IsShelleyBasedEra era, IsCardanoEra era) => FromJSON ( TxOut CtxUTxO era) Source # | |
( IsShelleyBasedEra era, IsCardanoEra era) => FromJSON ( TxOut CtxTx era) Source # | |
toShelleyTxOut :: forall 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 # | |
Eq TxIx Source # | |
Ord TxIx Source # | |
Show TxIx Source # | |
ToJSON TxIx Source # | |
FromJSON TxIx Source # | |
Instances
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.
ShelleyTx :: ShelleyBasedEra era -> Tx ( ShelleyLedgerEra era) -> Tx era |
Instances
Eq ( InAnyCardanoEra Tx ) Source # | |
Defined in Cardano.Api.Tx (==) :: InAnyCardanoEra Tx -> InAnyCardanoEra Tx -> Bool Source # (/=) :: InAnyCardanoEra Tx -> InAnyCardanoEra Tx -> Bool Source # |
|
Eq ( Tx era) Source # | |
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 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 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 #
ShelleyBootstrapWitness :: ShelleyBasedEra era -> BootstrapWitness StandardCrypto -> KeyWitness era | |
ShelleyKeyWitness :: ShelleyBasedEra era -> WitVKey Witness StandardCrypto -> KeyWitness era |
Instances
Eq ( KeyWitness era) Source # | |
Defined in Cardano.Api.Tx (==) :: KeyWitness era -> KeyWitness era -> Bool Source # (/=) :: KeyWitness era -> KeyWitness era -> Bool Source # |
|
Show ( KeyWitness era) Source # | |
Defined in Cardano.Api.Tx |
|
HasTypeProxy era => HasTypeProxy ( KeyWitness era) Source # | |
Defined in Cardano.Api.Tx data AsType ( KeyWitness era) Source # proxyToAsType :: Proxy ( KeyWitness era) -> AsType ( KeyWitness era) Source # |
|
IsCardanoEra era => SerialiseAsCBOR ( KeyWitness era) Source # | |
Defined in Cardano.Api.Tx serialiseToCBOR :: KeyWitness era -> ByteString Source # deserialiseFromCBOR :: AsType ( KeyWitness era) -> ByteString -> Either DecoderError ( KeyWitness era) Source # |
|
IsCardanoEra era => HasTextEnvelope ( KeyWitness era) Source # | |
Defined in Cardano.Api.Tx textEnvelopeType :: AsType ( KeyWitness era) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: KeyWitness era -> TextEnvelopeDescr Source # |
|
data AsType ( KeyWitness era) Source # | |
Defined in Cardano.Api.Tx |
data ShelleyWitnessSigningKey Source #
data ShelleySigningKey Source #
We support making key witnesses with both normal and extended signing keys.
ShelleyNormalSigningKey ( SignKeyDSIGN StandardCrypto ) |
A normal ed25519 signing key |
ShelleyExtendedSigningKey XPrv |
An extended ed25519 signing key |
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.
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
.
ProtocolParameters | |
|
Instances
checkProtocolParameters :: forall era. IsCardanoEra era => ShelleyBasedEra era -> ProtocolParameters -> Either ProtocolParametersError () Source #
data ProtocolParametersError Source #
Instances
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 :: forall 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.
data PlutusScript lang where Source #
Plutus scripts.
Note that Plutus scripts have a binary serialisation but no JSON serialisation.
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.
PScript ( PlutusScript lang) | |
PReferenceScript TxIn ( Maybe ScriptHash ) |
Instances
Eq ( PlutusScriptOrReferenceInput lang) Source # | |
Defined in Cardano.Api.Script (==) :: PlutusScriptOrReferenceInput lang -> PlutusScriptOrReferenceInput lang -> Bool Source # (/=) :: PlutusScriptOrReferenceInput lang -> PlutusScriptOrReferenceInput lang -> Bool Source # |
|
Show ( PlutusScriptOrReferenceInput lang) Source # | |
Defined in Cardano.Api.Script |
data SimpleScriptOrReferenceInput lang Source #
SScript ( SimpleScript lang) | |
SReferenceScript TxIn ( Maybe ScriptHash ) |
Instances
Eq ( SimpleScriptOrReferenceInput lang) Source # | |
Defined in Cardano.Api.Script (==) :: SimpleScriptOrReferenceInput lang -> SimpleScriptOrReferenceInput lang -> Bool Source # (/=) :: SimpleScriptOrReferenceInput lang -> SimpleScriptOrReferenceInput lang -> Bool Source # |
|
Show ( SimpleScriptOrReferenceInput lang) Source # | |
Defined in Cardano.Api.Script |
toPlutusData :: ScriptData -> Data Source #
fromPlutusData :: Data -> ScriptData Source #
toAlonzoData :: ScriptData -> Data ledgerera Source #
fromAlonzoData :: Data ledgerera -> ScriptData 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.
ReferenceScript :: ReferenceTxInsScriptsInlineDatumsSupportedInEra era -> ScriptInAnyLang -> ReferenceScript era | |
ReferenceScriptNone :: ReferenceScript era |
Instances
data ReferenceTxInsScriptsInlineDatumsSupportedInEra era where Source #
ReferenceTxInsScriptsInlineDatumsInBabbageEra :: ReferenceTxInsScriptsInlineDatumsSupportedInEra BabbageEra |
Instances
Eq ( ReferenceTxInsScriptsInlineDatumsSupportedInEra era) Source # | |
Show ( ReferenceTxInsScriptsInlineDatumsSupportedInEra era) Source # | |
Defined in Cardano.Api.Script |
refInsScriptsAndInlineDatsSupportedInEra :: CardanoEra era -> Maybe ( ReferenceTxInsScriptsInlineDatumsSupportedInEra era) Source #
refScriptToShelleyScript :: CardanoEra era -> ReferenceScript era -> StrictMaybe ( Script ( ShelleyLedgerEra era)) Source #
Certificates
data Certificate Source #
Instances
Eq Certificate Source # | |
Defined in Cardano.Api.Certificate (==) :: Certificate -> Certificate -> Bool Source # (/=) :: Certificate -> Certificate -> Bool Source # |
|
Show Certificate Source # | |
Defined in Cardano.Api.Certificate |
|
ToCBOR Certificate Source # | |
Defined in Cardano.Api.Certificate toCBOR :: Certificate -> Encoding Source # encodedSizeExpr :: ( forall t. ToCBOR t => Proxy t -> Size ) -> Proxy Certificate -> Size Source # encodedListSizeExpr :: ( forall t. ToCBOR t => Proxy t -> Size ) -> Proxy [ Certificate ] -> Size Source # |
|
FromCBOR Certificate Source # | |
Defined in Cardano.Api.Certificate |
|
HasTypeProxy Certificate Source # | |
Defined in Cardano.Api.Certificate data AsType Certificate Source # |
|
SerialiseAsCBOR Certificate Source # | |
Defined in Cardano.Api.Certificate |
|
HasTextEnvelope Certificate Source # | |
data AsType Certificate Source # | |
Defined in Cardano.Api.Certificate |
Operational certificates
data OperationalCertificate Source #
Instances
Eq OperationalCertificate Source # | |
Defined in Cardano.Api.OperationalCertificate |
|
Show OperationalCertificate Source # | |
Defined in Cardano.Api.OperationalCertificate |
|
ToCBOR OperationalCertificate Source # | |
Defined in Cardano.Api.OperationalCertificate toCBOR :: OperationalCertificate -> Encoding Source # encodedSizeExpr :: ( forall t. ToCBOR t => Proxy t -> Size ) -> Proxy OperationalCertificate -> Size Source # encodedListSizeExpr :: ( forall t. ToCBOR t => Proxy t -> Size ) -> Proxy [ OperationalCertificate ] -> Size Source # |
|
FromCBOR OperationalCertificate Source # | |
Defined in Cardano.Api.OperationalCertificate |
|
HasTypeProxy OperationalCertificate Source # | |
SerialiseAsCBOR OperationalCertificate Source # | |
HasTextEnvelope OperationalCertificate Source # | |
data AsType OperationalCertificate Source # | |
data OperationalCertificateIssueCounter Source #
OperationalCertificateIssueCounter | |
|
Instances
data OperationalCertIssueError Source #
OperationalCertKeyMismatch ( VerificationKey StakePoolKey ) ( VerificationKey StakePoolKey ) |
The stake pool verification key expected for the
Order: pool vkey expected, pool skey supplied |
Instances
Stake Pool
data StakePoolMetadata Source #
A representation of the required fields for off-chain stake pool metadata.
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 #
Instances
Eq StakePoolMetadataReference Source # | |
Defined in Cardano.Api.Certificate |
|
Show StakePoolMetadataReference Source # | |
Defined in Cardano.Api.Certificate |
data StakePoolParameters Source #
StakePoolParameters PoolId ( Hash VrfKey ) Lovelace Rational StakeAddress Lovelace [ Hash StakeKey ] [ StakePoolRelay ] ( Maybe StakePoolMetadataReference ) |
Instances
Eq StakePoolParameters Source # | |
Defined in Cardano.Api.Certificate (==) :: StakePoolParameters -> StakePoolParameters -> Bool Source # (/=) :: StakePoolParameters -> StakePoolParameters -> Bool Source # |
|
Show StakePoolParameters Source # | |
Defined in Cardano.Api.Certificate |
stakePoolOwners :: StakePoolParameters -> [ Hash StakeKey ] Source #
stakePoolRelays :: StakePoolParameters -> [ StakePoolRelay ] Source #
data StakePoolRelay Source #
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 (==) :: StakePoolRelay -> StakePoolRelay -> Bool Source # (/=) :: StakePoolRelay -> StakePoolRelay -> Bool Source # |
|
Show StakePoolRelay Source # | |
Defined in Cardano.Api.Certificate |
An epoch, i.e. the number of the epoch.
Instances
Enum EpochNo | |
Defined in Cardano.Slotting.Slot succ :: EpochNo -> EpochNo Source # pred :: EpochNo -> EpochNo Source # toEnum :: Int -> EpochNo Source # fromEnum :: EpochNo -> Int Source # enumFrom :: EpochNo -> [ EpochNo ] Source # enumFromThen :: EpochNo -> EpochNo -> [ EpochNo ] Source # enumFromTo :: EpochNo -> EpochNo -> [ EpochNo ] Source # enumFromThenTo :: EpochNo -> EpochNo -> EpochNo -> [ EpochNo ] Source # |
|
Eq EpochNo | |
Num EpochNo | |
Defined in Cardano.Slotting.Slot |
|
Ord EpochNo | |
Defined in Cardano.Slotting.Slot |
|
Show EpochNo | |
Generic EpochNo | |
NFData EpochNo | |
Defined in Cardano.Slotting.Slot |
|
ToJSON EpochNo | |
FromJSON EpochNo | |
ToCBOR EpochNo | |
FromCBOR EpochNo | |
NoThunks EpochNo | |
Serialise EpochNo | |
Condense EpochNo | |
type Rep EpochNo | |
Defined in Cardano.Slotting.Slot |
Stake pool operator's keys
data StakePoolKey Source #
Instances
type PoolId = Hash StakePoolKey Source #
KES keys
Instances
Instances
Eq KESPeriod | |
Ord KESPeriod | |
Defined in Cardano.Protocol.TPraos.OCert |
|
Show KESPeriod | |
Generic KESPeriod | |
ToCBOR KESPeriod | |
FromCBOR KESPeriod | |
NoThunks KESPeriod | |
type Rep KESPeriod | |
Defined in Cardano.Protocol.TPraos.OCert
type
Rep
KESPeriod
=
D1
('
MetaData
"KESPeriod" "Cardano.Protocol.TPraos.OCert" "cardano-protocol-tpraos-0.1.0.0-La5Cvz4HrqgBuFHns9l3Vn" '
True
) (
C1
('
MetaCons
"KESPeriod" '
PrefixI
'
True
) (
S1
('
MetaSel
('
Just
"unKESPeriod") '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
Word
)))
|
VRF keys
Instances
Low level protocol interaction with a Cardano node
data LocalNodeConnectInfo mode Source #
data ShelleyMode Source #
The Shelley-only consensus mode consists of only the Shelley era.
This was used for the early Shelley testnets prior to the use of the
multi-era
CardanoMode
. It is useful for setting up Shelley test networks
(e.g. for benchmarking) without having to go through the complication of the
hard fork from Byron to Shelley eras. It also shows how a single-era
consensus mode works. It may be replaced by other single-era modes in future.
Instances
FromJSON ( EraInMode ShelleyEra ShelleyMode ) Source # | |
Defined in Cardano.Api.Modes parseJSON :: Value -> Parser ( EraInMode ShelleyEra ShelleyMode ) Source # parseJSONList :: Value -> Parser [ EraInMode ShelleyEra ShelleyMode ] Source # |
data ConsensusMode mode where Source #
This GADT provides a value-level representation of all the consensus modes. This enables pattern matching on the era to allow them to be treated in a non-uniform way.
Instances
Show ( ConsensusMode mode) Source # | |
Defined in Cardano.Api.Modes |
data LocalNodeClientProtocols block point tip slot tx txid txerr query m Source #
The protocols we can use with a local node. Use in conjunction with
connectToLocalNode
.
These protocols use the types from the rest of this API. The conversion
to/from the types used by the underlying wire formats is handled by
connectToLocalNode
.
LocalNodeClientProtocols ( LocalChainSyncClient block point tip m) ( Maybe ( LocalTxSubmissionClient tx txerr m ())) ( Maybe ( LocalStateQueryClient block point query m ())) ( Maybe ( LocalTxMonitorClient txid tx slot m ())) |
Shelley based eras
type family ShelleyLedgerEra era where ... Source #
A type family that connects our era type tags to equivalent type tags used in the Shelley ledger library.
This type mapping connect types from this API with types in the Shelley ledger library which allows writing conversion functions in a more generic way.
Local State Query
data DebugLedgerState era where Source #
DebugLedgerState :: ShelleyLedgerEra era ~ ledgerera => NewEpochState ledgerera -> DebugLedgerState era |
Instances
decodeDebugLedgerState :: forall era. FromCBOR ( DebugLedgerState era) => SerialisedDebugLedgerState era -> Either ByteString ( DebugLedgerState era) Source #
newtype ProtocolState era Source #
ProtocolState ( Serialised ( ChainDepState ( ConsensusProtocol era))) |
decodeProtocolState :: FromCBOR ( ChainDepState ( ConsensusProtocol era)) => ProtocolState era -> Either ( ByteString , DecoderError ) ( ChainDepState ( ConsensusProtocol era)) Source #
newtype SerialisedDebugLedgerState era Source #
newtype SerialisedCurrentEpochState era Source #
SerialisedCurrentEpochState ( Serialised ( EpochState ( ShelleyLedgerEra era))) |
decodeCurrentEpochState :: forall 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) Source #
Instances
EraCast UTxO Source # | |
Defined in Cardano.Api.Query eraCast :: ( IsCardanoEra fromEra, IsCardanoEra toEra) => CardanoEra toEra -> UTxO fromEra -> Either EraCastError ( UTxO toEra) Source # |
|
Eq ( UTxO era) Source # | |
Show ( UTxO era) Source # | |
IsCardanoEra era => ToJSON ( UTxO era) Source # | |
( IsCardanoEra era, IsShelleyBasedEra era, FromJSON ( TxOut CtxUTxO era)) => FromJSON ( UTxO era) Source # | |
data AcquiringFailure Source #
Establish a connection to a node and execute a single query using the local state query protocol.
Instances
Show AcquiringFailure Source # | |
Defined in Cardano.Api.IPC |
newtype SystemStart Source #
System start
Slots are counted from the system start.
Instances
Various calculations
data LeadershipError Source #
Instances
Show LeadershipError Source # | |
Defined in Cardano.Api.LedgerState |
|
Error LeadershipError Source # | |
Defined in Cardano.Api.LedgerState displayError :: LeadershipError -> String Source # |
currentEpochEligibleLeadershipSlots Source #
:: forall era ledgerera. ShelleyLedgerEra era ~ ledgerera | |
=> Era ledgerera | |
=> PraosProtocolSupportsNode ( ConsensusProtocol era) | |
=> HasField "_d" ( PParams ledgerera) UnitInterval | |
=> Share ( TxOut ( ShelleyLedgerEra era)) ~ Interns ( Credential ' Staking ( Crypto ( ShelleyLedgerEra era))) | |
=> FromCBOR ( ChainDepState ( ConsensusProtocol era)) | |
=> ShelleyBasedEra era | |
-> ShelleyGenesis StandardShelley | |
-> EpochInfo ( Either Text ) | |
-> ProtocolParameters | |
-> ProtocolState era | |
-> PoolId | |
-> SigningKey VrfKey | |
-> SerialisedCurrentEpochState era | |
-> EpochNo |
Current EpochInfo |
-> Either LeadershipError ( Set SlotNo ) |
Return the slots at which a particular stake pool operator is expected to mint a block.
nextEpochEligibleLeadershipSlots Source #
:: forall era. HasField "_d" ( PParams ( ShelleyLedgerEra era)) UnitInterval | |
=> 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 |
We need the mark stake distribution in order to predict the following epoch's leadership schedule |
-> ProtocolState era | |
-> PoolId |
Potential slot leading stake pool |
-> SigningKey VrfKey |
VRF signing key of the stake pool |
-> ProtocolParameters | |
-> EpochInfo ( Either Text ) | |
-> ( ChainTip , EpochNo ) | |
-> Either LeadershipError ( Set SlotNo ) |
Conversions
shelleyPayAddrToPlutusPubKHash :: Address ShelleyAddr -> Maybe PubKeyHash Source #
Converts a Shelley payment address to a Plutus public key hash.
toConsensusGenTx :: ConsensusBlockForMode mode ~ block => TxInMode mode -> GenTx block Source #
toShelleyNetwork :: NetworkId -> Network Source #
fromShelleyPParams :: PParams ledgerera -> ProtocolParameters Source #