Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Hydra.Cardano.Api.Prelude
Synopsis
- class Error e where
- prettyError :: e -> Doc ann
- data Doc ann
- class Pretty a where
- pretty :: a -> Doc ann
- prettyList :: [a] -> Doc ann
- 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 Block era where
- ByronBlock :: ByronBlock -> Block ByronEra
- ShelleyBlock :: forall era. ShelleyBasedEra era -> ShelleyBlock (ConsensusProtocol era) (ShelleyLedgerEra era) -> Block era
- class Monad m => MonadIO (m :: Type -> Type) where
- newtype File content (direction :: FileDirection) = File {}
- newtype ExceptT e (m :: Type -> Type) a = ExceptT (m (Either e a))
- type Except e = ExceptT e Identity
- class Monad m => MonadError e (m :: Type -> Type) | m -> e where
- throwError :: e -> m a
- catchError :: m a -> (e -> m a) -> m a
- class (forall (m :: Type -> Type). Monad m => Monad (t m)) => MonadTrans (t :: (Type -> Type) -> Type -> Type) where
- data AddressInEra era where
- AddressInEra :: forall addrtype era. AddressTypeInEra addrtype era -> Address addrtype -> AddressInEra era
- data AddressTypeInEra addrtype era where
- ByronAddressInAnyEra :: forall era. AddressTypeInEra ByronAddr era
- ShelleyAddressInEra :: forall era. ShelleyBasedEra era -> AddressTypeInEra ShelleyAddr era
- data BalancedTxBody era = BalancedTxBody (TxBodyContent BuildTx era) (TxBody era) (TxOut CtxTx era) Coin
- data KeyWitness era
- data PlutusScript lang
- data Script lang where
- SimpleScript :: !SimpleScript -> Script SimpleScript'
- PlutusScript :: forall lang. !(PlutusScriptVersion lang) -> !(PlutusScript lang) -> Script lang
- data ScriptInEra era where
- ScriptInEra :: forall lang era. ScriptLanguageInEra lang era -> Script lang -> ScriptInEra era
- data ScriptLanguage lang where
- SimpleScriptLanguage :: ScriptLanguage SimpleScript'
- PlutusScriptLanguage :: forall lang. PlutusScriptVersion lang -> ScriptLanguage lang
- data ScriptWitness witctx era where
- SimpleScriptWitness :: forall era witctx. ScriptLanguageInEra SimpleScript' era -> SimpleScriptOrReferenceInput SimpleScript' -> ScriptWitness witctx era
- PlutusScriptWitness :: forall lang era witctx. ScriptLanguageInEra lang era -> PlutusScriptVersion lang -> PlutusScriptOrReferenceInput lang -> ScriptDatum witctx -> ScriptRedeemer -> ExecutionUnits -> ScriptWitness witctx era
- data Tx era where
- pattern Tx :: TxBody era -> [KeyWitness era] -> Tx era
- data TxAuxScripts era where
- TxAuxScriptsNone :: forall era. TxAuxScripts era
- TxAuxScripts :: forall era. AllegraEraOnwards era -> [ScriptInEra era] -> TxAuxScripts era
- 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
- pattern TxBody :: TxBodyContent ViewTx era -> TxBody era
- data TxBodyContent build era = TxBodyContent {
- txIns :: TxIns build era
- txInsCollateral :: TxInsCollateral era
- txInsReference :: TxInsReference build era
- txOuts :: [TxOut CtxTx era]
- txTotalCollateral :: TxTotalCollateral era
- txReturnCollateral :: TxReturnCollateral CtxTx era
- txFee :: TxFee era
- txValidityLowerBound :: TxValidityLowerBound era
- txValidityUpperBound :: TxValidityUpperBound era
- txMetadata :: TxMetadataInEra era
- txAuxScripts :: TxAuxScripts era
- txExtraKeyWits :: TxExtraKeyWitnesses era
- txProtocolParams :: BuildTxWith build (Maybe (LedgerProtocolParameters era))
- txWithdrawals :: TxWithdrawals build era
- txCertificates :: TxCertificates build era
- txUpdateProposal :: TxUpdateProposal era
- txMintValue :: TxMintValue build era
- txScriptValidity :: TxScriptValidity era
- txProposalProcedures :: Maybe (Featured ConwayEraOnwards era (TxProposalProcedures build era))
- txVotingProcedures :: Maybe (Featured ConwayEraOnwards era (TxVotingProcedures build era))
- txCurrentTreasuryValue :: Maybe (Featured ConwayEraOnwards era Coin)
- txTreasuryDonation :: Maybe (Featured ConwayEraOnwards era Coin)
- data TxBodyScriptData era where
- TxBodyNoScriptData :: forall era. TxBodyScriptData era
- TxBodyScriptData :: forall era. AlonzoEraOnwardsConstraints era => AlonzoEraOnwards era -> TxDats (ShelleyLedgerEra era) -> Redeemers (ShelleyLedgerEra era) -> TxBodyScriptData era
- data TxExtraKeyWitnesses era where
- TxExtraKeyWitnessesNone :: forall era. TxExtraKeyWitnesses era
- TxExtraKeyWitnesses :: forall era. AlonzoEraOnwards era -> [Hash PaymentKey] -> TxExtraKeyWitnesses era
- data TxFee era where
- TxFeeExplicit :: forall era. ShelleyBasedEra era -> Coin -> TxFee era
- type TxIns build era = [(TxIn, BuildTxWith build (Witness WitCtxTxIn era))]
- data TxInsCollateral era where
- TxInsCollateralNone :: forall era. TxInsCollateral era
- TxInsCollateral :: forall era. AlonzoEraOnwards era -> [TxIn] -> TxInsCollateral era
- data TxInsReference build era where
- TxInsReferenceNone :: forall build era. TxInsReference build era
- TxInsReference :: forall era build. BabbageEraOnwards era -> [TxIn] -> TxInsReference build era
- data TxMetadataInEra era where
- TxMetadataNone :: forall era. TxMetadataInEra era
- TxMetadataInEra :: forall era. ShelleyBasedEra era -> TxMetadata -> TxMetadataInEra era
- data TxMintValue build era where
- TxMintNone :: forall build era. TxMintValue build era
- TxMintValue :: forall era build. MaryEraOnwards era -> Value -> BuildTxWith build (Map PolicyId (ScriptWitness WitCtxMint era)) -> TxMintValue build era
- data TxOut ctx era = TxOut (AddressInEra era) (TxOutValue era) (TxOutDatum ctx era) (ReferenceScript era)
- data TxOutDatum ctx era where
- TxOutDatumNone :: forall ctx era. TxOutDatum ctx era
- TxOutDatumHash :: forall era ctx. AlonzoEraOnwards era -> Hash ScriptData -> TxOutDatum ctx era
- TxOutDatumInline :: forall era ctx. BabbageEraOnwards era -> HashableScriptData -> TxOutDatum ctx era
- pattern TxOutDatumInTx :: AlonzoEraOnwards era -> HashableScriptData -> TxOutDatum CtxTx era
- data TxScriptValidity era where
- TxScriptValidityNone :: forall era. TxScriptValidity era
- TxScriptValidity :: forall era. AlonzoEraOnwards era -> ScriptValidity -> TxScriptValidity era
- data TxValidityLowerBound era where
- TxValidityNoLowerBound :: forall era. TxValidityLowerBound era
- TxValidityLowerBound :: forall era. AllegraEraOnwards era -> SlotNo -> TxValidityLowerBound era
- data TxValidityUpperBound era where
- TxValidityUpperBound :: forall era. ShelleyBasedEra era -> Maybe SlotNo -> TxValidityUpperBound era
- data Witness witctx era where
- KeyWitness :: forall witctx era. KeyWitnessInCtx witctx -> Witness witctx era
- ScriptWitness :: forall witctx era. ScriptWitnessInCtx witctx -> ScriptWitness witctx era -> Witness witctx era
- data Address addrtype
- data family Hash keyrole
- data family SigningKey keyrole
- data family VerificationKey keyrole
- data BlockHeader = BlockHeader !SlotNo !(Hash BlockHeader) !BlockNo
- data ChainPoint
- data CtxTx
- data CtxUTxO
- data ExecutionUnits = ExecutionUnits {}
- data NetworkId
- newtype PolicyId = PolicyId {}
- data ScriptData
- data ScriptDatum witctx where
- newtype ScriptHash = ScriptHash (ScriptHash StandardCrypto)
- newtype TxId = TxId (Hash StandardCrypto EraIndependentTxBody)
- data TxIn = TxIn TxId TxIx
- data TxOutValue era where
- TxOutValueByron :: forall era. Coin -> TxOutValue era
- TxOutValueShelleyBased :: forall era. (Eq (Value (ShelleyLedgerEra era)), Show (Value (ShelleyLedgerEra era))) => ShelleyBasedEra era -> Value (ShelleyLedgerEra era) -> TxOutValue era
- data Value
- class FromJSON a
- class ToJSON a
- class Typeable a => FromCBOR a
- class Typeable a => ToCBOR a
- data PaymentKey
- data ConwayEra
- data AddressAny
- data ByronAddr
- data PaymentCredential
- class HasTypeProxy addr => SerialiseAddress addr where
- serialiseAddress :: addr -> Text
- deserialiseAddress :: AsType addr -> Text -> Maybe addr
- data ShelleyAddr
- data StakeAddress
- newtype StakeAddressPointer = StakeAddressPointer {
- unStakeAddressPointer :: Ptr
- data StakeAddressReference
- data StakeCredential
- newtype AnchorDataHash = AnchorDataHash {
- unAnchorDataHash :: SafeHash StandardCrypto AnchorData
- newtype AnchorUrl = AnchorUrl {
- unAnchorUrl :: Url
- data BlockInMode where
- BlockInMode :: forall era. CardanoEra era -> Block era -> BlockInMode
- data ChainTip
- data Certificate era where
- ShelleyRelatedCertificate :: forall era. ShelleyToBabbageEra era -> ShelleyTxCert (ShelleyLedgerEra era) -> Certificate era
- ConwayCertificate :: forall era. ConwayEraOnwards era -> ConwayTxCert (ShelleyLedgerEra era) -> Certificate era
- data CommitteeColdkeyResignationRequirements era where
- CommitteeColdkeyResignationRequirements :: forall era. ConwayEraOnwards era -> Credential 'ColdCommitteeRole (EraCrypto (ShelleyLedgerEra era)) -> Maybe (Anchor (EraCrypto (ShelleyLedgerEra era))) -> CommitteeColdkeyResignationRequirements era
- data CommitteeHotKeyAuthorizationRequirements era where
- CommitteeHotKeyAuthorizationRequirements :: forall era. ConwayEraOnwards era -> Credential 'ColdCommitteeRole (EraCrypto (ShelleyLedgerEra era)) -> Credential 'HotCommitteeRole (EraCrypto (ShelleyLedgerEra era)) -> CommitteeHotKeyAuthorizationRequirements era
- data DRepMetadataReference
- data DRepRegistrationRequirements era where
- DRepRegistrationRequirements :: forall era. ConwayEraOnwards era -> Credential 'DRepRole (EraCrypto (ShelleyLedgerEra era)) -> Coin -> DRepRegistrationRequirements era
- data DRepUnregistrationRequirements era where
- DRepUnregistrationRequirements :: forall era. ConwayEraOnwards era -> Credential 'DRepRole (EraCrypto (ShelleyLedgerEra era)) -> Coin -> DRepUnregistrationRequirements era
- data DRepUpdateRequirements era where
- DRepUpdateRequirements :: forall era. ConwayEraOnwards era -> Credential 'DRepRole (EraCrypto (ShelleyLedgerEra era)) -> DRepUpdateRequirements era
- data GenesisKeyDelegationRequirements ere where
- GenesisKeyDelegationRequirements :: forall ere. ShelleyToBabbageEra ere -> Hash GenesisKey -> Hash GenesisDelegateKey -> Hash VrfKey -> GenesisKeyDelegationRequirements ere
- data MirCertificateRequirements era where
- MirCertificateRequirements :: forall era. ShelleyToBabbageEra era -> MIRPot -> MIRTarget (EraCrypto (ShelleyLedgerEra era)) -> MirCertificateRequirements era
- data StakeAddressRequirements era where
- StakeAddrRegistrationConway :: forall era. ConwayEraOnwards era -> Coin -> StakeCredential -> StakeAddressRequirements era
- StakeAddrRegistrationPreConway :: forall era. ShelleyToBabbageEra era -> StakeCredential -> StakeAddressRequirements era
- data StakeDelegationRequirements era where
- StakeDelegationRequirementsConwayOnwards :: forall era. ConwayEraOnwards era -> StakeCredential -> Delegatee (EraCrypto (ShelleyLedgerEra era)) -> StakeDelegationRequirements era
- StakeDelegationRequirementsPreConway :: forall era. ShelleyToBabbageEra era -> StakeCredential -> PoolId -> StakeDelegationRequirements era
- data StakePoolMetadataReference
- data StakePoolParameters
- data StakePoolRegistrationRequirements era where
- StakePoolRegistrationRequirementsConwayOnwards :: forall era. ConwayEraOnwards era -> PoolParams (EraCrypto (ShelleyLedgerEra era)) -> StakePoolRegistrationRequirements era
- StakePoolRegistrationRequirementsPreConway :: forall era. ShelleyToBabbageEra era -> PoolParams (EraCrypto (ShelleyLedgerEra era)) -> StakePoolRegistrationRequirements era
- data StakePoolRelay
- data StakePoolRetirementRequirements era where
- StakePoolRetirementRequirementsConwayOnwards :: forall era. ConwayEraOnwards era -> PoolId -> EpochNo -> StakePoolRetirementRequirements era
- StakePoolRetirementRequirementsPreConway :: forall era. ShelleyToBabbageEra era -> PoolId -> EpochNo -> StakePoolRetirementRequirements era
- newtype ScriptLockedTxInsError = ScriptLockedTxIns [TxIn]
- data TxInsExistError
- = TxInsDoNotExist [TxIn]
- | EmptyUTxO
- data QueryConvenienceError
- newtype TxCurrentTreasuryValue = TxCurrentTreasuryValue {}
- data DRepMetadata
- data InputDecodeError
- data InputFormat a where
- InputFormatBech32 :: forall a. SerialiseAsBech32 a => InputFormat a
- InputFormatHex :: forall a. SerialiseAsRawBytes a => InputFormat a
- InputFormatTextEnvelope :: forall a. HasTextEnvelope a => InputFormat a
- data SomeAddressVerificationKey
- = AByronVerificationKey (VerificationKey ByronKey)
- | APaymentVerificationKey (VerificationKey PaymentKey)
- | APaymentExtendedVerificationKey (VerificationKey PaymentExtendedKey)
- | AGenesisUTxOVerificationKey (VerificationKey GenesisUTxOKey)
- | AGenesisExtendedVerificationKey (VerificationKey GenesisExtendedKey)
- | AGenesisDelegateExtendedVerificationKey (VerificationKey GenesisDelegateExtendedKey)
- | AKesVerificationKey (VerificationKey KesKey)
- | AVrfVerificationKey (VerificationKey VrfKey)
- | AStakeVerificationKey (VerificationKey StakeKey)
- | AStakeExtendedVerificationKey (VerificationKey StakeExtendedKey)
- | ADRepVerificationKey (VerificationKey DRepKey)
- | ADRepExtendedVerificationKey (VerificationKey DRepExtendedKey)
- | ACommitteeColdVerificationKey (VerificationKey CommitteeColdKey)
- | ACommitteeColdExtendedVerificationKey (VerificationKey CommitteeColdExtendedKey)
- | ACommitteeHotVerificationKey (VerificationKey CommitteeHotKey)
- | ACommitteeHotExtendedVerificationKey (VerificationKey CommitteeHotExtendedKey)
- data AllegraEraOnwards era where
- class IsAllegraBasedEra era where
- allegraBasedEra :: AllegraEraOnwards era
- data AlonzoEraOnwards era where
- class IsAlonzoBasedEra era where
- alonzoBasedEra :: AlonzoEraOnwards era
- data BabbageEraOnwards era where
- class IsBabbageBasedEra era where
- babbageBasedEra :: BabbageEraOnwards era
- data ByronToAlonzoEra era where
- data ConwayEraOnwards era where
- class IsConwayBasedEra era where
- conwayBasedEra :: ConwayEraOnwards era
- class IsMaryBasedEra era where
- maryBasedEra :: MaryEraOnwards era
- data MaryEraOnwards era where
- data AnyShelleyBasedEra where
- AnyShelleyBasedEra :: forall era. Typeable era => ShelleyBasedEra era -> AnyShelleyBasedEra
- data InAnyShelleyBasedEra (thing :: Type -> Type) where
- InAnyShelleyBasedEra :: forall era (thing :: Type -> Type). Typeable era => ShelleyBasedEra era -> thing era -> InAnyShelleyBasedEra thing
- class IsCardanoEra era => IsShelleyBasedEra era where
- shelleyBasedEra :: ShelleyBasedEra era
- data ShelleyBasedEra era where
- ShelleyBasedEraShelley :: ShelleyBasedEra ShelleyEra
- ShelleyBasedEraAllegra :: ShelleyBasedEra AllegraEra
- ShelleyBasedEraMary :: ShelleyBasedEra MaryEra
- ShelleyBasedEraAlonzo :: ShelleyBasedEra AlonzoEra
- ShelleyBasedEraBabbage :: ShelleyBasedEra BabbageEra
- ShelleyBasedEraConway :: ShelleyBasedEra ConwayEra
- data ShelleyEraOnly era where
- data ShelleyToAllegraEra era where
- data ShelleyToAlonzoEra era where
- data ShelleyToBabbageEra era where
- data ShelleyToMaryEra era where
- data AllegraEra
- data AlonzoEra
- data AnyCardanoEra where
- AnyCardanoEra :: forall era. Typeable era => CardanoEra era -> AnyCardanoEra
- data BabbageEra
- data ByronEra
- data CardanoEra era where
- data MaryEra
- data ShelleyEra
- class Eon (eon :: Type -> Type) where
- inEonForEra :: a -> (eon era -> a) -> CardanoEra era -> a
- data EraInEon (eon :: Type -> Type) where
- data InAnyCardanoEra (thing :: Type -> Type) where
- InAnyCardanoEra :: forall era (thing :: Type -> Type). Typeable era => CardanoEra era -> thing era -> InAnyCardanoEra thing
- class HasTypeProxy era => IsCardanoEra era where
- cardanoEra :: CardanoEra era
- class ToCardanoEra (eon :: Type -> Type) where
- toCardanoEra :: eon era -> CardanoEra era
- data FileError e
- data Featured (eon :: Type -> Type) era a where
- data AutoBalanceError era
- data FeeEstimationMode era
- newtype RequiredByronKeyWitnesses = RequiredByronKeyWitnesses {}
- newtype RequiredShelleyKeyWitnesses = RequiredShelleyKeyWitnesses {}
- data ResolvablePointers where
- ResolvablePointers :: forall era. (Era (ShelleyLedgerEra era), Show (PlutusPurpose AsIx (ShelleyLedgerEra era)), Show (PlutusPurpose AsItem (ShelleyLedgerEra era)), Show (PlutusScript (ShelleyLedgerEra era))) => ShelleyBasedEra era -> !(Map (PlutusPurpose AsIx (ShelleyLedgerEra era)) (PlutusPurpose AsItem (ShelleyLedgerEra era), Maybe (PlutusScriptBytes, Language), ScriptHash StandardCrypto)) -> ResolvablePointers
- data ScriptExecutionError
- = ScriptErrorMissingTxIn TxIn
- | ScriptErrorTxInWithoutDatum TxIn
- | ScriptErrorWrongDatum (Hash ScriptData)
- | ScriptErrorEvaluationFailed EvaluationError [Text]
- | ScriptErrorExecutionUnitsOverflow
- | ScriptErrorNotPlutusWitnessedTxIn ScriptWitnessIndex ScriptHash
- | ScriptErrorRedeemerPointsToUnknownScriptHash ScriptWitnessIndex
- | ScriptErrorMissingScript ScriptWitnessIndex ResolvablePointers
- | ScriptErrorMissingCostModel Language
- | (EraPlutusContext (ShelleyLedgerEra era), Show (ContextError (ShelleyLedgerEra era))) => ScriptErrorTranslationError (ContextError (ShelleyLedgerEra era))
- newtype TotalReferenceScriptsSize = TotalReferenceScriptsSize {}
- data TransactionValidityError era where
- TransactionValidityIntervalError :: forall era. PastHorizonException -> TransactionValidityError era
- TransactionValidityCostModelError :: forall era. Map AnyPlutusScriptVersion CostModel -> String -> TransactionValidityError era
- data TxBodyErrorAutoBalance era
- = TxBodyError TxBodyError
- | TxBodyScriptExecutionError [(ScriptWitnessIndex, ScriptExecutionError)]
- | TxBodyScriptBadScriptValidity
- | TxBodyErrorAdaBalanceNegative Coin
- | TxBodyErrorAdaBalanceTooSmall TxOutInAnyEra Coin Coin
- | TxBodyErrorByronEraNotSupported
- | TxBodyErrorMissingParamMinUTxO
- | TxBodyErrorValidityInterval (TransactionValidityError era)
- | TxBodyErrorMinUTxONotMet TxOutInAnyEra Coin
- | TxBodyErrorNonAdaAssetsUnbalanced Value
- | TxBodyErrorScriptWitnessIndexMissingFromExecUnitsMap ScriptWitnessIndex (Map ScriptWitnessIndex ExecutionUnits)
- data TxBodyError
- = TxBodyEmptyTxIns
- | TxBodyEmptyTxInsCollateral
- | TxBodyEmptyTxOuts
- | TxBodyOutputNegative !Quantity !TxOutInAnyEra
- | TxBodyOutputOverflow !Quantity !TxOutInAnyEra
- | TxBodyMetadataError ![(Word64, TxMetadataRangeError)]
- | TxBodyMintAdaError
- | TxBodyInIxOverflow !TxIn
- | TxBodyMissingProtocolParams
- | TxBodyProtocolParamsConversionError !ProtocolParametersConversionError
- data TxFeeEstimationError era
- = TxFeeEstimationTransactionTranslationError (TransactionValidityError era)
- | TxFeeEstimationScriptExecutionError (TxBodyErrorAutoBalance era)
- | TxFeeEstimationBalanceError (TxBodyErrorAutoBalance era)
- | TxFeeEstimationxBodyError TxBodyError
- | TxFeeEstimationFinalConstructionError TxBodyError
- | TxFeeEstimationOnlyMaryOnwardsSupportedError
- type AlonzoGenesisFile = File AlonzoGenesisConfig
- type ByronGenesisFile = File ByronGenesisConfig
- type ConwayGenesisFile = File ConwayGenesisConfig
- newtype GenesisHashAlonzo = GenesisHashAlonzo {
- unGenesisHashAlonzo :: Hash Blake2b_256 ByteString
- newtype GenesisHashConway = GenesisHashConway {
- unGenesisHashConway :: Hash Blake2b_256 ByteString
- newtype GenesisHashShelley = GenesisHashShelley {
- unGenesisHashShelley :: Hash Blake2b_256 ByteString
- data ShelleyConfig = ShelleyConfig {}
- type ShelleyGenesisFile = File ShelleyGenesisConfig
- data GenesisParameters era = GenesisParameters {
- protocolParamSystemStart :: UTCTime
- protocolParamNetworkId :: NetworkId
- protocolParamActiveSlotsCoefficient :: Rational
- protocolParamSecurity :: Int
- protocolParamEpochLength :: EpochSize
- protocolParamSlotLength :: NominalDiffTime
- protocolParamSlotsPerKESPeriod :: Int
- protocolParamMaxKESEvolutions :: Int
- protocolParamUpdateQuorum :: Int
- protocolParamMaxLovelaceSupply :: Coin
- protocolInitialUpdateableProtocolParameters :: PParams (ShelleyLedgerEra era)
- class Typeable t => HasTypeProxy t where
- data AsType t
- proxyToAsType :: Proxy t -> AsType t
- data family AsType t
- class AsTxMetadata a where
- asTxMetadata :: a -> TxMetadata
- data FromSomeType (c :: Type -> Constraint) b where
- FromSomeType :: forall (c :: Type -> Constraint) a b. c a => AsType a -> (a -> b) -> FromSomeType c b
- data FileDirection
- type SocketPath = File Socket 'InOut
- data LocalChainSyncClient block point tip (m :: Type -> Type)
- = NoLocalChainSyncClient
- | LocalChainSyncClientPipelined (ChainSyncClientPipelined block point tip m ())
- | LocalChainSyncClient (ChainSyncClient block point tip m ())
- data LocalNodeClientParams where
- LocalNodeClientParamsSingleBlock :: forall block. (ProtocolClient block, LedgerSupportsProtocol (ShelleyBlock (TPraos StandardCrypto) (ShelleyEra StandardCrypto))) => ProtocolClientInfoArgs block -> (NodeToClientVersion -> LocalNodeClientProtocolsForBlock block) -> LocalNodeClientParams
- LocalNodeClientParamsCardano :: forall block. (ProtocolClient block, CardanoHardForkConstraints (ConsensusCryptoForBlock block)) => ProtocolClientInfoArgs block -> (NodeToClientVersion -> LocalNodeClientProtocolsForBlock block) -> LocalNodeClientParams
- data LocalNodeClientProtocols block point tip slot tx txid txerr (query :: Type -> Type) (m :: Type -> Type) = LocalNodeClientProtocols {
- localChainSyncClient :: LocalChainSyncClient block point tip m
- localTxSubmissionClient :: Maybe (LocalTxSubmissionClient tx txerr m ())
- localStateQueryClient :: Maybe (LocalStateQueryClient block point query m ())
- localTxMonitoringClient :: Maybe (LocalTxMonitorClient txid tx slot m ())
- type LocalNodeClientProtocolsInMode = LocalNodeClientProtocols BlockInMode ChainPoint ChainTip SlotNo TxInMode TxIdInMode TxValidationErrorInCardanoMode QueryInMode IO
- data LocalNodeConnectInfo = LocalNodeConnectInfo {}
- data LocalTxMonitoringQuery
- data LocalTxMonitoringResult
- data LocalStateQueryExpr block point (query :: Type -> Type) r (m :: Type -> Type) a
- data UnsupportedNtcVersionError = UnsupportedNtcVersionError !MinNodeToClientVersion !NodeToClientVersion
- data TxIdInMode where
- TxIdInMode :: forall era. CardanoEra era -> TxId -> TxIdInMode
- data TxInMode where
- TxInMode :: forall era. ShelleyBasedEra era -> Tx era -> TxInMode
- TxInByronSpecial :: GenTx ByronBlock -> TxInMode
- data TxValidationErrorInCardanoMode where
- TxValidationErrorInCardanoMode :: forall era. TxValidationError era -> TxValidationErrorInCardanoMode
- TxValidationEraMismatch :: EraMismatch -> TxValidationErrorInCardanoMode
- data ByronKey
- data ByronKeyLegacy
- data CommitteeColdExtendedKey
- data CommitteeColdKey
- data CommitteeHotExtendedKey
- data CommitteeHotKey
- data DRepExtendedKey
- data DRepKey
- data GenesisDelegateExtendedKey
- data GenesisDelegateKey
- data GenesisExtendedKey
- data GenesisKey
- data GenesisUTxOKey
- data PaymentExtendedKey
- data StakeExtendedKey
- data StakeKey
- data AnyNewEpochState where
- AnyNewEpochState :: forall era. ShelleyBasedEra era -> NewEpochState (ShelleyLedgerEra era) -> AnyNewEpochState
- data ConditionResult
- data Env = Env {
- envLedgerConfig :: CardanoLedgerConfig StandardCrypto
- envConsensusConfig :: CardanoConsensusConfig StandardCrypto
- data FoldBlocksError
- data FoldStatus
- data GenesisConfig = GenesisCardano !NodeConfig !Config !GenesisHashShelley !(TransitionConfig (LatestKnownEra StandardCrypto))
- data GenesisConfigError
- = NEError !Text
- | NEByronConfig !FilePath !ConfigurationError
- | NEShelleyConfig !FilePath !Text
- | NEAlonzoConfig !FilePath !Text
- | NEConwayConfig !FilePath !Text
- | NECardanoConfig !Text
- data InitialLedgerStateError
- newtype LedgerState where
- LedgerState {
- clsState :: CardanoLedgerState StandardCrypto
- pattern LedgerStateAllegra :: LedgerState StandardAllegraBlock -> LedgerState
- pattern LedgerStateAlonzo :: LedgerState StandardAlonzoBlock -> LedgerState
- pattern LedgerStateBabbage :: LedgerState StandardBabbageBlock -> LedgerState
- pattern LedgerStateByron :: LedgerState ByronBlock -> LedgerState
- pattern LedgerStateConway :: LedgerState StandardConwayBlock -> LedgerState
- pattern LedgerStateMary :: LedgerState StandardMaryBlock -> LedgerState
- pattern LedgerStateShelley :: LedgerState StandardShelleyBlock -> LedgerState
- LedgerState {
- data LedgerStateError
- = ApplyBlockHashMismatch Text
- | ApplyBlockError (CardanoLedgerError StandardCrypto)
- | InvalidRollback SlotNo ChainPoint
- | TerminationEpochReached EpochNo
- | UnexpectedLedgerState AnyShelleyBasedEra (CardanoLedgerState StandardCrypto)
- | ByronEraUnsupported
- | DebugError !String
- data NodeConfig = NodeConfig {
- ncPBftSignatureThreshold :: !(Maybe Double)
- ncByronGenesisFile :: !(File ByronGenesisConfig 'In)
- ncByronGenesisHash :: !GenesisHashByron
- ncShelleyGenesisFile :: !(File ShelleyGenesisConfig 'In)
- ncShelleyGenesisHash :: !GenesisHashShelley
- ncAlonzoGenesisFile :: !(File AlonzoGenesis 'In)
- ncAlonzoGenesisHash :: !GenesisHashAlonzo
- ncConwayGenesisFile :: !(Maybe (File ConwayGenesisConfig 'In))
- ncConwayGenesisHash :: !(Maybe GenesisHashConway)
- ncRequiresNetworkMagic :: !RequiresNetworkMagic
- ncByronProtocolVersion :: !ProtocolVersion
- ncHardForkTriggers :: !CardanoHardForkTriggers
- type NodeConfigFile = File NodeConfig
- data ValidationMode
- type family ChainDepStateProtocol era where ...
- type family ConsensusBlockForEra era where ...
- data ConsensusModeParams where
- type family ConsensusProtocol era where ...
- type MonadIOTransError e (t :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) = (MonadIO m, MonadIO (t m), MonadCatch m, MonadTrans t, MonadError e (t m))
- type MonadTransError e (t :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) = (Monad m, MonadTrans t, MonadError e (t m))
- data OperationalCertIssueError
- data OperationalCertificate
- data OperationalCertificateIssueCounter
- type Ann = AnsiStyle
- data BlockType blk where
- ByronBlockType :: BlockType (HardForkBlock '[ByronBlock])
- ShelleyBlockType :: BlockType (HardForkBlock '[ShelleyBlock (TPraos StandardCrypto) StandardShelley])
- CardanoBlockType :: BlockType (HardForkBlock (CardanoEras StandardCrypto))
- class (RunNode blk, IOLike m) => Protocol (m :: Type -> Type) blk where
- data ProtocolInfoArgs blk
- protocolInfo :: ProtocolInfoArgs blk -> (ProtocolInfo blk, m [BlockForging m blk])
- data family ProtocolInfoArgs blk
- data SomeBlockType where
- SomeBlockType :: forall blk. BlockType blk -> SomeBlockType
- newtype CostModel = CostModel [Int64]
- data ExecutionUnitPrices = ExecutionUnitPrices {}
- data PraosNonce
- data ProtocolParametersConversionError
- = PpceOutOfBounds !ProtocolParameterName !Rational
- | PpceVersionInvalid !ProtocolParameterVersion
- | PpceInvalidCostModel !CostModel !CostModelApplyError
- | PpceMissingParameter !ProtocolParameterName
- data ProtocolParametersUpdate = ProtocolParametersUpdate {
- protocolUpdateProtocolVersion :: Maybe (Natural, Natural)
- protocolUpdateDecentralization :: Maybe Rational
- protocolUpdateExtraPraosEntropy :: Maybe (Maybe PraosNonce)
- protocolUpdateMaxBlockHeaderSize :: Maybe Word16
- protocolUpdateMaxBlockBodySize :: Maybe Word32
- protocolUpdateMaxTxSize :: Maybe Word32
- protocolUpdateTxFeeFixed :: Maybe Coin
- protocolUpdateTxFeePerByte :: Maybe Coin
- protocolUpdateMinUTxOValue :: Maybe Coin
- protocolUpdateStakeAddressDeposit :: Maybe Coin
- protocolUpdateStakePoolDeposit :: Maybe Coin
- protocolUpdateMinPoolCost :: Maybe Coin
- protocolUpdatePoolRetireMaxEpoch :: Maybe EpochInterval
- protocolUpdateStakePoolTargetNum :: Maybe Natural
- protocolUpdatePoolPledgeInfluence :: Maybe Rational
- protocolUpdateMonetaryExpansion :: Maybe Rational
- protocolUpdateTreasuryCut :: Maybe Rational
- protocolUpdateCostModels :: Map AnyPlutusScriptVersion CostModel
- protocolUpdatePrices :: Maybe ExecutionUnitPrices
- protocolUpdateMaxTxExUnits :: Maybe ExecutionUnits
- protocolUpdateMaxBlockExUnits :: Maybe ExecutionUnits
- protocolUpdateMaxValueSize :: Maybe Natural
- protocolUpdateCollateralPercent :: Maybe Natural
- protocolUpdateMaxCollateralInputs :: Maybe Natural
- protocolUpdateUTxOCostPerByte :: Maybe Coin
- data UpdateProposal = UpdateProposal !(Map (Hash GenesisKey) ProtocolParametersUpdate) !EpochNo
- data EraHistory where
- EraHistory :: forall (xs :: [Type]). CardanoBlock StandardCrypto ~ HardForkBlock xs => Interpreter xs -> EraHistory
- newtype LedgerEpochInfo = LedgerEpochInfo {
- unLedgerEpochInfo :: EpochInfo (Either Text)
- data QueryInEra era result where
- QueryByronUpdateState :: QueryInEra ByronEra ByronUpdateState
- QueryInShelleyBasedEra :: forall era result. ShelleyBasedEra era -> QueryInShelleyBasedEra era result -> QueryInEra era result
- data QueryInShelleyBasedEra era result where
- QueryEpoch :: forall era. QueryInShelleyBasedEra era EpochNo
- QueryGenesisParameters :: forall era. QueryInShelleyBasedEra era (GenesisParameters ShelleyEra)
- QueryProtocolParameters :: forall era. QueryInShelleyBasedEra era (PParams (ShelleyLedgerEra era))
- QueryProtocolParametersUpdate :: forall era. QueryInShelleyBasedEra era (Map (Hash GenesisKey) ProtocolParametersUpdate)
- QueryStakeDistribution :: forall era. QueryInShelleyBasedEra era (Map (Hash StakePoolKey) Rational)
- QueryUTxO :: forall era. QueryUTxOFilter -> QueryInShelleyBasedEra era (UTxO era)
- QueryStakeAddresses :: forall era. Set StakeCredential -> NetworkId -> QueryInShelleyBasedEra era (Map StakeAddress Coin, Map StakeAddress PoolId)
- QueryStakePools :: forall era. QueryInShelleyBasedEra era (Set PoolId)
- QueryStakePoolParameters :: forall era. Set PoolId -> QueryInShelleyBasedEra era (Map PoolId StakePoolParameters)
- QueryDebugLedgerState :: forall era. QueryInShelleyBasedEra era (SerialisedDebugLedgerState era)
- QueryProtocolState :: forall era. QueryInShelleyBasedEra era (ProtocolState era)
- QueryCurrentEpochState :: forall era. QueryInShelleyBasedEra era (SerialisedCurrentEpochState era)
- QueryPoolState :: forall era. Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedPoolState era)
- QueryPoolDistribution :: forall era. Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedPoolDistribution era)
- QueryStakeSnapshot :: forall era. Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedStakeSnapshots era)
- QueryStakeDelegDeposits :: forall era. Set StakeCredential -> QueryInShelleyBasedEra era (Map StakeCredential Coin)
- QueryAccountState :: forall era. QueryInShelleyBasedEra era AccountState
- QueryConstitution :: forall era. QueryInShelleyBasedEra era (Constitution (ShelleyLedgerEra era))
- QueryGovState :: forall era. QueryInShelleyBasedEra era (GovState (ShelleyLedgerEra era))
- QueryDRepState :: forall era. Set (Credential 'DRepRole StandardCrypto) -> QueryInShelleyBasedEra era (Map (Credential 'DRepRole StandardCrypto) (DRepState StandardCrypto))
- QueryDRepStakeDistr :: forall era. Set (DRep StandardCrypto) -> QueryInShelleyBasedEra era (Map (DRep StandardCrypto) Coin)
- QueryCommitteeMembersState :: forall era. Set (Credential 'ColdCommitteeRole StandardCrypto) -> Set (Credential 'HotCommitteeRole StandardCrypto) -> Set MemberStatus -> QueryInShelleyBasedEra era (CommitteeMembersState StandardCrypto)
- QueryStakeVoteDelegatees :: forall era. Set StakeCredential -> QueryInShelleyBasedEra era (Map StakeCredential (DRep StandardCrypto))
- data QueryInMode result where
- QueryCurrentEra :: QueryInMode AnyCardanoEra
- QueryInEra :: forall era result1. QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
- QueryEraHistory :: QueryInMode EraHistory
- QuerySystemStart :: QueryInMode SystemStart
- QueryChainBlockNo :: QueryInMode (WithOrigin BlockNo)
- QueryChainPoint :: QueryInMode ChainPoint
- data QueryUTxOFilter
- newtype SlotsInEpoch = SlotsInEpoch Word64
- newtype SlotsToEpochEnd = SlotsToEpochEnd Word64
- newtype DelegationsAndRewards = DelegationsAndRewards (Map StakeAddress Coin, Map StakeAddress PoolId)
- data AnyPlutusScriptVersion where
- AnyPlutusScriptVersion :: forall lang. PlutusScriptVersion lang -> AnyPlutusScriptVersion
- data AnyScriptLanguage where
- AnyScriptLanguage :: forall lang. ScriptLanguage lang -> AnyScriptLanguage
- class HasScriptLanguageInEra lang era where
- scriptLanguageInEra :: ScriptLanguageInEra lang era
- class IsScriptLanguage lang => IsPlutusScriptLanguage lang where
- class HasTypeProxy lang => IsScriptLanguage lang where
- scriptLanguage :: ScriptLanguage lang
- class IsScriptWitnessInCtx ctx where
- data KeyWitnessInCtx witctx where
- data PlutusScriptV1
- data PlutusScriptV2
- data PlutusScriptV3
- data PlutusScriptVersion lang where
- data SimpleScript
- data ScriptInAnyLang where
- ScriptInAnyLang :: forall lang. ScriptLanguage lang -> Script lang -> ScriptInAnyLang
- data ScriptLanguageInEra lang era where
- SimpleScriptInShelley :: ScriptLanguageInEra SimpleScript' ShelleyEra
- SimpleScriptInAllegra :: ScriptLanguageInEra SimpleScript' AllegraEra
- SimpleScriptInMary :: ScriptLanguageInEra SimpleScript' MaryEra
- SimpleScriptInAlonzo :: ScriptLanguageInEra SimpleScript' AlonzoEra
- SimpleScriptInBabbage :: ScriptLanguageInEra SimpleScript' BabbageEra
- SimpleScriptInConway :: ScriptLanguageInEra SimpleScript' ConwayEra
- PlutusScriptV1InAlonzo :: ScriptLanguageInEra PlutusScriptV1 AlonzoEra
- PlutusScriptV1InBabbage :: ScriptLanguageInEra PlutusScriptV1 BabbageEra
- PlutusScriptV1InConway :: ScriptLanguageInEra PlutusScriptV1 ConwayEra
- PlutusScriptV2InBabbage :: ScriptLanguageInEra PlutusScriptV2 BabbageEra
- PlutusScriptV2InConway :: ScriptLanguageInEra PlutusScriptV2 ConwayEra
- PlutusScriptV3InConway :: ScriptLanguageInEra PlutusScriptV3 ConwayEra
- type ScriptRedeemer = HashableScriptData
- data ScriptWitnessInCtx witctx where
- data SimpleScript'
- class ToAlonzoScript lang era where
- toLedgerScript :: PlutusScript lang -> AlonzoScript (ShelleyLedgerEra era)
- data WitCtx witctx where
- data WitCtxMint
- data WitCtxStake
- data WitCtxTxIn
- data HashableScriptData
- data ScriptDataJsonBytesError
- data ScriptDataJsonError
- data ScriptDataJsonSchemaError
- = ScriptDataJsonNullNotAllowed
- | ScriptDataJsonBoolNotAllowed
- | ScriptDataJsonNumberNotInteger !Double
- | ScriptDataJsonNotObject !Value
- | ScriptDataJsonBadObject ![(Text, Value)]
- | ScriptDataJsonBadMapPair !Value
- | ScriptDataJsonTypeMismatch !Text !Value
- newtype ScriptDataRangeError = ScriptDataConstructorOutOfRange Integer
- data ScriptDataJsonSchema
- data Bech32DecodeError
- = Bech32DecodingError !DecodingError
- | Bech32UnexpectedPrefix !Text !(Set Text)
- | Bech32DataPartToBytesError !Text
- | Bech32DeserialiseFromBytesError !ByteString
- | Bech32WrongPrefix !Text !Text
- class (HasTypeProxy a, SerialiseAsRawBytes a) => SerialiseAsBech32 a
- class HasTypeProxy a => SerialiseAsCBOR a where
- serialiseToCBOR :: a -> ByteString
- deserialiseFromCBOR :: AsType a -> ByteString -> Either DecoderError a
- newtype JsonDecodeError = JsonDecodeError String
- data FromSomeTypeCDDL c b where
- FromCDDLTx :: forall b. Text -> (InAnyShelleyBasedEra Tx -> b) -> FromSomeTypeCDDL TextEnvelope b
- FromCDDLWitness :: forall b. Text -> (InAnyShelleyBasedEra KeyWitness -> b) -> FromSomeTypeCDDL TextEnvelope b
- data TextEnvelopeCddlError
- data RawBytesHexError
- class (HasTypeProxy a, Typeable a) => SerialiseAsRawBytes a where
- serialiseToRawBytes :: a -> ByteString
- deserialiseFromRawBytes :: AsType a -> ByteString -> Either SerialiseAsRawBytesError a
- newtype SerialiseAsRawBytesError = SerialiseAsRawBytesError {}
- class SerialiseAsCBOR a => HasTextEnvelope a where
- data TextEnvelope = TextEnvelope {}
- data TextEnvelopeDescr
- data TextEnvelopeError
- = TextEnvelopeTypeError ![TextEnvelopeType] !TextEnvelopeType
- | TextEnvelopeDecodeError !DecoderError
- | TextEnvelopeAesonDecodeError !String
- newtype TextEnvelopeType = TextEnvelopeType String
- newtype UsingBech32 a = UsingBech32 a
- newtype UsingRawBytes a = UsingRawBytes a
- newtype UsingRawBytesHex a = UsingRawBytesHex a
- data StakePoolMetadata
- data StakePoolMetadataValidationError
- data AnyScriptWitness era where
- AnyScriptWitness :: forall witctx era. ScriptWitness witctx era -> AnyScriptWitness era
- data BuildTx
- data BuildTxWith build a where
- ViewTx :: forall a. BuildTxWith ViewTx a
- BuildTxWith :: forall a. a -> BuildTxWith BuildTx a
- data ViewTx
- data ScriptWitnessIndex
- data TxCertificates build era where
- TxCertificatesNone :: forall build era. TxCertificates build era
- TxCertificates :: forall era build. ShelleyBasedEra era -> [Certificate era] -> BuildTxWith build (Map StakeCredential (Witness WitCtxStake era)) -> TxCertificates build era
- data TxOutInAnyEra where
- TxOutInAnyEra :: forall era. CardanoEra era -> TxOut CtxTx era -> TxOutInAnyEra
- data TxProposalProcedures build era where
- TxProposalProceduresNone :: forall build era. TxProposalProcedures build era
- TxProposalProcedures :: forall era build. EraPParams (ShelleyLedgerEra era) => OSet (ProposalProcedure (ShelleyLedgerEra era)) -> BuildTxWith build (Map (ProposalProcedure (ShelleyLedgerEra era)) (ScriptWitness WitCtxStake era)) -> TxProposalProcedures build era
- data TxReturnCollateral ctx era where
- TxReturnCollateralNone :: forall ctx era. TxReturnCollateral ctx era
- TxReturnCollateral :: forall era ctx. BabbageEraOnwards era -> TxOut ctx era -> TxReturnCollateral ctx era
- data TxTotalCollateral era where
- TxTotalCollateralNone :: forall era. TxTotalCollateral era
- TxTotalCollateral :: forall era. BabbageEraOnwards era -> Coin -> TxTotalCollateral era
- data TxUpdateProposal era where
- TxUpdateProposalNone :: forall era. TxUpdateProposal era
- TxUpdateProposal :: forall era. ShelleyToBabbageEra era -> UpdateProposal -> TxUpdateProposal era
- data TxVotingProcedures build era where
- TxVotingProceduresNone :: forall build era. TxVotingProcedures build era
- TxVotingProcedures :: forall era build. VotingProcedures (ShelleyLedgerEra era) -> BuildTxWith build (Map (Voter (EraCrypto (ShelleyLedgerEra era))) (ScriptWitness WitCtxStake era)) -> TxVotingProcedures build era
- data TxWithdrawals build era where
- TxWithdrawalsNone :: forall build era. TxWithdrawals build era
- TxWithdrawals :: forall era build. ShelleyBasedEra era -> [(StakeAddress, Coin, BuildTxWith build (Witness WitCtxStake era))] -> TxWithdrawals build era
- data ScriptValidity
- 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)
- | WitnessGenesisUTxOKey (SigningKey GenesisUTxOKey)
- | WitnessCommitteeColdKey (SigningKey CommitteeColdKey)
- | WitnessCommitteeColdExtendedKey (SigningKey CommitteeColdExtendedKey)
- | WitnessCommitteeHotKey (SigningKey CommitteeHotKey)
- | WitnessCommitteeHotExtendedKey (SigningKey CommitteeHotExtendedKey)
- | WitnessDRepKey (SigningKey DRepKey)
- | WitnessDRepExtendedKey (SigningKey DRepExtendedKey)
- newtype TxIx = TxIx Word
- newtype TxMetadata = TxMetadata (Map Word64 TxMetadataValue)
- data TxMetadataJsonError
- data TxMetadataJsonSchemaError
- = TxMetadataJsonNullNotAllowed
- | TxMetadataJsonBoolNotAllowed
- | TxMetadataJsonNumberNotInteger !Double
- | TxMetadataJsonNotObject !Value
- | TxMetadataJsonBadObject ![(Text, Value)]
- | TxMetadataJsonBadMapPair !Value
- | TxMetadataJsonTypeMismatch !Text !Value
- data TxMetadataRangeError
- data TxMetadataJsonSchema
- data TxMetadataValue
- data AssetId
- newtype AssetName = AssetName ByteString
- newtype Quantity = Quantity Integer
- data ValueNestedBundle
- newtype ValueNestedRep = ValueNestedRep [ValueNestedBundle]
- newtype ShowOf a = ShowOf a
- data CommitteeMembersState c = CommitteeMembersState {
- csCommittee :: !(Map (Credential 'ColdCommitteeRole c) (CommitteeMemberState c))
- csThreshold :: !(Maybe UnitInterval)
- csEpochNo :: !EpochNo
- data MemberStatus
- newtype EpochSlots = EpochSlots {}
- data MIRPot
- data MIRTarget c
- = StakeAddressesMIR !(Map (Credential 'Staking c) DeltaCoin)
- | SendToOppositePotMIR !Coin
- newtype BlockNo = BlockNo {}
- newtype EpochNo = EpochNo {}
- newtype SlotNo = SlotNo {}
- newtype SystemStart = SystemStart {}
- newtype NetworkMagic = NetworkMagic {}
- data NodeToClientVersion
- newtype ChainSyncClient header point tip (m :: Type -> Type) a = ChainSyncClient {
- runChainSyncClient :: m (ClientStIdle header point tip m a)
- newtype ChainSyncClientPipelined header point tip (m :: Type -> Type) a = ChainSyncClientPipelined {
- runChainSyncClientPipelined :: m (ClientPipelinedStIdle 'Z header point tip m a)
- newtype LocalStateQueryClient block point (query :: Type -> Type) (m :: Type -> Type) a = LocalStateQueryClient {
- runLocalStateQueryClient :: m (ClientStIdle block point query m a)
- newtype LocalTxMonitorClient txid tx slot (m :: Type -> Type) a = LocalTxMonitorClient {
- runLocalTxMonitorClient :: m (ClientStIdle txid tx slot m a)
- data MempoolSizeAndCapacity = MempoolSizeAndCapacity {
- capacityInBytes :: !Word32
- sizeInBytes :: !Word32
- numberOfTxs :: !Word32
- newtype LocalTxSubmissionClient tx reject (m :: Type -> Type) a = LocalTxSubmissionClient {
- runLocalTxSubmissionClient :: m (LocalTxClientStIdle tx reject m a)
- data SubmitResult reason
- = SubmitSuccess
- | SubmitFail reason
- pattern Block :: BlockHeader -> [Tx era] -> Block era
- (<+>) :: Doc ann -> Doc ann -> Doc ann
- runParsecParser :: Parser a -> Text -> Parser a
- left :: forall (m :: Type -> Type) x a. Monad m => x -> ExceptT x m a
- right :: forall (m :: Type -> Type) a x. Monad m => a -> ExceptT x m a
- throwE :: forall (m :: Type -> Type) e a. Monad m => e -> ExceptT e m a
- runExcept :: Except e a -> Either e a
- mapExcept :: (Either e a -> Either e' b) -> Except e a -> Except e' b
- withExcept :: (e -> e') -> Except e a -> Except e' a
- runExceptT :: ExceptT e m a -> m (Either e a)
- mapExceptT :: (m (Either e a) -> n (Either e' b)) -> ExceptT e m a -> ExceptT e' n b
- withExceptT :: forall (m :: Type -> Type) e e' a. Functor m => (e -> e') -> ExceptT e m a -> ExceptT e' m a
- liftCallCC :: CallCC m (Either e a) (Either e b) -> CallCC (ExceptT e m) a b
- liftEither :: MonadError e m => Either e a -> m a
- modifyError :: forall e' t (m :: Type -> Type) e a. MonadTransError e' t m => (e -> e') -> ExceptT e m a -> t m a
- hsep :: [Doc ann] -> Doc ann
- catchE :: forall (m :: Type -> Type) e a e'. Monad m => ExceptT e m a -> (e -> ExceptT e' m a) -> ExceptT e' m a
- except :: forall (m :: Type -> Type) e a. Monad m => Either e a -> ExceptT e m a
- handleE :: forall (m :: Type -> Type) e e' a. Monad m => (e -> ExceptT e' m a) -> ExceptT e m a -> ExceptT e' m a
- tryE :: forall (m :: Type -> Type) e a. Monad m => ExceptT e m a -> ExceptT e m (Either e a)
- finallyE :: forall (m :: Type -> Type) e a. Monad m => ExceptT e m a -> ExceptT e m () -> ExceptT e m a
- liftListen :: Monad m => Listen w m (Either e a) -> Listen w (ExceptT e m) a
- liftPass :: Monad m => Pass w m (Either e a) -> Pass w (ExceptT e m) a
- hoistMaybe :: forall (m :: Type -> Type) x a. Monad m => x -> Maybe a -> ExceptT x m a
- blue :: Doc AnsiStyle -> Doc AnsiStyle
- createAndValidateTransactionBody :: ShelleyBasedEra era -> TxBodyContent BuildTx era -> Either TxBodyError (TxBody era)
- defaultTxBodyContent :: ShelleyBasedEra era -> TxBodyContent BuildTx era
- fromLedgerValue :: ShelleyBasedEra era -> Value (ShelleyLedgerEra era) -> Value
- green :: Doc AnsiStyle -> Doc AnsiStyle
- makeShelleyKeyWitness :: ShelleyBasedEra era -> TxBody era -> ShelleyWitnessSigningKey -> KeyWitness era
- policyId :: Parser PolicyId
- queryEraHistory :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError EraHistory)
- queryProtocolParameters :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (PParams (ShelleyLedgerEra era))))
- queryStakePools :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Set PoolId)))
- querySystemStart :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError SystemStart)
- red :: Doc AnsiStyle -> Doc AnsiStyle
- signShelleyTransaction :: ShelleyBasedEra era -> TxBody era -> [ShelleyWitnessSigningKey] -> Tx era
- toLedgerValue :: MaryEraOnwards era -> Value -> Value (ShelleyLedgerEra era)
- txOutValueToValue :: TxOutValue era -> Value
- renderTxIn :: TxIn -> Text
- renderValue :: Value -> Text
- anyAddressInShelleyBasedEra :: ShelleyBasedEra era -> AddressAny -> AddressInEra era
- toAddressAny :: Address addr -> AddressAny
- lovelaceToTxOutValue :: ShelleyBasedEra era -> Coin -> TxOutValue era
- unUTxO :: UTxO era -> Map TxIn (TxOut CtxUTxO era)
- anyAddressInEra :: CardanoEra era -> AddressAny -> Either String (AddressInEra era)
- byronAddressInEra :: Address ByronAddr -> AddressInEra era
- isKeyAddress :: AddressInEra era -> Bool
- lexPlausibleAddressString :: Parser Text
- makeByronAddress :: NetworkId -> VerificationKey ByronKey -> Address ByronAddr
- makeByronAddressInEra :: NetworkId -> VerificationKey ByronKey -> AddressInEra era
- makeShelleyAddress :: NetworkId -> PaymentCredential -> StakeAddressReference -> Address ShelleyAddr
- makeShelleyAddressInEra :: ShelleyBasedEra era -> NetworkId -> PaymentCredential -> StakeAddressReference -> AddressInEra era
- makeStakeAddress :: NetworkId -> StakeCredential -> StakeAddress
- parseAddressAny :: Parser AddressAny
- shelleyAddressInEra :: ShelleyBasedEra era -> Address ShelleyAddr -> AddressInEra era
- stakeAddressCredential :: StakeAddress -> StakeCredential
- chainPointToHeaderHash :: ChainPoint -> Maybe (Hash BlockHeader)
- chainPointToSlotNo :: ChainPoint -> Maybe SlotNo
- chainTipToChainPoint :: ChainTip -> ChainPoint
- getBlockHeader :: Block era -> BlockHeader
- makeChainTip :: WithOrigin BlockNo -> ChainPoint -> ChainTip
- makeCommitteeColdkeyResignationCertificate :: CommitteeColdkeyResignationRequirements era -> Certificate era
- makeCommitteeHotKeyAuthorizationCertificate :: CommitteeHotKeyAuthorizationRequirements era -> Certificate era
- makeDrepRegistrationCertificate :: DRepRegistrationRequirements era -> Maybe (Anchor (EraCrypto (ShelleyLedgerEra era))) -> Certificate era
- makeDrepUnregistrationCertificate :: DRepUnregistrationRequirements era -> Certificate era
- makeDrepUpdateCertificate :: DRepUpdateRequirements era -> Maybe (Anchor (EraCrypto (ShelleyLedgerEra era))) -> Certificate era
- makeGenesisKeyDelegationCertificate :: GenesisKeyDelegationRequirements era -> Certificate era
- makeMIRCertificate :: MirCertificateRequirements era -> Certificate era
- makeStakeAddressAndDRepDelegationCertificate :: ConwayEraOnwards era -> StakeCredential -> Delegatee (EraCrypto (ShelleyLedgerEra era)) -> Coin -> Certificate era
- makeStakeAddressDelegationCertificate :: StakeDelegationRequirements era -> Certificate era
- makeStakeAddressRegistrationCertificate :: StakeAddressRequirements era -> Certificate era
- makeStakeAddressUnregistrationCertificate :: StakeAddressRequirements era -> Certificate era
- makeStakePoolRegistrationCertificate :: StakePoolRegistrationRequirements era -> Certificate era
- makeStakePoolRetirementCertificate :: StakePoolRetirementRequirements era -> Certificate era
- selectStakeCredentialWitness :: Certificate era -> Maybe StakeCredential
- constructBalancedTx :: ShelleyBasedEra era -> TxBodyContent BuildTx era -> AddressInEra era -> Maybe Word -> UTxO era -> LedgerProtocolParameters era -> LedgerEpochInfo -> SystemStart -> Set PoolId -> Map StakeCredential Coin -> Map (Credential 'DRepRole StandardCrypto) Coin -> [ShelleyWitnessSigningKey] -> Either (TxBodyErrorAutoBalance era) (Tx era)
- notScriptLockedTxIns :: [TxIn] -> UTxO era -> Either ScriptLockedTxInsError ()
- renderNotScriptLockedTxInsError :: ScriptLockedTxInsError -> Text
- renderTxInsExistError :: TxInsExistError -> Text
- txInsExistInUTxO :: [TxIn] -> UTxO era -> Either TxInsExistError ()
- determineEra :: LocalNodeConnectInfo -> ExceptT AcquiringFailure IO AnyCardanoEra
- executeQueryAnyMode :: LocalNodeConnectInfo -> QueryInMode (Either EraMismatch result) -> ExceptT QueryConvenienceError IO result
- executeQueryCardanoMode :: SocketPath -> NetworkId -> QueryInMode (Either EraMismatch result) -> ExceptT QueryConvenienceError IO result
- queryStateForBalancedTx :: CardanoEra era -> [TxIn] -> [Certificate era] -> LocalStateQueryExpr block point QueryInMode r IO (Either QueryConvenienceError (UTxO era, LedgerProtocolParameters era, EraHistory, SystemStart, Set PoolId, Map StakeCredential Coin, Map (Credential 'DRepRole StandardCrypto) Coin, Maybe (Featured ConwayEraOnwards era TxCurrentTreasuryValue)))
- renderQueryConvenienceError :: QueryConvenienceError -> Text
- hashDRepMetadata :: ByteString -> (DRepMetadata, Hash DRepMetadata)
- deserialiseAnyVerificationKey :: ByteString -> Either InputDecodeError SomeAddressVerificationKey
- deserialiseAnyVerificationKeyBech32 :: ByteString -> Either Bech32DecodeError SomeAddressVerificationKey
- deserialiseAnyVerificationKeyTextEnvelope :: ByteString -> Either TextEnvelopeError SomeAddressVerificationKey
- deserialiseInput :: AsType a -> NonEmpty (InputFormat a) -> ByteString -> Either InputDecodeError a
- deserialiseInputAnyOf :: [FromSomeType SerialiseAsBech32 b] -> [FromSomeType HasTextEnvelope b] -> ByteString -> Either InputDecodeError b
- mapSomeAddressVerificationKey :: (forall keyrole. Key keyrole => VerificationKey keyrole -> a) -> SomeAddressVerificationKey -> a
- renderInputDecodeError :: InputDecodeError -> Doc ann
- renderSomeAddressVerificationKey :: SomeAddressVerificationKey -> Text
- alonzoEraOnwardsConstraints :: AlonzoEraOnwards era -> (AlonzoEraOnwardsConstraints era => a) -> a
- alonzoEraOnwardsToShelleyBasedEra :: AlonzoEraOnwards era -> ShelleyBasedEra era
- babbageEraOnwardsConstraints :: BabbageEraOnwards era -> (BabbageEraOnwardsConstraints era => a) -> a
- babbageEraOnwardsToShelleyBasedEra :: BabbageEraOnwards era -> ShelleyBasedEra era
- byronToAlonzoEraConstraints :: ByronToAlonzoEra era -> (ByronToAlonzoEraConstraints era => a) -> a
- conwayEraOnwardsConstraints :: ConwayEraOnwards era -> (ConwayEraOnwardsConstraints era => a) -> a
- conwayEraOnwardsToShelleyBasedEra :: ConwayEraOnwards era -> ShelleyBasedEra era
- maryEraOnwardsConstraints :: MaryEraOnwards era -> (MaryEraOnwardsConstraints era => a) -> a
- maryEraOnwardsToShelleyBasedEra :: MaryEraOnwards era -> ShelleyBasedEra era
- forShelleyBasedEraInEon :: Eon eon => ShelleyBasedEra era -> a -> (eon era -> a) -> a
- forShelleyBasedEraInEonMaybe :: Eon eon => ShelleyBasedEra era -> (eon era -> a) -> Maybe a
- forShelleyBasedEraMaybeEon :: Eon eon => ShelleyBasedEra era -> Maybe (eon era)
- inAnyShelleyBasedEra :: ShelleyBasedEra era -> thing era -> InAnyShelleyBasedEra thing
- inEonForShelleyBasedEra :: Eon eon => a -> (eon era -> a) -> ShelleyBasedEra era -> a
- inEonForShelleyBasedEraMaybe :: Eon eon => (eon era -> a) -> ShelleyBasedEra era -> Maybe a
- requireShelleyBasedEra :: Applicative m => CardanoEra era -> m (Maybe (ShelleyBasedEra era))
- shelleyBasedEraConstraints :: ShelleyBasedEra era -> (ShelleyBasedEraConstraints era => a) -> a
- shelleyEraOnlyConstraints :: ShelleyEraOnly era -> (ShelleyEraOnlyConstraints era => a) -> a
- shelleyEraOnlyToShelleyBasedEra :: ShelleyEraOnly era -> ShelleyBasedEra era
- shelleyToAllegraEraConstraints :: ShelleyToAllegraEra era -> (ShelleyToAllegraEraConstraints era => a) -> a
- shelleyToAllegraEraToShelleyBasedEra :: ShelleyToAllegraEra era -> ShelleyBasedEra era
- shelleyToAlonzoEraConstraints :: ShelleyToAlonzoEra era -> (ShelleyToAlonzoEraConstraints era => a) -> a
- shelleyToAlonzoEraToShelleyBasedEra :: ShelleyToAlonzoEra era -> ShelleyBasedEra era
- shelleyToBabbageEraConstraints :: ShelleyToBabbageEra era -> (ShelleyToBabbageEraConstraints era => a) -> a
- shelleyToBabbageEraToShelleyBasedEra :: ShelleyToBabbageEra era -> ShelleyBasedEra era
- shelleyToMaryEraConstraints :: ShelleyToMaryEra era -> (ShelleyToMaryEraConstraints era => a) -> a
- shelleyToMaryEraToShelleyBasedEra :: ShelleyToMaryEra era -> ShelleyBasedEra era
- alonzoEraOnwardsToMaryEraOnwards :: AlonzoEraOnwards era -> MaryEraOnwards era
- babbageEraOnwardsToAlonzoEraOnwards :: BabbageEraOnwards era -> AlonzoEraOnwards era
- babbageEraOnwardsToMaryEraOnwards :: BabbageEraOnwards era -> MaryEraOnwards era
- caseByronOrShelleyBasedEra :: a -> (ShelleyBasedEraConstraints era => ShelleyBasedEra era -> a) -> CardanoEra era -> a
- caseByronToAlonzoOrBabbageEraOnwards :: (ByronToAlonzoEraConstraints era => ByronToAlonzoEra era -> a) -> (BabbageEraOnwardsConstraints era => BabbageEraOnwards era -> a) -> CardanoEra era -> a
- caseShelleyEraOnlyOrAllegraEraOnwards :: (ShelleyEraOnlyConstraints era => ShelleyEraOnly era -> a) -> (AllegraEraOnwardsConstraints era => AllegraEraOnwards era -> a) -> ShelleyBasedEra era -> a
- caseShelleyToAllegraOrMaryEraOnwards :: (ShelleyToAllegraEraConstraints era => ShelleyToAllegraEra era -> a) -> (MaryEraOnwardsConstraints era => MaryEraOnwards era -> a) -> ShelleyBasedEra era -> a
- caseShelleyToAlonzoOrBabbageEraOnwards :: (ShelleyToAlonzoEraConstraints era => ShelleyToAlonzoEra era -> a) -> (BabbageEraOnwardsConstraints era => BabbageEraOnwards era -> a) -> ShelleyBasedEra era -> a
- caseShelleyToBabbageOrConwayEraOnwards :: (ShelleyToBabbageEraConstraints era => ShelleyToBabbageEra era -> a) -> (ConwayEraOnwardsConstraints era => ConwayEraOnwards era -> a) -> ShelleyBasedEra era -> a
- caseShelleyToMaryOrAlonzoEraOnwards :: (ShelleyToMaryEraConstraints era => ShelleyToMaryEra era -> a) -> (AlonzoEraOnwardsConstraints era => AlonzoEraOnwards era -> a) -> ShelleyBasedEra era -> a
- shelleyToAlonzoEraToShelleyToBabbageEra :: ShelleyToAlonzoEra era -> ShelleyToBabbageEra era
- anyCardanoEra :: CardanoEra era -> AnyCardanoEra
- cardanoEraConstraints :: CardanoEra era -> (CardanoEraConstraints era => a) -> a
- forEraInEon :: Eon eon => CardanoEra era -> a -> (eon era -> a) -> a
- forEraInEonMaybe :: Eon eon => CardanoEra era -> (eon era -> a) -> Maybe a
- forEraMaybeEon :: Eon eon => CardanoEra era -> Maybe (eon era)
- inAnyCardanoEra :: CardanoEra era -> thing era -> InAnyCardanoEra thing
- inEonForEraMaybe :: Eon eon => (eon era -> a) -> CardanoEra era -> Maybe a
- maybeEon :: (Eon eon, IsCardanoEra era) => Maybe (eon era)
- monoidForEraInEon :: (Eon eon, Monoid a) => CardanoEra era -> (eon era -> a) -> a
- monoidForEraInEonA :: (Eon eon, Applicative f, Monoid a) => CardanoEra era -> (eon era -> f a) -> f a
- throwErrorAsException :: Error e => e -> IO a
- asFeaturedInEra :: forall (eon :: Type -> Type) a era. Eon eon => a -> CardanoEra era -> Maybe (Featured eon era a)
- asFeaturedInShelleyBasedEra :: forall (eon :: Type -> Type) a era. Eon eon => a -> ShelleyBasedEra era -> Maybe (Featured eon era a)
- unFeatured :: forall (eon :: Type -> Type) era a. Featured eon era a -> a
- calculateMinTxFee :: ShelleyBasedEra era -> PParams (ShelleyLedgerEra era) -> UTxO era -> TxBody era -> Word -> Coin
- calculateMinimumUTxO :: ShelleyBasedEra era -> TxOut CtxTx era -> PParams (ShelleyLedgerEra era) -> Coin
- estimateBalancedTxBody :: MaryEraOnwards era -> TxBodyContent BuildTx era -> PParams (ShelleyLedgerEra era) -> Set PoolId -> Map StakeCredential Coin -> Map (Credential 'DRepRole StandardCrypto) Coin -> Map ScriptWitnessIndex ExecutionUnits -> Coin -> Int -> Int -> Int -> AddressInEra era -> Value -> Either (TxFeeEstimationError era) (BalancedTxBody era)
- estimateOrCalculateBalancedTxBody :: ShelleyBasedEra era -> FeeEstimationMode era -> PParams (ShelleyLedgerEra era) -> TxBodyContent BuildTx era -> Set PoolId -> Map StakeCredential Coin -> Map (Credential 'DRepRole StandardCrypto) Coin -> AddressInEra era -> Either (AutoBalanceError era) (BalancedTxBody era)
- estimateTransactionKeyWitnessCount :: TxBodyContent BuildTx era -> Word
- evaluateTransactionBalance :: ShelleyBasedEra era -> PParams (ShelleyLedgerEra era) -> Set PoolId -> Map StakeCredential Coin -> Map (Credential 'DRepRole StandardCrypto) Coin -> UTxO era -> TxBody era -> TxOutValue era
- evaluateTransactionExecutionUnits :: CardanoEra era -> SystemStart -> LedgerEpochInfo -> LedgerProtocolParameters era -> UTxO era -> TxBody era -> Either (TransactionValidityError era) (Map ScriptWitnessIndex (Either ScriptExecutionError (EvalTxExecutionUnitsLog, ExecutionUnits)))
- evaluateTransactionFee :: ShelleyBasedEra era -> PParams (ShelleyLedgerEra era) -> TxBody era -> Word -> Word -> Int -> Coin
- makeTransactionBodyAutoBalance :: ShelleyBasedEra era -> SystemStart -> LedgerEpochInfo -> LedgerProtocolParameters era -> Set PoolId -> Map StakeCredential Coin -> Map (Credential 'DRepRole StandardCrypto) Coin -> UTxO era -> TxBodyContent BuildTx era -> AddressInEra era -> Maybe Word -> Either (TxBodyErrorAutoBalance era) (BalancedTxBody era)
- renderSafeHashAsHex :: SafeHash c tag -> Text
- intoFile :: File content 'Out -> content -> (File content 'Out -> stream -> result) -> (content -> stream) -> result
- mapFile :: forall content (direction :: FileDirection). (FilePath -> FilePath) -> File content direction -> File content direction
- onlyIn :: File content 'InOut -> File content 'In
- onlyOut :: File content 'InOut -> File content 'Out
- readByteStringFile :: MonadIO m => File content 'In -> m (Either (FileError e) ByteString)
- readLazyByteStringFile :: MonadIO m => File content 'In -> m (Either (FileError e) ByteString)
- readTextFile :: MonadIO m => File content 'In -> m (Either (FileError e) Text)
- writeByteStringFile :: MonadIO m => File content 'Out -> ByteString -> m (Either (FileError e) ())
- writeByteStringFileWithOwnerPermissions :: FilePath -> ByteString -> IO (Either (FileError e) ())
- writeByteStringOutput :: MonadIO m => Maybe (File content 'Out) -> ByteString -> m (Either (FileError e) ())
- writeLazyByteStringFile :: MonadIO m => File content 'Out -> ByteString -> m (Either (FileError e) ())
- writeLazyByteStringFileWithOwnerPermissions :: File content 'Out -> ByteString -> IO (Either (FileError e) ())
- writeLazyByteStringOutput :: MonadIO m => Maybe (File content 'Out) -> ByteString -> m (Either (FileError e) ())
- writeTextFile :: MonadIO m => File content 'Out -> Text -> m (Either (FileError e) ())
- writeTextFileWithOwnerPermissions :: File content 'Out -> Text -> IO (Either (FileError e) ())
- writeTextOutput :: MonadIO m => Maybe (File content 'Out) -> Text -> m (Either (FileError e) ())
- writeSecrets :: FilePath -> [Char] -> [Char] -> (a -> ByteString) -> [a] -> IO ()
- connectToLocalNode :: MonadIO m => LocalNodeConnectInfo -> LocalNodeClientProtocolsInMode -> m ()
- connectToLocalNodeWithVersion :: MonadIO m => LocalNodeConnectInfo -> (NodeToClientVersion -> LocalNodeClientProtocolsInMode) -> m ()
- getLocalChainTip :: MonadIO m => LocalNodeConnectInfo -> m ChainTip
- mkLocalNodeClientParams :: ConsensusModeParams -> (NodeToClientVersion -> LocalNodeClientProtocolsInMode) -> LocalNodeClientParams
- queryNodeLocalState :: LocalNodeConnectInfo -> Target ChainPoint -> QueryInMode result -> ExceptT AcquiringFailure IO result
- queryTxMonitoringLocal :: MonadIO m => LocalNodeConnectInfo -> LocalTxMonitoringQuery -> m LocalTxMonitoringResult
- submitTxToNodeLocal :: MonadIO m => LocalNodeConnectInfo -> TxInMode -> m (SubmitResult TxValidationErrorInCardanoMode)
- executeLocalStateQueryExpr :: LocalNodeConnectInfo -> Target ChainPoint -> LocalStateQueryExpr BlockInMode ChainPoint QueryInMode () IO a -> IO (Either AcquiringFailure a)
- queryExpr :: QueryInMode a -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
- generateInsecureSigningKey :: (MonadIO m, Key keyrole, SerialiseAsRawBytes (SigningKey keyrole)) => StdGen -> AsType keyrole -> m (SigningKey keyrole, StdGen)
- generateSigningKey :: (MonadIO m, Key keyrole) => AsType keyrole -> m (SigningKey keyrole)
- readKeyFile :: AsType a -> NonEmpty (InputFormat a) -> FilePath -> IO (Either (FileError InputDecodeError) a)
- readKeyFileAnyOf :: forall content b. [FromSomeType SerialiseAsBech32 b] -> [FromSomeType HasTextEnvelope b] -> File content 'In -> IO (Either (FileError InputDecodeError) b)
- readKeyFileTextEnvelope :: HasTextEnvelope a => AsType a -> File content 'In -> IO (Either (FileError InputDecodeError) a)
- applyBlock :: Env -> LedgerState -> ValidationMode -> BlockInMode -> Either LedgerStateError (LedgerState, [LedgerEvent])
- chainSyncClientPipelinedWithLedgerState :: forall (m :: Type -> Type) a. Monad m => Env -> LedgerState -> ValidationMode -> ChainSyncClientPipelined (BlockInMode, Either LedgerStateError (LedgerState, [LedgerEvent])) ChainPoint ChainTip m a -> ChainSyncClientPipelined BlockInMode ChainPoint ChainTip m a
- chainSyncClientWithLedgerState :: forall (m :: Type -> Type) a. Monad m => Env -> LedgerState -> ValidationMode -> ChainSyncClient (BlockInMode, Either LedgerStateError (LedgerState, [LedgerEvent])) ChainPoint ChainTip m a -> ChainSyncClient BlockInMode ChainPoint ChainTip m a
- decodeLedgerState :: CardanoCodecConfig StandardCrypto -> forall s. Decoder s LedgerState
- encodeLedgerState :: CardanoCodecConfig StandardCrypto -> LedgerState -> Encoding
- envSecurityParam :: Env -> Word64
- foldBlocks :: forall a t (m :: Type -> Type). (Show a, MonadIOTransError FoldBlocksError t m) => NodeConfigFile 'In -> SocketPath -> ValidationMode -> a -> (Env -> LedgerState -> [LedgerEvent] -> BlockInMode -> a -> IO (a, FoldStatus)) -> t m a
- foldEpochState :: forall t (m :: Type -> Type) s. MonadIOTransError FoldBlocksError t m => NodeConfigFile 'In -> SocketPath -> ValidationMode -> EpochNo -> s -> (AnyNewEpochState -> SlotNo -> BlockNo -> StateT s IO ConditionResult) -> t m (ConditionResult, s)
- fromConditionResult :: ConditionResult -> Bool
- genesisConfigToEnv :: GenesisConfig -> Either GenesisConfigError Env
- getAnyNewEpochState :: ShelleyBasedEra era -> LedgerState -> Either LedgerStateError AnyNewEpochState
- initialLedgerState :: forall t (m :: Type -> Type). MonadIOTransError InitialLedgerStateError t m => NodeConfigFile 'In -> t m (Env, LedgerState)
- mkProtocolInfoCardano :: GenesisConfig -> (ProtocolInfo (CardanoBlock StandardCrypto), IO [BlockForging IO (CardanoBlock StandardCrypto)])
- readAlonzoGenesisConfig :: forall t (m :: Type -> Type) era. MonadIOTransError GenesisConfigError t m => Maybe (CardanoEra era) -> NodeConfig -> t m AlonzoGenesis
- readByronGenesisConfig :: forall t (m :: Type -> Type). MonadIOTransError GenesisConfigError t m => NodeConfig -> t m Config
- readCardanoGenesisConfig :: forall t (m :: Type -> Type) era. MonadIOTransError GenesisConfigError t m => Maybe (CardanoEra era) -> NodeConfig -> t m GenesisConfig
- readConwayGenesisConfig :: forall t (m :: Type -> Type). MonadIOTransError GenesisConfigError t m => NodeConfig -> t m (ConwayGenesis StandardCrypto)
- readNodeConfig :: (MonadError Text m, MonadIO m) => NodeConfigFile 'In -> m NodeConfig
- readShelleyGenesisConfig :: forall t (m :: Type -> Type). MonadIOTransError GenesisConfigError t m => NodeConfig -> t m ShelleyConfig
- shelleyPraosNonce :: GenesisHashShelley -> Nonce
- toConditionResult :: Bool -> ConditionResult
- handleIOExceptionsLiftWith :: (MonadIOTransError e' t m, Exception e) => (e -> e') -> m a -> t m a
- handleIOExceptionsWith :: (MonadError e' m, MonadCatch m, Exception e) => (e -> e') -> m a -> m a
- hoistIOEither :: forall e t (m :: Type -> Type) a. MonadIOTransError e t m => IO (Either e a) -> t m a
- liftExceptT :: forall e t (m :: Type -> Type) a. MonadTransError e t m => ExceptT e m a -> t m a
- liftMaybe :: MonadError e m => e -> Maybe a -> m a
- fromNetworkMagic :: NetworkMagic -> NetworkId
- toNetworkMagic :: NetworkId -> NetworkMagic
- getHotKey :: OperationalCertificate -> VerificationKey KesKey
- getKesPeriod :: OperationalCertificate -> Word
- getOpCertCount :: OperationalCertificate -> Word64
- issueOperationalCertificate :: VerificationKey KesKey -> Either (SigningKey StakePoolKey) (SigningKey GenesisDelegateExtendedKey) -> KESPeriod -> OperationalCertificateIssueCounter -> Either OperationalCertIssueError (OperationalCertificate, OperationalCertificateIssueCounter)
- black :: Doc AnsiStyle -> Doc AnsiStyle
- cyan :: Doc AnsiStyle -> Doc AnsiStyle
- docToLazyText :: Doc AnsiStyle -> Text
- docToString :: Doc AnsiStyle -> String
- docToText :: Doc AnsiStyle -> Text
- magenta :: Doc AnsiStyle -> Doc AnsiStyle
- prettyException :: Exception a => a -> Doc ann
- pshow :: Show a => a -> Doc ann
- white :: Doc AnsiStyle -> Doc AnsiStyle
- yellow :: Doc AnsiStyle -> Doc AnsiStyle
- reflBlockType :: BlockType blk -> BlockType blk' -> Maybe (blk :~: blk')
- fromAlonzoCostModel :: CostModel -> CostModel
- fromLedgerPParams :: ShelleyBasedEra era -> PParams (ShelleyLedgerEra era) -> ProtocolParameters
- makePraosNonce :: ByteString -> PraosNonce
- makeShelleyUpdateProposal :: ProtocolParametersUpdate -> [Hash GenesisKey] -> EpochNo -> UpdateProposal
- toAlonzoCostModel :: CostModel -> Language -> Either ProtocolParametersConversionError CostModel
- toAlonzoCostModels :: Map AnyPlutusScriptVersion CostModel -> Either ProtocolParametersConversionError CostModels
- toLedgerPParams :: ShelleyBasedEra era -> ProtocolParameters -> Either ProtocolParametersConversionError (PParams (ShelleyLedgerEra era))
- getProgress :: SlotNo -> EraHistory -> Either PastHorizonException (RelativeTime, SlotLength)
- getSlotForRelativeTime :: RelativeTime -> EraHistory -> Either PastHorizonException SlotNo
- slotToEpoch :: SlotNo -> EraHistory -> Either PastHorizonException (EpochNo, SlotsInEpoch, SlotsToEpochEnd)
- toLedgerEpochInfo :: EraHistory -> LedgerEpochInfo
- queryAccountState :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch AccountState))
- queryChainBlockNo :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (WithOrigin BlockNo))
- queryChainPoint :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError ChainPoint)
- queryCommitteeMembersState :: ConwayEraOnwards era -> Set (Credential 'ColdCommitteeRole StandardCrypto) -> Set (Credential 'HotCommitteeRole StandardCrypto) -> Set MemberStatus -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (CommitteeMembersState StandardCrypto)))
- queryConstitution :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Constitution (ShelleyLedgerEra era))))
- queryConstitutionHash :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SafeHash (EraCrypto (ShelleyLedgerEra era)) AnchorData)))
- queryCurrentEpochState :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedCurrentEpochState era)))
- queryCurrentEra :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError AnyCardanoEra)
- queryDRepStakeDistribution :: ConwayEraOnwards era -> Set (DRep StandardCrypto) -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map (DRep StandardCrypto) Coin)))
- queryDRepState :: ConwayEraOnwards era -> Set (Credential 'DRepRole StandardCrypto) -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map (Credential 'DRepRole StandardCrypto) (DRepState StandardCrypto))))
- queryDebugLedgerState :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedDebugLedgerState era)))
- queryEpoch :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch EpochNo))
- queryGenesisParameters :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (GenesisParameters ShelleyEra)))
- queryGovState :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (GovState (ShelleyLedgerEra era))))
- queryPoolDistribution :: BabbageEraOnwards era -> Maybe (Set PoolId) -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedPoolDistribution era)))
- queryPoolState :: BabbageEraOnwards era -> Maybe (Set PoolId) -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedPoolState era)))
- queryProtocolParametersUpdate :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map (Hash GenesisKey) ProtocolParametersUpdate)))
- queryProtocolState :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (ProtocolState era)))
- queryStakeAddresses :: ShelleyBasedEra era -> Set StakeCredential -> NetworkId -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map StakeAddress Coin, Map StakeAddress PoolId)))
- queryStakeDelegDeposits :: BabbageEraOnwards era -> Set StakeCredential -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map StakeCredential Coin)))
- queryStakeDistribution :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map (Hash StakePoolKey) Rational)))
- queryStakePoolParameters :: ShelleyBasedEra era -> Set PoolId -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map PoolId StakePoolParameters)))
- queryStakeSnapshot :: BabbageEraOnwards era -> Maybe (Set PoolId) -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedStakeSnapshots era)))
- queryStakeVoteDelegatees :: ConwayEraOnwards era -> Set StakeCredential -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map StakeCredential (DRep StandardCrypto))))
- queryUtxo :: ShelleyBasedEra era -> QueryUTxOFilter -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (UTxO era)))
- mergeDelegsAndRewards :: DelegationsAndRewards -> [(StakeAddress, Maybe Coin, Maybe PoolId)]
- eraOfScriptInEra :: ScriptInEra era -> ShelleyBasedEra era
- eraOfScriptLanguageInEra :: ScriptLanguageInEra lang era -> ShelleyBasedEra era
- examplePlutusScriptAlwaysFails :: WitCtx witctx -> PlutusScript PlutusScriptV1
- examplePlutusScriptAlwaysSucceeds :: WitCtx witctx -> PlutusScript PlutusScriptV1
- hashScript :: Script lang -> ScriptHash
- languageOfScriptLanguageInEra :: ScriptLanguageInEra lang era -> ScriptLanguage lang
- scriptWitnessScript :: ScriptWitness witctx era -> Maybe (ScriptInEra era)
- toScriptInAnyLang :: Script lang -> ScriptInAnyLang
- toScriptInEra :: ShelleyBasedEra era -> ScriptInAnyLang -> Maybe (ScriptInEra era)
- getOriginalScriptDataBytes :: HashableScriptData -> ByteString
- getScriptData :: HashableScriptData -> ScriptData
- hashScriptDataBytes :: HashableScriptData -> Hash ScriptData
- scriptDataFromJson :: ScriptDataJsonSchema -> Value -> Either ScriptDataJsonError HashableScriptData
- scriptDataJsonToHashable :: ScriptDataJsonSchema -> Value -> Either ScriptDataJsonBytesError HashableScriptData
- scriptDataToJson :: ScriptDataJsonSchema -> HashableScriptData -> Value
- unsafeHashableScriptData :: ScriptData -> HashableScriptData
- validateScriptData :: ScriptData -> Either ScriptDataRangeError ()
- deserialiseAnyOfFromBech32 :: [FromSomeType SerialiseAsBech32 b] -> Text -> Either Bech32DecodeError b
- deserialiseFromBech32 :: SerialiseAsBech32 a => AsType a -> Text -> Either Bech32DecodeError a
- serialiseToBech32 :: SerialiseAsBech32 a => a -> Text
- deserialiseFromJSON :: FromJSON a => AsType a -> ByteString -> Either JsonDecodeError a
- prettyPrintJSON :: ToJSON a => a -> ByteString
- readFileJSON :: FromJSON a => AsType a -> FilePath -> IO (Either (FileError JsonDecodeError) a)
- serialiseToJSON :: ToJSON a => a -> ByteString
- writeFileJSON :: ToJSON a => FilePath -> a -> IO (Either (FileError ()) ())
- deserialiseByronTxCddl :: TextEnvelope -> Either TextEnvelopeCddlError (ATxAux ByteString)
- deserialiseFromTextEnvelopeCddlAnyOf :: [FromSomeTypeCDDL TextEnvelope b] -> TextEnvelope -> Either TextEnvelopeCddlError b
- deserialiseTxLedgerCddl :: ShelleyBasedEra era -> TextEnvelope -> Either TextEnvelopeError (Tx era)
- deserialiseWitnessLedgerCddl :: ShelleyBasedEra era -> TextEnvelope -> Either TextEnvelopeCddlError (KeyWitness era)
- readFileTextEnvelopeCddlAnyOf :: [FromSomeTypeCDDL TextEnvelope b] -> FilePath -> IO (Either (FileError TextEnvelopeCddlError) b)
- serialiseTxLedgerCddl :: ShelleyBasedEra era -> Tx era -> TextEnvelope
- serialiseWitnessLedgerCddl :: ShelleyBasedEra era -> KeyWitness era -> TextEnvelope
- writeTxFileTextEnvelopeCddl :: ShelleyBasedEra era -> File content 'Out -> Tx era -> IO (Either (FileError ()) ())
- writeTxWitnessFileTextEnvelopeCddl :: ShelleyBasedEra era -> File () 'Out -> KeyWitness era -> IO (Either (FileError ()) ())
- deserialiseFromRawBytesHex :: SerialiseAsRawBytes a => AsType a -> ByteString -> Either RawBytesHexError a
- serialiseToRawBytesHex :: SerialiseAsRawBytes a => a -> ByteString
- serialiseToRawBytesHexText :: SerialiseAsRawBytes a => a -> Text
- deserialiseFromTextEnvelope :: HasTextEnvelope a => AsType a -> TextEnvelope -> Either TextEnvelopeError a
- deserialiseFromTextEnvelopeAnyOf :: [FromSomeType HasTextEnvelope b] -> TextEnvelope -> Either TextEnvelopeError b
- readFileTextEnvelope :: HasTextEnvelope a => AsType a -> File content 'In -> IO (Either (FileError TextEnvelopeError) a)
- readFileTextEnvelopeAnyOf :: [FromSomeType HasTextEnvelope b] -> File content 'In -> IO (Either (FileError TextEnvelopeError) b)
- readTextEnvelopeFromFile :: FilePath -> IO (Either (FileError TextEnvelopeError) TextEnvelope)
- readTextEnvelopeOfTypeFromFile :: TextEnvelopeType -> FilePath -> IO (Either (FileError TextEnvelopeError) TextEnvelope)
- serialiseToTextEnvelope :: HasTextEnvelope a => Maybe TextEnvelopeDescr -> a -> TextEnvelope
- textEnvelopeRawCBOR :: TextEnvelope -> ByteString
- textEnvelopeToJSON :: HasTextEnvelope a => Maybe TextEnvelopeDescr -> a -> ByteString
- textEnvelopeTypeInEra :: HasTextEnvelope (f era) => CardanoEra era -> AsType (f era) -> TextEnvelopeType
- writeFileTextEnvelope :: HasTextEnvelope a => File content 'Out -> Maybe TextEnvelopeDescr -> a -> IO (Either (FileError ()) ())
- validateAndHashStakePoolMetadata :: ByteString -> Either StakePoolMetadataValidationError (StakePoolMetadata, Hash StakePoolMetadata)
- addTxIn :: (TxIn, BuildTxWith build (Witness WitCtxTxIn era)) -> TxBodyContent build era -> TxBodyContent build era
- addTxOut :: TxOut CtxTx era -> TxBodyContent build era -> TxBodyContent build era
- collectTxBodyScriptWitnesses :: ShelleyBasedEra era -> TxBodyContent BuildTx era -> [(ScriptWitnessIndex, AnyScriptWitness era)]
- defaultTxFee :: ShelleyBasedEra era -> TxFee era
- defaultTxValidityUpperBound :: ShelleyBasedEra era -> TxValidityUpperBound era
- fromLedgerTxOuts :: ShelleyBasedEra era -> TxBody (ShelleyLedgerEra era) -> TxBodyScriptData era -> [TxOut CtxTx era]
- genesisUTxOPseudoTxIn :: NetworkId -> Hash GenesisUTxOKey -> TxIn
- getReferenceInputsSizeForTxIds :: ShelleyLedgerEra era ~ ledgerera => BabbageEraOnwards era -> UTxO ledgerera -> Set TxIn -> Int
- getTxBodyContent :: TxBody era -> TxBodyContent ViewTx era
- getTxId :: TxBody era -> TxId
- getTxIdByron :: ATxAux ByteString -> TxId
- makeByronTransactionBody :: TxIns BuildTx ByronEra -> [TxOut CtxTx ByronEra] -> Either TxBodyError (Annotated Tx ByteString)
- modTxIns :: (TxIns build era -> TxIns build era) -> TxBodyContent build era -> TxBodyContent build era
- modTxOuts :: ([TxOut CtxTx era] -> [TxOut CtxTx era]) -> TxBodyContent build era -> TxBodyContent build era
- parseHash :: SerialiseAsRawBytes (Hash a) => AsType (Hash a) -> Parser (Hash a)
- renderScriptWitnessIndex :: ScriptWitnessIndex -> String
- setTxAuxScripts :: TxAuxScripts era -> TxBodyContent build era -> TxBodyContent build era
- setTxCertificates :: TxCertificates build era -> TxBodyContent build era -> TxBodyContent build era
- setTxCurrentTreasuryValue :: Maybe (Featured ConwayEraOnwards era Coin) -> TxBodyContent build era -> TxBodyContent build era
- setTxExtraKeyWits :: TxExtraKeyWitnesses era -> TxBodyContent build era -> TxBodyContent build era
- setTxFee :: TxFee era -> TxBodyContent build era -> TxBodyContent build era
- setTxIns :: TxIns build era -> TxBodyContent build era -> TxBodyContent build era
- setTxInsCollateral :: TxInsCollateral era -> TxBodyContent build era -> TxBodyContent build era
- setTxInsReference :: TxInsReference build era -> TxBodyContent build era -> TxBodyContent build era
- setTxMetadata :: TxMetadataInEra era -> TxBodyContent build era -> TxBodyContent build era
- setTxMintValue :: TxMintValue build era -> TxBodyContent build era -> TxBodyContent build era
- setTxOuts :: [TxOut CtxTx era] -> TxBodyContent build era -> TxBodyContent build era
- setTxProtocolParams :: BuildTxWith build (Maybe (LedgerProtocolParameters era)) -> TxBodyContent build era -> TxBodyContent build era
- setTxReturnCollateral :: TxReturnCollateral CtxTx era -> TxBodyContent build era -> TxBodyContent build era
- setTxScriptValidity :: TxScriptValidity era -> TxBodyContent build era -> TxBodyContent build era
- setTxTotalCollateral :: TxTotalCollateral era -> TxBodyContent build era -> TxBodyContent build era
- setTxTreasuryDonation :: Maybe (Featured ConwayEraOnwards era Coin) -> TxBodyContent build era -> TxBodyContent build era
- setTxUpdateProposal :: TxUpdateProposal era -> TxBodyContent build era -> TxBodyContent build era
- setTxValidityLowerBound :: TxValidityLowerBound era -> TxBodyContent build era -> TxBodyContent build era
- setTxValidityUpperBound :: TxValidityUpperBound era -> TxBodyContent build era -> TxBodyContent build era
- setTxWithdrawals :: TxWithdrawals build era -> TxBodyContent build era -> TxBodyContent build era
- toCtxUTxOTxOut :: TxOut CtxTx era -> TxOut CtxUTxO era
- txOutInAnyEra :: CardanoEra era -> TxOut CtxTx era -> TxOutInAnyEra
- txOutValueToLovelace :: TxOutValue era -> Coin
- getTxBody :: Tx era -> TxBody era
- getTxWitnesses :: Tx era -> [KeyWitness era]
- makeByronKeyWitness :: IsByronKey key => NetworkId -> Annotated Tx ByteString -> SigningKey key -> KeyWitness ByronEra
- makeShelleyBootstrapWitness :: ShelleyBasedEra era -> WitnessNetworkIdOrByronAddress -> TxBody era -> SigningKey ByronKey -> KeyWitness era
- makeSignedByronTransaction :: [KeyWitness era] -> Annotated Tx ByteString -> ATxAux ByteString
- makeSignedTransaction :: [KeyWitness era] -> TxBody era -> Tx era
- signByronTransaction :: NetworkId -> Annotated Tx ByteString -> [SigningKey ByronKey] -> ATxAux ByteString
- txScriptValidityToScriptValidity :: TxScriptValidity era -> ScriptValidity
- makeTransactionMetadata :: Map Word64 TxMetadataValue -> TxMetadata
- mergeTransactionMetadata :: (TxMetadataValue -> TxMetadataValue -> TxMetadataValue) -> TxMetadata -> TxMetadata -> TxMetadata
- metaBytesChunks :: ByteString -> TxMetadataValue
- metaTextChunks :: Text -> TxMetadataValue
- metadataFromJson :: TxMetadataJsonSchema -> Value -> Either TxMetadataJsonError TxMetadata
- metadataToJson :: TxMetadataJsonSchema -> TxMetadata -> Value
- metadataValueFromJsonNoSchema :: Value -> Either TxMetadataJsonSchemaError TxMetadataValue
- metadataValueToJsonNoSchema :: TxMetadataValue -> Value
- validateTxMetadata :: TxMetadata -> Either [(Word64, TxMetadataRangeError)] ()
- bounded :: (Bounded a, Integral a, Show a) => String -> ReadM a
- parseFilePath :: String -> String -> Parser FilePath
- textShow :: Show a => a -> Text
- unsafeBoundedRational :: (HasCallStack, Typeable r, BoundedRational r) => Rational -> r
- filterValue :: (AssetId -> Bool) -> Value -> Value
- lovelaceToQuantity :: Coin -> Quantity
- lovelaceToValue :: Coin -> Value
- negateValue :: Value -> Value
- quantityToLovelace :: Quantity -> Coin
- renderValuePretty :: Value -> Text
- scriptPolicyId :: Script lang -> PolicyId
- selectAsset :: Value -> AssetId -> Quantity
- selectLovelace :: Value -> Coin
- valueFromList :: [(AssetId, Quantity)] -> Value
- valueFromNestedRep :: ValueNestedRep -> Value
- valueToList :: Value -> [(AssetId, Quantity)]
- valueToLovelace :: Value -> Maybe Coin
- valueToNestedRep :: Value -> ValueNestedRep
- parseValue :: Parser Value
- vsep :: [Doc ann] -> Doc ann
- bimapExceptT :: forall (m :: Type -> Type) x y a b. Functor m => (x -> y) -> (a -> b) -> ExceptT x m a -> ExceptT y m b
- bracketExceptT :: forall (m :: Type -> Type) e a b c. Monad m => ExceptT e m a -> (a -> ExceptT e m b) -> (a -> ExceptT e m c) -> ExceptT e m c
- bracketExceptionT :: forall (m :: Type -> Type) e a c b. MonadMask m => ExceptT e m a -> (a -> ExceptT e m c) -> (a -> ExceptT e m b) -> ExceptT e m b
- catchExceptT :: (MonadCatch m, Exception e) => m a -> (e -> x) -> ExceptT x m a
- catchIOExceptT :: forall (m :: Type -> Type) a x. MonadIO m => IO a -> (IOException -> x) -> ExceptT x m a
- catchLeftT :: forall (m :: Type -> Type) e a. Monad m => ExceptT e m a -> (e -> ExceptT e m a) -> ExceptT e m a
- catchesExceptT :: (Foldable f, MonadCatch m) => m a -> f (Handler m x) -> ExceptT x m a
- exceptT :: Monad m => (x -> m b) -> (a -> m b) -> ExceptT x m a -> m b
- firstExceptT :: forall (m :: Type -> Type) x y a. Functor m => (x -> y) -> ExceptT x m a -> ExceptT y m a
- handleExceptT :: (MonadCatch m, Exception e) => (e -> x) -> m a -> ExceptT x m a
- handleIOExceptT :: forall (m :: Type -> Type) x a. MonadIO m => (IOException -> x) -> IO a -> ExceptT x m a
- handleLeftT :: forall (m :: Type -> Type) e a. Monad m => (e -> ExceptT e m a) -> ExceptT e m a -> ExceptT e m a
- handlesExceptT :: (Foldable f, MonadCatch m) => f (Handler m x) -> m a -> ExceptT x m a
- hoistEither :: forall (m :: Type -> Type) x a. Monad m => Either x a -> ExceptT x m a
- hoistExceptT :: (forall b. m b -> n b) -> ExceptT x m a -> ExceptT x n a
- hushM :: Monad m => Either e a -> (e -> m ()) -> m (Maybe a)
- newExceptT :: m (Either x a) -> ExceptT x m a
- onLeft :: forall e x (m :: Type -> Type) a. Monad m => (e -> ExceptT x m a) -> ExceptT x m (Either e a) -> ExceptT x m a
- onNothing :: forall x (m :: Type -> Type) a. Monad m => ExceptT x m a -> ExceptT x m (Maybe a) -> ExceptT x m a
- secondExceptT :: forall (m :: Type -> Type) a b x. Functor m => (a -> b) -> ExceptT x m a -> ExceptT x m b
- castHash :: CastHash roleA roleB => Hash roleA -> Hash roleB
- castSigningKey :: CastSigningKeyRole keyroleA keyroleB => SigningKey keyroleA -> SigningKey keyroleB
- castVerificationKey :: CastVerificationKeyRole keyroleA keyroleB => VerificationKey keyroleA -> VerificationKey keyroleB
- class Error e where
- prettyError :: e -> Doc ann
- data Doc ann
- class Pretty a where
- pretty :: a -> Doc ann
- prettyList :: [a] -> Doc ann
- 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 Block era where
- ByronBlock :: ByronBlock -> Block ByronEra
- ShelleyBlock :: forall era. ShelleyBasedEra era -> ShelleyBlock (ConsensusProtocol era) (ShelleyLedgerEra era) -> Block era
- class Monad m => MonadIO (m :: Type -> Type) where
- newtype File content (direction :: FileDirection) = File {}
- newtype ExceptT e (m :: Type -> Type) a = ExceptT (m (Either e a))
- type Except e = ExceptT e Identity
- class Monad m => MonadError e (m :: Type -> Type) | m -> e where
- throwError :: e -> m a
- catchError :: m a -> (e -> m a) -> m a
- class (forall (m :: Type -> Type). Monad m => Monad (t m)) => MonadTrans (t :: (Type -> Type) -> Type -> Type) where
- data ReferenceScript era where
- ReferenceScript :: forall era. BabbageEraOnwards era -> ScriptInAnyLang -> ReferenceScript era
- ReferenceScriptNone :: forall era. ReferenceScript era
- newtype LedgerProtocolParameters era = LedgerProtocolParameters {}
- data AddressInEra era where
- AddressInEra :: forall addrtype era. AddressTypeInEra addrtype era -> Address addrtype -> AddressInEra era
- data AddressTypeInEra addrtype era where
- ByronAddressInAnyEra :: forall era. AddressTypeInEra ByronAddr era
- ShelleyAddressInEra :: forall era. ShelleyBasedEra era -> AddressTypeInEra ShelleyAddr era
- data BalancedTxBody era = BalancedTxBody (TxBodyContent BuildTx era) (TxBody era) (TxOut CtxTx era) Coin
- data KeyWitness era where
- ShelleyBootstrapWitness :: forall era. ShelleyBasedEra era -> BootstrapWitness StandardCrypto -> KeyWitness era
- ShelleyKeyWitness :: forall era. ShelleyBasedEra era -> WitVKey 'Witness StandardCrypto -> KeyWitness era
- data PlutusScript lang where
- PlutusScriptSerialised :: forall lang. ShortByteString -> PlutusScript lang
- data Script lang where
- SimpleScript :: !SimpleScript -> Script SimpleScript'
- PlutusScript :: forall lang. !(PlutusScriptVersion lang) -> !(PlutusScript lang) -> Script lang
- data ScriptInEra era where
- ScriptInEra :: forall lang era. ScriptLanguageInEra lang era -> Script lang -> ScriptInEra era
- data ScriptLanguage lang where
- SimpleScriptLanguage :: ScriptLanguage SimpleScript'
- PlutusScriptLanguage :: forall lang. PlutusScriptVersion lang -> ScriptLanguage lang
- data ScriptWitness witctx era where
- SimpleScriptWitness :: forall era witctx. ScriptLanguageInEra SimpleScript' era -> SimpleScriptOrReferenceInput SimpleScript' -> ScriptWitness witctx era
- PlutusScriptWitness :: forall lang era witctx. ScriptLanguageInEra lang era -> PlutusScriptVersion lang -> PlutusScriptOrReferenceInput lang -> ScriptDatum witctx -> ScriptRedeemer -> ExecutionUnits -> ScriptWitness witctx era
- data Tx era where
- ShelleyTx :: forall era. ShelleyBasedEra era -> Tx (ShelleyLedgerEra era) -> Tx era
- pattern Tx :: TxBody era -> [KeyWitness era] -> Tx era
- data TxAuxScripts era where
- TxAuxScriptsNone :: forall era. TxAuxScripts era
- TxAuxScripts :: forall era. AllegraEraOnwards era -> [ScriptInEra era] -> TxAuxScripts era
- 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
- pattern TxBody :: TxBodyContent ViewTx era -> TxBody era
- data TxBodyContent build era = TxBodyContent {
- txIns :: TxIns build era
- txInsCollateral :: TxInsCollateral era
- txInsReference :: TxInsReference build era
- txOuts :: [TxOut CtxTx era]
- txTotalCollateral :: TxTotalCollateral era
- txReturnCollateral :: TxReturnCollateral CtxTx era
- txFee :: TxFee era
- txValidityLowerBound :: TxValidityLowerBound era
- txValidityUpperBound :: TxValidityUpperBound era
- txMetadata :: TxMetadataInEra era
- txAuxScripts :: TxAuxScripts era
- txExtraKeyWits :: TxExtraKeyWitnesses era
- txProtocolParams :: BuildTxWith build (Maybe (LedgerProtocolParameters era))
- txWithdrawals :: TxWithdrawals build era
- txCertificates :: TxCertificates build era
- txUpdateProposal :: TxUpdateProposal era
- txMintValue :: TxMintValue build era
- txScriptValidity :: TxScriptValidity era
- txProposalProcedures :: Maybe (Featured ConwayEraOnwards era (TxProposalProcedures build era))
- txVotingProcedures :: Maybe (Featured ConwayEraOnwards era (TxVotingProcedures build era))
- txCurrentTreasuryValue :: Maybe (Featured ConwayEraOnwards era Coin)
- txTreasuryDonation :: Maybe (Featured ConwayEraOnwards era Coin)
- data TxBodyScriptData era where
- TxBodyNoScriptData :: forall era. TxBodyScriptData era
- TxBodyScriptData :: forall era. AlonzoEraOnwardsConstraints era => AlonzoEraOnwards era -> TxDats (ShelleyLedgerEra era) -> Redeemers (ShelleyLedgerEra era) -> TxBodyScriptData era
- data TxExtraKeyWitnesses era where
- TxExtraKeyWitnessesNone :: forall era. TxExtraKeyWitnesses era
- TxExtraKeyWitnesses :: forall era. AlonzoEraOnwards era -> [Hash PaymentKey] -> TxExtraKeyWitnesses era
- data TxFee era where
- TxFeeExplicit :: forall era. ShelleyBasedEra era -> Coin -> TxFee era
- type TxIns build era = [(TxIn, BuildTxWith build (Witness WitCtxTxIn era))]
- data TxInsCollateral era where
- TxInsCollateralNone :: forall era. TxInsCollateral era
- TxInsCollateral :: forall era. AlonzoEraOnwards era -> [TxIn] -> TxInsCollateral era
- data TxInsReference build era where
- TxInsReferenceNone :: forall build era. TxInsReference build era
- TxInsReference :: forall era build. BabbageEraOnwards era -> [TxIn] -> TxInsReference build era
- data TxMetadataInEra era where
- TxMetadataNone :: forall era. TxMetadataInEra era
- TxMetadataInEra :: forall era. ShelleyBasedEra era -> TxMetadata -> TxMetadataInEra era
- data TxMintValue build era where
- TxMintNone :: forall build era. TxMintValue build era
- TxMintValue :: forall era build. MaryEraOnwards era -> Value -> BuildTxWith build (Map PolicyId (ScriptWitness WitCtxMint era)) -> TxMintValue build era
- data TxOut ctx era = TxOut (AddressInEra era) (TxOutValue era) (TxOutDatum ctx era) (ReferenceScript era)
- data TxOutDatum ctx era where
- TxOutDatumNone :: forall ctx era. TxOutDatum ctx era
- TxOutDatumHash :: forall era ctx. AlonzoEraOnwards era -> Hash ScriptData -> TxOutDatum ctx era
- TxOutDatumInline :: forall era ctx. BabbageEraOnwards era -> HashableScriptData -> TxOutDatum ctx era
- pattern TxOutDatumInTx :: AlonzoEraOnwards era -> HashableScriptData -> TxOutDatum CtxTx era
- data TxScriptValidity era where
- TxScriptValidityNone :: forall era. TxScriptValidity era
- TxScriptValidity :: forall era. AlonzoEraOnwards era -> ScriptValidity -> TxScriptValidity era
- data TxValidityLowerBound era where
- TxValidityNoLowerBound :: forall era. TxValidityLowerBound era
- TxValidityLowerBound :: forall era. AllegraEraOnwards era -> SlotNo -> TxValidityLowerBound era
- data TxValidityUpperBound era where
- TxValidityUpperBound :: forall era. ShelleyBasedEra era -> Maybe SlotNo -> TxValidityUpperBound era
- data Witness witctx era where
- KeyWitness :: forall witctx era. KeyWitnessInCtx witctx -> Witness witctx era
- ScriptWitness :: forall witctx era. ScriptWitnessInCtx witctx -> ScriptWitness witctx era -> Witness witctx era
- data Address addrtype where
- ShelleyAddress :: Network -> PaymentCredential StandardCrypto -> StakeReference StandardCrypto -> Address ShelleyAddr
- data AcquiringFailure
- data family Hash keyrole
- data PlutusScriptOrReferenceInput lang
- = PScript (PlutusScript lang)
- | PReferenceScript TxIn (Maybe ScriptHash)
- type PoolId = Hash StakePoolKey
- 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
- type family ShelleyLedgerEra era = (ledgerera :: Type) | ledgerera -> era where ...
- data family SigningKey keyrole
- data family VerificationKey keyrole
- data BlockHeader = BlockHeader !SlotNo !(Hash BlockHeader) !BlockNo
- data ChainPoint
- data CtxTx
- data CtxUTxO
- data ExecutionUnits = ExecutionUnits {}
- data NetworkId
- newtype PolicyId = PolicyId {}
- data ScriptData
- data ScriptDatum witctx where
- newtype ScriptHash = ScriptHash (ScriptHash StandardCrypto)
- newtype TxId = TxId (Hash StandardCrypto EraIndependentTxBody)
- data TxIn = TxIn TxId TxIx
- data TxOutValue era where
- TxOutValueByron :: forall era. Coin -> TxOutValue era
- TxOutValueShelleyBased :: forall era. (Eq (Value (ShelleyLedgerEra era)), Show (Value (ShelleyLedgerEra era))) => ShelleyBasedEra era -> Value (ShelleyLedgerEra era) -> TxOutValue era
- data Value
- class FromJSON a
- class ToJSON a
- class Typeable a => FromCBOR a
- class Typeable a => ToCBOR a
- data PaymentKey
- data ConwayEra
- data AddressAny
- data ByronAddr
- data PaymentCredential
- class HasTypeProxy addr => SerialiseAddress addr where
- serialiseAddress :: addr -> Text
- deserialiseAddress :: AsType addr -> Text -> Maybe addr
- data ShelleyAddr
- data StakeAddress where
- StakeAddress :: Network -> StakeCredential StandardCrypto -> StakeAddress
- newtype StakeAddressPointer = StakeAddressPointer {
- unStakeAddressPointer :: Ptr
- data StakeAddressReference
- data StakeCredential
- newtype AnchorDataHash = AnchorDataHash {
- unAnchorDataHash :: SafeHash StandardCrypto AnchorData
- newtype AnchorUrl = AnchorUrl {
- unAnchorUrl :: Url
- data BlockInMode where
- BlockInMode :: forall era. CardanoEra era -> Block era -> BlockInMode
- data ChainTip
- data Certificate era where
- ShelleyRelatedCertificate :: forall era. ShelleyToBabbageEra era -> ShelleyTxCert (ShelleyLedgerEra era) -> Certificate era
- ConwayCertificate :: forall era. ConwayEraOnwards era -> ConwayTxCert (ShelleyLedgerEra era) -> Certificate era
- data CommitteeColdkeyResignationRequirements era where
- CommitteeColdkeyResignationRequirements :: forall era. ConwayEraOnwards era -> Credential 'ColdCommitteeRole (EraCrypto (ShelleyLedgerEra era)) -> Maybe (Anchor (EraCrypto (ShelleyLedgerEra era))) -> CommitteeColdkeyResignationRequirements era
- data CommitteeHotKeyAuthorizationRequirements era where
- CommitteeHotKeyAuthorizationRequirements :: forall era. ConwayEraOnwards era -> Credential 'ColdCommitteeRole (EraCrypto (ShelleyLedgerEra era)) -> Credential 'HotCommitteeRole (EraCrypto (ShelleyLedgerEra era)) -> CommitteeHotKeyAuthorizationRequirements era
- data DRepMetadataReference = DRepMetadataReference Text (Hash DRepMetadata)
- data DRepRegistrationRequirements era where
- DRepRegistrationRequirements :: forall era. ConwayEraOnwards era -> Credential 'DRepRole (EraCrypto (ShelleyLedgerEra era)) -> Coin -> DRepRegistrationRequirements era
- data DRepUnregistrationRequirements era where
- DRepUnregistrationRequirements :: forall era. ConwayEraOnwards era -> Credential 'DRepRole (EraCrypto (ShelleyLedgerEra era)) -> Coin -> DRepUnregistrationRequirements era
- data DRepUpdateRequirements era where
- DRepUpdateRequirements :: forall era. ConwayEraOnwards era -> Credential 'DRepRole (EraCrypto (ShelleyLedgerEra era)) -> DRepUpdateRequirements era
- data GenesisKeyDelegationRequirements ere where
- GenesisKeyDelegationRequirements :: forall ere. ShelleyToBabbageEra ere -> Hash GenesisKey -> Hash GenesisDelegateKey -> Hash VrfKey -> GenesisKeyDelegationRequirements ere
- data MirCertificateRequirements era where
- MirCertificateRequirements :: forall era. ShelleyToBabbageEra era -> MIRPot -> MIRTarget (EraCrypto (ShelleyLedgerEra era)) -> MirCertificateRequirements era
- data StakeAddressRequirements era where
- StakeAddrRegistrationConway :: forall era. ConwayEraOnwards era -> Coin -> StakeCredential -> StakeAddressRequirements era
- StakeAddrRegistrationPreConway :: forall era. ShelleyToBabbageEra era -> StakeCredential -> StakeAddressRequirements era
- data StakeDelegationRequirements era where
- StakeDelegationRequirementsConwayOnwards :: forall era. ConwayEraOnwards era -> StakeCredential -> Delegatee (EraCrypto (ShelleyLedgerEra era)) -> StakeDelegationRequirements era
- StakeDelegationRequirementsPreConway :: forall era. ShelleyToBabbageEra era -> StakeCredential -> PoolId -> StakeDelegationRequirements era
- data StakePoolMetadataReference = StakePoolMetadataReference {}
- data StakePoolParameters = StakePoolParameters {}
- data StakePoolRegistrationRequirements era where
- StakePoolRegistrationRequirementsConwayOnwards :: forall era. ConwayEraOnwards era -> PoolParams (EraCrypto (ShelleyLedgerEra era)) -> StakePoolRegistrationRequirements era
- StakePoolRegistrationRequirementsPreConway :: forall era. ShelleyToBabbageEra era -> PoolParams (EraCrypto (ShelleyLedgerEra era)) -> StakePoolRegistrationRequirements era
- data StakePoolRelay
- = StakePoolRelayIp (Maybe IPv4) (Maybe IPv6) (Maybe PortNumber)
- | StakePoolRelayDnsARecord ByteString (Maybe PortNumber)
- | StakePoolRelayDnsSrvRecord ByteString
- data StakePoolRetirementRequirements era where
- StakePoolRetirementRequirementsConwayOnwards :: forall era. ConwayEraOnwards era -> PoolId -> EpochNo -> StakePoolRetirementRequirements era
- StakePoolRetirementRequirementsPreConway :: forall era. ShelleyToBabbageEra era -> PoolId -> EpochNo -> StakePoolRetirementRequirements era
- newtype ScriptLockedTxInsError = ScriptLockedTxIns [TxIn]
- data TxInsExistError
- = TxInsDoNotExist [TxIn]
- | EmptyUTxO
- data QueryConvenienceError
- newtype TxCurrentTreasuryValue = TxCurrentTreasuryValue {}
- newtype DRepMetadata = DRepMetadata ByteString
- data InputDecodeError
- data InputFormat a where
- InputFormatBech32 :: forall a. SerialiseAsBech32 a => InputFormat a
- InputFormatHex :: forall a. SerialiseAsRawBytes a => InputFormat a
- InputFormatTextEnvelope :: forall a. HasTextEnvelope a => InputFormat a
- data SomeAddressVerificationKey
- = AByronVerificationKey (VerificationKey ByronKey)
- | APaymentVerificationKey (VerificationKey PaymentKey)
- | APaymentExtendedVerificationKey (VerificationKey PaymentExtendedKey)
- | AGenesisUTxOVerificationKey (VerificationKey GenesisUTxOKey)
- | AGenesisExtendedVerificationKey (VerificationKey GenesisExtendedKey)
- | AGenesisDelegateExtendedVerificationKey (VerificationKey GenesisDelegateExtendedKey)
- | AKesVerificationKey (VerificationKey KesKey)
- | AVrfVerificationKey (VerificationKey VrfKey)
- | AStakeVerificationKey (VerificationKey StakeKey)
- | AStakeExtendedVerificationKey (VerificationKey StakeExtendedKey)
- | ADRepVerificationKey (VerificationKey DRepKey)
- | ADRepExtendedVerificationKey (VerificationKey DRepExtendedKey)
- | ACommitteeColdVerificationKey (VerificationKey CommitteeColdKey)
- | ACommitteeColdExtendedVerificationKey (VerificationKey CommitteeColdExtendedKey)
- | ACommitteeHotVerificationKey (VerificationKey CommitteeHotKey)
- | ACommitteeHotExtendedVerificationKey (VerificationKey CommitteeHotExtendedKey)
- data AllegraEraOnwards era where
- class IsAllegraBasedEra era where
- allegraBasedEra :: AllegraEraOnwards era
- data AlonzoEraOnwards era where
- class IsAlonzoBasedEra era where
- alonzoBasedEra :: AlonzoEraOnwards era
- data BabbageEraOnwards era where
- class IsBabbageBasedEra era where
- babbageBasedEra :: BabbageEraOnwards era
- data ByronToAlonzoEra era where
- data ConwayEraOnwards era where
- class IsConwayBasedEra era where
- conwayBasedEra :: ConwayEraOnwards era
- class IsMaryBasedEra era where
- maryBasedEra :: MaryEraOnwards era
- data MaryEraOnwards era where
- data AnyShelleyBasedEra where
- AnyShelleyBasedEra :: forall era. Typeable era => ShelleyBasedEra era -> AnyShelleyBasedEra
- data InAnyShelleyBasedEra (thing :: Type -> Type) where
- InAnyShelleyBasedEra :: forall era (thing :: Type -> Type). Typeable era => ShelleyBasedEra era -> thing era -> InAnyShelleyBasedEra thing
- class IsCardanoEra era => IsShelleyBasedEra era where
- shelleyBasedEra :: ShelleyBasedEra era
- data ShelleyBasedEra era where
- ShelleyBasedEraShelley :: ShelleyBasedEra ShelleyEra
- ShelleyBasedEraAllegra :: ShelleyBasedEra AllegraEra
- ShelleyBasedEraMary :: ShelleyBasedEra MaryEra
- ShelleyBasedEraAlonzo :: ShelleyBasedEra AlonzoEra
- ShelleyBasedEraBabbage :: ShelleyBasedEra BabbageEra
- ShelleyBasedEraConway :: ShelleyBasedEra ConwayEra
- data ShelleyEraOnly era where
- data ShelleyToAllegraEra era where
- data ShelleyToAlonzoEra era where
- data ShelleyToBabbageEra era where
- data ShelleyToMaryEra era where
- data AllegraEra
- data AlonzoEra
- data AnyCardanoEra where
- AnyCardanoEra :: forall era. Typeable era => CardanoEra era -> AnyCardanoEra
- data BabbageEra
- data ByronEra
- data CardanoEra era where
- data MaryEra
- data ShelleyEra
- class Eon (eon :: Type -> Type) where
- inEonForEra :: a -> (eon era -> a) -> CardanoEra era -> a
- data EraInEon (eon :: Type -> Type) where
- data InAnyCardanoEra (thing :: Type -> Type) where
- InAnyCardanoEra :: forall era (thing :: Type -> Type). Typeable era => CardanoEra era -> thing era -> InAnyCardanoEra thing
- class HasTypeProxy era => IsCardanoEra era where
- cardanoEra :: CardanoEra era
- class ToCardanoEra (eon :: Type -> Type) where
- toCardanoEra :: eon era -> CardanoEra era
- data FileError e
- data Featured (eon :: Type -> Type) era a where
- data AutoBalanceError era
- data FeeEstimationMode era
- newtype RequiredByronKeyWitnesses = RequiredByronKeyWitnesses {}
- newtype RequiredShelleyKeyWitnesses = RequiredShelleyKeyWitnesses {}
- data ResolvablePointers where
- ResolvablePointers :: forall era. (Era (ShelleyLedgerEra era), Show (PlutusPurpose AsIx (ShelleyLedgerEra era)), Show (PlutusPurpose AsItem (ShelleyLedgerEra era)), Show (PlutusScript (ShelleyLedgerEra era))) => ShelleyBasedEra era -> !(Map (PlutusPurpose AsIx (ShelleyLedgerEra era)) (PlutusPurpose AsItem (ShelleyLedgerEra era), Maybe (PlutusScriptBytes, Language), ScriptHash StandardCrypto)) -> ResolvablePointers
- data ScriptExecutionError
- = ScriptErrorMissingTxIn TxIn
- | ScriptErrorTxInWithoutDatum TxIn
- | ScriptErrorWrongDatum (Hash ScriptData)
- | ScriptErrorEvaluationFailed EvaluationError [Text]
- | ScriptErrorExecutionUnitsOverflow
- | ScriptErrorNotPlutusWitnessedTxIn ScriptWitnessIndex ScriptHash
- | ScriptErrorRedeemerPointsToUnknownScriptHash ScriptWitnessIndex
- | ScriptErrorMissingScript ScriptWitnessIndex ResolvablePointers
- | ScriptErrorMissingCostModel Language
- | (EraPlutusContext (ShelleyLedgerEra era), Show (ContextError (ShelleyLedgerEra era))) => ScriptErrorTranslationError (ContextError (ShelleyLedgerEra era))
- newtype TotalReferenceScriptsSize = TotalReferenceScriptsSize {}
- data TransactionValidityError era where
- TransactionValidityIntervalError :: forall era. PastHorizonException -> TransactionValidityError era
- TransactionValidityCostModelError :: forall era. Map AnyPlutusScriptVersion CostModel -> String -> TransactionValidityError era
- data TxBodyErrorAutoBalance era
- = TxBodyError TxBodyError
- | TxBodyScriptExecutionError [(ScriptWitnessIndex, ScriptExecutionError)]
- | TxBodyScriptBadScriptValidity
- | TxBodyErrorAdaBalanceNegative Coin
- | TxBodyErrorAdaBalanceTooSmall TxOutInAnyEra Coin Coin
- | TxBodyErrorByronEraNotSupported
- | TxBodyErrorMissingParamMinUTxO
- | TxBodyErrorValidityInterval (TransactionValidityError era)
- | TxBodyErrorMinUTxONotMet TxOutInAnyEra Coin
- | TxBodyErrorNonAdaAssetsUnbalanced Value
- | TxBodyErrorScriptWitnessIndexMissingFromExecUnitsMap ScriptWitnessIndex (Map ScriptWitnessIndex ExecutionUnits)
- data TxBodyError
- = TxBodyEmptyTxIns
- | TxBodyEmptyTxInsCollateral
- | TxBodyEmptyTxOuts
- | TxBodyOutputNegative !Quantity !TxOutInAnyEra
- | TxBodyOutputOverflow !Quantity !TxOutInAnyEra
- | TxBodyMetadataError ![(Word64, TxMetadataRangeError)]
- | TxBodyMintAdaError
- | TxBodyInIxOverflow !TxIn
- | TxBodyMissingProtocolParams
- | TxBodyProtocolParamsConversionError !ProtocolParametersConversionError
- data TxFeeEstimationError era
- = TxFeeEstimationTransactionTranslationError (TransactionValidityError era)
- | TxFeeEstimationScriptExecutionError (TxBodyErrorAutoBalance era)
- | TxFeeEstimationBalanceError (TxBodyErrorAutoBalance era)
- | TxFeeEstimationxBodyError TxBodyError
- | TxFeeEstimationFinalConstructionError TxBodyError
- | TxFeeEstimationOnlyMaryOnwardsSupportedError
- type AlonzoGenesisFile = File AlonzoGenesisConfig
- type ByronGenesisFile = File ByronGenesisConfig
- type ConwayGenesisFile = File ConwayGenesisConfig
- newtype GenesisHashAlonzo = GenesisHashAlonzo {
- unGenesisHashAlonzo :: Hash Blake2b_256 ByteString
- newtype GenesisHashConway = GenesisHashConway {
- unGenesisHashConway :: Hash Blake2b_256 ByteString
- newtype GenesisHashShelley = GenesisHashShelley {
- unGenesisHashShelley :: Hash Blake2b_256 ByteString
- data ShelleyConfig = ShelleyConfig {}
- type ShelleyGenesisFile = File ShelleyGenesisConfig
- data GenesisParameters era = GenesisParameters {
- protocolParamSystemStart :: UTCTime
- protocolParamNetworkId :: NetworkId
- protocolParamActiveSlotsCoefficient :: Rational
- protocolParamSecurity :: Int
- protocolParamEpochLength :: EpochSize
- protocolParamSlotLength :: NominalDiffTime
- protocolParamSlotsPerKESPeriod :: Int
- protocolParamMaxKESEvolutions :: Int
- protocolParamUpdateQuorum :: Int
- protocolParamMaxLovelaceSupply :: Coin
- protocolInitialUpdateableProtocolParameters :: PParams (ShelleyLedgerEra era)
- class Typeable t => HasTypeProxy t where
- data AsType t
- proxyToAsType :: Proxy t -> AsType t
- data family AsType t
- class AsTxMetadata a where
- asTxMetadata :: a -> TxMetadata
- data FromSomeType (c :: Type -> Constraint) b where
- FromSomeType :: forall (c :: Type -> Constraint) a b. c a => AsType a -> (a -> b) -> FromSomeType c b
- data FileDirection
- type SocketPath = File Socket 'InOut
- data LocalChainSyncClient block point tip (m :: Type -> Type)
- = NoLocalChainSyncClient
- | LocalChainSyncClientPipelined (ChainSyncClientPipelined block point tip m ())
- | LocalChainSyncClient (ChainSyncClient block point tip m ())
- data LocalNodeClientParams where
- LocalNodeClientParamsSingleBlock :: forall block. (ProtocolClient block, LedgerSupportsProtocol (ShelleyBlock (TPraos StandardCrypto) (ShelleyEra StandardCrypto))) => ProtocolClientInfoArgs block -> (NodeToClientVersion -> LocalNodeClientProtocolsForBlock block) -> LocalNodeClientParams
- LocalNodeClientParamsCardano :: forall block. (ProtocolClient block, CardanoHardForkConstraints (ConsensusCryptoForBlock block)) => ProtocolClientInfoArgs block -> (NodeToClientVersion -> LocalNodeClientProtocolsForBlock block) -> LocalNodeClientParams
- data LocalNodeClientProtocols block point tip slot tx txid txerr (query :: Type -> Type) (m :: Type -> Type) = LocalNodeClientProtocols {
- localChainSyncClient :: LocalChainSyncClient block point tip m
- localTxSubmissionClient :: Maybe (LocalTxSubmissionClient tx txerr m ())
- localStateQueryClient :: Maybe (LocalStateQueryClient block point query m ())
- localTxMonitoringClient :: Maybe (LocalTxMonitorClient txid tx slot m ())
- type LocalNodeClientProtocolsInMode = LocalNodeClientProtocols BlockInMode ChainPoint ChainTip SlotNo TxInMode TxIdInMode TxValidationErrorInCardanoMode QueryInMode IO
- data LocalNodeConnectInfo = LocalNodeConnectInfo {}
- data LocalTxMonitoringQuery
- data LocalTxMonitoringResult
- data LocalStateQueryExpr block point (query :: Type -> Type) r (m :: Type -> Type) a
- data UnsupportedNtcVersionError = UnsupportedNtcVersionError !MinNodeToClientVersion !NodeToClientVersion
- data TxIdInMode where
- TxIdInMode :: forall era. CardanoEra era -> TxId -> TxIdInMode
- data TxInMode where
- TxInMode :: forall era. ShelleyBasedEra era -> Tx era -> TxInMode
- TxInByronSpecial :: GenTx ByronBlock -> TxInMode
- data TxValidationErrorInCardanoMode where
- TxValidationErrorInCardanoMode :: forall era. TxValidationError era -> TxValidationErrorInCardanoMode
- TxValidationEraMismatch :: EraMismatch -> TxValidationErrorInCardanoMode
- data ByronKey
- data ByronKeyLegacy
- data CommitteeColdExtendedKey
- data CommitteeColdKey
- data CommitteeHotExtendedKey
- data CommitteeHotKey
- data DRepExtendedKey
- data DRepKey
- data GenesisDelegateExtendedKey
- data GenesisDelegateKey
- data GenesisExtendedKey
- data GenesisKey
- data GenesisUTxOKey
- data PaymentExtendedKey
- data StakeExtendedKey
- data StakeKey
- data AnyNewEpochState where
- AnyNewEpochState :: forall era. ShelleyBasedEra era -> NewEpochState (ShelleyLedgerEra era) -> AnyNewEpochState
- data ConditionResult
- data Env = Env {
- envLedgerConfig :: CardanoLedgerConfig StandardCrypto
- envConsensusConfig :: CardanoConsensusConfig StandardCrypto
- data FoldBlocksError
- data FoldStatus
- data GenesisConfig = GenesisCardano !NodeConfig !Config !GenesisHashShelley !(TransitionConfig (LatestKnownEra StandardCrypto))
- data GenesisConfigError
- = NEError !Text
- | NEByronConfig !FilePath !ConfigurationError
- | NEShelleyConfig !FilePath !Text
- | NEAlonzoConfig !FilePath !Text
- | NEConwayConfig !FilePath !Text
- | NECardanoConfig !Text
- data InitialLedgerStateError
- newtype LedgerState where
- LedgerState {
- clsState :: CardanoLedgerState StandardCrypto
- pattern LedgerStateAllegra :: LedgerState StandardAllegraBlock -> LedgerState
- pattern LedgerStateAlonzo :: LedgerState StandardAlonzoBlock -> LedgerState
- pattern LedgerStateBabbage :: LedgerState StandardBabbageBlock -> LedgerState
- pattern LedgerStateByron :: LedgerState ByronBlock -> LedgerState
- pattern LedgerStateConway :: LedgerState StandardConwayBlock -> LedgerState
- pattern LedgerStateMary :: LedgerState StandardMaryBlock -> LedgerState
- pattern LedgerStateShelley :: LedgerState StandardShelleyBlock -> LedgerState
- LedgerState {
- data LedgerStateError
- = ApplyBlockHashMismatch Text
- | ApplyBlockError (CardanoLedgerError StandardCrypto)
- | InvalidRollback SlotNo ChainPoint
- | TerminationEpochReached EpochNo
- | UnexpectedLedgerState AnyShelleyBasedEra (CardanoLedgerState StandardCrypto)
- | ByronEraUnsupported
- | DebugError !String
- data NodeConfig = NodeConfig {
- ncPBftSignatureThreshold :: !(Maybe Double)
- ncByronGenesisFile :: !(File ByronGenesisConfig 'In)
- ncByronGenesisHash :: !GenesisHashByron
- ncShelleyGenesisFile :: !(File ShelleyGenesisConfig 'In)
- ncShelleyGenesisHash :: !GenesisHashShelley
- ncAlonzoGenesisFile :: !(File AlonzoGenesis 'In)
- ncAlonzoGenesisHash :: !GenesisHashAlonzo
- ncConwayGenesisFile :: !(Maybe (File ConwayGenesisConfig 'In))
- ncConwayGenesisHash :: !(Maybe GenesisHashConway)
- ncRequiresNetworkMagic :: !RequiresNetworkMagic
- ncByronProtocolVersion :: !ProtocolVersion
- ncHardForkTriggers :: !CardanoHardForkTriggers
- type NodeConfigFile = File NodeConfig
- data ValidationMode
- type family ChainDepStateProtocol era where ...
- type family ConsensusBlockForEra era where ...
- data ConsensusModeParams where
- type family ConsensusProtocol era where ...
- type MonadIOTransError e (t :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) = (MonadIO m, MonadIO (t m), MonadCatch m, MonadTrans t, MonadError e (t m))
- type MonadTransError e (t :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) = (Monad m, MonadTrans t, MonadError e (t m))
- data OperationalCertIssueError = OperationalCertKeyMismatch (VerificationKey StakePoolKey) (VerificationKey StakePoolKey)
- data OperationalCertificate = OperationalCertificate !(OCert StandardCrypto) !(VerificationKey StakePoolKey)
- data OperationalCertificateIssueCounter = OperationalCertificateIssueCounter {}
- type Ann = AnsiStyle
- data BlockType blk where
- ByronBlockType :: BlockType (HardForkBlock '[ByronBlock])
- ShelleyBlockType :: BlockType (HardForkBlock '[ShelleyBlock (TPraos StandardCrypto) StandardShelley])
- CardanoBlockType :: BlockType (HardForkBlock (CardanoEras StandardCrypto))
- class (RunNode blk, IOLike m) => Protocol (m :: Type -> Type) blk where
- data ProtocolInfoArgs blk
- protocolInfo :: ProtocolInfoArgs blk -> (ProtocolInfo blk, m [BlockForging m blk])
- data family ProtocolInfoArgs blk
- data SomeBlockType where
- SomeBlockType :: forall blk. BlockType blk -> SomeBlockType
- newtype CostModel = CostModel [Int64]
- data ExecutionUnitPrices = ExecutionUnitPrices {}
- data PraosNonce
- data ProtocolParametersConversionError
- = PpceOutOfBounds !ProtocolParameterName !Rational
- | PpceVersionInvalid !ProtocolParameterVersion
- | PpceInvalidCostModel !CostModel !CostModelApplyError
- | PpceMissingParameter !ProtocolParameterName
- data ProtocolParametersUpdate = ProtocolParametersUpdate {
- protocolUpdateProtocolVersion :: Maybe (Natural, Natural)
- protocolUpdateDecentralization :: Maybe Rational
- protocolUpdateExtraPraosEntropy :: Maybe (Maybe PraosNonce)
- protocolUpdateMaxBlockHeaderSize :: Maybe Word16
- protocolUpdateMaxBlockBodySize :: Maybe Word32
- protocolUpdateMaxTxSize :: Maybe Word32
- protocolUpdateTxFeeFixed :: Maybe Coin
- protocolUpdateTxFeePerByte :: Maybe Coin
- protocolUpdateMinUTxOValue :: Maybe Coin
- protocolUpdateStakeAddressDeposit :: Maybe Coin
- protocolUpdateStakePoolDeposit :: Maybe Coin
- protocolUpdateMinPoolCost :: Maybe Coin
- protocolUpdatePoolRetireMaxEpoch :: Maybe EpochInterval
- protocolUpdateStakePoolTargetNum :: Maybe Natural
- protocolUpdatePoolPledgeInfluence :: Maybe Rational
- protocolUpdateMonetaryExpansion :: Maybe Rational
- protocolUpdateTreasuryCut :: Maybe Rational
- protocolUpdateCostModels :: Map AnyPlutusScriptVersion CostModel
- protocolUpdatePrices :: Maybe ExecutionUnitPrices
- protocolUpdateMaxTxExUnits :: Maybe ExecutionUnits
- protocolUpdateMaxBlockExUnits :: Maybe ExecutionUnits
- protocolUpdateMaxValueSize :: Maybe Natural
- protocolUpdateCollateralPercent :: Maybe Natural
- protocolUpdateMaxCollateralInputs :: Maybe Natural
- protocolUpdateUTxOCostPerByte :: Maybe Coin
- data UpdateProposal = UpdateProposal !(Map (Hash GenesisKey) ProtocolParametersUpdate) !EpochNo
- data EraHistory where
- EraHistory :: forall (xs :: [Type]). CardanoBlock StandardCrypto ~ HardForkBlock xs => Interpreter xs -> EraHistory
- newtype LedgerEpochInfo = LedgerEpochInfo {
- unLedgerEpochInfo :: EpochInfo (Either Text)
- data QueryInEra era result where
- QueryByronUpdateState :: QueryInEra ByronEra ByronUpdateState
- QueryInShelleyBasedEra :: forall era result. ShelleyBasedEra era -> QueryInShelleyBasedEra era result -> QueryInEra era result
- data QueryInShelleyBasedEra era result where
- QueryEpoch :: forall era. QueryInShelleyBasedEra era EpochNo
- QueryGenesisParameters :: forall era. QueryInShelleyBasedEra era (GenesisParameters ShelleyEra)
- QueryProtocolParameters :: forall era. QueryInShelleyBasedEra era (PParams (ShelleyLedgerEra era))
- QueryProtocolParametersUpdate :: forall era. QueryInShelleyBasedEra era (Map (Hash GenesisKey) ProtocolParametersUpdate)
- QueryStakeDistribution :: forall era. QueryInShelleyBasedEra era (Map (Hash StakePoolKey) Rational)
- QueryUTxO :: forall era. QueryUTxOFilter -> QueryInShelleyBasedEra era (UTxO era)
- QueryStakeAddresses :: forall era. Set StakeCredential -> NetworkId -> QueryInShelleyBasedEra era (Map StakeAddress Coin, Map StakeAddress PoolId)
- QueryStakePools :: forall era. QueryInShelleyBasedEra era (Set PoolId)
- QueryStakePoolParameters :: forall era. Set PoolId -> QueryInShelleyBasedEra era (Map PoolId StakePoolParameters)
- QueryDebugLedgerState :: forall era. QueryInShelleyBasedEra era (SerialisedDebugLedgerState era)
- QueryProtocolState :: forall era. QueryInShelleyBasedEra era (ProtocolState era)
- QueryCurrentEpochState :: forall era. QueryInShelleyBasedEra era (SerialisedCurrentEpochState era)
- QueryPoolState :: forall era. Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedPoolState era)
- QueryPoolDistribution :: forall era. Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedPoolDistribution era)
- QueryStakeSnapshot :: forall era. Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedStakeSnapshots era)
- QueryStakeDelegDeposits :: forall era. Set StakeCredential -> QueryInShelleyBasedEra era (Map StakeCredential Coin)
- QueryAccountState :: forall era. QueryInShelleyBasedEra era AccountState
- QueryConstitution :: forall era. QueryInShelleyBasedEra era (Constitution (ShelleyLedgerEra era))
- QueryGovState :: forall era. QueryInShelleyBasedEra era (GovState (ShelleyLedgerEra era))
- QueryDRepState :: forall era. Set (Credential 'DRepRole StandardCrypto) -> QueryInShelleyBasedEra era (Map (Credential 'DRepRole StandardCrypto) (DRepState StandardCrypto))
- QueryDRepStakeDistr :: forall era. Set (DRep StandardCrypto) -> QueryInShelleyBasedEra era (Map (DRep StandardCrypto) Coin)
- QueryCommitteeMembersState :: forall era. Set (Credential 'ColdCommitteeRole StandardCrypto) -> Set (Credential 'HotCommitteeRole StandardCrypto) -> Set MemberStatus -> QueryInShelleyBasedEra era (CommitteeMembersState StandardCrypto)
- QueryStakeVoteDelegatees :: forall era. Set StakeCredential -> QueryInShelleyBasedEra era (Map StakeCredential (DRep StandardCrypto))
- data QueryInMode result where
- QueryCurrentEra :: QueryInMode AnyCardanoEra
- QueryInEra :: forall era result1. QueryInEra era result1 -> QueryInMode (Either EraMismatch result1)
- QueryEraHistory :: QueryInMode EraHistory
- QuerySystemStart :: QueryInMode SystemStart
- QueryChainBlockNo :: QueryInMode (WithOrigin BlockNo)
- QueryChainPoint :: QueryInMode ChainPoint
- data QueryUTxOFilter
- newtype SlotsInEpoch = SlotsInEpoch Word64
- newtype SlotsToEpochEnd = SlotsToEpochEnd Word64
- newtype DelegationsAndRewards = DelegationsAndRewards (Map StakeAddress Coin, Map StakeAddress PoolId)
- data AnyPlutusScriptVersion where
- AnyPlutusScriptVersion :: forall lang. PlutusScriptVersion lang -> AnyPlutusScriptVersion
- data AnyScriptLanguage where
- AnyScriptLanguage :: forall lang. ScriptLanguage lang -> AnyScriptLanguage
- class HasScriptLanguageInEra lang era where
- scriptLanguageInEra :: ScriptLanguageInEra lang era
- class IsScriptLanguage lang => IsPlutusScriptLanguage lang where
- class HasTypeProxy lang => IsScriptLanguage lang where
- scriptLanguage :: ScriptLanguage lang
- class IsScriptWitnessInCtx ctx where
- data KeyWitnessInCtx witctx where
- data PlutusScriptV1
- data PlutusScriptV2
- data PlutusScriptV3
- data PlutusScriptVersion lang where
- data SimpleScript
- data ScriptInAnyLang where
- ScriptInAnyLang :: forall lang. ScriptLanguage lang -> Script lang -> ScriptInAnyLang
- data ScriptLanguageInEra lang era where
- SimpleScriptInShelley :: ScriptLanguageInEra SimpleScript' ShelleyEra
- SimpleScriptInAllegra :: ScriptLanguageInEra SimpleScript' AllegraEra
- SimpleScriptInMary :: ScriptLanguageInEra SimpleScript' MaryEra
- SimpleScriptInAlonzo :: ScriptLanguageInEra SimpleScript' AlonzoEra
- SimpleScriptInBabbage :: ScriptLanguageInEra SimpleScript' BabbageEra
- SimpleScriptInConway :: ScriptLanguageInEra SimpleScript' ConwayEra
- PlutusScriptV1InAlonzo :: ScriptLanguageInEra PlutusScriptV1 AlonzoEra
- PlutusScriptV1InBabbage :: ScriptLanguageInEra PlutusScriptV1 BabbageEra
- PlutusScriptV1InConway :: ScriptLanguageInEra PlutusScriptV1 ConwayEra
- PlutusScriptV2InBabbage :: ScriptLanguageInEra PlutusScriptV2 BabbageEra
- PlutusScriptV2InConway :: ScriptLanguageInEra PlutusScriptV2 ConwayEra
- PlutusScriptV3InConway :: ScriptLanguageInEra PlutusScriptV3 ConwayEra
- type ScriptRedeemer = HashableScriptData
- data ScriptWitnessInCtx witctx where
- data SimpleScript'
- class ToAlonzoScript lang era where
- toLedgerScript :: PlutusScript lang -> AlonzoScript (ShelleyLedgerEra era)
- data WitCtx witctx where
- data WitCtxMint
- data WitCtxStake
- data WitCtxTxIn
- data HashableScriptData
- data ScriptDataJsonBytesError
- data ScriptDataJsonError
- data ScriptDataJsonSchemaError
- = ScriptDataJsonNullNotAllowed
- | ScriptDataJsonBoolNotAllowed
- | ScriptDataJsonNumberNotInteger !Double
- | ScriptDataJsonNotObject !Value
- | ScriptDataJsonBadObject ![(Text, Value)]
- | ScriptDataJsonBadMapPair !Value
- | ScriptDataJsonTypeMismatch !Text !Value
- newtype ScriptDataRangeError = ScriptDataConstructorOutOfRange Integer
- data ScriptDataJsonSchema
- data Bech32DecodeError
- = Bech32DecodingError !DecodingError
- | Bech32UnexpectedPrefix !Text !(Set Text)
- | Bech32DataPartToBytesError !Text
- | Bech32DeserialiseFromBytesError !ByteString
- | Bech32WrongPrefix !Text !Text
- class (HasTypeProxy a, SerialiseAsRawBytes a) => SerialiseAsBech32 a
- class HasTypeProxy a => SerialiseAsCBOR a where
- serialiseToCBOR :: a -> ByteString
- deserialiseFromCBOR :: AsType a -> ByteString -> Either DecoderError a
- newtype JsonDecodeError = JsonDecodeError String
- data FromSomeTypeCDDL c b where
- FromCDDLTx :: forall b. Text -> (InAnyShelleyBasedEra Tx -> b) -> FromSomeTypeCDDL TextEnvelope b
- FromCDDLWitness :: forall b. Text -> (InAnyShelleyBasedEra KeyWitness -> b) -> FromSomeTypeCDDL TextEnvelope b
- data TextEnvelopeCddlError
- data RawBytesHexError
- class (HasTypeProxy a, Typeable a) => SerialiseAsRawBytes a where
- serialiseToRawBytes :: a -> ByteString
- deserialiseFromRawBytes :: AsType a -> ByteString -> Either SerialiseAsRawBytesError a
- newtype SerialiseAsRawBytesError = SerialiseAsRawBytesError {}
- class SerialiseAsCBOR a => HasTextEnvelope a where
- data TextEnvelope = TextEnvelope {}
- data TextEnvelopeDescr
- data TextEnvelopeError
- = TextEnvelopeTypeError ![TextEnvelopeType] !TextEnvelopeType
- | TextEnvelopeDecodeError !DecoderError
- | TextEnvelopeAesonDecodeError !String
- newtype TextEnvelopeType = TextEnvelopeType String
- newtype UsingBech32 a = UsingBech32 a
- newtype UsingRawBytes a = UsingRawBytes a
- newtype UsingRawBytesHex a = UsingRawBytesHex a
- data StakePoolMetadata = StakePoolMetadata {}
- data StakePoolMetadataValidationError
- data AnyScriptWitness era where
- AnyScriptWitness :: forall witctx era. ScriptWitness witctx era -> AnyScriptWitness era
- data BuildTx
- data BuildTxWith build a where
- ViewTx :: forall a. BuildTxWith ViewTx a
- BuildTxWith :: forall a. a -> BuildTxWith BuildTx a
- data ViewTx
- data ScriptWitnessIndex
- data TxCertificates build era where
- TxCertificatesNone :: forall build era. TxCertificates build era
- TxCertificates :: forall era build. ShelleyBasedEra era -> [Certificate era] -> BuildTxWith build (Map StakeCredential (Witness WitCtxStake era)) -> TxCertificates build era
- data TxOutInAnyEra where
- TxOutInAnyEra :: forall era. CardanoEra era -> TxOut CtxTx era -> TxOutInAnyEra
- data TxProposalProcedures build era where
- TxProposalProceduresNone :: forall build era. TxProposalProcedures build era
- TxProposalProcedures :: forall era build. EraPParams (ShelleyLedgerEra era) => OSet (ProposalProcedure (ShelleyLedgerEra era)) -> BuildTxWith build (Map (ProposalProcedure (ShelleyLedgerEra era)) (ScriptWitness WitCtxStake era)) -> TxProposalProcedures build era
- data TxReturnCollateral ctx era where
- TxReturnCollateralNone :: forall ctx era. TxReturnCollateral ctx era
- TxReturnCollateral :: forall era ctx. BabbageEraOnwards era -> TxOut ctx era -> TxReturnCollateral ctx era
- data TxTotalCollateral era where
- TxTotalCollateralNone :: forall era. TxTotalCollateral era
- TxTotalCollateral :: forall era. BabbageEraOnwards era -> Coin -> TxTotalCollateral era
- data TxUpdateProposal era where
- TxUpdateProposalNone :: forall era. TxUpdateProposal era
- TxUpdateProposal :: forall era. ShelleyToBabbageEra era -> UpdateProposal -> TxUpdateProposal era
- data TxVotingProcedures build era where
- TxVotingProceduresNone :: forall build era. TxVotingProcedures build era
- TxVotingProcedures :: forall era build. VotingProcedures (ShelleyLedgerEra era) -> BuildTxWith build (Map (Voter (EraCrypto (ShelleyLedgerEra era))) (ScriptWitness WitCtxStake era)) -> TxVotingProcedures build era
- data TxWithdrawals build era where
- TxWithdrawalsNone :: forall build era. TxWithdrawals build era
- TxWithdrawals :: forall era build. ShelleyBasedEra era -> [(StakeAddress, Coin, BuildTxWith build (Witness WitCtxStake era))] -> TxWithdrawals build era
- data ScriptValidity
- 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)
- | WitnessGenesisUTxOKey (SigningKey GenesisUTxOKey)
- | WitnessCommitteeColdKey (SigningKey CommitteeColdKey)
- | WitnessCommitteeColdExtendedKey (SigningKey CommitteeColdExtendedKey)
- | WitnessCommitteeHotKey (SigningKey CommitteeHotKey)
- | WitnessCommitteeHotExtendedKey (SigningKey CommitteeHotExtendedKey)
- | WitnessDRepKey (SigningKey DRepKey)
- | WitnessDRepExtendedKey (SigningKey DRepExtendedKey)
- newtype TxIx = TxIx Word
- newtype TxMetadata = TxMetadata (Map Word64 TxMetadataValue)
- data TxMetadataJsonError
- data TxMetadataJsonSchemaError
- = TxMetadataJsonNullNotAllowed
- | TxMetadataJsonBoolNotAllowed
- | TxMetadataJsonNumberNotInteger !Double
- | TxMetadataJsonNotObject !Value
- | TxMetadataJsonBadObject ![(Text, Value)]
- | TxMetadataJsonBadMapPair !Value
- | TxMetadataJsonTypeMismatch !Text !Value
- data TxMetadataRangeError
- data TxMetadataJsonSchema
- data TxMetadataValue
- data AssetId
- newtype AssetName = AssetName ByteString
- newtype Quantity = Quantity Integer
- data ValueNestedBundle
- newtype ValueNestedRep = ValueNestedRep [ValueNestedBundle]
- newtype ShowOf a = ShowOf a
- data CommitteeMembersState c = CommitteeMembersState {
- csCommittee :: !(Map (Credential 'ColdCommitteeRole c) (CommitteeMemberState c))
- csThreshold :: !(Maybe UnitInterval)
- csEpochNo :: !EpochNo
- data MemberStatus
- newtype EpochSlots = EpochSlots {}
- data MIRPot
- data MIRTarget c
- = StakeAddressesMIR !(Map (Credential 'Staking c) DeltaCoin)
- | SendToOppositePotMIR !Coin
- newtype BlockNo = BlockNo {}
- newtype EpochNo = EpochNo {}
- newtype SlotNo = SlotNo {}
- newtype SystemStart = SystemStart {}
- newtype NetworkMagic = NetworkMagic {}
- data NodeToClientVersion
- newtype ChainSyncClient header point tip (m :: Type -> Type) a = ChainSyncClient {
- runChainSyncClient :: m (ClientStIdle header point tip m a)
- newtype ChainSyncClientPipelined header point tip (m :: Type -> Type) a = ChainSyncClientPipelined {
- runChainSyncClientPipelined :: m (ClientPipelinedStIdle 'Z header point tip m a)
- newtype LocalStateQueryClient block point (query :: Type -> Type) (m :: Type -> Type) a = LocalStateQueryClient {
- runLocalStateQueryClient :: m (ClientStIdle block point query m a)
- newtype LocalTxMonitorClient txid tx slot (m :: Type -> Type) a = LocalTxMonitorClient {
- runLocalTxMonitorClient :: m (ClientStIdle txid tx slot m a)
- data MempoolSizeAndCapacity = MempoolSizeAndCapacity {
- capacityInBytes :: !Word32
- sizeInBytes :: !Word32
- numberOfTxs :: !Word32
- newtype LocalTxSubmissionClient tx reject (m :: Type -> Type) a = LocalTxSubmissionClient {
- runLocalTxSubmissionClient :: m (LocalTxClientStIdle tx reject m a)
- data SubmitResult reason
- = SubmitSuccess
- | SubmitFail reason
- data GovernanceAction era
- = MotionOfNoConfidence (StrictMaybe (GovPurposeId 'CommitteePurpose (ShelleyLedgerEra era)))
- | ProposeNewConstitution (StrictMaybe (GovPurposeId 'ConstitutionPurpose (ShelleyLedgerEra era))) (Anchor StandardCrypto) (StrictMaybe (ScriptHash StandardCrypto))
- | ProposeNewCommittee (StrictMaybe (GovPurposeId 'CommitteePurpose (ShelleyLedgerEra era))) [Credential 'ColdCommitteeRole StandardCrypto] (Map (Credential 'ColdCommitteeRole StandardCrypto) EpochNo) Rational
- | InfoAct
- | TreasuryWithdrawal [(Network, StakeCredential, Coin)] !(StrictMaybe (ScriptHash StandardCrypto))
- | InitiateHardfork (StrictMaybe (GovPurposeId 'HardForkPurpose (ShelleyLedgerEra era))) ProtVer
- | UpdatePParams (StrictMaybe (GovPurposeId 'PParamUpdatePurpose (ShelleyLedgerEra era))) (PParamsUpdate (ShelleyLedgerEra era)) !(StrictMaybe (ScriptHash StandardCrypto))
- newtype Proposal era = Proposal {
- unProposal :: ProposalProcedure (ShelleyLedgerEra era)
- newtype GovernanceActionId era = GovernanceActionId {
- unGovernanceActionId :: GovActionId (EraCrypto (ShelleyLedgerEra era))
- data Vote
- newtype Voter era = Voter (Voter (EraCrypto (ShelleyLedgerEra era)))
- newtype VotesMergingConflict era = VotesMergingConflict (Voter (EraCrypto (ShelleyLedgerEra era)), [GovActionId (EraCrypto (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 KesKey
- data VrfKey
- data StakePoolKey
- data AnyProposals = EraPParams era => AnyProposals (Proposals era)
- data AnyRatificationState = EraPParams era => AnyRatificationState (RatifyState era)
- data LedgerEvent
- = PoolRegistration
- | PoolReRegistration
- | IncrementalRewardsDistribution EpochNo (Map StakeCredential (Set (Reward StandardCrypto)))
- | RewardsDistribution EpochNo (Map StakeCredential (Set (Reward StandardCrypto)))
- | MIRDistribution MIRDistributionDetails
- | PoolReap PoolReapDetails
- | SuccessfulPlutusScript (NonEmpty (PlutusWithContext StandardCrypto))
- | FailedPlutusScript (NonEmpty (PlutusWithContext StandardCrypto))
- | NewGovernanceProposals (TxId StandardCrypto) AnyProposals
- | EpochBoundaryRatificationState AnyRatificationState
- data MIRDistributionDetails = MIRDistributionDetails {}
- data PoolReapDetails = PoolReapDetails {}
- data LeadershipError
- = LeaderErrDecodeLedgerStateFailure
- | LeaderErrDecodeProtocolStateFailure (ByteString, DecoderError)
- | LeaderErrDecodeProtocolEpochStateFailure DecoderError
- | LeaderErrGenesisSlot
- | LeaderErrStakePoolHasNoStake PoolId
- | LeaderErrStakeDistribUnstable SlotNo SlotNo SlotNo SlotNo
- | LeaderErrSlotRangeCalculationFailure Text
- | LeaderErrCandidateNonceStillEvolving
- 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
- data CommonProtocolParametersUpdate = CommonProtocolParametersUpdate {
- cppMinFeeA :: StrictMaybe Coin
- cppMinFeeB :: StrictMaybe Coin
- cppMaxBlockBodySize :: StrictMaybe Word32
- cppMaxTxSize :: StrictMaybe Word32
- cppMaxBlockHeaderSize :: StrictMaybe Word16
- cppKeyDeposit :: StrictMaybe Coin
- cppPoolDeposit :: StrictMaybe Coin
- cppPoolRetireMaxEpoch :: StrictMaybe EpochInterval
- cppStakePoolTargetNum :: StrictMaybe Natural
- cppPoolPledgeInfluence :: StrictMaybe NonNegativeInterval
- cppTreasuryExpansion :: StrictMaybe UnitInterval
- cppMonetaryExpansion :: StrictMaybe UnitInterval
- cppMinPoolCost :: StrictMaybe Coin
- newtype DeprecatedAfterBabbagePParams ledgerera = DeprecatedAfterBabbagePParams (StrictMaybe ProtVer)
- newtype DeprecatedAfterMaryPParams ledgerera = DeprecatedAfterMaryPParams (StrictMaybe Coin)
- 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
- newtype IntroducedInBabbagePParams era = IntroducedInBabbagePParams (StrictMaybe CoinPerByte)
- data IntroducedInConwayPParams era = IntroducedInConwayPParams {
- icPoolVotingThresholds :: StrictMaybe PoolVotingThresholds
- icDRepVotingThresholds :: StrictMaybe DRepVotingThresholds
- icMinCommitteeSize :: StrictMaybe Natural
- icCommitteeTermLength :: StrictMaybe EpochInterval
- icGovActionLifetime :: StrictMaybe EpochInterval
- icGovActionDeposit :: StrictMaybe Coin
- icDRepDeposit :: StrictMaybe Coin
- icDRepActivity :: StrictMaybe EpochInterval
- icMinFeeRefScriptCostPerByte :: StrictMaybe NonNegativeInterval
- data ProtocolParameters = ProtocolParameters {
- protocolParamProtocolVersion :: (Natural, Natural)
- protocolParamDecentralization :: Maybe Rational
- protocolParamExtraPraosEntropy :: Maybe PraosNonce
- protocolParamMaxBlockHeaderSize :: Natural
- protocolParamMaxBlockBodySize :: Natural
- protocolParamMaxTxSize :: Natural
- protocolParamTxFeeFixed :: Coin
- protocolParamTxFeePerByte :: Coin
- protocolParamMinUTxOValue :: Maybe Coin
- protocolParamStakeAddressDeposit :: Coin
- protocolParamStakePoolDeposit :: Coin
- protocolParamMinPoolCost :: Coin
- protocolParamPoolRetireMaxEpoch :: EpochInterval
- 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 Coin
- data ProtocolParametersError
- data ShelleyToAlonzoPParams ledgerera = ShelleyToAlonzoPParams (StrictMaybe Nonce) (StrictMaybe UnitInterval)
- newtype CurrentEpochState era = CurrentEpochState (EpochState (ShelleyLedgerEra era))
- newtype PoolDistribution era = PoolDistribution {
- unPoolDistr :: PoolDistr (EraCrypto (ShelleyLedgerEra era))
- newtype PoolState era = PoolState (PState (ShelleyLedgerEra era))
- newtype ProtocolState era = ProtocolState (Serialised (ChainDepState (ConsensusProtocol era)))
- newtype SerialisedCurrentEpochState era = SerialisedCurrentEpochState (Serialised (EpochState (ShelleyLedgerEra era)))
- newtype SerialisedDebugLedgerState era = SerialisedDebugLedgerState (Serialised (NewEpochState (ShelleyLedgerEra era)))
- newtype SerialisedPoolDistribution era = SerialisedPoolDistribution (Serialised (PoolDistr (EraCrypto (ShelleyLedgerEra era))))
- newtype SerialisedPoolState era = SerialisedPoolState (Serialised (PState (ShelleyLedgerEra era)))
- newtype SerialisedStakeSnapshots era = SerialisedStakeSnapshots (Serialised (StakeSnapshots (EraCrypto (ShelleyLedgerEra era))))
- newtype StakeSnapshot era = StakeSnapshot (StakeSnapshots (EraCrypto (ShelleyLedgerEra era)))
- newtype DebugLedgerState era = DebugLedgerState {
- unDebugLedgerState :: NewEpochState (ShelleyLedgerEra era)
- data SimpleScriptOrReferenceInput lang
- data ShelleySigningKey
- = ShelleyNormalSigningKey (SignKeyDSIGN StandardCrypto)
- | ShelleyExtendedSigningKey XPrv
- newtype KESPeriod = KESPeriod {
- unKESPeriod :: Word
- pattern Block :: BlockHeader -> [Tx era] -> Block era
- (<+>) :: Doc ann -> Doc ann -> Doc ann
- runParsecParser :: Parser a -> Text -> Parser a
- left :: forall (m :: Type -> Type) x a. Monad m => x -> ExceptT x m a
- right :: forall (m :: Type -> Type) a x. Monad m => a -> ExceptT x m a
- throwE :: forall (m :: Type -> Type) e a. Monad m => e -> ExceptT e m a
- runExcept :: Except e a -> Either e a
- mapExcept :: (Either e a -> Either e' b) -> Except e a -> Except e' b
- withExcept :: (e -> e') -> Except e a -> Except e' a
- runExceptT :: ExceptT e m a -> m (Either e a)
- mapExceptT :: (m (Either e a) -> n (Either e' b)) -> ExceptT e m a -> ExceptT e' n b
- withExceptT :: forall (m :: Type -> Type) e e' a. Functor m => (e -> e') -> ExceptT e m a -> ExceptT e' m a
- liftCallCC :: CallCC m (Either e a) (Either e b) -> CallCC (ExceptT e m) a b
- liftEither :: MonadError e m => Either e a -> m a
- modifyError :: forall e' t (m :: Type -> Type) e a. MonadTransError e' t m => (e -> e') -> ExceptT e m a -> t m a
- hsep :: [Doc ann] -> Doc ann
- catchE :: forall (m :: Type -> Type) e a e'. Monad m => ExceptT e m a -> (e -> ExceptT e' m a) -> ExceptT e' m a
- except :: forall (m :: Type -> Type) e a. Monad m => Either e a -> ExceptT e m a
- handleE :: forall (m :: Type -> Type) e e' a. Monad m => (e -> ExceptT e' m a) -> ExceptT e m a -> ExceptT e' m a
- tryE :: forall (m :: Type -> Type) e a. Monad m => ExceptT e m a -> ExceptT e m (Either e a)
- finallyE :: forall (m :: Type -> Type) e a. Monad m => ExceptT e m a -> ExceptT e m () -> ExceptT e m a
- liftListen :: Monad m => Listen w m (Either e a) -> Listen w (ExceptT e m) a
- liftPass :: Monad m => Pass w m (Either e a) -> Pass w (ExceptT e m) a
- hoistMaybe :: forall (m :: Type -> Type) x a. Monad m => x -> Maybe a -> ExceptT x m a
- blue :: Doc AnsiStyle -> Doc AnsiStyle
- createAndValidateTransactionBody :: ShelleyBasedEra era -> TxBodyContent BuildTx era -> Either TxBodyError (TxBody era)
- defaultTxBodyContent :: ShelleyBasedEra era -> TxBodyContent BuildTx era
- fromLedgerValue :: ShelleyBasedEra era -> Value (ShelleyLedgerEra era) -> Value
- green :: Doc AnsiStyle -> Doc AnsiStyle
- makeShelleyKeyWitness :: ShelleyBasedEra era -> TxBody era -> ShelleyWitnessSigningKey -> KeyWitness era
- policyId :: Parser PolicyId
- queryEraHistory :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError EraHistory)
- queryProtocolParameters :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (PParams (ShelleyLedgerEra era))))
- queryStakePools :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Set PoolId)))
- querySystemStart :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError SystemStart)
- red :: Doc AnsiStyle -> Doc AnsiStyle
- signShelleyTransaction :: ShelleyBasedEra era -> TxBody era -> [ShelleyWitnessSigningKey] -> Tx era
- toLedgerValue :: MaryEraOnwards era -> Value -> Value (ShelleyLedgerEra era)
- fromAlonzoCostModels :: CostModels -> Map AnyPlutusScriptVersion CostModel
- fromAlonzoPrices :: Prices -> ExecutionUnitPrices
- fromPlutusData :: Data -> ScriptData
- fromShelleyMetadata :: Map Word64 Metadatum -> Map Word64 TxMetadataValue
- toAlonzoPrices :: ExecutionUnitPrices -> Either ProtocolParametersConversionError Prices
- toPlutusData :: ScriptData -> Data
- toShelleyMetadata :: Map Word64 TxMetadataValue -> Map Word64 Metadatum
- toShelleyNetwork :: NetworkId -> Network
- txOutValueToValue :: TxOutValue era -> Value
- renderTxIn :: TxIn -> Text
- renderValue :: Value -> Text
- anyAddressInShelleyBasedEra :: ShelleyBasedEra era -> AddressAny -> AddressInEra era
- toAddressAny :: Address addr -> AddressAny
- lovelaceToTxOutValue :: ShelleyBasedEra era -> Coin -> TxOutValue era
- unUTxO :: UTxO era -> Map TxIn (TxOut CtxUTxO era)
- anyAddressInEra :: CardanoEra era -> AddressAny -> Either String (AddressInEra era)
- byronAddressInEra :: Address ByronAddr -> AddressInEra era
- isKeyAddress :: AddressInEra era -> Bool
- lexPlausibleAddressString :: Parser Text
- makeByronAddress :: NetworkId -> VerificationKey ByronKey -> Address ByronAddr
- makeByronAddressInEra :: NetworkId -> VerificationKey ByronKey -> AddressInEra era
- makeShelleyAddress :: NetworkId -> PaymentCredential -> StakeAddressReference -> Address ShelleyAddr
- makeShelleyAddressInEra :: ShelleyBasedEra era -> NetworkId -> PaymentCredential -> StakeAddressReference -> AddressInEra era
- makeStakeAddress :: NetworkId -> StakeCredential -> StakeAddress
- parseAddressAny :: Parser AddressAny
- shelleyAddressInEra :: ShelleyBasedEra era -> Address ShelleyAddr -> AddressInEra era
- stakeAddressCredential :: StakeAddress -> StakeCredential
- chainPointToHeaderHash :: ChainPoint -> Maybe (Hash BlockHeader)
- chainPointToSlotNo :: ChainPoint -> Maybe SlotNo
- chainTipToChainPoint :: ChainTip -> ChainPoint
- getBlockHeader :: Block era -> BlockHeader
- makeChainTip :: WithOrigin BlockNo -> ChainPoint -> ChainTip
- makeCommitteeColdkeyResignationCertificate :: CommitteeColdkeyResignationRequirements era -> Certificate era
- makeCommitteeHotKeyAuthorizationCertificate :: CommitteeHotKeyAuthorizationRequirements era -> Certificate era
- makeDrepRegistrationCertificate :: DRepRegistrationRequirements era -> Maybe (Anchor (EraCrypto (ShelleyLedgerEra era))) -> Certificate era
- makeDrepUnregistrationCertificate :: DRepUnregistrationRequirements era -> Certificate era
- makeDrepUpdateCertificate :: DRepUpdateRequirements era -> Maybe (Anchor (EraCrypto (ShelleyLedgerEra era))) -> Certificate era
- makeGenesisKeyDelegationCertificate :: GenesisKeyDelegationRequirements era -> Certificate era
- makeMIRCertificate :: MirCertificateRequirements era -> Certificate era
- makeStakeAddressAndDRepDelegationCertificate :: ConwayEraOnwards era -> StakeCredential -> Delegatee (EraCrypto (ShelleyLedgerEra era)) -> Coin -> Certificate era
- makeStakeAddressDelegationCertificate :: StakeDelegationRequirements era -> Certificate era
- makeStakeAddressRegistrationCertificate :: StakeAddressRequirements era -> Certificate era
- makeStakeAddressUnregistrationCertificate :: StakeAddressRequirements era -> Certificate era
- makeStakePoolRegistrationCertificate :: StakePoolRegistrationRequirements era -> Certificate era
- makeStakePoolRetirementCertificate :: StakePoolRetirementRequirements era -> Certificate era
- selectStakeCredentialWitness :: Certificate era -> Maybe StakeCredential
- constructBalancedTx :: ShelleyBasedEra era -> TxBodyContent BuildTx era -> AddressInEra era -> Maybe Word -> UTxO era -> LedgerProtocolParameters era -> LedgerEpochInfo -> SystemStart -> Set PoolId -> Map StakeCredential Coin -> Map (Credential 'DRepRole StandardCrypto) Coin -> [ShelleyWitnessSigningKey] -> Either (TxBodyErrorAutoBalance era) (Tx era)
- notScriptLockedTxIns :: [TxIn] -> UTxO era -> Either ScriptLockedTxInsError ()
- renderNotScriptLockedTxInsError :: ScriptLockedTxInsError -> Text
- renderTxInsExistError :: TxInsExistError -> Text
- txInsExistInUTxO :: [TxIn] -> UTxO era -> Either TxInsExistError ()
- determineEra :: LocalNodeConnectInfo -> ExceptT AcquiringFailure IO AnyCardanoEra
- executeQueryAnyMode :: LocalNodeConnectInfo -> QueryInMode (Either EraMismatch result) -> ExceptT QueryConvenienceError IO result
- executeQueryCardanoMode :: SocketPath -> NetworkId -> QueryInMode (Either EraMismatch result) -> ExceptT QueryConvenienceError IO result
- queryStateForBalancedTx :: CardanoEra era -> [TxIn] -> [Certificate era] -> LocalStateQueryExpr block point QueryInMode r IO (Either QueryConvenienceError (UTxO era, LedgerProtocolParameters era, EraHistory, SystemStart, Set PoolId, Map StakeCredential Coin, Map (Credential 'DRepRole StandardCrypto) Coin, Maybe (Featured ConwayEraOnwards era TxCurrentTreasuryValue)))
- renderQueryConvenienceError :: QueryConvenienceError -> Text
- hashDRepMetadata :: ByteString -> (DRepMetadata, Hash DRepMetadata)
- deserialiseAnyVerificationKey :: ByteString -> Either InputDecodeError SomeAddressVerificationKey
- deserialiseAnyVerificationKeyBech32 :: ByteString -> Either Bech32DecodeError SomeAddressVerificationKey
- deserialiseAnyVerificationKeyTextEnvelope :: ByteString -> Either TextEnvelopeError SomeAddressVerificationKey
- deserialiseInput :: AsType a -> NonEmpty (InputFormat a) -> ByteString -> Either InputDecodeError a
- deserialiseInputAnyOf :: [FromSomeType SerialiseAsBech32 b] -> [FromSomeType HasTextEnvelope b] -> ByteString -> Either InputDecodeError b
- mapSomeAddressVerificationKey :: (forall keyrole. Key keyrole => VerificationKey keyrole -> a) -> SomeAddressVerificationKey -> a
- renderInputDecodeError :: InputDecodeError -> Doc ann
- renderSomeAddressVerificationKey :: SomeAddressVerificationKey -> Text
- alonzoEraOnwardsConstraints :: AlonzoEraOnwards era -> (AlonzoEraOnwardsConstraints era => a) -> a
- alonzoEraOnwardsToShelleyBasedEra :: AlonzoEraOnwards era -> ShelleyBasedEra era
- babbageEraOnwardsConstraints :: BabbageEraOnwards era -> (BabbageEraOnwardsConstraints era => a) -> a
- babbageEraOnwardsToShelleyBasedEra :: BabbageEraOnwards era -> ShelleyBasedEra era
- byronToAlonzoEraConstraints :: ByronToAlonzoEra era -> (ByronToAlonzoEraConstraints era => a) -> a
- conwayEraOnwardsConstraints :: ConwayEraOnwards era -> (ConwayEraOnwardsConstraints era => a) -> a
- conwayEraOnwardsToShelleyBasedEra :: ConwayEraOnwards era -> ShelleyBasedEra era
- maryEraOnwardsConstraints :: MaryEraOnwards era -> (MaryEraOnwardsConstraints era => a) -> a
- maryEraOnwardsToShelleyBasedEra :: MaryEraOnwards era -> ShelleyBasedEra era
- forShelleyBasedEraInEon :: Eon eon => ShelleyBasedEra era -> a -> (eon era -> a) -> a
- forShelleyBasedEraInEonMaybe :: Eon eon => ShelleyBasedEra era -> (eon era -> a) -> Maybe a
- forShelleyBasedEraMaybeEon :: Eon eon => ShelleyBasedEra era -> Maybe (eon era)
- inAnyShelleyBasedEra :: ShelleyBasedEra era -> thing era -> InAnyShelleyBasedEra thing
- inEonForShelleyBasedEra :: Eon eon => a -> (eon era -> a) -> ShelleyBasedEra era -> a
- inEonForShelleyBasedEraMaybe :: Eon eon => (eon era -> a) -> ShelleyBasedEra era -> Maybe a
- requireShelleyBasedEra :: Applicative m => CardanoEra era -> m (Maybe (ShelleyBasedEra era))
- shelleyBasedEraConstraints :: ShelleyBasedEra era -> (ShelleyBasedEraConstraints era => a) -> a
- shelleyEraOnlyConstraints :: ShelleyEraOnly era -> (ShelleyEraOnlyConstraints era => a) -> a
- shelleyEraOnlyToShelleyBasedEra :: ShelleyEraOnly era -> ShelleyBasedEra era
- shelleyToAllegraEraConstraints :: ShelleyToAllegraEra era -> (ShelleyToAllegraEraConstraints era => a) -> a
- shelleyToAllegraEraToShelleyBasedEra :: ShelleyToAllegraEra era -> ShelleyBasedEra era
- shelleyToAlonzoEraConstraints :: ShelleyToAlonzoEra era -> (ShelleyToAlonzoEraConstraints era => a) -> a
- shelleyToAlonzoEraToShelleyBasedEra :: ShelleyToAlonzoEra era -> ShelleyBasedEra era
- shelleyToBabbageEraConstraints :: ShelleyToBabbageEra era -> (ShelleyToBabbageEraConstraints era => a) -> a
- shelleyToBabbageEraToShelleyBasedEra :: ShelleyToBabbageEra era -> ShelleyBasedEra era
- shelleyToMaryEraConstraints :: ShelleyToMaryEra era -> (ShelleyToMaryEraConstraints era => a) -> a
- shelleyToMaryEraToShelleyBasedEra :: ShelleyToMaryEra era -> ShelleyBasedEra era
- alonzoEraOnwardsToMaryEraOnwards :: AlonzoEraOnwards era -> MaryEraOnwards era
- babbageEraOnwardsToAlonzoEraOnwards :: BabbageEraOnwards era -> AlonzoEraOnwards era
- babbageEraOnwardsToMaryEraOnwards :: BabbageEraOnwards era -> MaryEraOnwards era
- caseByronOrShelleyBasedEra :: a -> (ShelleyBasedEraConstraints era => ShelleyBasedEra era -> a) -> CardanoEra era -> a
- caseByronToAlonzoOrBabbageEraOnwards :: (ByronToAlonzoEraConstraints era => ByronToAlonzoEra era -> a) -> (BabbageEraOnwardsConstraints era => BabbageEraOnwards era -> a) -> CardanoEra era -> a
- caseShelleyEraOnlyOrAllegraEraOnwards :: (ShelleyEraOnlyConstraints era => ShelleyEraOnly era -> a) -> (AllegraEraOnwardsConstraints era => AllegraEraOnwards era -> a) -> ShelleyBasedEra era -> a
- caseShelleyToAllegraOrMaryEraOnwards :: (ShelleyToAllegraEraConstraints era => ShelleyToAllegraEra era -> a) -> (MaryEraOnwardsConstraints era => MaryEraOnwards era -> a) -> ShelleyBasedEra era -> a
- caseShelleyToAlonzoOrBabbageEraOnwards :: (ShelleyToAlonzoEraConstraints era => ShelleyToAlonzoEra era -> a) -> (BabbageEraOnwardsConstraints era => BabbageEraOnwards era -> a) -> ShelleyBasedEra era -> a
- caseShelleyToBabbageOrConwayEraOnwards :: (ShelleyToBabbageEraConstraints era => ShelleyToBabbageEra era -> a) -> (ConwayEraOnwardsConstraints era => ConwayEraOnwards era -> a) -> ShelleyBasedEra era -> a
- caseShelleyToMaryOrAlonzoEraOnwards :: (ShelleyToMaryEraConstraints era => ShelleyToMaryEra era -> a) -> (AlonzoEraOnwardsConstraints era => AlonzoEraOnwards era -> a) -> ShelleyBasedEra era -> a
- shelleyToAlonzoEraToShelleyToBabbageEra :: ShelleyToAlonzoEra era -> ShelleyToBabbageEra era
- anyCardanoEra :: CardanoEra era -> AnyCardanoEra
- cardanoEraConstraints :: CardanoEra era -> (CardanoEraConstraints era => a) -> a
- forEraInEon :: Eon eon => CardanoEra era -> a -> (eon era -> a) -> a
- forEraInEonMaybe :: Eon eon => CardanoEra era -> (eon era -> a) -> Maybe a
- forEraMaybeEon :: Eon eon => CardanoEra era -> Maybe (eon era)
- inAnyCardanoEra :: CardanoEra era -> thing era -> InAnyCardanoEra thing
- inEonForEraMaybe :: Eon eon => (eon era -> a) -> CardanoEra era -> Maybe a
- maybeEon :: (Eon eon, IsCardanoEra era) => Maybe (eon era)
- monoidForEraInEon :: (Eon eon, Monoid a) => CardanoEra era -> (eon era -> a) -> a
- monoidForEraInEonA :: (Eon eon, Applicative f, Monoid a) => CardanoEra era -> (eon era -> f a) -> f a
- throwErrorAsException :: Error e => e -> IO a
- asFeaturedInEra :: forall (eon :: Type -> Type) a era. Eon eon => a -> CardanoEra era -> Maybe (Featured eon era a)
- asFeaturedInShelleyBasedEra :: forall (eon :: Type -> Type) a era. Eon eon => a -> ShelleyBasedEra era -> Maybe (Featured eon era a)
- unFeatured :: forall (eon :: Type -> Type) era a. Featured eon era a -> a
- calculateMinTxFee :: ShelleyBasedEra era -> PParams (ShelleyLedgerEra era) -> UTxO era -> TxBody era -> Word -> Coin
- calculateMinimumUTxO :: ShelleyBasedEra era -> TxOut CtxTx era -> PParams (ShelleyLedgerEra era) -> Coin
- estimateBalancedTxBody :: MaryEraOnwards era -> TxBodyContent BuildTx era -> PParams (ShelleyLedgerEra era) -> Set PoolId -> Map StakeCredential Coin -> Map (Credential 'DRepRole StandardCrypto) Coin -> Map ScriptWitnessIndex ExecutionUnits -> Coin -> Int -> Int -> Int -> AddressInEra era -> Value -> Either (TxFeeEstimationError era) (BalancedTxBody era)
- estimateOrCalculateBalancedTxBody :: ShelleyBasedEra era -> FeeEstimationMode era -> PParams (ShelleyLedgerEra era) -> TxBodyContent BuildTx era -> Set PoolId -> Map StakeCredential Coin -> Map (Credential 'DRepRole StandardCrypto) Coin -> AddressInEra era -> Either (AutoBalanceError era) (BalancedTxBody era)
- estimateTransactionKeyWitnessCount :: TxBodyContent BuildTx era -> Word
- evaluateTransactionBalance :: ShelleyBasedEra era -> PParams (ShelleyLedgerEra era) -> Set PoolId -> Map StakeCredential Coin -> Map (Credential 'DRepRole StandardCrypto) Coin -> UTxO era -> TxBody era -> TxOutValue era
- evaluateTransactionExecutionUnits :: CardanoEra era -> SystemStart -> LedgerEpochInfo -> LedgerProtocolParameters era -> UTxO era -> TxBody era -> Either (TransactionValidityError era) (Map ScriptWitnessIndex (Either ScriptExecutionError (EvalTxExecutionUnitsLog, ExecutionUnits)))
- evaluateTransactionFee :: ShelleyBasedEra era -> PParams (ShelleyLedgerEra era) -> TxBody era -> Word -> Word -> Int -> Coin
- makeTransactionBodyAutoBalance :: ShelleyBasedEra era -> SystemStart -> LedgerEpochInfo -> LedgerProtocolParameters era -> Set PoolId -> Map StakeCredential Coin -> Map (Credential 'DRepRole StandardCrypto) Coin -> UTxO era -> TxBodyContent BuildTx era -> AddressInEra era -> Maybe Word -> Either (TxBodyErrorAutoBalance era) (BalancedTxBody era)
- renderSafeHashAsHex :: SafeHash c tag -> Text
- intoFile :: File content 'Out -> content -> (File content 'Out -> stream -> result) -> (content -> stream) -> result
- mapFile :: forall content (direction :: FileDirection). (FilePath -> FilePath) -> File content direction -> File content direction
- onlyIn :: File content 'InOut -> File content 'In
- onlyOut :: File content 'InOut -> File content 'Out
- readByteStringFile :: MonadIO m => File content 'In -> m (Either (FileError e) ByteString)
- readLazyByteStringFile :: MonadIO m => File content 'In -> m (Either (FileError e) ByteString)
- readTextFile :: MonadIO m => File content 'In -> m (Either (FileError e) Text)
- writeByteStringFile :: MonadIO m => File content 'Out -> ByteString -> m (Either (FileError e) ())
- writeByteStringFileWithOwnerPermissions :: FilePath -> ByteString -> IO (Either (FileError e) ())
- writeByteStringOutput :: MonadIO m => Maybe (File content 'Out) -> ByteString -> m (Either (FileError e) ())
- writeLazyByteStringFile :: MonadIO m => File content 'Out -> ByteString -> m (Either (FileError e) ())
- writeLazyByteStringFileWithOwnerPermissions :: File content 'Out -> ByteString -> IO (Either (FileError e) ())
- writeLazyByteStringOutput :: MonadIO m => Maybe (File content 'Out) -> ByteString -> m (Either (FileError e) ())
- writeTextFile :: MonadIO m => File content 'Out -> Text -> m (Either (FileError e) ())
- writeTextFileWithOwnerPermissions :: File content 'Out -> Text -> IO (Either (FileError e) ())
- writeTextOutput :: MonadIO m => Maybe (File content 'Out) -> Text -> m (Either (FileError e) ())
- writeSecrets :: FilePath -> [Char] -> [Char] -> (a -> ByteString) -> [a] -> IO ()
- connectToLocalNode :: MonadIO m => LocalNodeConnectInfo -> LocalNodeClientProtocolsInMode -> m ()
- connectToLocalNodeWithVersion :: MonadIO m => LocalNodeConnectInfo -> (NodeToClientVersion -> LocalNodeClientProtocolsInMode) -> m ()
- getLocalChainTip :: MonadIO m => LocalNodeConnectInfo -> m ChainTip
- mkLocalNodeClientParams :: ConsensusModeParams -> (NodeToClientVersion -> LocalNodeClientProtocolsInMode) -> LocalNodeClientParams
- queryNodeLocalState :: LocalNodeConnectInfo -> Target ChainPoint -> QueryInMode result -> ExceptT AcquiringFailure IO result
- queryTxMonitoringLocal :: MonadIO m => LocalNodeConnectInfo -> LocalTxMonitoringQuery -> m LocalTxMonitoringResult
- submitTxToNodeLocal :: MonadIO m => LocalNodeConnectInfo -> TxInMode -> m (SubmitResult TxValidationErrorInCardanoMode)
- executeLocalStateQueryExpr :: LocalNodeConnectInfo -> Target ChainPoint -> LocalStateQueryExpr BlockInMode ChainPoint QueryInMode () IO a -> IO (Either AcquiringFailure a)
- queryExpr :: QueryInMode a -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError a)
- generateInsecureSigningKey :: (MonadIO m, Key keyrole, SerialiseAsRawBytes (SigningKey keyrole)) => StdGen -> AsType keyrole -> m (SigningKey keyrole, StdGen)
- generateSigningKey :: (MonadIO m, Key keyrole) => AsType keyrole -> m (SigningKey keyrole)
- readKeyFile :: AsType a -> NonEmpty (InputFormat a) -> FilePath -> IO (Either (FileError InputDecodeError) a)
- readKeyFileAnyOf :: forall content b. [FromSomeType SerialiseAsBech32 b] -> [FromSomeType HasTextEnvelope b] -> File content 'In -> IO (Either (FileError InputDecodeError) b)
- readKeyFileTextEnvelope :: HasTextEnvelope a => AsType a -> File content 'In -> IO (Either (FileError InputDecodeError) a)
- applyBlock :: Env -> LedgerState -> ValidationMode -> BlockInMode -> Either LedgerStateError (LedgerState, [LedgerEvent])
- chainSyncClientPipelinedWithLedgerState :: forall (m :: Type -> Type) a. Monad m => Env -> LedgerState -> ValidationMode -> ChainSyncClientPipelined (BlockInMode, Either LedgerStateError (LedgerState, [LedgerEvent])) ChainPoint ChainTip m a -> ChainSyncClientPipelined BlockInMode ChainPoint ChainTip m a
- chainSyncClientWithLedgerState :: forall (m :: Type -> Type) a. Monad m => Env -> LedgerState -> ValidationMode -> ChainSyncClient (BlockInMode, Either LedgerStateError (LedgerState, [LedgerEvent])) ChainPoint ChainTip m a -> ChainSyncClient BlockInMode ChainPoint ChainTip m a
- decodeLedgerState :: CardanoCodecConfig StandardCrypto -> forall s. Decoder s LedgerState
- encodeLedgerState :: CardanoCodecConfig StandardCrypto -> LedgerState -> Encoding
- envSecurityParam :: Env -> Word64
- foldBlocks :: forall a t (m :: Type -> Type). (Show a, MonadIOTransError FoldBlocksError t m) => NodeConfigFile 'In -> SocketPath -> ValidationMode -> a -> (Env -> LedgerState -> [LedgerEvent] -> BlockInMode -> a -> IO (a, FoldStatus)) -> t m a
- foldEpochState :: forall t (m :: Type -> Type) s. MonadIOTransError FoldBlocksError t m => NodeConfigFile 'In -> SocketPath -> ValidationMode -> EpochNo -> s -> (AnyNewEpochState -> SlotNo -> BlockNo -> StateT s IO ConditionResult) -> t m (ConditionResult, s)
- fromConditionResult :: ConditionResult -> Bool
- genesisConfigToEnv :: GenesisConfig -> Either GenesisConfigError Env
- getAnyNewEpochState :: ShelleyBasedEra era -> LedgerState -> Either LedgerStateError AnyNewEpochState
- initialLedgerState :: forall t (m :: Type -> Type). MonadIOTransError InitialLedgerStateError t m => NodeConfigFile 'In -> t m (Env, LedgerState)
- mkProtocolInfoCardano :: GenesisConfig -> (ProtocolInfo (CardanoBlock StandardCrypto), IO [BlockForging IO (CardanoBlock StandardCrypto)])
- readAlonzoGenesisConfig :: forall t (m :: Type -> Type) era. MonadIOTransError GenesisConfigError t m => Maybe (CardanoEra era) -> NodeConfig -> t m AlonzoGenesis
- readByronGenesisConfig :: forall t (m :: Type -> Type). MonadIOTransError GenesisConfigError t m => NodeConfig -> t m Config
- readCardanoGenesisConfig :: forall t (m :: Type -> Type) era. MonadIOTransError GenesisConfigError t m => Maybe (CardanoEra era) -> NodeConfig -> t m GenesisConfig
- readConwayGenesisConfig :: forall t (m :: Type -> Type). MonadIOTransError GenesisConfigError t m => NodeConfig -> t m (ConwayGenesis StandardCrypto)
- readNodeConfig :: (MonadError Text m, MonadIO m) => NodeConfigFile 'In -> m NodeConfig
- readShelleyGenesisConfig :: forall t (m :: Type -> Type). MonadIOTransError GenesisConfigError t m => NodeConfig -> t m ShelleyConfig
- shelleyPraosNonce :: GenesisHashShelley -> Nonce
- toConditionResult :: Bool -> ConditionResult
- handleIOExceptionsLiftWith :: (MonadIOTransError e' t m, Exception e) => (e -> e') -> m a -> t m a
- handleIOExceptionsWith :: (MonadError e' m, MonadCatch m, Exception e) => (e -> e') -> m a -> m a
- hoistIOEither :: forall e t (m :: Type -> Type) a. MonadIOTransError e t m => IO (Either e a) -> t m a
- liftExceptT :: forall e t (m :: Type -> Type) a. MonadTransError e t m => ExceptT e m a -> t m a
- liftMaybe :: MonadError e m => e -> Maybe a -> m a
- fromNetworkMagic :: NetworkMagic -> NetworkId
- toNetworkMagic :: NetworkId -> NetworkMagic
- getHotKey :: OperationalCertificate -> VerificationKey KesKey
- getKesPeriod :: OperationalCertificate -> Word
- getOpCertCount :: OperationalCertificate -> Word64
- issueOperationalCertificate :: VerificationKey KesKey -> Either (SigningKey StakePoolKey) (SigningKey GenesisDelegateExtendedKey) -> KESPeriod -> OperationalCertificateIssueCounter -> Either