Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
A Haskell API for Cardano, tailored to the Hydra project.
This package provides a wrapper around the cardano-ledger
, cardano-api
and
plutus
libraries with extra utilities and function commonly used across the
Hydra project.
NOTE: We always use the **latest era** available in our codebase, so to ease
type signatures and notations, we specialize any type of the cardano-api
normally parameterized by an era to the latest era Era
. As a consequence,
we've defined pattern synonyms for most constructors in the cardano-api
to
also get rid of era witnesses.
NOTE: This module also uses the **latest plutus version** available
(currently PlutusScriptVersion
). So make sure that you give it a plutus script
of the right version (e.g. when compiling and serializing plutus-tx).
Synopsis
- data StandardCrypto
- type Era = ConwayEra
- type LedgerEra = ShelleyLedgerEra Era
- ledgerEraVersion :: Version
- newtype LedgerProtocolParameters era = LedgerProtocolParameters {}
- type ReferenceScript = ReferenceScript Era
- type AddressInEra = AddressInEra Era
- type AddressTypeInEra addrType = AddressTypeInEra addrType Era
- type BalancedTxBody = BalancedTxBody Era
- type KeyWitness = KeyWitness Era
- type PlutusScript = PlutusScript PlutusScriptV2
- type Script = Script PlutusScriptV2
- type ScriptInEra = ScriptInEra Era
- type ScriptLanguage = ScriptLanguage PlutusScriptV2
- type ScriptWitness witCtx = ScriptWitness witCtx Era
- type Tx = Tx Era
- type TxAuxScripts = TxAuxScripts Era
- type TxBody = TxBody Era
- type TxBodyContent buidl = TxBodyContent buidl Era
- type TxBodyScriptData = TxBodyScriptData Era
- type TxExtraKeyWitnesses = TxExtraKeyWitnesses Era
- type TxFee = TxFee Era
- type TxIns buidl = [(TxIn, BuildTxWith buidl (Witness WitCtxTxIn Era))]
- type TxInsCollateral = TxInsCollateral Era
- type TxInsReference buidl = TxInsReference buidl Era
- type TxMetadataInEra = TxMetadataInEra Era
- type TxMintValue buidl = TxMintValue buidl Era
- type TxOut ctx = TxOut ctx Era
- type TxOutDatum ctx = TxOutDatum ctx Era
- type TxScriptValidity = TxScriptValidity Era
- type TxValidityLowerBound = TxValidityLowerBound Era
- type TxValidityUpperBound = TxValidityUpperBound Era
- type Witness witCtx = Witness witCtx Era
- pattern ReferenceScript :: ScriptInAnyLang -> ReferenceScript
- pattern BalancedTxBody :: TxBodyContent BuildTx -> TxBody -> TxOut CtxTx -> Coin -> BalancedTxBody
- pattern KeyWitness :: KeyWitnessInCtx ctx -> Witness ctx
- pattern PlutusScript :: PlutusScript -> Script
- pattern ScriptWitness :: ScriptWitnessInCtx ctx -> ScriptWitness ctx -> Witness ctx
- pattern Tx :: TxBody -> [KeyWitness] -> Tx
- pattern TxAuxScripts :: [ScriptInEra] -> TxAuxScripts
- pattern TxBody :: TxBodyContent ViewTx -> TxBody
- pattern TxBodyContent :: TxIns buidl -> TxInsCollateral -> TxInsReference buidl -> [TxOut CtxTx] -> TxTotalCollateral Era -> TxReturnCollateral CtxTx Era -> TxFee -> TxValidityLowerBound -> TxValidityUpperBound -> TxMetadataInEra -> TxAuxScripts -> TxExtraKeyWitnesses -> BuildTxWith buidl (Maybe (LedgerProtocolParameters Era)) -> TxWithdrawals buidl Era -> TxCertificates buidl Era -> TxUpdateProposal Era -> TxMintValue buidl -> TxScriptValidity -> Maybe (Featured ConwayEraOnwards Era (TxProposalProcedures buidl Era)) -> Maybe (Featured ConwayEraOnwards Era (TxVotingProcedures buidl Era)) -> Maybe (Featured ConwayEraOnwards Era Coin) -> Maybe (Featured ConwayEraOnwards Era Coin) -> TxBodyContent buidl
- pattern TxBodyScriptData :: TxDats (ShelleyLedgerEra Era) -> Redeemers (ShelleyLedgerEra Era) -> TxBodyScriptData
- pattern TxExtraKeyWitnesses :: [Hash PaymentKey] -> TxExtraKeyWitnesses
- pattern TxInsCollateral :: [TxIn] -> TxInsCollateral
- pattern TxInsReference :: [TxIn] -> TxInsReference buidl
- pattern TxMetadataInEra :: TxMetadata -> TxMetadataInEra
- pattern TxMintValue :: Value -> BuildTxWith buidl (Map PolicyId (ScriptWitness WitCtxMint)) -> TxMintValue buidl
- pattern TxOut :: AddressInEra -> Value -> TxOutDatum ctx -> ReferenceScript -> TxOut ctx
- pattern TxScriptValidity :: ScriptValidity -> TxScriptValidity
- pattern TxValidityLowerBound :: SlotNo -> TxValidityLowerBound
- pattern TxValidityUpperBound :: SlotNo -> TxValidityUpperBound
- pattern TxOutDatumNone :: TxOutDatum ctx
- pattern TxOutDatumHash :: Hash ScriptData -> TxOutDatum ctx
- pattern TxOutDatumInline :: HashableScriptData -> TxOutDatum ctx
- pattern ReferenceScriptNone :: ReferenceScript Era
- pattern ByronAddressInAnyEra :: AddressTypeInEra ByronAddr
- pattern ShelleyAddressInEra :: Address ShelleyAddr -> AddressInEra
- pattern PlutusScriptLanguage :: ScriptLanguage
- pattern PlutusScriptWitness :: PlutusScript -> ScriptDatum witctx -> ScriptRedeemer -> ExecutionUnits -> ScriptWitness witctx
- pattern TxAuxScriptsNone :: TxAuxScripts
- pattern TxExtraKeyWitnessesNone :: TxExtraKeyWitnesses
- pattern TxFeeExplicit :: Coin -> TxFee
- pattern TxInsCollateralNone :: TxInsCollateral
- pattern TxInsReferenceNone :: TxInsReference buidl
- pattern TxMetadataNone :: TxMetadataInEra
- pattern TxOutDatumInTx :: HashableScriptData -> TxOutDatum CtxTx
- pattern TxValidityNoLowerBound :: TxValidityLowerBound
- pattern ShelleyTxBody :: TxBody LedgerEra -> [Script LedgerEra] -> TxBodyScriptData -> Maybe (AlonzoTxAuxData LedgerEra) -> TxScriptValidity -> TxBody
- pattern TxBodyNoScriptData :: TxBodyScriptData
- pattern TxScriptValidityNone :: TxScriptValidity
- pattern PlutusScriptSerialised :: ShortByteString -> PlutusScript
- pattern ShelleyBootstrapWitness :: BootstrapWitness StandardCrypto -> KeyWitness
- pattern ShelleyKeyWitness :: WitVKey 'Witness StandardCrypto -> KeyWitness
- pattern ByronAddressInEra :: Address ByronAddr -> AddressInEra
- pattern ShelleyAddressInAnyEra :: AddressTypeInEra ShelleyAddr
- pattern TxMintValueNone :: TxMintValue buidl
- pattern TxValidityNoUpperBound :: TxValidityUpperBound
- upperBound :: TxValidityUpperBound -> SlotNo
- lowerBound :: TxValidityLowerBound -> SlotNo
- createAndValidateTransactionBody :: TxBodyContent BuildTx -> Either TxBodyError TxBody
- defaultTxBodyContent :: TxBodyContent BuildTx
- makeShelleyKeyWitness :: TxBody -> ShelleyWitnessSigningKey -> KeyWitness
- signShelleyTransaction :: TxBody -> [ShelleyWitnessSigningKey] -> Tx
- txAuxScripts :: TxBodyContent buidl -> TxAuxScripts
- txCertificates :: TxBodyContent buidl -> TxCertificates buidl Era
- txCurrentTreasuryValue :: TxBodyContent buidl -> Maybe (Featured ConwayEraOnwards Era Coin)
- txExtraKeyWits :: TxBodyContent buidl -> TxExtraKeyWitnesses
- txFee :: TxBodyContent buidl -> TxFee
- txIns :: TxBodyContent buidl -> TxIns buidl
- txInsCollateral :: TxBodyContent buidl -> TxInsCollateral
- txInsReference :: TxBodyContent buidl -> TxInsReference buidl
- txMetadata :: TxBodyContent buidl -> TxMetadataInEra
- txMintValue :: TxBodyContent buidl -> TxMintValue buidl
- txOuts :: TxBodyContent buidl -> [TxOut CtxTx]
- txProposalProcedures :: TxBodyContent buidl -> Maybe (Featured ConwayEraOnwards Era (TxProposalProcedures buidl Era))
- txProtocolParams :: TxBodyContent buidl -> BuildTxWith buidl (Maybe (LedgerProtocolParameters Era))
- txReturnCollateral :: TxBodyContent buidl -> TxReturnCollateral CtxTx Era
- txScriptValidity :: TxBodyContent buidl -> TxScriptValidity
- txTotalCollateral :: TxBodyContent buidl -> TxTotalCollateral Era
- txTreasuryDonation :: TxBodyContent buidl -> Maybe (Featured ConwayEraOnwards Era Coin)
- txUpdateProposal :: TxBodyContent buidl -> TxUpdateProposal Era
- txValidityLowerBound :: TxBodyContent buidl -> TxValidityLowerBound
- txValidityUpperBound :: TxBodyContent buidl -> TxValidityUpperBound
- txVotingProcedures :: TxBodyContent buidl -> Maybe (Featured ConwayEraOnwards Era (TxVotingProcedures buidl Era))
- txWithdrawals :: TxBodyContent buidl -> TxWithdrawals buidl Era
- plutusScript :: Script -> PlutusScript
- txBody :: Tx -> TxBody
- txBodyContent :: TxBody -> TxBodyContent ViewTx
- address :: AddressInEra -> Address ShelleyAddr
- txOutAddress :: TxOut ctx -> AddressInEra
- txOutValue :: TxOut ctx -> Value
- txOutDatum :: TxOut ctx -> TxOutDatum ctx
- txOutReferenceScript :: TxOut ctx -> ReferenceScript
- txOutDatumHash :: TxOutDatum ctx -> Hash ScriptData
- byronAddress :: AddressInEra -> Address ByronAddr
- balancedTxBodyContent :: BalancedTxBody -> TxBodyContent BuildTx
- balancedTxBody :: BalancedTxBody -> TxBody
- balancedTxChangeOutput :: BalancedTxBody -> TxOut CtxTx
- balancedTxFee :: BalancedTxBody -> Coin
- shelleyBootstrapWitness :: KeyWitness -> BootstrapWitness StandardCrypto
- shelleyKeyWitness :: KeyWitness -> WitVKey 'Witness StandardCrypto
- plutusScriptSerialised :: PlutusScript -> ShortByteString
- plutusScriptWitnessScript :: ScriptWitness witctx -> PlutusScript
- plutusScriptWitnessDatum :: ScriptWitness witctx -> ScriptDatum witctx
- plutusScriptWitnessRedeemer :: ScriptWitness witctx -> ScriptRedeemer
- plutusScriptWitnessExecutionUnits :: ScriptWitness witctx -> ExecutionUnits
- txKeyWitnesses :: Tx -> [KeyWitness]
- txBodyLedgerTxBody :: TxBody -> TxBody LedgerEra
- txBodyScripts :: TxBody -> [Script LedgerEra]
- txBodyScriptData :: TxBody -> TxBodyScriptData
- txBodyAuxiliaryData :: TxBody -> Maybe (AlonzoTxAuxData LedgerEra)
- txBodyScriptValidity :: TxBody -> TxScriptValidity
- txAuxScripts' :: TxAuxScripts -> [ScriptInEra]
- txBodyScriptDatums :: TxBodyScriptData -> TxDats (ShelleyLedgerEra Era)
- txBodyScriptRedeemers :: TxBodyScriptData -> Redeemers (ShelleyLedgerEra Era)
- txExtraKeyWitnesses :: TxExtraKeyWitnesses -> [Hash PaymentKey]
- txFeeExplicit :: TxFee -> Coin
- txInsReference' :: TxInsReference buidl -> [TxIn]
- txInsCollateral' :: TxInsCollateral -> [TxIn]
- txMetadataInEra :: TxMetadataInEra -> TxMetadata
- txMintValueInEra :: TxMintValue buidl -> Value
- txMintValueScriptWitnesses :: TxMintValue buidl -> BuildTxWith buidl (Map PolicyId (ScriptWitness WitCtxMint))
- referenceScript :: ReferenceScript -> ScriptInAnyLang
- txOutDatumScriptData :: TxOutDatum CtxTx -> HashableScriptData
- txOutDatumInlineScriptData :: TxOutDatum ctx -> HashableScriptData
- txScriptValidity' :: TxScriptValidity -> ScriptValidity
- type UTxO = UTxO' (TxOut CtxUTxO Era)
- newtype UTxO' out = UTxO (Map TxIn out)
- class ToTxContext f where
- toTxContext :: f CtxUTxO era -> f CtxTx era
- class ToUTxOContext f where
- toUTxOContext :: f CtxTx era -> f CtxUTxO era
- type ToScriptData a = ToData a
- type FromScriptData a = FromData a
- toLedgerUTxO :: UTxO -> UTxO LedgerEra
- fromLedgerValue :: MaryValue StandardCrypto -> Value
- toLedgerValue :: Value -> MaryValue StandardCrypto
- mkVkAddress :: IsShelleyBasedEra era => NetworkId -> VerificationKey PaymentKey -> AddressInEra era
- genBlockHeader :: Gen BlockHeader
- genBlockHeaderHash :: Gen (Hash BlockHeader)
- getChainPoint :: BlockHeader -> ChainPoint
- modifyTxOutDatum :: (TxOutDatum ctx0 era -> TxOutDatum ctx1 era) -> TxOut ctx0 era -> TxOut ctx1 era
- toLedgerExUnits :: ExecutionUnits -> ExUnits
- toPlutusKeyHash :: Hash PaymentKey -> PubKeyHash
- signWith :: forall era. IsShelleyBasedEra era => TxId -> SigningKey PaymentKey -> KeyWitness era
- fromLedgerScript :: (HasCallStack, AlonzoEraScript era) => AlonzoScript era -> PlutusScript lang
- fromLedgerData :: Data era -> HashableScriptData
- fromPlutusScript :: SerialisedScript -> PlutusScript lang
- mkScriptRef :: SerialisedScript -> ReferenceScript Era
- toScriptData :: ToScriptData a => a -> HashableScriptData
- mkScriptDatum :: ToScriptData a => a -> ScriptDatum WitCtxTxIn
- getPaymentScriptHash :: AddressInEra era -> Maybe ScriptHash
- mkTxIn :: Tx era -> Word -> TxIn
- toLedgerTxIn :: TxIn -> TxIn StandardCrypto
- signTx :: IsShelleyBasedEra era => SigningKey PaymentKey -> Tx era -> Tx era
- toLedgerPolicyID :: PolicyId -> PolicyID StandardCrypto
- toLedgerScriptHash :: PolicyId -> ScriptHash StandardCrypto
- findRedeemerSpending :: FromData a => Tx Era -> TxIn -> Maybe a
- mkTxOutValue :: forall era. IsShelleyBasedEra era => IsMaryBasedEra era => Value -> TxOutValue era
- fromPlutusAddress :: IsShelleyBasedEra era => Network -> Address -> AddressInEra era
- unsafeScriptDataHashFromBytes :: HasCallStack => ByteString -> Hash ScriptData
- fromPlutusValue :: Value -> Maybe Value
- minUTxOValue :: PParams LedgerEra -> TxOut CtxTx Era -> Value
- txOuts' :: Tx era -> [TxOut CtxTx era]
- mkTxOutDatum :: forall era a. (ToScriptData a, IsAlonzoBasedEra era) => a -> TxOutDatum CtxTx era
- toLedgerScriptValidity :: TxScriptValidity era -> IsValid
- toLedgerTxId :: TxId -> TxId StandardCrypto
- fromLedgerTxIn :: TxIn StandardCrypto -> TxIn
- txIns' :: Tx era -> [TxIn]
- fromLedgerTxOut :: IsShelleyBasedEra era => TxOut (ShelleyLedgerEra era) -> TxOut ctx era
- toLedgerTxOut :: IsShelleyBasedEra era => TxOut CtxUTxO era -> TxOut (ShelleyLedgerEra era)
- renderUTxO :: IsString str => UTxO -> str
- toLedgerValidityInterval :: (TxValidityLowerBound era, TxValidityUpperBound era) -> ValidityInterval
- fromPlutusCurrencySymbol :: MonadFail m => CurrencySymbol -> m PolicyId
- mkScriptWitness :: forall ctx era lang. (IsPlutusScriptLanguage lang, HasScriptLanguageInEra lang era) => PlutusScript lang -> ScriptDatum ctx -> ScriptRedeemer -> ScriptWitness ctx era
- lookupRedeemer :: FromData a => PlutusPurpose AsIx LedgerEra -> TxBodyScriptData Era -> Maybe a
- fromLedgerUTxO :: UTxO LedgerEra -> UTxO
- toLedgerKeyWitness :: [KeyWitness era] -> Set (WitVKey 'Witness StandardCrypto)
- toLedgerBootstrapWitness :: [KeyWitness era] -> Set (BootstrapWitness StandardCrypto)
- fromLedgerTxWitness :: forall era. (IsShelleyBasedEra era, UsesStandardCrypto era, Era (ShelleyLedgerEra era)) => AlonzoTxWits (ShelleyLedgerEra era) -> [KeyWitness era]
- toLedgerKeyHash :: Hash PaymentKey -> KeyHash 'Witness StandardCrypto
- unsafePaymentKeyHashFromBytes :: HasCallStack => ByteString -> Hash PaymentKey
- unsafeScriptHashFromBytes :: HasCallStack => ByteString -> ScriptHash
- unsafeCastHash :: (SerialiseAsCBOR (Hash a), SerialiseAsCBOR (Hash b), HasCallStack) => Hash a -> Hash b
- fromLedgerExUnits :: ExUnits -> ExecutionUnits
- genBlockHeaderAt :: SlotNo -> Gen BlockHeader
- genChainPoint :: Gen ChainPoint
- genChainPointAt :: SlotNo -> Gen ChainPoint
- mkScriptAddress :: forall lang era. (IsShelleyBasedEra era, IsPlutusScriptLanguage lang) => NetworkId -> PlutusScript lang -> AddressInEra era
- fromLedgerAddr :: IsShelleyBasedEra era => Addr StandardCrypto -> AddressInEra era
- toLedgerAddr :: AddressInEra era -> Addr StandardCrypto
- fromScriptData :: FromScriptData a => HashableScriptData -> Maybe a
- txOutScriptData :: TxOut CtxTx era -> Maybe HashableScriptData
- lookupScriptData :: forall era. (UsesStandardCrypto era, Era (ShelleyLedgerEra era)) => Tx era -> TxOut CtxUTxO era -> Maybe HashableScriptData
- toLedgerData :: Era era => HashableScriptData -> Data era
- hashScriptInAnyLang :: ScriptInAnyLang -> ScriptHash
- toPlutusCurrencySymbol :: PolicyId -> CurrencySymbol
- fromLedgerTxId :: TxId StandardCrypto -> TxId
- withWitness :: TxIn -> (TxIn, BuildTxWith BuildTx (Witness WitCtxTxIn Era))
- txInputSet :: Tx era -> Set TxIn
- fromPlutusTxOutRef :: TxOutRef -> TxIn
- toPlutusTxOutRef :: TxIn -> TxOutRef
- genTxIn :: Gen TxIn
- findRedeemerMinting :: FromData a => Tx Era -> PolicyId -> Maybe a
- findScriptMinting :: forall lang. Tx Era -> PolicyId -> Maybe (PlutusScript lang)
- txSpendingUTxO :: UTxO -> Tx Era
- fromLedgerTx :: IsShelleyBasedEra era => Tx (ShelleyLedgerEra era) -> Tx era
- utxoProducedByTx :: Tx Era -> UTxO
- txFee' :: Tx era -> Coin
- toLedgerTx :: Tx era -> Tx (ShelleyLedgerEra era)
- recomputeIntegrityHash :: (AlonzoEraPParams ppera, AlonzoEraTxWits txera, AlonzoEraTxBody txera, EraTx txera) => PParams ppera -> [Language] -> Tx txera -> Tx txera
- convertConwayTx :: Tx Conway -> Tx Babbage
- mkTxOutDatumHash :: forall era a ctx. (ToScriptData a, IsAlonzoBasedEra era) => a -> TxOutDatum ctx era
- mkTxOutDatumInline :: forall era a ctx. (ToScriptData a, IsBabbageBasedEra era) => a -> TxOutDatum ctx era
- fromLedgerValidityInterval :: ValidityInterval -> (TxValidityLowerBound Era, TxValidityUpperBound Era)
- valueSize :: Value -> Int
- txMintAssets :: Tx era -> [(AssetId, Quantity)]
- fromLedgerMultiAsset :: MultiAsset StandardCrypto -> Value
- toPlutusValue :: Value -> Value
- setMinUTxOValue :: PParams LedgerEra -> TxOut CtxUTxO Era -> TxOut ctx Era
- mkTxOutAutoBalance :: PParams LedgerEra -> AddressInEra Era -> Value -> TxOutDatum CtxTx Era -> ReferenceScript Era -> TxOut CtxTx Era
- modifyTxOutValue :: IsMaryBasedEra era => IsShelleyBasedEra era => (Value -> Value) -> TxOut ctx era -> TxOut ctx era
- modifyTxOutAddress :: (AddressInEra era -> AddressInEra era) -> TxOut ctx era -> TxOut ctx era
- findTxOutByAddress :: AddressInEra era -> Tx era -> Maybe (TxIn, TxOut CtxTx era)
- findTxOutByScript :: forall lang. IsPlutusScriptLanguage lang => UTxO -> PlutusScript lang -> Maybe (TxIn, TxOut CtxUTxO Era)
- isVkTxOut :: forall ctx era. VerificationKey PaymentKey -> TxOut ctx era -> Bool
- isScriptTxOut :: forall lang ctx era. IsPlutusScriptLanguage lang => PlutusScript lang -> TxOut ctx era -> Bool
- fromPlutusTxOut :: forall era. (IsMaryBasedEra era, IsAlonzoBasedEra era, IsBabbageBasedEra era, IsShelleyBasedEra era) => Network -> TxOut -> Maybe (TxOut CtxUTxO era)
- toPlutusTxOut :: HasCallStack => TxOut CtxUTxO Era -> Maybe TxOut
- utxoFromTx :: Tx Era -> UTxO
- resolveInputsUTxO :: UTxO -> Tx Era -> UTxO
- mkScriptReference :: forall ctx era lang. (IsPlutusScriptLanguage lang, HasScriptLanguageInEra lang era) => TxIn -> PlutusScript lang -> ScriptDatum ctx -> ScriptRedeemer -> ScriptWitness ctx era
- 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 Address addrtype where
- ByronAddress :: Address -> Address ByronAddr
- ShelleyAddress :: Network -> PaymentCredential StandardCrypto -> StakeReference StandardCrypto -> Address ShelleyAddr
- data PParams era
- data AcquiringFailure
- data family Hash keyrole
- data PlutusScriptOrReferenceInput lang = PScript (PlutusScript lang)
- 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
- newtype Coin = Coin {}
- 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
- 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
- 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
- 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
Common type-alias
data StandardCrypto #
Instances
Crypto StandardCrypto | |
Defined in Cardano.Ledger.Crypto type HASH StandardCrypto type ADDRHASH StandardCrypto type DSIGN StandardCrypto type KES StandardCrypto type VRF StandardCrypto | |
PraosCrypto StandardCrypto | |
Defined in Cardano.Protocol.TPraos.API | |
PraosCrypto StandardCrypto | |
Defined in Ouroboros.Consensus.Protocol.Praos | |
(CardanoHardForkConstraints StandardCrypto, IOLike m) => Protocol m (CardanoBlock StandardCrypto) | |
Defined in Cardano.Api.Protocol data ProtocolInfoArgs (CardanoBlock StandardCrypto) # protocolInfo :: ProtocolInfoArgs (CardanoBlock StandardCrypto) -> (ProtocolInfo (CardanoBlock StandardCrypto), m [BlockForging m (CardanoBlock StandardCrypto)]) # | |
(IOLike m, LedgerSupportsProtocol (ShelleyBlock (TPraos StandardCrypto) (ShelleyEra StandardCrypto))) => Protocol m (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) | |
Defined in Cardano.Api.Protocol data ProtocolInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) # protocolInfo :: ProtocolInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) -> (ProtocolInfo (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley), m [BlockForging m (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley)]) # | |
ConvertLedgerEvent (HardForkBlock (CardanoEras StandardCrypto)) | |
Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent toLedgerEvent :: WrapLedgerEvent (HardForkBlock (CardanoEras StandardCrypto)) -> Maybe LedgerEvent # | |
CardanoHardForkConstraints StandardCrypto => ProtocolClient (CardanoBlock StandardCrypto) | |
Defined in Cardano.Api.Protocol data ProtocolClientInfoArgs (CardanoBlock StandardCrypto) protocolClientInfo :: ProtocolClientInfoArgs (CardanoBlock StandardCrypto) -> ProtocolClientInfo (CardanoBlock StandardCrypto) | |
ConvertLedgerEvent (ShelleyBlock protocol (AllegraEra StandardCrypto)) | |
Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (AllegraEra StandardCrypto)) -> Maybe LedgerEvent # | |
ConvertLedgerEvent (ShelleyBlock protocol (AlonzoEra StandardCrypto)) | |
Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (AlonzoEra StandardCrypto)) -> Maybe LedgerEvent # | |
ConvertLedgerEvent (ShelleyBlock protocol (BabbageEra StandardCrypto)) | |
Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (BabbageEra StandardCrypto)) -> Maybe LedgerEvent # | |
ConvertLedgerEvent (ShelleyBlock protocol (ConwayEra StandardCrypto)) | |
Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (ConwayEra StandardCrypto)) -> Maybe LedgerEvent # | |
ConvertLedgerEvent (ShelleyBlock protocol (MaryEra StandardCrypto)) | |
Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (MaryEra StandardCrypto)) -> Maybe LedgerEvent # | |
ConvertLedgerEvent (ShelleyBlock protocol (ShelleyEra StandardCrypto)) | |
Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (ShelleyEra StandardCrypto)) -> Maybe LedgerEvent # | |
LedgerSupportsProtocol (ShelleyBlock (TPraos StandardCrypto) (ShelleyEra StandardCrypto)) => ProtocolClient (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) | |
Defined in Cardano.Api.Protocol data ProtocolClientInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) protocolClientInfo :: ProtocolClientInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) -> ProtocolClientInfo (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) | |
type ADDRHASH StandardCrypto | |
Defined in Cardano.Ledger.Crypto type ADDRHASH StandardCrypto = Blake2b_224 | |
type DSIGN StandardCrypto | |
Defined in Cardano.Ledger.Crypto type DSIGN StandardCrypto = Ed25519DSIGN | |
type HASH StandardCrypto | |
Defined in Cardano.Ledger.Crypto type HASH StandardCrypto = Blake2b_256 | |
type KES StandardCrypto | |
Defined in Cardano.Ledger.Crypto type KES StandardCrypto = Sum6KES Ed25519DSIGN Blake2b_256 | |
type VRF StandardCrypto | |
Defined in Cardano.Ledger.Crypto type VRF StandardCrypto = PraosVRF | |
data ProtocolClientInfoArgs (CardanoBlock StandardCrypto) | |
Defined in Cardano.Api.Protocol data ProtocolClientInfoArgs (CardanoBlock StandardCrypto) = ProtocolClientInfoArgsCardano EpochSlots | |
data ProtocolInfoArgs (CardanoBlock StandardCrypto) | |
Defined in Cardano.Api.Protocol data ProtocolInfoArgs (CardanoBlock StandardCrypto) = ProtocolInfoArgsCardano (CardanoProtocolParams StandardCrypto) | |
data ProtocolClientInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) | |
Defined in Cardano.Api.Protocol data ProtocolClientInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) = ProtocolClientInfoArgsShelley | |
data ProtocolInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) | |
Defined in Cardano.Api.Protocol data ProtocolInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) = ProtocolInfoArgsShelley (ShelleyGenesis StandardCrypto) (ProtocolParamsShelleyBased StandardCrypto) (ProtocolParams (ShelleyBlock (TPraos StandardCrypto) StandardShelley)) |
type LedgerEra = ShelleyLedgerEra Era Source #
Currently supported ledger era.
ledgerEraVersion :: Version Source #
Associated version for the fixed LedgerEra
.
newtype LedgerProtocolParameters era #
Instances
IsShelleyBasedEra era => Show (LedgerProtocolParameters era) | |
Defined in Cardano.Api.ProtocolParameters | |
IsShelleyBasedEra era => Eq (LedgerProtocolParameters era) | |
Defined in Cardano.Api.ProtocolParameters (==) :: LedgerProtocolParameters era -> LedgerProtocolParameters era -> Bool Source # (/=) :: LedgerProtocolParameters era -> LedgerProtocolParameters era -> Bool Source # |
Wrapped Types
type ReferenceScript = ReferenceScript Era Source #
type AddressInEra = AddressInEra Era Source #
type AddressTypeInEra addrType = AddressTypeInEra addrType Era Source #
type BalancedTxBody = BalancedTxBody Era Source #
type KeyWitness = KeyWitness Era Source #
type Script = Script PlutusScriptV2 Source #
type ScriptInEra = ScriptInEra Era Source #
type ScriptWitness witCtx = ScriptWitness witCtx Era Source #
type TxAuxScripts = TxAuxScripts Era Source #
type TxBodyContent buidl = TxBodyContent buidl Era Source #
type TxBodyScriptData = TxBodyScriptData Era Source #
type TxIns buidl = [(TxIn, BuildTxWith buidl (Witness WitCtxTxIn Era))] Source #
type TxInsCollateral = TxInsCollateral Era Source #
type TxInsReference buidl = TxInsReference buidl Era Source #
type TxMetadataInEra = TxMetadataInEra Era Source #
type TxMintValue buidl = TxMintValue buidl Era Source #
type TxOutDatum ctx = TxOutDatum ctx Era Source #
type TxScriptValidity = TxScriptValidity Era Source #
pattern ReferenceScript :: ScriptInAnyLang -> ReferenceScript Source #
pattern BalancedTxBody :: TxBodyContent BuildTx -> TxBody -> TxOut CtxTx -> Coin -> BalancedTxBody Source #
pattern KeyWitness :: KeyWitnessInCtx ctx -> Witness ctx Source #
pattern PlutusScript :: PlutusScript -> Script Source #
pattern ScriptWitness :: ScriptWitnessInCtx ctx -> ScriptWitness ctx -> Witness ctx Source #
pattern TxAuxScripts :: [ScriptInEra] -> TxAuxScripts Source #
pattern TxBodyContent :: TxIns buidl -> TxInsCollateral -> TxInsReference buidl -> [TxOut CtxTx] -> TxTotalCollateral Era -> TxReturnCollateral CtxTx Era -> TxFee -> TxValidityLowerBound -> TxValidityUpperBound -> TxMetadataInEra -> TxAuxScripts -> TxExtraKeyWitnesses -> BuildTxWith buidl (Maybe (LedgerProtocolParameters Era)) -> TxWithdrawals buidl Era -> TxCertificates buidl Era -> TxUpdateProposal Era -> TxMintValue buidl -> TxScriptValidity -> Maybe (Featured ConwayEraOnwards Era (TxProposalProcedures buidl Era)) -> Maybe (Featured ConwayEraOnwards Era (TxVotingProcedures buidl Era)) -> Maybe (Featured ConwayEraOnwards Era Coin) -> Maybe (Featured ConwayEraOnwards Era Coin) -> TxBodyContent buidl Source #
pattern TxBodyScriptData :: TxDats (ShelleyLedgerEra Era) -> Redeemers (ShelleyLedgerEra Era) -> TxBodyScriptData Source #
pattern TxExtraKeyWitnesses :: [Hash PaymentKey] -> TxExtraKeyWitnesses Source #
pattern TxInsCollateral :: [TxIn] -> TxInsCollateral Source #
pattern TxInsReference :: [TxIn] -> TxInsReference buidl Source #
pattern TxMetadataInEra :: TxMetadata -> TxMetadataInEra Source #
pattern TxMintValue :: Value -> BuildTxWith buidl (Map PolicyId (ScriptWitness WitCtxMint)) -> TxMintValue buidl Source #
pattern TxOut :: AddressInEra -> Value -> TxOutDatum ctx -> ReferenceScript -> TxOut ctx Source #
TxOut specialized for Era
pattern TxScriptValidity :: ScriptValidity -> TxScriptValidity Source #
pattern TxValidityLowerBound :: SlotNo -> TxValidityLowerBound Source #
pattern TxValidityUpperBound :: SlotNo -> TxValidityUpperBound Source #
pattern TxOutDatumNone :: TxOutDatum ctx Source #
pattern TxOutDatumHash :: Hash ScriptData -> TxOutDatum ctx Source #
pattern TxOutDatumInline :: HashableScriptData -> TxOutDatum ctx Source #
pattern ReferenceScriptNone :: ReferenceScript Era Source #
pattern ByronAddressInAnyEra :: AddressTypeInEra ByronAddr Source #
pattern ShelleyAddressInEra :: Address ShelleyAddr -> AddressInEra Source #
pattern PlutusScriptLanguage :: ScriptLanguage Source #
pattern PlutusScriptWitness :: PlutusScript -> ScriptDatum witctx -> ScriptRedeemer -> ExecutionUnits -> ScriptWitness witctx Source #
pattern TxAuxScriptsNone :: TxAuxScripts Source #
pattern TxExtraKeyWitnessesNone :: TxExtraKeyWitnesses Source #
pattern TxFeeExplicit :: Coin -> TxFee Source #
pattern TxInsCollateralNone :: TxInsCollateral Source #
pattern TxInsReferenceNone :: TxInsReference buidl Source #
pattern TxMetadataNone :: TxMetadataInEra Source #
pattern TxOutDatumInTx :: HashableScriptData -> TxOutDatum CtxTx Source #
pattern TxValidityNoLowerBound :: TxValidityLowerBound Source #
pattern ShelleyTxBody :: TxBody LedgerEra -> [Script LedgerEra] -> TxBodyScriptData -> Maybe (AlonzoTxAuxData LedgerEra) -> TxScriptValidity -> TxBody Source #
pattern TxBodyNoScriptData :: TxBodyScriptData Source #
pattern TxScriptValidityNone :: TxScriptValidity Source #
pattern PlutusScriptSerialised :: ShortByteString -> PlutusScript Source #
pattern ShelleyBootstrapWitness :: BootstrapWitness StandardCrypto -> KeyWitness Source #
pattern ShelleyKeyWitness :: WitVKey 'Witness StandardCrypto -> KeyWitness Source #
pattern ByronAddressInEra :: Address ByronAddr -> AddressInEra Source #
pattern ShelleyAddressInAnyEra :: AddressTypeInEra ShelleyAddr Source #
pattern TxMintValueNone :: TxMintValue buidl Source #
pattern TxValidityNoUpperBound :: TxValidityUpperBound Source #
signShelleyTransaction :: TxBody -> [ShelleyWitnessSigningKey] -> Tx Source #
txAuxScripts :: TxBodyContent buidl -> TxAuxScripts Source #
txCertificates :: TxBodyContent buidl -> TxCertificates buidl Era Source #
txCurrentTreasuryValue :: TxBodyContent buidl -> Maybe (Featured ConwayEraOnwards Era Coin) Source #
txExtraKeyWits :: TxBodyContent buidl -> TxExtraKeyWitnesses Source #
txFee :: TxBodyContent buidl -> TxFee Source #
txIns :: TxBodyContent buidl -> TxIns buidl Source #
txInsCollateral :: TxBodyContent buidl -> TxInsCollateral Source #
txInsReference :: TxBodyContent buidl -> TxInsReference buidl Source #
txMetadata :: TxBodyContent buidl -> TxMetadataInEra Source #
txMintValue :: TxBodyContent buidl -> TxMintValue buidl Source #
txProposalProcedures :: TxBodyContent buidl -> Maybe (Featured ConwayEraOnwards Era (TxProposalProcedures buidl Era)) Source #
txProtocolParams :: TxBodyContent buidl -> BuildTxWith buidl (Maybe (LedgerProtocolParameters Era)) Source #
txReturnCollateral :: TxBodyContent buidl -> TxReturnCollateral CtxTx Era Source #
txScriptValidity :: TxBodyContent buidl -> TxScriptValidity Source #
txTotalCollateral :: TxBodyContent buidl -> TxTotalCollateral Era Source #
txTreasuryDonation :: TxBodyContent buidl -> Maybe (Featured ConwayEraOnwards Era Coin) Source #
txUpdateProposal :: TxBodyContent buidl -> TxUpdateProposal Era Source #
txValidityLowerBound :: TxBodyContent buidl -> TxValidityLowerBound Source #
txValidityUpperBound :: TxBodyContent buidl -> TxValidityUpperBound Source #
txVotingProcedures :: TxBodyContent buidl -> Maybe (Featured ConwayEraOnwards Era (TxVotingProcedures buidl Era)) Source #
txWithdrawals :: TxBodyContent buidl -> TxWithdrawals buidl Era Source #
plutusScript :: Script -> PlutusScript Source #
address :: AddressInEra -> Address ShelleyAddr Source #
txOutAddress :: TxOut ctx -> AddressInEra Source #
txOutValue :: TxOut ctx -> Value Source #
txOutDatum :: TxOut ctx -> TxOutDatum ctx Source #
txOutReferenceScript :: TxOut ctx -> ReferenceScript Source #
txOutDatumHash :: TxOutDatum ctx -> Hash ScriptData Source #
balancedTxFee :: BalancedTxBody -> Coin Source #
shelleyBootstrapWitness :: KeyWitness -> BootstrapWitness StandardCrypto Source #
shelleyKeyWitness :: KeyWitness -> WitVKey 'Witness StandardCrypto Source #
plutusScriptWitnessScript :: ScriptWitness witctx -> PlutusScript Source #
plutusScriptWitnessDatum :: ScriptWitness witctx -> ScriptDatum witctx Source #
plutusScriptWitnessRedeemer :: ScriptWitness witctx -> ScriptRedeemer Source #
plutusScriptWitnessExecutionUnits :: ScriptWitness witctx -> ExecutionUnits Source #
txKeyWitnesses :: Tx -> [KeyWitness] Source #
txBodyLedgerTxBody :: TxBody -> TxBody LedgerEra Source #
txBodyScripts :: TxBody -> [Script LedgerEra] Source #
txAuxScripts' :: TxAuxScripts -> [ScriptInEra] Source #
txBodyScriptDatums :: TxBodyScriptData -> TxDats (ShelleyLedgerEra Era) Source #
txBodyScriptRedeemers :: TxBodyScriptData -> Redeemers (ShelleyLedgerEra Era) Source #
txFeeExplicit :: TxFee -> Coin Source #
txInsReference' :: TxInsReference buidl -> [TxIn] Source #
txInsCollateral' :: TxInsCollateral -> [TxIn] Source #
txMintValueInEra :: TxMintValue buidl -> Value Source #
txMintValueScriptWitnesses :: TxMintValue buidl -> BuildTxWith buidl (Map PolicyId (ScriptWitness WitCtxMint)) Source #
UTxO
Newtype with phantom types mostly required to work around the poor interface
of UTXO
and provide Monoid
and Foldable
instances to make utxo
manipulation bareable.
Instances
Extras
class ToTxContext f where Source #
A convenient type-class for transforming types in CtxUTxO
to CtxTx
.
See also ToUtxoContext
for the reverse.
toTxContext :: f CtxUTxO era -> f CtxTx era Source #
Instances
ToTxContext TxOut Source # | |
Defined in Hydra.Cardano.Api.CtxTx | |
ToTxContext TxOutDatum Source # | |
Defined in Hydra.Cardano.Api.CtxTx toTxContext :: forall (era :: k). TxOutDatum CtxUTxO era -> TxOutDatum CtxTx era Source # |
class ToUTxOContext f where Source #
A convenient type-class for transforming types in CtxTx
to CtxUTxO
.
See also ToTxContext
for the reverse.
toUTxOContext :: f CtxTx era -> f CtxUTxO era Source #
Instances
ToUTxOContext TxOut Source # | |
Defined in Hydra.Cardano.Api.CtxUTxO | |
ToUTxOContext TxOutDatum Source # | |
Defined in Hydra.Cardano.Api.CtxUTxO toUTxOContext :: forall (era :: k). TxOutDatum CtxTx era -> TxOutDatum CtxUTxO era Source # |
type ToScriptData a = ToData a Source #
Data-types that can be marshalled into a generic ScriptData
structure.
type FromScriptData a = FromData a Source #
Data-types that can be unmarshalled from a generic ScriptData
structure.
toLedgerUTxO :: UTxO -> UTxO LedgerEra Source #
fromLedgerValue :: MaryValue StandardCrypto -> Value Source #
toLedgerValue :: Value -> MaryValue StandardCrypto Source #
mkVkAddress :: IsShelleyBasedEra era => NetworkId -> VerificationKey PaymentKey -> AddressInEra era Source #
Construct a Shelley-style address from a verification key. This address has no stake rights.
TODO: NetworkId
here is an annoying API because it requires a network magic
for testnet addresses. Nevertheless, the network magic is only needed for
Byron addresses; Shelley addresses use a different kind of network
discriminant which is currently fully captured as 'Mainnet | Testnet'.
So, it would be a slightly better DX to use Mainnet | Testnet as an interface here since we are only constructing Shelley addresses.
genBlockHeader :: Gen BlockHeader Source #
Fully arbitrary block header with completely random hash.
genBlockHeaderHash :: Gen (Hash BlockHeader) Source #
Generate a random block header hash.
getChainPoint :: BlockHeader -> ChainPoint Source #
Get the chain point corresponding to a given BlockHeader
.
modifyTxOutDatum :: (TxOutDatum ctx0 era -> TxOutDatum ctx1 era) -> TxOut ctx0 era -> TxOut ctx1 era Source #
Alter the datum of a TxOut
with the given transformation.
toLedgerExUnits :: ExecutionUnits -> ExUnits Source #
Convert a cardano-api ExecutionUnits
into a cardano-ledger ExUnits
toPlutusKeyHash :: Hash PaymentKey -> PubKeyHash Source #
Convert a cardano-api Hash
into a plutus PubKeyHash
signWith :: forall era. IsShelleyBasedEra era => TxId -> SigningKey PaymentKey -> KeyWitness era Source #
Construct a KeyWitness
from a transaction id and credentials.
fromLedgerScript :: (HasCallStack, AlonzoEraScript era) => AlonzoScript era -> PlutusScript lang Source #
fromLedgerData :: Data era -> HashableScriptData Source #
Convert a cardano-ledger script Data
into a cardano-api ScriptDatum
.
fromPlutusScript :: SerialisedScript -> PlutusScript lang Source #
Convert a serialized plutus script into a cardano-api Script
.
mkScriptRef :: SerialisedScript -> ReferenceScript Era Source #
Construct a ReferenceScript
from any given Plutus script.
NOTE: The script is treated as a PlutusScriptVersion
toScriptData :: ToScriptData a => a -> HashableScriptData Source #
Serialise some type into a generic script data.
mkScriptDatum :: ToScriptData a => a -> ScriptDatum WitCtxTxIn Source #
Construct a ScriptDatum
for use as transaction witness.
getPaymentScriptHash :: AddressInEra era -> Maybe ScriptHash Source #
Extract the payment part of an address, as a script hash.
mkTxIn :: Tx era -> Word -> TxIn Source #
Create a TxIn
(a.k.a UTXO) from a transaction and output index.
toLedgerTxIn :: TxIn -> TxIn StandardCrypto Source #
signTx :: IsShelleyBasedEra era => SigningKey PaymentKey -> Tx era -> Tx era Source #
Sign transaction using the provided secret key It only works for tx not containing scripts. You can't sign a script utxo with this.
toLedgerPolicyID :: PolicyId -> PolicyID StandardCrypto Source #
Convert Cardano api PolicyId
to Cardano ledger PolicyID
.
toLedgerScriptHash :: PolicyId -> ScriptHash StandardCrypto Source #
findRedeemerSpending :: FromData a => Tx Era -> TxIn -> Maybe a Source #
Find and deserialise from ScriptData
, a redeemer from the transaction
associated to the given input.
mkTxOutValue :: forall era. IsShelleyBasedEra era => IsMaryBasedEra era => Value -> TxOutValue era Source #
Inject some Value
into a TxOutValue
fromPlutusAddress :: IsShelleyBasedEra era => Network -> Address -> AddressInEra era Source #
Convert a plutus Address
to an api AddressInEra
.
NOTE: Requires the Network
discriminator (Testnet or Mainnet) because
Plutus addresses are stripped off it.
unsafeScriptDataHashFromBytes :: HasCallStack => ByteString -> Hash ScriptData Source #
Unsafe wrap some bytes as a 'Hash ScriptData', relying on the fact that Plutus is using Blake2b_256 for hashing data (according to 'cardano-ledger').
Pre-condition: the input bytestring MUST be of length 32.
mkTxOutDatum :: forall era a. (ToScriptData a, IsAlonzoBasedEra era) => a -> TxOutDatum CtxTx era Source #
Construct a TxOutDatum
to be included in the tx from some serialisable data.
toLedgerScriptValidity :: TxScriptValidity era -> IsValid Source #
Convert a cardano-api TxScriptValidity
into a cardano-ledger IsValid
boolean wrapper.
toLedgerTxId :: TxId -> TxId StandardCrypto Source #
fromLedgerTxIn :: TxIn StandardCrypto -> TxIn Source #
fromLedgerTxOut :: IsShelleyBasedEra era => TxOut (ShelleyLedgerEra era) -> TxOut ctx era Source #
toLedgerTxOut :: IsShelleyBasedEra era => TxOut CtxUTxO era -> TxOut (ShelleyLedgerEra era) Source #
renderUTxO :: IsString str => UTxO -> str Source #
Get a human-readable pretty text representation of a UTxO.
toLedgerValidityInterval :: (TxValidityLowerBound era, TxValidityUpperBound era) -> ValidityInterval Source #
fromPlutusCurrencySymbol :: MonadFail m => CurrencySymbol -> m PolicyId Source #
Convert a plutus CurrencySymbol
into a cardano-api PolicyId
.
mkScriptWitness :: forall ctx era lang. (IsPlutusScriptLanguage lang, HasScriptLanguageInEra lang era) => PlutusScript lang -> ScriptDatum ctx -> ScriptRedeemer -> ScriptWitness ctx era Source #
Construct a full script witness from a datum, a redeemer and a full
Script
. That witness has no execution budget.
lookupRedeemer :: FromData a => PlutusPurpose AsIx LedgerEra -> TxBodyScriptData Era -> Maybe a Source #
fromLedgerUTxO :: UTxO LedgerEra -> UTxO Source #
toLedgerKeyWitness :: [KeyWitness era] -> Set (WitVKey 'Witness StandardCrypto) Source #
Convert a List
of cardano-api's KeyWitness
into a Set
of
cardano-ledger's WitVKey
.
NOTE: KeyWitness
is a bigger type than WitVKey
witness, this function
does not only the type conversion but also the selection of the right
underlying constructors. That means the size of the resulting set may be
smaller than the size of the list (but never bigger).
toLedgerBootstrapWitness :: [KeyWitness era] -> Set (BootstrapWitness StandardCrypto) Source #
Convert a List
of cardano-api's KeyWitness
into a Set
of
cardano-ledger's BootstrapWitness
.
NOTE: See note on toLedgerKeyWitness
.
fromLedgerTxWitness :: forall era. (IsShelleyBasedEra era, UsesStandardCrypto era, Era (ShelleyLedgerEra era)) => AlonzoTxWits (ShelleyLedgerEra era) -> [KeyWitness era] Source #
Convert a cardano-ledger's TxWitness
object into a list of cardano-api's
KeyWitness
.
NOTE: this only concerns key and bootstrap witnesses. Scripts and auxiliary data are obviously not part of the resulting list.
toLedgerKeyHash :: Hash PaymentKey -> KeyHash 'Witness StandardCrypto Source #
Convert a cardano-api Hash
into a cardano-ledger KeyHash
unsafePaymentKeyHashFromBytes :: HasCallStack => ByteString -> Hash PaymentKey Source #
Unsafe wrap some bytes as a 'Hash PaymentKey'.
Pre-condition: the input bytestring MUST be of length 28.
unsafeScriptHashFromBytes :: HasCallStack => ByteString -> ScriptHash Source #
Unsafe wrap some bytes as a ScriptHash
, relying on the fact that Plutus
is using Blake2b_224 for hashing data (according to 'cardano-ledger').
Pre-condition: the input bytestring MUST be of length 28.
unsafeCastHash :: (SerialiseAsCBOR (Hash a), SerialiseAsCBOR (Hash b), HasCallStack) => Hash a -> Hash b Source #
fromLedgerExUnits :: ExUnits -> ExecutionUnits Source #
Convert a cardano-ledger ExUnits
into a cardano-api ExecutionUnits
genBlockHeaderAt :: SlotNo -> Gen BlockHeader Source #
Generate a random block header with completely random hash, but at a certain slot.
genChainPoint :: Gen ChainPoint Source #
Generate a chain point with a likely invalid block header hash.
genChainPointAt :: SlotNo -> Gen ChainPoint Source #
Generate a chain point at given slot with a likely invalid block header hash.
mkScriptAddress :: forall lang era. (IsShelleyBasedEra era, IsPlutusScriptLanguage lang) => NetworkId -> PlutusScript lang -> AddressInEra era Source #
Construct a Shelley-style address from a Plutus script. This address has no stake rights.
fromLedgerAddr :: IsShelleyBasedEra era => Addr StandardCrypto -> AddressInEra era Source #
From a ledger Addr
to an api AddressInEra
toLedgerAddr :: AddressInEra era -> Addr StandardCrypto Source #
From an api AddressInEra
to a ledger Addr
fromScriptData :: FromScriptData a => HashableScriptData -> Maybe a Source #
Deserialise some generic script data into some type.
txOutScriptData :: TxOut CtxTx era -> Maybe HashableScriptData Source #
Get the HashableScriptData
associated to the a TxOut
. Note that this
requires the CtxTx
context. To get script data in a CtxUTxO
context, see
lookupScriptData
.
lookupScriptData :: forall era. (UsesStandardCrypto era, Era (ShelleyLedgerEra era)) => Tx era -> TxOut CtxUTxO era -> Maybe HashableScriptData Source #
Lookup included datum of given TxOut
.
toLedgerData :: Era era => HashableScriptData -> Data era Source #
Convert a cardano-api script data into a cardano-ledger script Data
.
XXX: This is a partial function. Ideally it would fall back to the
Data
portion in HashableScriptData
.
hashScriptInAnyLang :: ScriptInAnyLang -> ScriptHash Source #
Like hashScript
, but for a ScriptInAnyLang
.
toPlutusCurrencySymbol :: PolicyId -> CurrencySymbol Source #
Convert Cardano api PolicyId
to Plutus CurrencySymbol
.
fromLedgerTxId :: TxId StandardCrypto -> TxId Source #
withWitness :: TxIn -> (TxIn, BuildTxWith BuildTx (Witness WitCtxTxIn Era)) Source #
Attach some verification-key witness to a TxIn
.
fromPlutusTxOutRef :: TxOutRef -> TxIn Source #
Convert a plutus' TxOutRef
into a cardano-api TxIn
toPlutusTxOutRef :: TxIn -> TxOutRef Source #
Convert a cardano-api TxIn
into a plutus TxOutRef
.
A more random generator than the 'Arbitrary TxIn' from cardano-ledger.
NOTE: This is using the Cardano ledger's deserialization framework using the
latest protocol version via maxBound
.
findScriptMinting :: forall lang. Tx Era -> PolicyId -> Maybe (PlutusScript lang) Source #
fromLedgerTx :: IsShelleyBasedEra era => Tx (ShelleyLedgerEra era) -> Tx era Source #
utxoProducedByTx :: Tx Era -> UTxO Source #
Get the UTxO that are produced by some transaction. XXX: Defined here to avoid cyclic module dependency
toLedgerTx :: Tx era -> Tx (ShelleyLedgerEra era) Source #
recomputeIntegrityHash :: (AlonzoEraPParams ppera, AlonzoEraTxWits txera, AlonzoEraTxBody txera, EraTx txera) => PParams ppera -> [Language] -> Tx txera -> Tx txera Source #
Compute the integrity hash of a transaction using a list of plutus languages.
convertConwayTx :: Tx Conway -> Tx Babbage Source #
Explicit downgrade from Conway to Babbage era.
XXX: This will invalidate the script integrity hash as datums and redeemers are serialized differently.
XXX: This is not a complete mapping and does silently drop things like protocol updates, certificates and voting procedures.
mkTxOutDatumHash :: forall era a ctx. (ToScriptData a, IsAlonzoBasedEra era) => a -> TxOutDatum ctx era Source #
Construct a TxOutDatum
as a ScriptData
hash from some serialisable data.
mkTxOutDatumInline :: forall era a ctx. (ToScriptData a, IsBabbageBasedEra era) => a -> TxOutDatum ctx era Source #
Construct an inline TxOutDatum
from some serialisable data.
fromLedgerValidityInterval :: ValidityInterval -> (TxValidityLowerBound Era, TxValidityUpperBound Era) Source #
txMintAssets :: Tx era -> [(AssetId, Quantity)] Source #
Access minted assets of a transaction, as an ordered association list.
fromLedgerMultiAsset :: MultiAsset StandardCrypto -> Value Source #
Convert a cardano-ledger MultiAsset
into a cardano-api Value
. The
cardano-api currently does not have an asset-only type. So this conversion
will construct a Value
with no AdaAssetId
entry in it.
setMinUTxOValue :: PParams LedgerEra -> TxOut CtxUTxO Era -> TxOut ctx Era Source #
Modify a TxOut
to set the minimum ada on the value.
mkTxOutAutoBalance :: PParams LedgerEra -> AddressInEra Era -> Value -> TxOutDatum CtxTx Era -> ReferenceScript Era -> TxOut CtxTx Era Source #
Automatically balance a given output with the minimum required amount. Number of assets, presence of datum and/or reference scripts may affect this minimum value.
modifyTxOutValue :: IsMaryBasedEra era => IsShelleyBasedEra era => (Value -> Value) -> TxOut ctx era -> TxOut ctx era Source #
Alter the value of a TxOut
with the given transformation.
modifyTxOutAddress :: (AddressInEra era -> AddressInEra era) -> TxOut ctx era -> TxOut ctx era Source #
Alter the address of a TxOut
with the given transformation.
findTxOutByAddress :: AddressInEra era -> Tx era -> Maybe (TxIn, TxOut CtxTx era) Source #
findTxOutByScript :: forall lang. IsPlutusScriptLanguage lang => UTxO -> PlutusScript lang -> Maybe (TxIn, TxOut CtxUTxO Era) Source #
Find a single script output in some UTxO
isVkTxOut :: forall ctx era. VerificationKey PaymentKey -> TxOut ctx era -> Bool Source #
Predicate to find or filter TxOut
owned by a key. This
is better than comparing the full address as it does not require a network
discriminator.
isScriptTxOut :: forall lang ctx era. IsPlutusScriptLanguage lang => PlutusScript lang -> TxOut ctx era -> Bool Source #
Predicate to find or filter TxOut
which are governed by some script. This
is better than comparing the full address as it does not require a network
discriminator.
fromPlutusTxOut :: forall era. (IsMaryBasedEra era, IsAlonzoBasedEra era, IsBabbageBasedEra era, IsShelleyBasedEra era) => Network -> TxOut -> Maybe (TxOut CtxUTxO era) Source #
toPlutusTxOut :: HasCallStack => TxOut CtxUTxO Era -> Maybe TxOut Source #
utxoFromTx :: Tx Era -> UTxO Source #
Construct a UTxO from a transaction. This constructs artificial TxIn
(a.k.a output reference) from the transaction itself, zipping them to the
outputs they correspond to.
mkScriptReference :: forall ctx era lang. (IsPlutusScriptLanguage lang, HasScriptLanguageInEra lang era) => TxIn -> PlutusScript lang -> ScriptDatum ctx -> ScriptRedeemer -> ScriptWitness ctx era Source #
Construct a reference script witness, only referring to a TxIn
which is
expected to contain the given script (only required to satisfy types).
Re-exports from cardano-api
prettyError :: e -> Doc ann #
Instances
Instances
Instances
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 #