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 c = ShelleyGenesis {
- sgSystemStart :: !UTCTime
- sgNetworkMagic :: !Word32
- sgNetworkId :: !Network
- sgActiveSlotsCoeff :: !PositiveUnitInterval
- sgSecurityParam :: !Word64
- sgEpochLength :: !EpochSize
- sgSlotsPerKESPeriod :: !Word64
- sgMaxKESEvolutions :: !Word64
- sgSlotLength :: !NominalDiffTimeMicro
- sgUpdateQuorum :: !Word64
- sgMaxLovelaceSupply :: !Word64
- sgProtocolParams :: !(PParams (ShelleyEra c))
- sgGenDelegs :: !(Map (KeyHash 'Genesis c) (GenDelegPair c))
- sgInitialFunds :: ListMap (Addr c) Coin
- sgStaking :: ShelleyGenesisStaking c
- shelleyGenesisDefaults :: ShelleyGenesis StandardCrypto
- class (Eq (VerificationKey keyrole), Show (VerificationKey keyrole), SerialiseAsRawBytes (Hash keyrole), HasTextEnvelope (VerificationKey keyrole), HasTextEnvelope (SigningKey keyrole)) => Key keyrole where
- data VerificationKey keyrole
- data SigningKey keyrole
- getVerificationKey :: SigningKey keyrole -> VerificationKey keyrole
- deterministicSigningKey :: AsType keyrole -> Seed -> SigningKey keyrole
- deterministicSigningKeySeedSize :: AsType keyrole -> Word
- verificationKeyHash :: VerificationKey keyrole -> Hash keyrole
- data family VerificationKey keyrole
- data family SigningKey keyrole
- data family Hash keyrole
- data family AsType t
- 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 :: ShelleyBasedEra 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 :: forall era. ShelleyBasedEra era -> TxBody (ShelleyLedgerEra era) -> [Script (ShelleyLedgerEra era)] -> TxBodyScriptData era -> Maybe (TxAuxData (ShelleyLedgerEra era)) -> TxScriptValidity era -> TxBody era
- newtype TxId = TxId (Hash StandardCrypto EraIndependentTxBody)
- toShelleyTxId :: TxId -> TxId StandardCrypto
- fromShelleyTxId :: TxId StandardCrypto -> TxId
- getTxIdShelley :: (EraCrypto (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 :: ShelleyLedgerEra era ~ ledgerera => ShelleyBasedEra era -> TxOut CtxUTxO era -> TxOut ledgerera
- fromShelleyTxOut :: ShelleyBasedEra era -> TxOut (ShelleyLedgerEra era) -> 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 :: forall era. ShelleyBasedEra era -> Tx (ShelleyLedgerEra era) -> Tx era
- data KeyWitness era where
- ShelleyBootstrapWitness :: forall era. ShelleyBasedEra era -> BootstrapWitness StandardCrypto -> KeyWitness era
- ShelleyKeyWitness :: forall era. 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 :: CardanoBlock StandardCrypto ~ block => block -> BlockInMode
- toConsensusBlock :: CardanoBlock StandardCrypto ~ block => BlockInMode -> block
- fromConsensusTip :: CardanoBlock StandardCrypto ~ block => Tip block -> ChainTip
- fromConsensusPointHF :: forall block (xs :: [Type]). HeaderHash block ~ OneEraHash xs => Point block -> ChainPoint
- toConsensusPointHF :: forall block (xs :: [Type]). 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
- newtype LedgerProtocolParameters era = LedgerProtocolParameters {
- unLedgerProtocolParameters :: PParams (ShelleyLedgerEra era)
- data EraBasedProtocolParametersUpdate era where
- ShelleyEraBasedProtocolParametersUpdate :: CommonProtocolParametersUpdate -> DeprecatedAfterMaryPParams ShelleyEra -> DeprecatedAfterBabbagePParams ShelleyEra -> ShelleyToAlonzoPParams ShelleyEra -> EraBasedProtocolParametersUpdate ShelleyEra
- AllegraEraBasedProtocolParametersUpdate :: CommonProtocolParametersUpdate -> DeprecatedAfterMaryPParams AllegraEra -> ShelleyToAlonzoPParams AllegraEra -> DeprecatedAfterBabbagePParams ShelleyEra -> EraBasedProtocolParametersUpdate AllegraEra
- MaryEraBasedProtocolParametersUpdate :: CommonProtocolParametersUpdate -> DeprecatedAfterMaryPParams MaryEra -> ShelleyToAlonzoPParams MaryEra -> DeprecatedAfterBabbagePParams ShelleyEra -> EraBasedProtocolParametersUpdate MaryEra
- AlonzoEraBasedProtocolParametersUpdate :: CommonProtocolParametersUpdate -> ShelleyToAlonzoPParams AlonzoEra -> AlonzoOnwardsPParams AlonzoEra -> DeprecatedAfterBabbagePParams ShelleyEra -> EraBasedProtocolParametersUpdate AlonzoEra
- BabbageEraBasedProtocolParametersUpdate :: CommonProtocolParametersUpdate -> AlonzoOnwardsPParams BabbageEra -> DeprecatedAfterBabbagePParams ShelleyEra -> IntroducedInBabbagePParams BabbageEra -> EraBasedProtocolParametersUpdate BabbageEra
- ConwayEraBasedProtocolParametersUpdate :: CommonProtocolParametersUpdate -> AlonzoOnwardsPParams ConwayEra -> IntroducedInBabbagePParams ConwayEra -> IntroducedInConwayPParams (ShelleyLedgerEra ConwayEra) -> EraBasedProtocolParametersUpdate ConwayEra
- data CommonProtocolParametersUpdate = CommonProtocolParametersUpdate {
- cppMinFeeA :: StrictMaybe Coin
- cppMinFeeB :: StrictMaybe Coin
- cppMaxBlockBodySize :: StrictMaybe Natural
- cppMaxTxSize :: StrictMaybe Natural
- cppMaxBlockHeaderSize :: StrictMaybe Natural
- cppKeyDeposit :: StrictMaybe Coin
- cppPoolDeposit :: StrictMaybe Coin
- cppPoolRetireMaxEpoch :: StrictMaybe EpochNo
- cppStakePoolTargetNum :: StrictMaybe Natural
- cppPoolPledgeInfluence :: StrictMaybe NonNegativeInterval
- cppTreasuryExpansion :: StrictMaybe UnitInterval
- cppMonetaryExpansion :: StrictMaybe UnitInterval
- cppMinPoolCost :: StrictMaybe Coin
- data AlonzoOnwardsPParams ledgerera = AlonzoOnwardsPParams {
- alCostModels :: StrictMaybe CostModels
- alPrices :: StrictMaybe Prices
- alMaxTxExUnits :: StrictMaybe ExUnits
- alMaxBlockExUnits :: StrictMaybe ExUnits
- alMaxValSize :: StrictMaybe Natural
- alCollateralPercentage :: StrictMaybe Natural
- alMaxCollateralInputs :: StrictMaybe Natural
- newtype DeprecatedAfterBabbagePParams ledgerera = DeprecatedAfterBabbagePParams (StrictMaybe ProtVer)
- newtype DeprecatedAfterMaryPParams ledgerera = DeprecatedAfterMaryPParams (StrictMaybe Coin)
- data ShelleyToAlonzoPParams ledgerera = ShelleyToAlonzoPParams (StrictMaybe Nonce) (StrictMaybe UnitInterval)
- newtype IntroducedInBabbagePParams era = IntroducedInBabbagePParams (StrictMaybe CoinPerByte)
- data IntroducedInConwayPParams era = IntroducedInConwayPParams {
- icPoolVotingThresholds :: StrictMaybe PoolVotingThresholds
- icDRepVotingThresholds :: StrictMaybe DRepVotingThresholds
- icMinCommitteeSize :: StrictMaybe Natural
- icCommitteeTermLength :: StrictMaybe EpochNo
- icGovActionLifetime :: StrictMaybe EpochNo
- icGovActionDeposit :: StrictMaybe Coin
- icDRepDeposit :: StrictMaybe Coin
- icDRepActivity :: StrictMaybe EpochNo
- createEraBasedProtocolParamUpdate :: ShelleyBasedEra era -> EraBasedProtocolParametersUpdate era -> PParamsUpdate (ShelleyLedgerEra era)
- convertToLedgerProtocolParameters :: ShelleyBasedEra era -> ProtocolParameters -> Either ProtocolParametersConversionError (LedgerProtocolParameters era)
- data ProtocolParameters = ProtocolParameters {
- protocolParamProtocolVersion :: (Natural, Natural)
- protocolParamDecentralization :: Maybe Rational
- protocolParamExtraPraosEntropy :: Maybe PraosNonce
- protocolParamMaxBlockHeaderSize :: Natural
- protocolParamMaxBlockBodySize :: Natural
- protocolParamMaxTxSize :: Natural
- protocolParamTxFeeFixed :: Lovelace
- protocolParamTxFeePerByte :: Lovelace
- protocolParamMinUTxOValue :: Maybe Lovelace
- protocolParamStakeAddressDeposit :: Lovelace
- protocolParamStakePoolDeposit :: Lovelace
- protocolParamMinPoolCost :: Lovelace
- protocolParamPoolRetireMaxEpoch :: EpochNo
- protocolParamStakePoolTargetNum :: Natural
- protocolParamPoolPledgeInfluence :: Rational
- protocolParamMonetaryExpansion :: Rational
- protocolParamTreasuryCut :: Rational
- 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 :: ShelleyBasedEra era -> ProtocolParameters -> Either ProtocolParametersError ()
- data ProtocolParametersError
- fromShelleyBasedScript :: ShelleyBasedEra era -> Script (ShelleyLedgerEra era) -> ScriptInEra era
- toShelleyScript :: ScriptInEra era -> Script (ShelleyLedgerEra era)
- toShelleyMultiSig :: (Era era, EraCrypto era ~ StandardCrypto) => SimpleScript -> Either MultiSigError (MultiSig era)
- fromShelleyMultiSig :: (Era era, EraCrypto era ~ StandardCrypto) => MultiSig era -> SimpleScript
- toAllegraTimelock :: (Era era, EraCrypto era ~ StandardCrypto) => SimpleScript -> Timelock era
- fromAllegraTimelock :: (Era era, EraCrypto era ~ StandardCrypto) => Timelock era -> SimpleScript
- toShelleyScriptHash :: ScriptHash -> ScriptHash StandardCrypto
- fromShelleyScriptHash :: ScriptHash StandardCrypto -> ScriptHash
- data PlutusScript lang where
- PlutusScriptSerialised :: forall lang. ShortByteString -> PlutusScript lang
- data PlutusScriptOrReferenceInput lang
- = PScript (PlutusScript lang)
- | PReferenceScript TxIn (Maybe ScriptHash)
- data SimpleScriptOrReferenceInput lang
- toPlutusData :: ScriptData -> Data
- fromPlutusData :: Data -> ScriptData
- toAlonzoData :: Era ledgerera => HashableScriptData -> Data ledgerera
- fromAlonzoData :: Data ledgerera -> HashableScriptData
- toAlonzoPrices :: ExecutionUnitPrices -> Either ProtocolParametersConversionError 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 :: Prices -> ExecutionUnits -> Maybe Lovelace
- data ReferenceScript era where
- ReferenceScript :: forall era. BabbageEraOnwards era -> ScriptInAnyLang -> ReferenceScript era
- ReferenceScriptNone :: forall era. ReferenceScript era
- refScriptToShelleyScript :: ShelleyBasedEra era -> ReferenceScript era -> StrictMaybe (Script (ShelleyLedgerEra era))
- data Certificate era where
- ShelleyRelatedCertificate :: forall era. ShelleyToBabbageEra era -> ShelleyTxCert (ShelleyLedgerEra era) -> Certificate era
- ConwayCertificate :: forall era. ConwayEraOnwards era -> ConwayTxCert (ShelleyLedgerEra era) -> Certificate era
- toShelleyCertificate :: Certificate era -> TxCert (ShelleyLedgerEra era)
- fromShelleyCertificate :: ShelleyBasedEra era -> TxCert (ShelleyLedgerEra era) -> Certificate era
- toShelleyPoolParams :: StakePoolParameters -> PoolParams StandardCrypto
- 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 {}
- createAnchor :: Url -> ByteString -> Anchor StandardCrypto
- createPreviousGovernanceActionId :: forall (r :: GovActionPurpose). TxId -> Word32 -> PrevGovActionId r StandardCrypto
- createGovernanceActionId :: TxId -> Word32 -> GovActionId StandardCrypto
- newtype DRepMetadata = DRepMetadata ByteString
- data DRepMetadataReference = DRepMetadataReference Text (Hash DRepMetadata)
- data StakePoolKey
- type PoolId = Hash StakePoolKey
- data KesKey
- newtype KESPeriod = KESPeriod {
- unKESPeriod :: Word
- data VrfKey
- data LocalNodeConnectInfo = LocalNodeConnectInfo ConsensusModeParams NetworkId SocketPath
- data LocalNodeClientProtocols block point tip slot tx txid txerr (query :: Type -> Type) (m :: Type -> Type) = 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 = (ledgerera :: Type) | ledgerera -> era where ...
- newtype DebugLedgerState era = DebugLedgerState {
- unDebugLedgerState :: NewEpochState (ShelleyLedgerEra era)
- decodeDebugLedgerState :: 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 :: ShelleyBasedEra era -> SerialisedCurrentEpochState era -> Either DecoderError (CurrentEpochState era)
- newtype PoolState era = PoolState (PState (ShelleyLedgerEra era))
- newtype SerialisedPoolState era = SerialisedPoolState (Serialised (PState (ShelleyLedgerEra era)))
- decodePoolState :: (Era (ShelleyLedgerEra era), DecCBOR (PState (ShelleyLedgerEra era))) => SerialisedPoolState era -> Either DecoderError (PoolState era)
- newtype PoolDistribution era = PoolDistribution {
- unPoolDistr :: PoolDistr (EraCrypto (ShelleyLedgerEra era))
- newtype SerialisedPoolDistribution era = SerialisedPoolDistribution (Serialised (PoolDistr (EraCrypto (ShelleyLedgerEra era))))
- decodePoolDistribution :: Crypto (EraCrypto (ShelleyLedgerEra era)) => ShelleyBasedEra era -> SerialisedPoolDistribution era -> Either DecoderError (PoolDistribution era)
- newtype StakeSnapshot era = StakeSnapshot (StakeSnapshots (EraCrypto (ShelleyLedgerEra era)))
- newtype SerialisedStakeSnapshots era = SerialisedStakeSnapshots (Serialised (StakeSnapshots (EraCrypto (ShelleyLedgerEra era))))
- decodeStakeSnapshot :: FromCBOR (StakeSnapshots (EraCrypto (ShelleyLedgerEra era))) => SerialisedStakeSnapshots era -> Either DecoderError (StakeSnapshot era)
- newtype UTxO era = UTxO {}
- data AcquiringFailure
- newtype SystemStart = SystemStart {
- getSystemStart :: UTCTime
- data GovernanceAction era
- = MotionOfNoConfidence (StrictMaybe (PrevGovActionId 'CommitteePurpose StandardCrypto))
- | ProposeNewConstitution (StrictMaybe (PrevGovActionId 'ConstitutionPurpose StandardCrypto)) (Anchor StandardCrypto)
- | ProposeNewCommittee (StrictMaybe (PrevGovActionId 'CommitteePurpose StandardCrypto)) [Hash CommitteeColdKey] (Map (Hash CommitteeColdKey) EpochNo) Rational
- | InfoAct
- | TreasuryWithdrawal [(Network, StakeCredential, Lovelace)]
- | InitiateHardfork (StrictMaybe (PrevGovActionId 'HardForkPurpose StandardCrypto)) ProtVer
- | UpdatePParams (StrictMaybe (PrevGovActionId 'PParamUpdatePurpose StandardCrypto)) (PParamsUpdate (ShelleyLedgerEra era))
- newtype GovernanceActionId era = GovernanceActionId {
- unGovernanceActionId :: GovActionId (EraCrypto (ShelleyLedgerEra era))
- newtype Proposal era = Proposal {
- unProposal :: ProposalProcedure (ShelleyLedgerEra era)
- newtype VotingProcedure era = VotingProcedure {
- unVotingProcedure :: VotingProcedure (ShelleyLedgerEra era)
- newtype VotingProcedures era = VotingProcedures {
- unVotingProcedures :: VotingProcedures (ShelleyLedgerEra era)
- data GovernancePoll = GovernancePoll {
- govPollQuestion :: Text
- govPollAnswers :: [Text]
- govPollNonce :: Maybe Word
- data GovernancePollAnswer = GovernancePollAnswer {}
- data GovernancePollError
- = ErrGovernancePollMismatch GovernancePollMismatchError
- | ErrGovernancePollNoAnswer
- | ErrGovernancePollUnauthenticated
- | ErrGovernancePollMalformedAnswer DecoderError
- | ErrGovernancePollInvalidAnswer GovernancePollInvalidAnswerError
- data Vote
- newtype Voter era = Voter (Voter (EraCrypto (ShelleyLedgerEra era)))
- createProposalProcedure :: ShelleyBasedEra era -> Network -> Lovelace -> Hash StakeKey -> GovernanceAction era -> Anchor StandardCrypto -> Proposal era
- createVotingProcedure :: ConwayEraOnwards era -> Vote -> Maybe (Url, Text) -> VotingProcedure era
- renderGovernancePollError :: GovernancePollError -> Text
- fromProposalProcedure :: ShelleyBasedEra era -> Proposal era -> (Lovelace, Hash StakeKey, GovernanceAction era)
- hashGovernancePoll :: GovernancePoll -> Hash GovernancePoll
- verifyPollAnswer :: GovernancePoll -> InAnyShelleyBasedEra Tx -> Either GovernancePollError [Hash PaymentKey]
- data LeadershipError
- = LeaderErrDecodeLedgerStateFailure
- | LeaderErrDecodeProtocolStateFailure (ByteString, DecoderError)
- | LeaderErrDecodeProtocolEpochStateFailure DecoderError
- | LeaderErrGenesisSlot
- | LeaderErrStakePoolHasNoStake PoolId
- | LeaderErrStakeDistribUnstable SlotNo SlotNo SlotNo SlotNo
- | LeaderErrSlotRangeCalculationFailure Text
- | LeaderErrCandidateNonceStillEvolving
- currentEpochEligibleLeadershipSlots :: ShelleyBasedEra era -> ShelleyGenesis StandardCrypto -> EpochInfo (Either Text) -> PParams (ShelleyLedgerEra era) -> ProtocolState era -> PoolId -> SigningKey VrfKey -> SerialisedPoolDistribution era -> EpochNo -> Either LeadershipError (Set SlotNo)
- nextEpochEligibleLeadershipSlots :: ShelleyBasedEra era -> ShelleyGenesis StandardCrypto -> SerialisedCurrentEpochState era -> ProtocolState era -> PoolId -> SigningKey VrfKey -> PParams (ShelleyLedgerEra era) -> EpochInfo (Either Text) -> (ChainTip, EpochNo) -> Either LeadershipError (Set SlotNo)
- shelleyPayAddrToPlutusPubKHash :: Address ShelleyAddr -> Maybe PubKeyHash
- toConsensusGenTx :: CardanoBlock StandardCrypto ~ block => TxInMode -> GenTx block
- fromAlonzoCostModels :: CostModels -> Map AnyPlutusScriptVersion CostModel
- toLedgerNonce :: Maybe PraosNonce -> Nonce
- toShelleyNetwork :: NetworkId -> Network
- fromShelleyPoolParams :: PoolParams StandardCrypto -> StakePoolParameters
- fromLedgerPParamsUpdate :: ShelleyBasedEra era -> PParamsUpdate (ShelleyLedgerEra era) -> ProtocolParametersUpdate
- emptyVotingProcedures :: VotingProcedures era
- singletonVotingProcedures :: ConwayEraOnwards era -> Voter (EraCrypto (ShelleyLedgerEra era)) -> GovActionId (EraCrypto (ShelleyLedgerEra era)) -> VotingProcedure (ShelleyLedgerEra era) -> VotingProcedures era
- unsafeMergeVotingProcedures :: VotingProcedures era -> VotingProcedures era -> VotingProcedures era
Documentation
module Cardano.Api
Genesis
data ShelleyGenesis c #
Constructors
ShelleyGenesis | |
Fields
|
Instances
shelleyGenesisDefaults :: ShelleyGenesis StandardCrypto #
Cryptographic key interface
class (Eq (VerificationKey keyrole), Show (VerificationKey keyrole), SerialiseAsRawBytes (Hash keyrole), HasTextEnvelope (VerificationKey keyrole), HasTextEnvelope (SigningKey keyrole)) => Key keyrole where #
Methods
getVerificationKey :: SigningKey keyrole -> VerificationKey keyrole #
deterministicSigningKey :: AsType keyrole -> Seed -> SigningKey keyrole #
deterministicSigningKeySeedSize :: AsType keyrole -> Word #
verificationKeyHash :: VerificationKey keyrole -> Hash keyrole #
Instances
data family VerificationKey keyrole #
Instances
data family SigningKey keyrole #
Instances
Hashes
Instances
Type Proxies
Instances
Payment addresses
Constructing and inspecting Shelley payment addresses
Constructors
ShelleyAddress :: Network -> PaymentCredential StandardCrypto -> StakeReference StandardCrypto -> Address ShelleyAddr |
Instances
toShelleyAddr :: AddressInEra era -> Addr StandardCrypto #
fromShelleyAddr :: ShelleyBasedEra era -> Addr StandardCrypto -> AddressInEra era #
fromShelleyAddrIsSbe :: ShelleyBasedEra era -> Addr StandardCrypto -> AddressInEra era #
fromShelleyAddrToAny :: Addr StandardCrypto -> AddressAny #
toShelleyStakeCredential :: StakeCredential -> StakeCredential StandardCrypto #
fromShelleyStakeCredential :: StakeCredential StandardCrypto -> StakeCredential #
Stake addresses
data PaymentCredential #
Constructors
PaymentCredentialByKey (Hash PaymentKey) | |
PaymentCredentialByScript ScriptHash |
Instances
Eq PaymentCredential | |
Defined in Cardano.Api.Address Methods (==) :: PaymentCredential -> PaymentCredential -> Bool Source # (/=) :: PaymentCredential -> PaymentCredential -> Bool Source # | |
Ord PaymentCredential | |
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 | |
Defined in Cardano.Api.Address |
data StakeAddress where #
Constructors
StakeAddress :: Network -> StakeCredential StandardCrypto -> StakeAddress |
Instances
data StakeAddressReference #
Constructors
StakeAddressByValue StakeCredential | |
StakeAddressByPointer StakeAddressPointer | |
NoStakeAddress |
Instances
Eq StakeAddressReference | |
Defined in Cardano.Api.Address Methods (==) :: StakeAddressReference -> StakeAddressReference -> Bool Source # (/=) :: StakeAddressReference -> StakeAddressReference -> Bool Source # | |
Show StakeAddressReference | |
Defined in Cardano.Api.Address |
data StakeCredential #
Constructors
StakeCredentialByKey (Hash StakeKey) | |
StakeCredentialByScript ScriptHash |
Instances
Eq StakeCredential | |
Defined in Cardano.Api.Address Methods (==) :: StakeCredential -> StakeCredential -> Bool Source # (/=) :: StakeCredential -> StakeCredential -> Bool Source # | |
Ord StakeCredential | |
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 | |
Defined in Cardano.Api.Address | |
ToJSON StakeCredential | |
Defined in Cardano.Api.Address Methods toJSON :: StakeCredential -> Value toEncoding :: StakeCredential -> Encoding toJSONList :: [StakeCredential] -> Value toEncodingList :: [StakeCredential] -> Encoding omitField :: StakeCredential -> Bool |
toShelleyStakeAddr :: StakeAddress -> RewardAcnt StandardCrypto #
fromShelleyStakeAddr :: RewardAcnt StandardCrypto -> StakeAddress #
fromShelleyStakeReference :: StakeReference StandardCrypto -> StakeAddressReference #
fromShelleyPaymentCredential :: PaymentCredential StandardCrypto -> PaymentCredential #
Building transactions
Constructing and inspecting transactions
Constructors
ShelleyTxBody :: forall era. ShelleyBasedEra era -> TxBody (ShelleyLedgerEra era) -> [Script (ShelleyLedgerEra era)] -> TxBodyScriptData era -> Maybe (TxAuxData (ShelleyLedgerEra era)) -> TxScriptValidity era -> TxBody era |
Instances
Eq (TxBody era) | |
Show (TxBody era) | |
HasTypeProxy era => HasTypeProxy (TxBody era) | |
Defined in Cardano.Api.TxBody | |
IsShelleyBasedEra era => HasTextEnvelope (TxBody era) | |
Defined in Cardano.Api.TxBody Methods textEnvelopeType :: AsType (TxBody era) -> TextEnvelopeType # textEnvelopeDefaultDescr :: TxBody era -> TextEnvelopeDescr # | |
IsShelleyBasedEra era => SerialiseAsCBOR (TxBody era) | |
Defined in Cardano.Api.TxBody Methods serialiseToCBOR :: TxBody era -> ByteString # deserialiseFromCBOR :: AsType (TxBody era) -> ByteString -> Either DecoderError (TxBody era) # | |
data AsType (TxBody era) | |
Defined in Cardano.Api.TxBody |
Constructors
TxId (Hash StandardCrypto EraIndependentTxBody) |
Instances
Eq TxId | |
Ord TxId | |
Show TxId | |
IsString TxId | |
Defined in Cardano.Api.TxIn Methods fromString :: String -> TxId Source # | |
FromJSON TxId | |
Defined in Cardano.Api.TxIn | |
HasTypeProxy TxId | |
Defined in Cardano.Api.TxIn | |
SerialiseAsRawBytes TxId | |
Defined in Cardano.Api.TxIn Methods serialiseToRawBytes :: TxId -> ByteString # deserialiseFromRawBytes :: AsType TxId -> ByteString -> Either SerialiseAsRawBytesError TxId # | |
ToJSON TxId | |
Defined in Cardano.Api.TxIn Methods toEncoding :: TxId -> Encoding toJSONList :: [TxId] -> Value toEncodingList :: [TxId] -> Encoding | |
ToJSONKey TxId | |
Defined in Cardano.Api.TxIn | |
FromJSONKey TxId | |
Defined in Cardano.Api.TxIn | |
data AsType TxId | |
Defined in Cardano.Api.TxIn |
toShelleyTxId :: TxId -> TxId StandardCrypto #
fromShelleyTxId :: TxId StandardCrypto -> TxId #
getTxIdShelley :: (EraCrypto (ShelleyLedgerEra era) ~ StandardCrypto, EraTxBody (ShelleyLedgerEra era)) => ShelleyBasedEra era -> TxBody (ShelleyLedgerEra era) -> TxId #
Instances
Eq TxIn | |
Ord TxIn | |
Show TxIn | |
FromJSON TxIn | |
Defined in Cardano.Api.TxIn | |
ToJSON TxIn | |
Defined in Cardano.Api.TxIn Methods toEncoding :: TxIn -> Encoding toJSONList :: [TxIn] -> Value toEncodingList :: [TxIn] -> Encoding | |
ToJSONKey TxIn | |
Defined in Cardano.Api.TxIn | |
FromJSONKey TxIn | |
Defined in Cardano.Api.TxIn | |
Pretty TxIn | |
Defined in Cardano.Api.TxIn |
toShelleyTxIn :: TxIn -> TxIn StandardCrypto #
fromShelleyTxIn :: TxIn StandardCrypto -> TxIn #
Constructors
TxOut (AddressInEra era) (TxOutValue era) (TxOutDatum ctx era) (ReferenceScript era) |
Instances
Eq (TxOut ctx era) | |
Show (TxOut ctx era) | |
IsShelleyBasedEra era => FromJSON (TxOut CtxUTxO era) | |
Defined in Cardano.Api.TxBody Methods parseJSON :: Value -> Parser (TxOut CtxUTxO era) parseJSONList :: Value -> Parser [TxOut CtxUTxO era] omittedField :: Maybe (TxOut CtxUTxO era) | |
IsShelleyBasedEra era => FromJSON (TxOut CtxTx era) | |
Defined in Cardano.Api.TxBody Methods parseJSON :: Value -> Parser (TxOut CtxTx era) parseJSONList :: Value -> Parser [TxOut CtxTx era] omittedField :: Maybe (TxOut CtxTx era) | |
IsCardanoEra era => ToJSON (TxOut ctx era) | |
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 :: ShelleyLedgerEra era ~ ledgerera => ShelleyBasedEra era -> TxOut CtxUTxO era -> TxOut ledgerera #
fromShelleyTxOut :: ShelleyBasedEra era -> TxOut (ShelleyLedgerEra era) -> TxOut ctx era #
Instances
Enum TxIx | |
Eq TxIx | |
Ord TxIx | |
Show TxIx | |
FromJSON TxIx | |
Defined in Cardano.Api.TxIn | |
ToJSON TxIx | |
Defined in Cardano.Api.TxIn Methods toEncoding :: TxIx -> Encoding toJSONList :: [TxIx] -> Value toEncodingList :: [TxIx] -> Encoding |
Instances
toShelleyLovelace :: Lovelace -> Coin #
fromShelleyLovelace :: Coin -> Lovelace #
toMaryValue :: Value -> MaryValue StandardCrypto #
fromMaryValue :: MaryValue StandardCrypto -> Value #
calcMinimumDeposit :: Value -> Lovelace -> Lovelace #
Arbitrary signing
signArbitraryBytesKes :: SigningKey KesKey -> Period -> ByteString -> SignedKES (KES StandardCrypto) ByteString #
Signing transactions
Creating transaction witnesses one by one, or all in one go.
Constructors
ShelleyTx :: forall era. ShelleyBasedEra era -> Tx (ShelleyLedgerEra era) -> Tx era |
Instances
Incremental signing and separate witnesses
data KeyWitness era where #
Constructors
ShelleyBootstrapWitness :: forall era. ShelleyBasedEra era -> BootstrapWitness StandardCrypto -> KeyWitness era | |
ShelleyKeyWitness :: forall era. ShelleyBasedEra era -> WitVKey 'Witness StandardCrypto -> KeyWitness era |
Instances
Eq (KeyWitness era) | |
Defined in Cardano.Api.Tx Methods (==) :: KeyWitness era -> KeyWitness era -> Bool Source # (/=) :: KeyWitness era -> KeyWitness era -> Bool Source # | |
Show (KeyWitness era) | |
Defined in Cardano.Api.Tx | |
HasTypeProxy era => HasTypeProxy (KeyWitness era) | |
Defined in Cardano.Api.Tx Associated Types data AsType (KeyWitness era) # Methods proxyToAsType :: Proxy (KeyWitness era) -> AsType (KeyWitness era) # | |
IsCardanoEra era => HasTextEnvelope (KeyWitness era) | |
Defined in Cardano.Api.Tx Methods textEnvelopeType :: AsType (KeyWitness era) -> TextEnvelopeType # textEnvelopeDefaultDescr :: KeyWitness era -> TextEnvelopeDescr # | |
IsCardanoEra era => SerialiseAsCBOR (KeyWitness era) | |
Defined in Cardano.Api.Tx Methods serialiseToCBOR :: KeyWitness era -> ByteString # deserialiseFromCBOR :: AsType (KeyWitness era) -> ByteString -> Either DecoderError (KeyWitness era) # | |
data AsType (KeyWitness era) | |
Defined in Cardano.Api.Tx |
data ShelleyWitnessSigningKey #
Constructors
data ShelleySigningKey #
Constructors
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 #
Blocks
fromConsensusBlock :: CardanoBlock StandardCrypto ~ block => block -> BlockInMode #
toConsensusBlock :: CardanoBlock StandardCrypto ~ block => BlockInMode -> block #
fromConsensusTip :: CardanoBlock StandardCrypto ~ block => Tip block -> ChainTip #
fromConsensusPointHF :: forall block (xs :: [Type]). HeaderHash block ~ OneEraHash xs => Point block -> ChainPoint #
toConsensusPointHF :: forall block (xs :: [Type]). HeaderHash block ~ OneEraHash xs => ChainPoint -> Point block #
Transaction metadata
Embedding additional structured data within transactions.
toShelleyMetadata :: Map Word64 TxMetadataValue -> Map Word64 Metadatum #
fromShelleyMetadata :: Map Word64 Metadatum -> Map Word64 TxMetadataValue #
toShelleyMetadatum :: TxMetadataValue -> Metadatum #
fromShelleyMetadatum :: Metadatum -> TxMetadataValue #
Protocol parameters
newtype LedgerProtocolParameters era #
Constructors
LedgerProtocolParameters | |
Fields
|
Instances
IsShelleyBasedEra era => Eq (LedgerProtocolParameters era) | |
Defined in Cardano.Api.ProtocolParameters Methods (==) :: LedgerProtocolParameters era -> LedgerProtocolParameters era -> Bool Source # (/=) :: LedgerProtocolParameters era -> LedgerProtocolParameters era -> Bool Source # | |
IsShelleyBasedEra era => Show (LedgerProtocolParameters era) | |
Defined in Cardano.Api.ProtocolParameters |
data EraBasedProtocolParametersUpdate era where #
Constructors
Instances
Show (EraBasedProtocolParametersUpdate era) | |
Defined in Cardano.Api.ProtocolParameters |
data CommonProtocolParametersUpdate #
Constructors
CommonProtocolParametersUpdate | |
Fields
|
Instances
data AlonzoOnwardsPParams ledgerera #
Constructors
AlonzoOnwardsPParams | |
Fields
|
Instances
Show (AlonzoOnwardsPParams ledgerera) | |
Defined in Cardano.Api.ProtocolParameters |
newtype DeprecatedAfterBabbagePParams ledgerera #
Constructors
DeprecatedAfterBabbagePParams (StrictMaybe ProtVer) |
Instances
Show (DeprecatedAfterBabbagePParams ledgerera) | |
Defined in Cardano.Api.ProtocolParameters |
newtype DeprecatedAfterMaryPParams ledgerera #
Constructors
DeprecatedAfterMaryPParams (StrictMaybe Coin) |
Instances
Show (DeprecatedAfterMaryPParams ledgerera) | |
Defined in Cardano.Api.ProtocolParameters |
data ShelleyToAlonzoPParams ledgerera #
Constructors
ShelleyToAlonzoPParams (StrictMaybe Nonce) (StrictMaybe UnitInterval) |
Instances
Show (ShelleyToAlonzoPParams ledgerera) | |
Defined in Cardano.Api.ProtocolParameters |
newtype IntroducedInBabbagePParams era #
Constructors
IntroducedInBabbagePParams (StrictMaybe CoinPerByte) |
Instances
Show (IntroducedInBabbagePParams era) | |
Defined in Cardano.Api.ProtocolParameters |
data IntroducedInConwayPParams era #
Constructors
IntroducedInConwayPParams | |
Fields
|
Instances
Show (IntroducedInConwayPParams era) | |
Defined in Cardano.Api.ProtocolParameters |
createEraBasedProtocolParamUpdate :: ShelleyBasedEra era -> EraBasedProtocolParametersUpdate era -> PParamsUpdate (ShelleyLedgerEra era) #
convertToLedgerProtocolParameters :: ShelleyBasedEra era -> ProtocolParameters -> Either ProtocolParametersConversionError (LedgerProtocolParameters era) #
data ProtocolParameters #
Constructors
Instances
checkProtocolParameters :: ShelleyBasedEra era -> ProtocolParameters -> Either ProtocolParametersError () #
data ProtocolParametersError #
Constructors
PParamsErrorMissingMinUTxoValue !AnyCardanoEra | |
PParamsErrorMissingAlonzoProtocolParameter |
Instances
Show ProtocolParametersError | |
Defined in Cardano.Api.ProtocolParameters | |
Error ProtocolParametersError | |
Defined in Cardano.Api.ProtocolParameters Methods prettyError :: ProtocolParametersError -> Doc ann # |
Scripts
fromShelleyBasedScript :: ShelleyBasedEra era -> Script (ShelleyLedgerEra era) -> ScriptInEra era #
toShelleyScript :: ScriptInEra era -> Script (ShelleyLedgerEra era) #
toShelleyMultiSig :: (Era era, EraCrypto era ~ StandardCrypto) => SimpleScript -> Either MultiSigError (MultiSig era) #
fromShelleyMultiSig :: (Era era, EraCrypto era ~ StandardCrypto) => MultiSig era -> SimpleScript #
toAllegraTimelock :: (Era era, EraCrypto era ~ StandardCrypto) => SimpleScript -> Timelock era #
fromAllegraTimelock :: (Era era, EraCrypto era ~ StandardCrypto) => Timelock era -> SimpleScript #
toShelleyScriptHash :: ScriptHash -> ScriptHash StandardCrypto #
fromShelleyScriptHash :: ScriptHash StandardCrypto -> ScriptHash #
data PlutusScript lang where #
Constructors
PlutusScriptSerialised :: forall lang. ShortByteString -> PlutusScript lang |
Instances
data PlutusScriptOrReferenceInput lang #
Constructors
PScript (PlutusScript lang) | |
PReferenceScript TxIn (Maybe ScriptHash) |
Instances
Eq (PlutusScriptOrReferenceInput lang) | |
Defined in Cardano.Api.Script Methods (==) :: PlutusScriptOrReferenceInput lang -> PlutusScriptOrReferenceInput lang -> Bool Source # (/=) :: PlutusScriptOrReferenceInput lang -> PlutusScriptOrReferenceInput lang -> Bool Source # | |
Show (PlutusScriptOrReferenceInput lang) | |
Defined in Cardano.Api.Script |
data SimpleScriptOrReferenceInput lang #
Constructors
SScript SimpleScript | |
SReferenceScript TxIn (Maybe ScriptHash) |
Instances
Eq (SimpleScriptOrReferenceInput lang) | |
Defined in Cardano.Api.Script Methods (==) :: SimpleScriptOrReferenceInput lang -> SimpleScriptOrReferenceInput lang -> Bool Source # (/=) :: SimpleScriptOrReferenceInput lang -> SimpleScriptOrReferenceInput lang -> Bool Source # | |
Show (SimpleScriptOrReferenceInput lang) | |
Defined in Cardano.Api.Script |
toPlutusData :: ScriptData -> Data #
fromPlutusData :: Data -> ScriptData #
toAlonzoData :: Era ledgerera => HashableScriptData -> Data ledgerera #
fromAlonzoData :: Data ledgerera -> HashableScriptData #
fromAlonzoPrices :: Prices -> ExecutionUnitPrices #
toAlonzoExUnits :: ExecutionUnits -> ExUnits #
fromAlonzoExUnits :: ExUnits -> ExecutionUnits #
toAlonzoRdmrPtr :: ScriptWitnessIndex -> RdmrPtr #
fromAlonzoRdmrPtr :: RdmrPtr -> ScriptWitnessIndex #
scriptDataToJsonDetailedSchema :: HashableScriptData -> Value #
calculateExecutionUnitsLovelace :: Prices -> ExecutionUnits -> Maybe Lovelace #
Reference Scripts
data ReferenceScript era where #
Constructors
ReferenceScript :: forall era. BabbageEraOnwards era -> ScriptInAnyLang -> ReferenceScript era | |
ReferenceScriptNone :: forall era. ReferenceScript era |
Instances
Eq (ReferenceScript era) | |
Defined in Cardano.Api.Script Methods (==) :: ReferenceScript era -> ReferenceScript era -> Bool Source # (/=) :: ReferenceScript era -> ReferenceScript era -> Bool Source # | |
Show (ReferenceScript era) | |
Defined in Cardano.Api.Script | |
IsCardanoEra era => FromJSON (ReferenceScript era) | |
Defined in Cardano.Api.Script Methods parseJSON :: Value -> Parser (ReferenceScript era) parseJSONList :: Value -> Parser [ReferenceScript era] omittedField :: Maybe (ReferenceScript era) | |
IsCardanoEra era => ToJSON (ReferenceScript era) | |
Defined in Cardano.Api.Script Methods toJSON :: ReferenceScript era -> Value toEncoding :: ReferenceScript era -> Encoding toJSONList :: [ReferenceScript era] -> Value toEncodingList :: [ReferenceScript era] -> Encoding omitField :: ReferenceScript era -> Bool |
refScriptToShelleyScript :: ShelleyBasedEra era -> ReferenceScript era -> StrictMaybe (Script (ShelleyLedgerEra era)) #
Certificates
data Certificate era where #
Constructors
ShelleyRelatedCertificate :: forall era. ShelleyToBabbageEra era -> ShelleyTxCert (ShelleyLedgerEra era) -> Certificate era | |
ConwayCertificate :: forall era. ConwayEraOnwards era -> ConwayTxCert (ShelleyLedgerEra era) -> Certificate era |
Instances
toShelleyCertificate :: Certificate era -> TxCert (ShelleyLedgerEra era) #
fromShelleyCertificate :: ShelleyBasedEra era -> TxCert (ShelleyLedgerEra era) -> Certificate era #
toShelleyPoolParams :: StakePoolParameters -> PoolParams StandardCrypto #
Operational certificates
data OperationalCertificate #
Constructors
OperationalCertificate !(OCert StandardCrypto) !(VerificationKey StakePoolKey) |
Instances
data OperationalCertificateIssueCounter #
Constructors
OperationalCertificateIssueCounter | |
Fields |
Instances
data OperationalCertIssueError #
Constructors
OperationalCertKeyMismatch (VerificationKey StakePoolKey) (VerificationKey StakePoolKey) |
Instances
Show OperationalCertIssueError | |
Defined in Cardano.Api.OperationalCertificate | |
Error OperationalCertIssueError | |
Defined in Cardano.Api.OperationalCertificate Methods prettyError :: OperationalCertIssueError -> Doc ann # |
Stake Pool
data StakePoolMetadata #
Constructors
StakePoolMetadata !Text !Text !Text !Text |
Instances
stakePoolName :: StakePoolMetadata -> Text #
stakePoolDescription :: StakePoolMetadata -> Text #
stakePoolTicker :: StakePoolMetadata -> Text #
stakePoolHomepage :: StakePoolMetadata -> Text #
data StakePoolMetadataReference #
Constructors
StakePoolMetadataReference Text (Hash StakePoolMetadata) |
Instances
Eq StakePoolMetadataReference | |
Defined in Cardano.Api.Certificate Methods (==) :: StakePoolMetadataReference -> StakePoolMetadataReference -> Bool Source # (/=) :: StakePoolMetadataReference -> StakePoolMetadataReference -> Bool Source # | |
Show StakePoolMetadataReference | |
Defined in Cardano.Api.Certificate |
stakePoolMetadataURL :: StakePoolMetadataReference -> Text #
data StakePoolParameters #
Constructors
StakePoolParameters PoolId (Hash VrfKey) Lovelace Rational StakeAddress Lovelace [Hash StakeKey] [StakePoolRelay] (Maybe StakePoolMetadataReference) |
Instances
Eq StakePoolParameters | |
Defined in Cardano.Api.Certificate Methods (==) :: StakePoolParameters -> StakePoolParameters -> Bool Source # (/=) :: StakePoolParameters -> StakePoolParameters -> Bool Source # | |
Show StakePoolParameters | |
Defined in Cardano.Api.Certificate |
stakePoolOwners :: StakePoolParameters -> [Hash StakeKey] #
data StakePoolRelay #
Constructors
StakePoolRelayIp (Maybe IPv4) (Maybe IPv6) (Maybe PortNumber) | |
StakePoolRelayDnsARecord ByteString (Maybe PortNumber) | |
StakePoolRelayDnsSrvRecord ByteString |
Instances
Eq StakePoolRelay | |
Defined in Cardano.Api.Certificate Methods (==) :: StakePoolRelay -> StakePoolRelay -> Bool Source # (/=) :: StakePoolRelay -> StakePoolRelay -> Bool Source # | |
Show StakePoolRelay | |
Defined in Cardano.Api.Certificate |
Instances
Enum EpochNo | |
Defined in Cardano.Slotting.Slot Methods 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 | |
FromJSON EpochNo | |
Defined in Cardano.Slotting.Slot | |
ToJSON EpochNo | |
Defined in Cardano.Slotting.Slot Methods toEncoding :: EpochNo -> Encoding toJSONList :: [EpochNo] -> Value toEncodingList :: [EpochNo] -> Encoding | |
NoThunks EpochNo | |
DecCBOR EpochNo | |
ToCBOR EpochNo | |
Defined in Cardano.Slotting.Slot | |
FromCBOR EpochNo | |
Serialise EpochNo | |
Defined in Cardano.Slotting.Slot | |
type Rep EpochNo | |
Defined in Cardano.Slotting.Slot |
Governance Actions
createAnchor :: Url -> ByteString -> Anchor StandardCrypto #
createPreviousGovernanceActionId :: forall (r :: GovActionPurpose). TxId -> Word32 -> PrevGovActionId r StandardCrypto #
createGovernanceActionId :: TxId -> Word32 -> GovActionId StandardCrypto #
DRep
newtype DRepMetadata #
Constructors
DRepMetadata ByteString |
Instances
data DRepMetadataReference #
Constructors
DRepMetadataReference Text (Hash DRepMetadata) |
Instances
Eq DRepMetadataReference | |
Defined in Cardano.Api.Certificate Methods (==) :: DRepMetadataReference -> DRepMetadataReference -> Bool Source # (/=) :: DRepMetadataReference -> DRepMetadataReference -> Bool Source # | |
Show DRepMetadataReference | |
Defined in Cardano.Api.Certificate |
Stake pool operator's keys
data StakePoolKey #
Instances
type PoolId = Hash StakePoolKey #
KES keys
Instances
Constructors
KESPeriod | |
Fields
|
Instances
Eq KESPeriod | |
Ord KESPeriod | |
Defined in Cardano.Protocol.TPraos.OCert | |
Show KESPeriod | |
Generic KESPeriod | |
EncCBOR KESPeriod | |
Defined in Cardano.Protocol.TPraos.OCert Methods encCBOR :: KESPeriod -> Encoding encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy KESPeriod -> Size encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [KESPeriod] -> Size | |
NoThunks KESPeriod | |
DecCBOR KESPeriod | |
ToCBOR KESPeriod | |
Defined in Cardano.Protocol.TPraos.OCert | |
FromCBOR KESPeriod | |
type Rep KESPeriod | |
Defined in Cardano.Protocol.TPraos.OCert |
VRF keys
Instances
Low level protocol interaction with a Cardano node
data LocalNodeConnectInfo #
Constructors
LocalNodeConnectInfo ConsensusModeParams NetworkId SocketPath |
data LocalNodeClientProtocols block point tip slot tx txid txerr (query :: Type -> Type) (m :: Type -> Type) #
Constructors
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 = (ledgerera :: Type) | ledgerera -> era where ... #
Equations
ShelleyLedgerEra ShelleyEra = StandardShelley | |
ShelleyLedgerEra AllegraEra = StandardAllegra | |
ShelleyLedgerEra MaryEra = StandardMary | |
ShelleyLedgerEra AlonzoEra = StandardAlonzo | |
ShelleyLedgerEra BabbageEra = StandardBabbage | |
ShelleyLedgerEra ConwayEra = StandardConway |
Local State Query
newtype DebugLedgerState era #
Constructors
DebugLedgerState | |
Fields
|
Instances
IsShelleyBasedEra era => ToJSON (DebugLedgerState era) | |
Defined in Cardano.Api.Query.Types Methods toJSON :: DebugLedgerState era -> Value toEncoding :: DebugLedgerState era -> Encoding toJSONList :: [DebugLedgerState era] -> Value toEncodingList :: [DebugLedgerState era] -> Encoding omitField :: DebugLedgerState era -> Bool | |
IsShelleyBasedEra era => FromCBOR (DebugLedgerState era) | |
Defined in Cardano.Api.Query.Types |
decodeDebugLedgerState :: FromCBOR (DebugLedgerState era) => SerialisedDebugLedgerState era -> Either ByteString (DebugLedgerState era) #
newtype ProtocolState era #
Constructors
ProtocolState (Serialised (ChainDepState (ConsensusProtocol era))) |
decodeProtocolState :: FromCBOR (ChainDepState (ConsensusProtocol era)) => ProtocolState era -> Either (ByteString, DecoderError) (ChainDepState (ConsensusProtocol era)) #
newtype SerialisedDebugLedgerState era #
Constructors
SerialisedDebugLedgerState (Serialised (NewEpochState (ShelleyLedgerEra era))) |
newtype CurrentEpochState era #
Constructors
CurrentEpochState (EpochState (ShelleyLedgerEra era)) |
newtype SerialisedCurrentEpochState era #
Constructors
SerialisedCurrentEpochState (Serialised (EpochState (ShelleyLedgerEra era))) |
decodeCurrentEpochState :: ShelleyBasedEra era -> SerialisedCurrentEpochState era -> Either DecoderError (CurrentEpochState era) #
Constructors
PoolState (PState (ShelleyLedgerEra era)) |
newtype SerialisedPoolState era #
Constructors
SerialisedPoolState (Serialised (PState (ShelleyLedgerEra era))) |
decodePoolState :: (Era (ShelleyLedgerEra era), DecCBOR (PState (ShelleyLedgerEra era))) => SerialisedPoolState era -> Either DecoderError (PoolState era) #
newtype PoolDistribution era #
Constructors
PoolDistribution | |
Fields
|
newtype SerialisedPoolDistribution era #
Constructors
SerialisedPoolDistribution (Serialised (PoolDistr (EraCrypto (ShelleyLedgerEra era)))) |
decodePoolDistribution :: Crypto (EraCrypto (ShelleyLedgerEra era)) => ShelleyBasedEra era -> SerialisedPoolDistribution era -> Either DecoderError (PoolDistribution era) #
newtype StakeSnapshot era #
Constructors
StakeSnapshot (StakeSnapshots (EraCrypto (ShelleyLedgerEra era))) |
newtype SerialisedStakeSnapshots era #
Constructors
SerialisedStakeSnapshots (Serialised (StakeSnapshots (EraCrypto (ShelleyLedgerEra era)))) |
decodeStakeSnapshot :: FromCBOR (StakeSnapshots (EraCrypto (ShelleyLedgerEra era))) => SerialisedStakeSnapshots era -> Either DecoderError (StakeSnapshot era) #
Instances
Eq (UTxO era) | |
Show (UTxO era) | |
(IsShelleyBasedEra era, FromJSON (TxOut CtxUTxO era)) => FromJSON (UTxO era) | |
Defined in Cardano.Api.Query Methods parseJSON :: Value -> Parser (UTxO era) parseJSONList :: Value -> Parser [UTxO era] omittedField :: Maybe (UTxO era) | |
IsCardanoEra era => ToJSON (UTxO era) | |
Defined in Cardano.Api.Query Methods toEncoding :: UTxO era -> Encoding toJSONList :: [UTxO era] -> Value toEncodingList :: [UTxO era] -> Encoding |
data AcquiringFailure #
Constructors
AFPointTooOld | |
AFPointNotOnChain |
Instances
Eq AcquiringFailure | |
Defined in Cardano.Api.IPC Methods (==) :: AcquiringFailure -> AcquiringFailure -> Bool Source # (/=) :: AcquiringFailure -> AcquiringFailure -> Bool Source # | |
Show AcquiringFailure | |
Defined in Cardano.Api.IPC |
newtype SystemStart #
Constructors
SystemStart | |
Fields
|
Instances
Governance
data GovernanceAction era #
Constructors
MotionOfNoConfidence (StrictMaybe (PrevGovActionId 'CommitteePurpose StandardCrypto)) | |
ProposeNewConstitution (StrictMaybe (PrevGovActionId 'ConstitutionPurpose StandardCrypto)) (Anchor StandardCrypto) | |
ProposeNewCommittee (StrictMaybe (PrevGovActionId 'CommitteePurpose StandardCrypto)) [Hash CommitteeColdKey] (Map (Hash CommitteeColdKey) EpochNo) Rational | |
InfoAct | |
TreasuryWithdrawal [(Network, StakeCredential, Lovelace)] | |
InitiateHardfork (StrictMaybe (PrevGovActionId 'HardForkPurpose StandardCrypto)) ProtVer | |
UpdatePParams (StrictMaybe (PrevGovActionId 'PParamUpdatePurpose StandardCrypto)) (PParamsUpdate (ShelleyLedgerEra era)) |
newtype GovernanceActionId era #
Constructors
GovernanceActionId | |
Fields
|
Instances
Constructors
Proposal | |
Fields
|
Instances
IsShelleyBasedEra era => Eq (Proposal era) | |
IsShelleyBasedEra era => Show (Proposal era) | |
HasTypeProxy era => HasTypeProxy (Proposal era) | |
IsShelleyBasedEra era => ToCBOR (Proposal era) | |
IsShelleyBasedEra era => FromCBOR (Proposal era) | |
IsShelleyBasedEra era => HasTextEnvelope (Proposal era) | |
Defined in Cardano.Api.Governance.Actions.ProposalProcedure Methods textEnvelopeType :: AsType (Proposal era) -> TextEnvelopeType # textEnvelopeDefaultDescr :: Proposal era -> TextEnvelopeDescr # | |
IsShelleyBasedEra era => SerialiseAsCBOR (Proposal era) | |
Defined in Cardano.Api.Governance.Actions.ProposalProcedure Methods serialiseToCBOR :: Proposal era -> ByteString # deserialiseFromCBOR :: AsType (Proposal era) -> ByteString -> Either DecoderError (Proposal era) # | |
data AsType (Proposal era) | |
newtype VotingProcedure era #
Constructors
VotingProcedure | |
Fields
|
Instances
newtype VotingProcedures era #
Constructors
VotingProcedures | |
Fields
|
Instances
data GovernancePoll #
Constructors
GovernancePoll | |
Fields
|
Instances
data GovernancePollAnswer #
Constructors
GovernancePollAnswer | |
Fields |
Instances
Eq GovernancePollAnswer | |
Defined in Cardano.Api.Governance.Poll Methods (==) :: GovernancePollAnswer -> GovernancePollAnswer -> Bool Source # (/=) :: GovernancePollAnswer -> GovernancePollAnswer -> Bool Source # | |
Show GovernancePollAnswer | |
Defined in Cardano.Api.Governance.Poll | |
HasTypeProxy GovernancePollAnswer | |
Defined in Cardano.Api.Governance.Poll Associated Types data AsType GovernancePollAnswer # Methods proxyToAsType :: Proxy GovernancePollAnswer -> AsType GovernancePollAnswer # | |
SerialiseAsCBOR GovernancePollAnswer | |
Defined in Cardano.Api.Governance.Poll Methods serialiseToCBOR :: GovernancePollAnswer -> ByteString # deserialiseFromCBOR :: AsType GovernancePollAnswer -> ByteString -> Either DecoderError GovernancePollAnswer # | |
AsTxMetadata GovernancePollAnswer | |
Defined in Cardano.Api.Governance.Poll Methods | |
data AsType GovernancePollAnswer | |
Defined in Cardano.Api.Governance.Poll |
data GovernancePollError #
Constructors
ErrGovernancePollMismatch GovernancePollMismatchError | |
ErrGovernancePollNoAnswer | |
ErrGovernancePollUnauthenticated | |
ErrGovernancePollMalformedAnswer DecoderError | |
ErrGovernancePollInvalidAnswer GovernancePollInvalidAnswerError |
Instances
Show GovernancePollError | |
Defined in Cardano.Api.Governance.Poll |
Constructors
Voter (Voter (EraCrypto (ShelleyLedgerEra era))) |
Instances
Eq (Voter era) | |
Ord (Voter era) | |
Show (Voter era) | |
IsShelleyBasedEra era => ToCBOR (Voter era) | |
IsShelleyBasedEra era => FromCBOR (Voter era) | |
createProposalProcedure :: ShelleyBasedEra era -> Network -> Lovelace -> Hash StakeKey -> GovernanceAction era -> Anchor StandardCrypto -> Proposal era #
createVotingProcedure :: ConwayEraOnwards era -> Vote -> Maybe (Url, Text) -> VotingProcedure era #
renderGovernancePollError :: GovernancePollError -> Text #
fromProposalProcedure :: ShelleyBasedEra era -> Proposal era -> (Lovelace, Hash StakeKey, GovernanceAction era) #
verifyPollAnswer :: GovernancePoll -> InAnyShelleyBasedEra Tx -> Either GovernancePollError [Hash PaymentKey] #
Various calculations
data LeadershipError #
Constructors
Instances
Show LeadershipError | |
Defined in Cardano.Api.LedgerState | |
Error LeadershipError | |
Defined in Cardano.Api.LedgerState Methods prettyError :: LeadershipError -> Doc ann # |
currentEpochEligibleLeadershipSlots :: ShelleyBasedEra era -> ShelleyGenesis StandardCrypto -> EpochInfo (Either Text) -> PParams (ShelleyLedgerEra era) -> ProtocolState era -> PoolId -> SigningKey VrfKey -> SerialisedPoolDistribution era -> EpochNo -> Either LeadershipError (Set SlotNo) #
nextEpochEligibleLeadershipSlots :: ShelleyBasedEra era -> ShelleyGenesis StandardCrypto -> SerialisedCurrentEpochState era -> ProtocolState era -> PoolId -> SigningKey VrfKey -> PParams (ShelleyLedgerEra era) -> EpochInfo (Either Text) -> (ChainTip, EpochNo) -> Either LeadershipError (Set SlotNo) #
Conversions
shelleyPayAddrToPlutusPubKHash :: Address ShelleyAddr -> Maybe PubKeyHash #
toConsensusGenTx :: CardanoBlock StandardCrypto ~ block => TxInMode -> GenTx block #
fromAlonzoCostModels :: CostModels -> Map AnyPlutusScriptVersion CostModel #
toLedgerNonce :: Maybe PraosNonce -> Nonce #
toShelleyNetwork :: NetworkId -> Network #
fromShelleyPoolParams :: PoolParams StandardCrypto -> StakePoolParameters #
fromLedgerPParamsUpdate :: ShelleyBasedEra era -> PParamsUpdate (ShelleyLedgerEra era) -> ProtocolParametersUpdate #
singletonVotingProcedures :: ConwayEraOnwards era -> Voter (EraCrypto (ShelleyLedgerEra era)) -> GovActionId (EraCrypto (ShelleyLedgerEra era)) -> VotingProcedure (ShelleyLedgerEra era) -> VotingProcedures era #
unsafeMergeVotingProcedures :: VotingProcedures era -> VotingProcedures era -> VotingProcedures era #