Safe Haskell | None |
---|---|
Language | Haskell2010 |
Cardano.Api
Contents
- Eras
- Eon support
- Eons
- Era case handling
- Type tags
- Cryptographic key interface
- Mnemonics
- Payment addresses
- Stake addresses
- Blocks
- Building transactions
- Building transactions
- Signing transactions
- Transaction metadata
- Governance action metadata
- Certificates
- Rewards
- Stake pool off-chain metadata
- Scripts
- Serialisation
- Errors
- Node interaction
- Node operation
- Constitutional Committee keys
- Genesis file
- Special transactions
- Protocol parameter updates
- Protocol parameters
- Node socket related
- Convenience functions
Description
This module provides a library interface for interacting with Cardano as a user of the system.
It is intended to be the complete API covering everything but without exposing constructors that reveal any lower level types.
In the interest of simplicity it glosses over some details of the system. Most simple tools should be able to work just using this interface, however you can go deeper and expose the types from the underlying libraries using Cardano.Api.Byron or Cardano.Api.Shelley.
Synopsis
- data ByronEra
- data ShelleyEra
- data AllegraEra
- data MaryEra
- data AlonzoEra
- data BabbageEra
- data ConwayEra
- data CardanoEra era where
- class HasTypeProxy era => IsCardanoEra era where
- cardanoEra :: CardanoEra era
- data AnyCardanoEra where
- AnyCardanoEra :: forall era. Typeable era => CardanoEra era -> AnyCardanoEra
- anyCardanoEra :: CardanoEra era -> AnyCardanoEra
- data InAnyCardanoEra (thing :: Type -> Type) where
- InAnyCardanoEra :: forall era (thing :: Type -> Type). Typeable era => CardanoEra era -> thing era -> InAnyCardanoEra thing
- inAnyCardanoEra :: CardanoEra era -> thing era -> InAnyCardanoEra thing
- cardanoEraConstraints :: CardanoEra era -> (CardanoEraConstraints era => a) -> a
- class ToCardanoEra (eon :: Type -> Type) where
- toCardanoEra :: eon era -> CardanoEra era
- class Eon (eon :: Type -> Type) where
- inEonForEra :: a -> (eon era -> a) -> CardanoEra era -> a
- data EraInEon (eon :: Type -> Type) where
- inEonForEraMaybe :: Eon eon => (eon era -> a) -> CardanoEra era -> Maybe 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)
- 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
- inEonForShelleyBasedEra :: Eon eon => a -> (eon era -> a) -> ShelleyBasedEra era -> a
- inEonForShelleyBasedEraMaybe :: Eon eon => (eon era -> a) -> ShelleyBasedEra era -> Maybe a
- 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)
- data Featured (eon :: Type -> Type) era a where
- mkFeatured :: forall (eon :: Type -> Type) era a. (IsCardanoEra era, Eon eon) => a -> Maybe (Featured eon era a)
- unFeatured :: forall (eon :: Type -> Type) era a. Featured eon era a -> 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)
- class Convert (f :: a -> Type) (g :: a -> Type) where
- convert :: forall (era :: a). f era -> g era
- class Inject t s where
- inject :: t -> s
- data ByronToAlonzoEra era where
- byronToAlonzoEraConstraints :: ByronToAlonzoEra era -> (ByronToAlonzoEraConstraints era => a) -> a
- data ShelleyEraOnly era where
- shelleyEraOnlyConstraints :: ShelleyEraOnly era -> (ShelleyEraOnlyConstraints era => a) -> a
- shelleyEraOnlyToShelleyBasedEra :: ShelleyEraOnly era -> ShelleyBasedEra era
- data ShelleyToAllegraEra era where
- shelleyToAllegraEraConstraints :: ShelleyToAllegraEra era -> (ShelleyToAllegraEraConstraints era => a) -> a
- shelleyToAllegraEraToShelleyBasedEra :: ShelleyToAllegraEra era -> ShelleyBasedEra era
- data ShelleyToMaryEra era where
- shelleyToMaryEraConstraints :: ShelleyToMaryEra era -> (ShelleyToMaryEraConstraints era => a) -> a
- shelleyToMaryEraToShelleyBasedEra :: ShelleyToMaryEra era -> ShelleyBasedEra era
- data ShelleyToAlonzoEra era where
- shelleyToAlonzoEraConstraints :: ShelleyToAlonzoEra era -> (ShelleyToAlonzoEraConstraints era => a) -> a
- shelleyToAlonzoEraToShelleyBasedEra :: ShelleyToAlonzoEra era -> ShelleyBasedEra era
- data ShelleyToBabbageEra era where
- shelleyToBabbageEraConstraints :: ShelleyToBabbageEra era -> (ShelleyToBabbageEraConstraints era => a) -> a
- shelleyToBabbageEraToShelleyBasedEra :: ShelleyToBabbageEra era -> ShelleyBasedEra era
- data ShelleyBasedEra era where
- ShelleyBasedEraShelley :: ShelleyBasedEra ShelleyEra
- ShelleyBasedEraAllegra :: ShelleyBasedEra AllegraEra
- ShelleyBasedEraMary :: ShelleyBasedEra MaryEra
- ShelleyBasedEraAlonzo :: ShelleyBasedEra AlonzoEra
- ShelleyBasedEraBabbage :: ShelleyBasedEra BabbageEra
- ShelleyBasedEraConway :: ShelleyBasedEra ConwayEra
- class IsCardanoEra era => IsShelleyBasedEra era where
- shelleyBasedEra :: ShelleyBasedEra era
- 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
- inAnyShelleyBasedEra :: ShelleyBasedEra era -> thing era -> InAnyShelleyBasedEra thing
- shelleyBasedEraConstraints :: ShelleyBasedEra era -> (ShelleyBasedEraConstraints era => a) -> a
- data AllegraEraOnwards era where
- class IsShelleyBasedEra era => IsAllegraBasedEra era where
- allegraBasedEra :: AllegraEraOnwards era
- data MaryEraOnwards era where
- maryEraOnwardsConstraints :: MaryEraOnwards era -> (MaryEraOnwardsConstraints era => a) -> a
- maryEraOnwardsToShelleyBasedEra :: MaryEraOnwards era -> ShelleyBasedEra era
- class IsAllegraBasedEra era => IsMaryBasedEra era where
- maryBasedEra :: MaryEraOnwards era
- data AlonzoEraOnwards era where
- alonzoEraOnwardsConstraints :: AlonzoEraOnwards era -> (AlonzoEraOnwardsConstraints era => a) -> a
- alonzoEraOnwardsToShelleyBasedEra :: AlonzoEraOnwards era -> ShelleyBasedEra era
- class IsMaryBasedEra era => IsAlonzoBasedEra era where
- alonzoBasedEra :: AlonzoEraOnwards era
- data BabbageEraOnwards era where
- babbageEraOnwardsConstraints :: BabbageEraOnwards era -> (BabbageEraOnwardsConstraints era => a) -> a
- babbageEraOnwardsToShelleyBasedEra :: BabbageEraOnwards era -> ShelleyBasedEra era
- class IsAlonzoBasedEra era => IsBabbageBasedEra era where
- babbageBasedEra :: BabbageEraOnwards era
- data ConwayEraOnwards era where
- conwayEraOnwardsConstraints :: ConwayEraOnwards era -> (ConwayEraOnwardsConstraints era => a) -> a
- conwayEraOnwardsToShelleyBasedEra :: ConwayEraOnwards era -> ShelleyBasedEra era
- conwayEraOnwardsToBabbageEraOnwards :: ConwayEraOnwards era -> BabbageEraOnwards era
- class IsBabbageBasedEra era => IsConwayBasedEra era where
- conwayBasedEra :: ConwayEraOnwards 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
- caseShelleyToMaryOrAlonzoEraOnwards :: (ShelleyToMaryEraConstraints era => ShelleyToMaryEra era -> a) -> (AlonzoEraOnwardsConstraints era => AlonzoEraOnwards 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
- shelleyToAlonzoEraToShelleyToBabbageEra :: ShelleyToAlonzoEra era -> ShelleyToBabbageEra era
- alonzoEraOnwardsToMaryEraOnwards :: AlonzoEraOnwards era -> MaryEraOnwards era
- babbageEraOnwardsToMaryEraOnwards :: BabbageEraOnwards era -> MaryEraOnwards era
- babbageEraOnwardsToAlonzoEraOnwards :: BabbageEraOnwards era -> AlonzoEraOnwards era
- requireShelleyBasedEra :: Applicative m => CardanoEra era -> m (Maybe (ShelleyBasedEra era))
- newtype File content (direction :: FileDirection) = File {}
- data FileDirection
- 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
- intoFile :: File content 'Out -> content -> (File content 'Out -> stream -> result) -> (content -> stream) -> result
- 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)
- writeByteStringFileWithOwnerPermissions :: FilePath -> ByteString -> IO (Either (FileError e) ())
- writeByteStringFile :: MonadIO m => File content 'Out -> ByteString -> m (Either (FileError e) ())
- writeByteStringOutput :: MonadIO m => Maybe (File content 'Out) -> ByteString -> m (Either (FileError e) ())
- writeLazyByteStringFileWithOwnerPermissions :: File content 'Out -> ByteString -> IO (Either (FileError e) ())
- writeLazyByteStringFile :: MonadIO m => File content 'Out -> ByteString -> m (Either (FileError e) ())
- writeLazyByteStringOutput :: MonadIO m => Maybe (File content 'Out) -> ByteString -> m (Either (FileError e) ())
- writeTextFileWithOwnerPermissions :: File content 'Out -> Text -> IO (Either (FileError e) ())
- writeTextFile :: MonadIO m => File content 'Out -> Text -> m (Either (FileError e) ())
- writeTextOutput :: MonadIO m => Maybe (File content 'Out) -> Text -> m (Either (FileError e) ())
- class Typeable t => HasTypeProxy t where
- data AsType t
- proxyToAsType :: Proxy t -> AsType t
- data family AsType t
- asType :: HasTypeProxy t => AsType t
- class (Eq (VerificationKey keyrole), Show (VerificationKey keyrole), SerialiseAsRawBytes (Hash keyrole), HasTextEnvelope (VerificationKey keyrole), HasTextEnvelope (SigningKey keyrole)) => Key keyrole where
- data VerificationKey keyrole
- data SigningKey keyrole
- getVerificationKey :: SigningKey keyrole -> VerificationKey keyrole
- deterministicSigningKey :: AsType keyrole -> Seed -> SigningKey keyrole
- deterministicSigningKeySeedSize :: AsType keyrole -> Word
- verificationKeyHash :: VerificationKey keyrole -> Hash keyrole
- data family SigningKey keyrole
- data family VerificationKey keyrole
- castVerificationKey :: CastVerificationKeyRole keyroleA keyroleB => VerificationKey keyroleA -> VerificationKey keyroleB
- castSigningKey :: CastSigningKeyRole keyroleA keyroleB => SigningKey keyroleA -> SigningKey keyroleB
- generateSigningKey :: (MonadIO m, Key keyrole) => AsType keyrole -> m (SigningKey keyrole)
- generateInsecureSigningKey :: (MonadIO m, Key keyrole, SerialiseAsRawBytes (SigningKey keyrole)) => StdGen -> AsType keyrole -> m (SigningKey keyrole, StdGen)
- data family Hash keyrole
- castHash :: CastHash roleA roleB => Hash roleA -> Hash roleB
- renderSafeHashAsHex :: SafeHash tag -> Text
- data MnemonicSize
- generateMnemonic :: MonadIO m => MnemonicSize -> m [Text]
- data MnemonicToSigningKeyError
- signingKeyFromMnemonic :: SigningKeyFromRootKey keyrole => AsType keyrole -> [Text] -> Word32 -> Either MnemonicToSigningKeyError (SigningKey keyrole)
- signingKeyFromMnemonicWithPaymentKeyIndex :: IndexedSigningKeyFromRootKey keyrole => AsType keyrole -> [Text] -> Word32 -> Word32 -> Either MnemonicToSigningKeyError (SigningKey keyrole)
- findMnemonicWordsWithPrefix :: Text -> [(Text, Int)]
- autocompleteMnemonicPrefix :: Text -> Maybe Text
- data Address addrtype where
- data ByronAddr
- data ShelleyAddr
- data NetworkId
- makeByronAddress :: NetworkId -> VerificationKey ByronKey -> Address ByronAddr
- data ByronKey
- data ByronKeyLegacy
- makeShelleyAddress :: NetworkId -> PaymentCredential -> StakeAddressReference -> Address ShelleyAddr
- data PaymentCredential
- newtype StakeAddressPointer = StakeAddressPointer {}
- data StakeAddressReference
- data PaymentKey
- data PaymentExtendedKey
- data AddressAny
- lexPlausibleAddressString :: Parser Text
- parseAddressAny :: SerialiseAddress addr => Parser addr
- data AddressInEra era where
- AddressInEra :: forall addrtype era. AddressTypeInEra addrtype era -> Address addrtype -> AddressInEra era
- isKeyAddress :: AddressInEra era -> Bool
- data AddressTypeInEra addrtype era where
- ByronAddressInAnyEra :: forall era. AddressTypeInEra ByronAddr era
- ShelleyAddressInEra :: forall era. ShelleyBasedEra era -> AddressTypeInEra ShelleyAddr era
- byronAddressInEra :: Address ByronAddr -> AddressInEra era
- shelleyAddressInEra :: ShelleyBasedEra era -> Address ShelleyAddr -> AddressInEra era
- anyAddressInShelleyBasedEra :: ShelleyBasedEra era -> AddressAny -> AddressInEra era
- anyAddressInEra :: CardanoEra era -> AddressAny -> Either String (AddressInEra era)
- toAddressAny :: Address addr -> AddressAny
- makeByronAddressInEra :: NetworkId -> VerificationKey ByronKey -> AddressInEra era
- makeShelleyAddressInEra :: ShelleyBasedEra era -> NetworkId -> PaymentCredential -> StakeAddressReference -> AddressInEra era
- data StakeAddress
- data StakeCredential
- makeStakeAddress :: NetworkId -> StakeCredential -> StakeAddress
- stakeAddressCredential :: StakeAddress -> StakeCredential
- data StakeKey
- data StakeExtendedKey
- newtype Quantity = Quantity Integer
- newtype PolicyId = PolicyId {}
- scriptPolicyId :: Script lang -> PolicyId
- newtype AssetName = AssetName ByteString
- data AssetId
- data Value
- parsePolicyId :: Parser PolicyId
- parseAssetName :: Parser AssetName
- parseTxOutMultiAssetValue :: Parser Value
- parseMintingMultiAssetValue :: MaryEraOnwards era -> Parser MultiAsset
- parseUTxOValue :: Parser Value
- selectAsset :: Value -> AssetId -> Quantity
- valueFromList :: [(AssetId, Quantity)] -> Value
- valueToList :: Value -> [(AssetId, Quantity)]
- filterValue :: (AssetId -> Bool) -> Value -> Value
- negateValue :: Value -> Value
- newtype ValueNestedRep = ValueNestedRep [ValueNestedBundle]
- data ValueNestedBundle
- valueToNestedRep :: Value -> ValueNestedRep
- valueFromNestedRep :: ValueNestedRep -> Value
- renderValue :: Value -> Text
- renderMultiAsset :: MultiAsset -> Text
- renderValuePretty :: Value -> Text
- renderMultiAssetPretty :: MultiAsset -> Text
- toLedgerValue :: MaryEraOnwards era -> Value -> Value (ShelleyLedgerEra era)
- fromLedgerValue :: ShelleyBasedEra era -> Value (ShelleyLedgerEra era) -> Value
- newtype PolicyAssets = PolicyAssets (Map AssetName Quantity)
- policyAssetsToValue :: PolicyId -> PolicyAssets -> Value
- valueToPolicyAssets :: Value -> Map PolicyId PolicyAssets
- multiAssetToPolicyAssets :: MultiAsset -> Map PolicyId PolicyAssets
- type Lovelace = Coin
- quantityToLovelace :: Quantity -> Lovelace
- lovelaceToQuantity :: Lovelace -> Quantity
- selectLovelace :: Value -> Lovelace
- lovelaceToValue :: Lovelace -> Value
- valueToLovelace :: Value -> Maybe Lovelace
- data Block era where
- ByronBlock :: ByronBlock -> Block ByronEra
- ShelleyBlock :: forall era. ShelleyBasedEra era -> ShelleyBlock (ConsensusProtocol era) (ShelleyLedgerEra era) -> Block era
- pattern Block :: BlockHeader -> [Tx era] -> Block era
- data BlockHeader = BlockHeader !SlotNo !(Hash BlockHeader) !BlockNo
- getBlockHeader :: Block era -> BlockHeader
- getBlockTxs :: Block era -> [Tx era]
- data ChainPoint
- newtype EpochNo = EpochNo {}
- data ChainTip
- newtype BlockNo = BlockNo {}
- chainTipToChainPoint :: ChainTip -> ChainPoint
- data TxBody era where
- ShelleyTxBody :: forall era. ShelleyBasedEra era -> TxBody (ShelleyLedgerEra era) -> [Script (ShelleyLedgerEra era)] -> TxBodyScriptData era -> Maybe (TxAuxData (ShelleyLedgerEra era)) -> TxScriptValidity era -> TxBody era
- pattern TxBody :: TxBodyContent ViewTx era -> TxBody era
- createTransactionBody :: HasCallStack => ShelleyBasedEra era -> TxBodyContent BuildTx era -> Either TxBodyError (TxBody era)
- createAndValidateTransactionBody :: ShelleyBasedEra era -> TxBodyContent BuildTx era -> Either TxBodyError (TxBody era)
- makeByronTransactionBody :: TxIns BuildTx ByronEra -> [TxOut CtxTx ByronEra] -> Either TxBodyError (Annotated Tx ByteString)
- data TxBodyContent build era = TxBodyContent {
- txIns :: TxIns build era
- txInsCollateral :: TxInsCollateral era
- txInsReference :: TxInsReference build era
- txOuts :: [TxOut CtxTx era]
- txTotalCollateral :: TxTotalCollateral era
- txReturnCollateral :: TxReturnCollateral CtxTx era
- txFee :: TxFee era
- txValidityLowerBound :: TxValidityLowerBound era
- txValidityUpperBound :: TxValidityUpperBound era
- txMetadata :: TxMetadataInEra era
- txAuxScripts :: TxAuxScripts era
- txExtraKeyWits :: TxExtraKeyWitnesses era
- txProtocolParams :: BuildTxWith build (Maybe (LedgerProtocolParameters era))
- txWithdrawals :: TxWithdrawals build era
- txCertificates :: TxCertificates build era
- txUpdateProposal :: TxUpdateProposal era
- txMintValue :: TxMintValue build era
- txScriptValidity :: TxScriptValidity era
- txProposalProcedures :: Maybe (Featured ConwayEraOnwards era (TxProposalProcedures build era))
- txVotingProcedures :: Maybe (Featured ConwayEraOnwards era (TxVotingProcedures build era))
- txCurrentTreasuryValue :: Maybe (Featured ConwayEraOnwards era (Maybe Coin))
- txTreasuryDonation :: Maybe (Featured ConwayEraOnwards era Coin)
- getTxBodyContent :: TxBody era -> TxBodyContent ViewTx era
- defaultTxBodyContent :: ShelleyBasedEra era -> TxBodyContent BuildTx era
- defaultTxFee :: ShelleyBasedEra era -> TxFee era
- defaultTxValidityUpperBound :: ShelleyBasedEra era -> TxValidityUpperBound era
- setTxIns :: TxIns build era -> TxBodyContent build era -> TxBodyContent build era
- modTxIns :: (TxIns build era -> TxIns build era) -> TxBodyContent build era -> TxBodyContent build era
- addTxIns :: TxIns build era -> TxBodyContent build era -> TxBodyContent build era
- addTxIn :: (TxIn, BuildTxWith build (Witness WitCtxTxIn era)) -> TxBodyContent build era -> TxBodyContent build era
- setTxInsCollateral :: TxInsCollateral era -> TxBodyContent build era -> TxBodyContent build era
- modTxInsCollateral :: (TxInsCollateral era -> TxInsCollateral era) -> TxBodyContent build era -> TxBodyContent build era
- addTxInsCollateral :: IsAlonzoBasedEra era => [TxIn] -> TxBodyContent build era -> TxBodyContent build era
- addTxInCollateral :: IsAlonzoBasedEra era => TxIn -> TxBodyContent build era -> TxBodyContent build era
- setTxInsReference :: TxInsReference build era -> TxBodyContent build era -> TxBodyContent build era
- modTxInsReference :: (TxInsReference build era -> TxInsReference build era) -> TxBodyContent build era -> TxBodyContent build era
- addTxInsReference :: (Applicative (BuildTxWith build), IsBabbageBasedEra era) => [TxIn] -> Set HashableScriptData -> TxBodyContent build era -> TxBodyContent build era
- addTxInReference :: (Applicative (BuildTxWith build), IsBabbageBasedEra era) => TxIn -> Maybe HashableScriptData -> TxBodyContent build era -> TxBodyContent build era
- setTxOuts :: [TxOut CtxTx era] -> TxBodyContent build era -> TxBodyContent build era
- modTxOuts :: ([TxOut CtxTx era] -> [TxOut CtxTx era]) -> TxBodyContent build era -> TxBodyContent build era
- addTxOuts :: [TxOut CtxTx era] -> TxBodyContent build era -> TxBodyContent build era
- addTxOut :: TxOut CtxTx era -> TxBodyContent build era -> TxBodyContent build era
- setTxTotalCollateral :: TxTotalCollateral era -> TxBodyContent build era -> TxBodyContent build era
- modTxTotalCollateral :: (TxTotalCollateral era -> TxTotalCollateral era) -> TxBodyContent build era -> TxBodyContent build era
- setTxReturnCollateral :: TxReturnCollateral CtxTx era -> TxBodyContent build era -> TxBodyContent build era
- modTxReturnCollateral :: (TxReturnCollateral CtxTx era -> TxReturnCollateral CtxTx era) -> TxBodyContent build era -> TxBodyContent build era
- setTxFee :: TxFee era -> TxBodyContent build era -> TxBodyContent build era
- modTxFee :: (TxFee era -> TxFee era) -> TxBodyContent build era -> TxBodyContent build era
- setTxValidityLowerBound :: TxValidityLowerBound era -> TxBodyContent build era -> TxBodyContent build era
- modTxValidityLowerBound :: (TxValidityLowerBound era -> TxValidityLowerBound era) -> TxBodyContent build era -> TxBodyContent build era
- setTxValidityUpperBound :: TxValidityUpperBound era -> TxBodyContent build era -> TxBodyContent build era
- modTxValidityUpperBound :: (TxValidityUpperBound era -> TxValidityUpperBound era) -> TxBodyContent build era -> TxBodyContent build era
- setTxMetadata :: TxMetadataInEra era -> TxBodyContent build era -> TxBodyContent build era
- modTxMetadata :: (TxMetadataInEra era -> TxMetadataInEra era) -> TxBodyContent build era -> TxBodyContent build era
- setTxAuxScripts :: TxAuxScripts era -> TxBodyContent build era -> TxBodyContent build era
- modTxAuxScripts :: (TxAuxScripts era -> TxAuxScripts era) -> TxBodyContent build era -> TxBodyContent build era
- setTxExtraKeyWits :: TxExtraKeyWitnesses era -> TxBodyContent build era -> TxBodyContent build era
- modTxExtraKeyWits :: (TxExtraKeyWitnesses era -> TxExtraKeyWitnesses era) -> TxBodyContent build era -> TxBodyContent build era
- addTxExtraKeyWits :: IsAlonzoBasedEra era => [Hash PaymentKey] -> TxBodyContent build era -> TxBodyContent build era
- setTxProtocolParams :: BuildTxWith build (Maybe (LedgerProtocolParameters era)) -> TxBodyContent build era -> TxBodyContent build era
- setTxWithdrawals :: TxWithdrawals build era -> TxBodyContent build era -> TxBodyContent build era
- modTxWithdrawals :: (TxWithdrawals build era -> TxWithdrawals build era) -> TxBodyContent build era -> TxBodyContent build era
- setTxCertificates :: TxCertificates build era -> TxBodyContent build era -> TxBodyContent build era
- modTxCertificates :: (TxCertificates build era -> TxCertificates build era) -> TxBodyContent build era -> TxBodyContent build era
- setTxUpdateProposal :: TxUpdateProposal era -> TxBodyContent build era -> TxBodyContent build era
- modTxUpdateProposal :: (TxUpdateProposal era -> TxUpdateProposal era) -> TxBodyContent build era -> TxBodyContent build era
- setTxMintValue :: TxMintValue build era -> TxBodyContent build era -> TxBodyContent build era
- modTxMintValue :: (TxMintValue build era -> TxMintValue build era) -> TxBodyContent build era -> TxBodyContent build era
- addTxMintValue :: IsMaryBasedEra era => Map PolicyId (PolicyAssets, BuildTxWith build (ScriptWitness WitCtxMint era)) -> TxBodyContent build era -> TxBodyContent build era
- subtractTxMintValue :: IsMaryBasedEra era => Map PolicyId (PolicyAssets, BuildTxWith build (ScriptWitness WitCtxMint era)) -> TxBodyContent build era -> TxBodyContent build era
- setTxScriptValidity :: TxScriptValidity era -> TxBodyContent build era -> TxBodyContent build era
- modTxScriptValidity :: (TxScriptValidity era -> TxScriptValidity era) -> TxBodyContent build era -> TxBodyContent build era
- setTxProposalProcedures :: Maybe (Featured ConwayEraOnwards era (TxProposalProcedures build era)) -> TxBodyContent build era -> TxBodyContent build era
- setTxVotingProcedures :: Maybe (Featured ConwayEraOnwards era (TxVotingProcedures build era)) -> TxBodyContent build era -> TxBodyContent build era
- setTxCurrentTreasuryValue :: Maybe (Featured ConwayEraOnwards era (Maybe Coin)) -> TxBodyContent build era -> TxBodyContent build era
- setTxTreasuryDonation :: Maybe (Featured ConwayEraOnwards era Coin) -> TxBodyContent build era -> TxBodyContent build era
- data TxBodyError
- = TxBodyPlutusScriptDecodeError DecoderError
- | TxBodyEmptyTxIns
- | TxBodyEmptyTxInsCollateral
- | TxBodyEmptyTxOuts
- | TxBodyOutputError !TxOutputError
- | TxBodyMetadataError ![(Word64, TxMetadataRangeError)]
- | TxBodyInIxOverflow !TxIn
- | TxBodyMissingProtocolParams
- | TxBodyProtocolParamsConversionError !ProtocolParametersConversionError
- data TxOutputError
- data TxBodyScriptData era where
- TxBodyNoScriptData :: forall era. TxBodyScriptData era
- TxBodyScriptData :: forall era. AlonzoEraOnwardsConstraints era => AlonzoEraOnwards era -> TxDats (ShelleyLedgerEra era) -> Redeemers (ShelleyLedgerEra era) -> TxBodyScriptData era
- newtype TxId = TxId (Hash HASH EraIndependentTxBody)
- getTxId :: TxBody era -> TxId
- getTxIdByron :: ATxAux ByteString -> TxId
- data TxIn = TxIn TxId TxIx
- type TxIns build era = [(TxIn, BuildTxWith build (Witness WitCtxTxIn era))]
- newtype TxIx = TxIx Word
- renderTxIn :: TxIn -> Text
- getReferenceInputsSizeForTxIds :: ShelleyLedgerEra era ~ ledgerera => BabbageEraOnwards era -> UTxO ledgerera -> Set TxIn -> Int
- data CtxTx
- data CtxUTxO
- data TxOut ctx era = TxOut (AddressInEra era) (TxOutValue era) (TxOutDatum ctx era) (ReferenceScript era)
- data TxOutValue era where
- TxOutValueByron :: Coin -> TxOutValue ByronEra
- TxOutValueShelleyBased :: forall era. (Eq (Value (ShelleyLedgerEra era)), Show (Value (ShelleyLedgerEra era))) => ShelleyBasedEra era -> Value (ShelleyLedgerEra era) -> TxOutValue era
- data TxOutInAnyEra where
- TxOutInAnyEra :: forall era. CardanoEra era -> TxOut CtxTx era -> TxOutInAnyEra
- txOutInAnyEra :: CardanoEra era -> TxOut CtxTx era -> TxOutInAnyEra
- txOutValueToLovelace :: TxOutValue era -> Coin
- txOutValueToValue :: TxOutValue era -> Value
- lovelaceToTxOutValue :: ShelleyBasedEra era -> Coin -> TxOutValue era
- data TxOutDatum ctx era where
- TxOutDatumNone :: forall ctx era. TxOutDatum ctx era
- TxOutDatumHash :: forall era ctx. AlonzoEraOnwards era -> Hash ScriptData -> TxOutDatum ctx era
- TxOutSupplementalDatum :: forall era. AlonzoEraOnwards era -> HashableScriptData -> TxOutDatum CtxTx era
- TxOutDatumInline :: forall era ctx. BabbageEraOnwards era -> HashableScriptData -> TxOutDatum ctx era
- parseHash :: SerialiseAsRawBytes (Hash a) => Parser (Hash a)
- data TxInsCollateral era where
- TxInsCollateralNone :: forall era. TxInsCollateral era
- TxInsCollateral :: forall era. AlonzoEraOnwards era -> [TxIn] -> TxInsCollateral era
- data TxInsReference build era where
- TxInsReferenceNone :: forall build era. TxInsReference build era
- TxInsReference :: forall era build. BabbageEraOnwards era -> [TxIn] -> TxInsReferenceDatums build -> TxInsReference build era
- data TxTotalCollateral era where
- TxTotalCollateralNone :: forall era. TxTotalCollateral era
- TxTotalCollateral :: forall era. BabbageEraOnwards era -> Coin -> TxTotalCollateral 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 TxFee era where
- TxFeeExplicit :: forall era. ShelleyBasedEra era -> Coin -> TxFee era
- data TxValidityLowerBound era where
- TxValidityNoLowerBound :: forall era. TxValidityLowerBound era
- TxValidityLowerBound :: forall era. AllegraEraOnwards era -> SlotNo -> TxValidityLowerBound era
- data TxValidityUpperBound era where
- TxValidityUpperBound :: forall era. ShelleyBasedEra era -> Maybe SlotNo -> TxValidityUpperBound era
- newtype SlotNo = SlotNo {}
- newtype EpochSlots = EpochSlots {}
- data TxMetadataInEra era where
- TxMetadataNone :: forall era. TxMetadataInEra era
- TxMetadataInEra :: forall era. ShelleyBasedEra era -> TxMetadata -> TxMetadataInEra era
- data TxAuxScripts era where
- TxAuxScriptsNone :: forall era. TxAuxScripts era
- TxAuxScripts :: forall era. AllegraEraOnwards era -> [ScriptInEra era] -> TxAuxScripts era
- data TxExtraKeyWitnesses era where
- TxExtraKeyWitnessesNone :: forall era. TxExtraKeyWitnesses era
- TxExtraKeyWitnesses :: forall era. AlonzoEraOnwards era -> [Hash PaymentKey] -> TxExtraKeyWitnesses 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 TxCertificates build era where
- TxCertificatesNone :: forall build era. TxCertificates build era
- TxCertificates :: forall era build. ShelleyBasedEra era -> OMap (Certificate era) (BuildTxWith build (Maybe (StakeCredential, Witness WitCtxStake era))) -> TxCertificates build era
- mkTxCertificates :: Applicative (BuildTxWith build) => ShelleyBasedEra era -> [(Certificate era, Maybe (ScriptWitness WitCtxStake era))] -> TxCertificates build era
- data TxUpdateProposal era where
- TxUpdateProposalNone :: forall era. TxUpdateProposal era
- TxUpdateProposal :: forall era. ShelleyToBabbageEra era -> UpdateProposal -> TxUpdateProposal era
- data TxMintValue build era where
- TxMintNone :: forall build era. TxMintValue build era
- TxMintValue :: forall era build. MaryEraOnwards era -> Map PolicyId (PolicyAssets, BuildTxWith build (ScriptWitness WitCtxMint era)) -> TxMintValue build era
- mkTxMintValue :: MaryEraOnwards era -> [(PolicyId, PolicyAssets, BuildTxWith build (ScriptWitness WitCtxMint era))] -> TxMintValue build era
- txMintValueToValue :: TxMintValue build era -> Value
- indexTxMintValue :: TxMintValue build era -> [(ScriptWitnessIndex, PolicyId, PolicyAssets, BuildTxWith build (ScriptWitness WitCtxMint era))]
- data TxVotingProcedures build era where
- TxVotingProceduresNone :: forall build era. TxVotingProcedures build era
- TxVotingProcedures :: forall era build. VotingProcedures (ShelleyLedgerEra era) -> BuildTxWith build (Map Voter (ScriptWitness WitCtxStake era)) -> TxVotingProcedures build era
- mkTxVotingProcedures :: Applicative (BuildTxWith build) => [(VotingProcedures era, Maybe (ScriptWitness WitCtxStake era))] -> Either (VotesMergingConflict era) (TxVotingProcedures build era)
- data TxProposalProcedures build era where
- TxProposalProceduresNone :: forall build era. TxProposalProcedures build era
- TxProposalProcedures :: forall era build. EraPParams (ShelleyLedgerEra era) => OMap (ProposalProcedure (ShelleyLedgerEra era)) (BuildTxWith build (Maybe (ScriptWitness WitCtxStake era))) -> TxProposalProcedures build era
- mkTxProposalProcedures :: forall era build. (Applicative (BuildTxWith build), IsShelleyBasedEra era) => [(ProposalProcedure (ShelleyLedgerEra era), Maybe (ScriptWitness WitCtxStake era))] -> TxProposalProcedures build era
- convProposalProcedures :: TxProposalProcedures build era -> OSet (ProposalProcedure (ShelleyLedgerEra era))
- data BuildTxWith build a where
- ViewTx :: forall a. BuildTxWith ViewTx a
- BuildTxWith :: forall a. a -> BuildTxWith BuildTx a
- data BuildTx
- data ViewTx
- buildTxWithToMaybe :: BuildTxWith build a -> Maybe a
- newtype LedgerEpochInfo = LedgerEpochInfo {}
- toLedgerEpochInfo :: EraHistory -> LedgerEpochInfo
- evaluateTransactionFee :: ShelleyBasedEra era -> PParams (ShelleyLedgerEra era) -> TxBody era -> Word -> Word -> Int -> Coin
- calculateMinTxFee :: ShelleyBasedEra era -> PParams (ShelleyLedgerEra era) -> UTxO era -> TxBody era -> Word -> Coin
- estimateTransactionKeyWitnessCount :: TxBodyContent BuildTx era -> Word
- calculateMinimumUTxO :: HasCallStack => ShelleyBasedEra era -> PParams (ShelleyLedgerEra era) -> TxOut CtxTx era -> Coin
- evaluateTransactionExecutionUnits :: CardanoEra era -> SystemStart -> LedgerEpochInfo -> LedgerProtocolParameters era -> UTxO era -> TxBody era -> Map ScriptWitnessIndex (Either ScriptExecutionError (EvalTxExecutionUnitsLog, ExecutionUnits))
- data ScriptExecutionError
- = ScriptErrorMissingTxIn TxIn
- | ScriptErrorTxInWithoutDatum TxIn
- | ScriptErrorWrongDatum (Hash ScriptData)
- | ScriptErrorEvaluationFailed DebugPlutusFailure
- | ScriptErrorExecutionUnitsOverflow
- | ScriptErrorNotPlutusWitnessedTxIn ScriptWitnessIndex ScriptHash
- | ScriptErrorRedeemerPointsToUnknownScriptHash ScriptWitnessIndex
- | ScriptErrorMissingScript ScriptWitnessIndex ResolvablePointers
- | ScriptErrorMissingCostModel Language
- | (EraPlutusContext (ShelleyLedgerEra era), Show (ContextError (ShelleyLedgerEra era))) => ScriptErrorTranslationError (ContextError (ShelleyLedgerEra era))
- data TransactionValidityError era where
- TransactionValidityIntervalError :: forall era. PastHorizonException -> TransactionValidityError era
- TransactionValidityCostModelError :: forall era. Map AnyPlutusScriptVersion CostModel -> String -> TransactionValidityError era
- evaluateTransactionBalance :: ShelleyBasedEra era -> PParams (ShelleyLedgerEra era) -> Set PoolId -> Map StakeCredential Coin -> Map (Credential 'DRepRole) Coin -> UTxO era -> TxBody era -> TxOutValue era
- estimateBalancedTxBody :: HasCallStack => MaryEraOnwards era -> TxBodyContent BuildTx era -> PParams (ShelleyLedgerEra era) -> Set PoolId -> Map StakeCredential Coin -> Map (Credential 'DRepRole) 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) Coin -> AddressInEra era -> Either (AutoBalanceError era) (BalancedTxBody era)
- makeTransactionBodyAutoBalance :: HasCallStack => ShelleyBasedEra era -> SystemStart -> LedgerEpochInfo -> LedgerProtocolParameters era -> Set PoolId -> Map StakeCredential Coin -> Map (Credential 'DRepRole) Coin -> UTxO era -> TxBodyContent BuildTx era -> AddressInEra era -> Maybe Word -> Either (TxBodyErrorAutoBalance era) (BalancedTxBody era)
- data AutoBalanceError era
- data BalancedTxBody era = BalancedTxBody (TxBodyContent BuildTx era) (TxBody era) (TxOut CtxTx era) Coin
- data FeeEstimationMode era
- newtype RequiredShelleyKeyWitnesses = RequiredShelleyKeyWitnesses {}
- newtype RequiredByronKeyWitnesses = RequiredByronKeyWitnesses {}
- newtype TotalReferenceScriptsSize = TotalReferenceScriptsSize {}
- data TxFeeEstimationError era
- = TxFeeEstimationTransactionTranslationError (TransactionValidityError era)
- | TxFeeEstimationScriptExecutionError (TxBodyErrorAutoBalance era)
- | TxFeeEstimationBalanceError (TxBodyErrorAutoBalance era)
- | TxFeeEstimationxBodyError TxBodyError
- | TxFeeEstimationFinalConstructionError TxBodyError
- | TxFeeEstimationOnlyMaryOnwardsSupportedError
- data TxBodyErrorAutoBalance era
- = TxBodyError TxBodyError
- | TxBodyScriptExecutionError [(ScriptWitnessIndex, ScriptExecutionError)]
- | TxBodyScriptBadScriptValidity
- | TxBodyErrorBalanceNegative Coin MultiAsset
- | TxBodyErrorAdaBalanceTooSmall TxOutInAnyEra Coin Coin
- | TxBodyErrorByronEraNotSupported
- | TxBodyErrorMissingParamMinUTxO
- | TxBodyErrorMinUTxONotMet TxOutInAnyEra Coin
- | TxBodyErrorNonAdaAssetsUnbalanced Value
- | TxBodyErrorScriptWitnessIndexMissingFromExecUnitsMap ScriptWitnessIndex (Map ScriptWitnessIndex ExecutionUnits)
- data TxScriptValidity era where
- TxScriptValidityNone :: forall era. TxScriptValidity era
- TxScriptValidity :: forall era. AlonzoEraOnwards era -> ScriptValidity -> TxScriptValidity era
- data ScriptValidity
- txScriptValidityToScriptValidity :: TxScriptValidity era -> ScriptValidity
- data Tx era where
- pattern Tx :: TxBody era -> [KeyWitness era] -> Tx era
- getTxBody :: Tx era -> TxBody era
- getTxWitnesses :: Tx era -> [KeyWitness era]
- signByronTransaction :: NetworkId -> Annotated Tx ByteString -> [SigningKey ByronKey] -> ATxAux ByteString
- signShelleyTransaction :: ShelleyBasedEra era -> TxBody era -> [ShelleyWitnessSigningKey] -> Tx era
- makeSignedByronTransaction :: [KeyWitness era] -> Annotated Tx ByteString -> ATxAux ByteString
- makeSignedTransaction :: [KeyWitness era] -> TxBody era -> Tx era
- data KeyWitness era
- makeByronKeyWitness :: IsByronKey key => NetworkId -> Annotated Tx ByteString -> SigningKey key -> KeyWitness ByronEra
- data ShelleyWitnessSigningKey
- = WitnessPaymentKey (SigningKey PaymentKey)
- | WitnessPaymentExtendedKey (SigningKey PaymentExtendedKey)
- | WitnessStakeKey (SigningKey StakeKey)
- | WitnessStakeExtendedKey (SigningKey StakeExtendedKey)
- | WitnessStakePoolKey (SigningKey StakePoolKey)
- | WitnessStakePoolExtendedKey (SigningKey StakePoolExtendedKey)
- | 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)
- makeShelleyKeyWitness :: ShelleyBasedEra era -> TxBody era -> ShelleyWitnessSigningKey -> KeyWitness era
- makeShelleyKeyWitness' :: ShelleyBasedEra era -> TxBody (ShelleyLedgerEra era) -> ShelleyWitnessSigningKey -> KeyWitness era
- makeShelleyBootstrapWitness :: ShelleyBasedEra era -> WitnessNetworkIdOrByronAddress -> TxBody era -> SigningKey ByronKey -> KeyWitness era
- makeShelleyBasedBootstrapWitness :: ShelleyBasedEra era -> WitnessNetworkIdOrByronAddress -> TxBody (ShelleyLedgerEra era) -> SigningKey ByronKey -> KeyWitness era
- newtype TxMetadata = TxMetadata {}
- class AsTxMetadata a where
- asTxMetadata :: a -> TxMetadata
- data TxMetadataValue
- makeTransactionMetadata :: Map Word64 TxMetadataValue -> TxMetadata
- mergeTransactionMetadata :: (TxMetadataValue -> TxMetadataValue -> TxMetadataValue) -> TxMetadata -> TxMetadata -> TxMetadata
- metaTextChunks :: Text -> TxMetadataValue
- metaBytesChunks :: ByteString -> TxMetadataValue
- validateTxMetadata :: TxMetadata -> Either [(Word64, TxMetadataRangeError)] ()
- data TxMetadataRangeError
- data TxMetadataJsonSchema
- metadataFromJson :: TxMetadataJsonSchema -> Value -> Either TxMetadataJsonError TxMetadata
- metadataToJson :: TxMetadataJsonSchema -> TxMetadata -> Value
- metadataValueFromJsonNoSchema :: Value -> Either TxMetadataJsonSchemaError TxMetadataValue
- metadataValueToJsonNoSchema :: TxMetadataValue -> Value
- data TxMetadataJsonError
- data TxMetadataJsonSchemaError
- = TxMetadataJsonNullNotAllowed
- | TxMetadataJsonBoolNotAllowed
- | TxMetadataJsonNumberNotInteger !Double
- | TxMetadataJsonNotObject !Value
- | TxMetadataJsonBadObject ![(Text, Value)]
- | TxMetadataJsonBadMapPair !Value
- | TxMetadataJsonTypeMismatch !Text !Value
- data CIP108 = BaseGovActionMetadata
- data DRepMetadata
- data DRepMetadataReference
- hashDRepMetadata :: ByteString -> (DRepMetadata, Hash DRepMetadata)
- data CIP119 = DrepRegistrationMetadata
- data Certificate era where
- ShelleyRelatedCertificate :: forall era. Typeable era => ShelleyToBabbageEra era -> ShelleyTxCert (ShelleyLedgerEra era) -> Certificate era
- ConwayCertificate :: forall era. Typeable era => ConwayEraOnwards era -> ConwayTxCert (ShelleyLedgerEra era) -> Certificate 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 -> StakeDelegationRequirements era
- StakeDelegationRequirementsPreConway :: forall era. ShelleyToBabbageEra era -> StakeCredential -> PoolId -> StakeDelegationRequirements era
- makeStakeAddressDelegationCertificate :: StakeDelegationRequirements era -> Certificate era
- makeStakeAddressRegistrationCertificate :: StakeAddressRequirements era -> Certificate era
- makeStakeAddressUnregistrationCertificate :: StakeAddressRequirements era -> Certificate era
- makeStakeAddressAndDRepDelegationCertificate :: ConwayEraOnwards era -> StakeCredential -> Delegatee -> Coin -> Certificate era
- data StakePoolRegistrationRequirements era where
- StakePoolRegistrationRequirementsConwayOnwards :: forall era. ConwayEraOnwards era -> PoolParams -> StakePoolRegistrationRequirements era
- StakePoolRegistrationRequirementsPreConway :: forall era. ShelleyToBabbageEra era -> PoolParams -> StakePoolRegistrationRequirements era
- data StakePoolRetirementRequirements era where
- StakePoolRetirementRequirementsConwayOnwards :: forall era. ConwayEraOnwards era -> PoolId -> EpochNo -> StakePoolRetirementRequirements era
- StakePoolRetirementRequirementsPreConway :: forall era. ShelleyToBabbageEra era -> PoolId -> EpochNo -> StakePoolRetirementRequirements era
- makeStakePoolRegistrationCertificate :: StakePoolRegistrationRequirements era -> Certificate era
- makeStakePoolRetirementCertificate :: StakePoolRetirementRequirements era -> Certificate era
- data StakePoolParameters
- data StakePoolRelay
- data StakePoolMetadataReference
- data AnchorDataFromCertificateError = InvalidPoolMetadataHashError Url ByteString
- getAnchorDataFromCertificate :: Certificate era -> Either AnchorDataFromCertificateError (Maybe Anchor)
- isDRepRegOrUpdateCert :: Certificate era -> Bool
- newtype DelegationsAndRewards = DelegationsAndRewards (Map StakeAddress Coin, Map StakeAddress PoolId)
- mergeDelegsAndRewards :: DelegationsAndRewards -> [(StakeAddress, Maybe Coin, Maybe PoolId)]
- data StakePoolMetadata
- validateAndHashStakePoolMetadata :: ByteString -> Either StakePoolMetadataValidationError (StakePoolMetadata, Hash StakePoolMetadata)
- data StakePoolMetadataValidationError
- data SimpleScript'
- data PlutusScriptV1
- data PlutusScriptV2
- data PlutusScriptV3
- data ScriptLanguage lang where
- SimpleScriptLanguage :: ScriptLanguage SimpleScript'
- PlutusScriptLanguage :: forall lang. IsPlutusScriptLanguage lang => PlutusScriptVersion lang -> ScriptLanguage lang
- data PlutusScriptVersion lang where
- data AnyScriptLanguage where
- AnyScriptLanguage :: forall lang. ScriptLanguage lang -> AnyScriptLanguage
- data AnyPlutusScriptVersion where
- AnyPlutusScriptVersion :: forall lang. IsPlutusScriptLanguage lang => PlutusScriptVersion lang -> AnyPlutusScriptVersion
- class IsScriptLanguage lang => IsPlutusScriptLanguage lang where
- class HasTypeProxy lang => IsScriptLanguage lang where
- scriptLanguage :: ScriptLanguage lang
- data Script lang where
- SimpleScript :: !SimpleScript -> Script SimpleScript'
- PlutusScript :: forall lang. IsPlutusScriptLanguage lang => !(PlutusScriptVersion lang) -> !(PlutusScript lang) -> Script lang
- data PlutusScriptInEra era lang where
- PlutusScriptInEra :: forall lang era. PlutusScript lang -> PlutusScriptInEra era lang
- data ScriptInAnyLang where
- ScriptInAnyLang :: forall lang. ScriptLanguage lang -> Script lang -> ScriptInAnyLang
- toScriptInAnyLang :: Script lang -> ScriptInAnyLang
- data ScriptInEra era where
- ScriptInEra :: forall lang era. ScriptLanguageInEra lang era -> Script lang -> ScriptInEra era
- toScriptInEra :: ShelleyBasedEra era -> ScriptInAnyLang -> Maybe (ScriptInEra era)
- eraOfScriptInEra :: ScriptInEra era -> ShelleyBasedEra era
- class HasScriptLanguageInEra lang era where
- scriptLanguageInEra :: ScriptLanguageInEra lang era
- class ToAlonzoScript lang era where
- toLedgerScript :: PlutusScript lang -> AlonzoScript (ShelleyLedgerEra era)
- type AlonzoEraOnwardsConstraints era = (HashAlgorithm HASH, Signable (VRF StandardCrypto) Seed, PraosProtocolSupportsNode (ConsensusProtocol era), ShelleyBlock (ConsensusProtocol era) (ShelleyLedgerEra era) ~ ConsensusBlockForEra era, ShelleyCompatible (ConsensusProtocol era) (ShelleyLedgerEra era), ADDRHASH ~ Blake2b_224, AlonzoEraPParams (ShelleyLedgerEra era), AlonzoEraTx (ShelleyLedgerEra era), AlonzoEraTxBody (ShelleyLedgerEra era), AlonzoEraTxOut (ShelleyLedgerEra era), AlonzoEraTxWits (ShelleyLedgerEra era), Era (ShelleyLedgerEra era), EraPParams (ShelleyLedgerEra era), EraTx (ShelleyLedgerEra era), EraTxBody (ShelleyLedgerEra era), EraTxOut (ShelleyLedgerEra era), EraUTxO (ShelleyLedgerEra era), HashAnnotated (TxBody (ShelleyLedgerEra era)) EraIndependentTxBody, MaryEraTxBody (ShelleyLedgerEra era), NativeScript (ShelleyLedgerEra era) ~ Timelock (ShelleyLedgerEra era), EraPlutusContext (ShelleyLedgerEra era), Script (ShelleyLedgerEra era) ~ AlonzoScript (ShelleyLedgerEra era), ScriptsNeeded (ShelleyLedgerEra era) ~ AlonzoScriptsNeeded (ShelleyLedgerEra era), ShelleyEraTxCert (ShelleyLedgerEra era), Value (ShelleyLedgerEra era) ~ MaryValue, FromCBOR (ChainDepState (ConsensusProtocol era)), FromCBOR (DebugLedgerState era), IsCardanoEra era, IsShelleyBasedEra era, ToJSON (ChainDepState (ConsensusProtocol era)), ToJSON (DebugLedgerState era), Typeable era, (era == ByronEra) ~ 'False)
- data WitCtxTxIn
- data WitCtxMint
- data WitCtxStake
- data WitCtx witctx where
- data ScriptWitness witctx era where
- SimpleScriptWitness :: forall era witctx. ScriptLanguageInEra SimpleScript' era -> SimpleScriptOrReferenceInput SimpleScript' -> ScriptWitness witctx era
- PlutusScriptWitness :: forall lang era witctx. IsPlutusScriptLanguage lang => ScriptLanguageInEra lang era -> PlutusScriptVersion lang -> PlutusScriptOrReferenceInput lang -> ScriptDatum witctx -> ScriptRedeemer -> ExecutionUnits -> ScriptWitness witctx era
- getScriptWitnessScript :: ScriptWitness witctx era -> Maybe (ScriptInEra era)
- getScriptWitnessReferenceInput :: ScriptWitness witctx era -> Maybe TxIn
- getScriptWitnessReferenceInputOrScript :: ScriptWitness witctx era -> Either (ScriptInEra era) TxIn
- data Witness witctx era where
- KeyWitness :: forall witctx era. KeyWitnessInCtx witctx -> Witness witctx era
- ScriptWitness :: forall witctx era. ScriptWitnessInCtx witctx -> ScriptWitness witctx era -> Witness witctx era
- data KeyWitnessInCtx witctx where
- data ScriptWitnessInCtx witctx where
- class IsScriptWitnessInCtx ctx where
- data ScriptDatum witctx where
- type ScriptRedeemer = HashableScriptData
- data AnyScriptWitness era where
- AnyScriptWitness :: forall witctx era. Typeable witctx => ScriptWitness witctx era -> AnyScriptWitness era
- data ScriptWitnessIndex
- renderScriptWitnessIndex :: ScriptWitnessIndex -> String
- collectTxBodyScriptWitnesses :: ShelleyBasedEra era -> TxBodyContent BuildTx era -> [(ScriptWitnessIndex, AnyScriptWitness era)]
- 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
- scriptLanguageSupportedInEra :: ShelleyBasedEra era -> ScriptLanguage lang -> Maybe (ScriptLanguageInEra lang era)
- sbeToSimpleScriptLanguageInEra :: ShelleyBasedEra era -> ScriptLanguageInEra SimpleScript' era
- languageOfScriptLanguageInEra :: ScriptLanguageInEra lang era -> ScriptLanguage lang
- eraOfScriptLanguageInEra :: ScriptLanguageInEra lang era -> ShelleyBasedEra era
- data SimpleScript
- data PlutusScript lang
- examplePlutusScriptAlwaysSucceeds :: WitCtx witctx -> PlutusScript PlutusScriptV1
- examplePlutusScriptAlwaysFails :: WitCtx witctx -> PlutusScript PlutusScriptV1
- collectPlutusScriptHashes :: AlonzoEraOnwards era -> Tx era -> UTxO era -> Map ScriptWitnessIndex ScriptHash
- data HashableScriptData
- hashScriptDataBytes :: HashableScriptData -> Hash ScriptData
- getOriginalScriptDataBytes :: HashableScriptData -> ByteString
- getScriptData :: HashableScriptData -> ScriptData
- unsafeHashableScriptData :: ScriptData -> HashableScriptData
- data ScriptData
- newtype ScriptDataRangeError = ScriptDataConstructorOutOfRange Integer
- validateScriptData :: ScriptData -> Either ScriptDataRangeError ()
- data ScriptDataJsonSchema
- scriptDataFromJson :: ScriptDataJsonSchema -> Value -> Either ScriptDataJsonError HashableScriptData
- scriptDataToJson :: ScriptDataJsonSchema -> HashableScriptData -> Value
- data ScriptDataJsonError
- data ScriptDataJsonSchemaError
- = ScriptDataJsonNullNotAllowed
- | ScriptDataJsonBoolNotAllowed
- | ScriptDataJsonNumberNotInteger !Double
- | ScriptDataJsonNotObject !Value
- | ScriptDataJsonBadObject ![(Text, Value)]
- | ScriptDataJsonBadMapPair !Value
- | ScriptDataJsonTypeMismatch !Text !Value
- data ScriptDataJsonBytesError
- scriptDataJsonToHashable :: ScriptDataJsonSchema -> Value -> Either ScriptDataJsonBytesError HashableScriptData
- data ExecutionUnits = ExecutionUnits {}
- data ExecutionUnitPrices = ExecutionUnitPrices {}
- newtype CostModel = CostModel [Int64]
- toAlonzoCostModel :: CostModel -> Language -> Either ProtocolParametersConversionError CostModel
- fromAlonzoCostModel :: CostModel -> CostModel
- toAlonzoCostModels :: Map AnyPlutusScriptVersion CostModel -> Either ProtocolParametersConversionError CostModels
- newtype ScriptHash = ScriptHash ScriptHash
- hashScript :: Script lang -> ScriptHash
- 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 InputDecodeError
- deserialiseInput :: NonEmpty (InputFormat a) -> ByteString -> Either InputDecodeError a
- deserialiseInputAnyOf :: [FromSomeType SerialiseAsBech32 b] -> [FromSomeType HasTextEnvelope b] -> ByteString -> Either InputDecodeError b
- renderInputDecodeError :: InputDecodeError -> Doc ann
- 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)
- | AStakePoolVerificationKey (VerificationKey StakePoolKey)
- | AStakePoolExtendedVerificationKey (VerificationKey StakePoolExtendedKey)
- | ADRepVerificationKey (VerificationKey DRepKey)
- | ADRepExtendedVerificationKey (VerificationKey DRepExtendedKey)
- | ACommitteeColdVerificationKey (VerificationKey CommitteeColdKey)
- | ACommitteeColdExtendedVerificationKey (VerificationKey CommitteeColdExtendedKey)
- | ACommitteeHotVerificationKey (VerificationKey CommitteeHotKey)
- | ACommitteeHotExtendedVerificationKey (VerificationKey CommitteeHotExtendedKey)
- deserialiseAnyVerificationKey :: ByteString -> Either InputDecodeError SomeAddressVerificationKey
- deserialiseAnyVerificationKeyBech32 :: ByteString -> Either Bech32DecodeError SomeAddressVerificationKey
- deserialiseAnyVerificationKeyTextEnvelope :: ByteString -> Either TextEnvelopeError SomeAddressVerificationKey
- renderSomeAddressVerificationKey :: SomeAddressVerificationKey -> Text
- mapSomeAddressVerificationKey :: (forall keyrole. Key keyrole => VerificationKey keyrole -> a) -> SomeAddressVerificationKey -> a
- class HasTypeProxy a => SerialiseAsCBOR a
- class Typeable a => ToCBOR a
- class Typeable a => FromCBOR a
- serialiseToCBOR :: SerialiseAsCBOR a => a -> ByteString
- deserialiseFromCBOR :: SerialiseAsCBOR a => AsType a -> ByteString -> Either DecoderError a
- class ToJSON a
- class FromJSON a
- serialiseToJSON :: ToJSON a => a -> ByteString
- deserialiseFromJSON :: FromJSON a => ByteString -> Either JsonDecodeError a
- newtype JsonDecodeError = JsonDecodeError String
- readFileJSON :: FromJSON a => FilePath -> IO (Either (FileError JsonDecodeError) a)
- writeFileJSON :: ToJSON a => FilePath -> a -> IO (Either (FileError ()) ())
- prettyPrintJSON :: ToJSON a => a -> ByteString
- class (HasTypeProxy a, SerialiseAsRawBytes a) => SerialiseAsBech32 a
- serialiseToBech32 :: SerialiseAsBech32 a => a -> Text
- deserialiseFromBech32 :: SerialiseAsBech32 a => Text -> Either Bech32DecodeError a
- deserialiseAnyOfFromBech32 :: [FromSomeType SerialiseAsBech32 b] -> Text -> Either Bech32DecodeError b
- data Bech32DecodeError
- = Bech32DecodingError !DecodingError
- | Bech32UnexpectedPrefix !Text !(Set Text)
- | Bech32DataPartToBytesError !Text
- | Bech32DeserialiseFromBytesError !ByteString
- | Bech32WrongPrefix !Text !Text
- | Bech32UnexpectedHeader !Text !Text
- newtype UsingBech32 a = UsingBech32 a
- class (SerialiseAsRawBytes a, HasTypeProxy a) => Cip129 a where
- cip129Bech32PrefixFor :: AsType a -> HumanReadablePart
- cip129HeaderHexByte :: a -> ByteString
- cip129Bech32PrefixesPermitted :: AsType a -> [Text]
- deserialiseFromBech32Cip129 :: Cip129 a => Text -> Either Bech32DecodeError a
- serialiseToBech32Cip129 :: Cip129 a => a -> Text
- serialiseGovActionIdToBech32Cip129 :: GovActionId -> Text
- deserialiseGovActionIdFromBech32Cip129 :: Text -> Either Bech32DecodeError GovActionId
- class HasTypeProxy addr => SerialiseAddress addr
- serialiseAddress :: SerialiseAddress addr => addr -> Text
- deserialiseAddress :: SerialiseAddress addr => AsType addr -> Text -> Maybe addr
- class (HasTypeProxy a, Typeable a) => SerialiseAsRawBytes a
- serialiseToRawBytes :: SerialiseAsRawBytes a => a -> ByteString
- deserialiseFromRawBytes :: SerialiseAsRawBytes a => AsType a -> ByteString -> Either SerialiseAsRawBytesError a
- newtype SerialiseAsRawBytesError = SerialiseAsRawBytesError {}
- serialiseToRawBytesHex :: SerialiseAsRawBytes a => a -> ByteString
- deserialiseFromRawBytesHex :: SerialiseAsRawBytes a => ByteString -> Either RawBytesHexError a
- serialiseToRawBytesHexText :: SerialiseAsRawBytes a => a -> Text
- data RawBytesHexError
- newtype UsingRawBytes a = UsingRawBytes a
- newtype UsingRawBytesHex a = UsingRawBytesHex a
- class SerialiseAsCBOR a => HasTextEnvelope a where
- data TextEnvelope = TextEnvelope {}
- newtype TextEnvelopeType = TextEnvelopeType String
- data TextEnvelopeDescr
- data TextEnvelopeError
- textEnvelopeTypeInEra :: HasTextEnvelope (f era) => CardanoEra era -> AsType (f era) -> TextEnvelopeType
- textEnvelopeRawCBOR :: TextEnvelope -> ByteString
- textEnvelopeToJSON :: HasTextEnvelope a => Maybe TextEnvelopeDescr -> a -> ByteString
- serialiseToTextEnvelope :: HasTextEnvelope a => Maybe TextEnvelopeDescr -> a -> TextEnvelope
- deserialiseFromTextEnvelope :: HasTextEnvelope a => TextEnvelope -> Either TextEnvelopeError a
- readFileTextEnvelope :: HasTextEnvelope a => File content 'In -> IO (Either (FileError TextEnvelopeError) a)
- writeFileTextEnvelope :: HasTextEnvelope a => File content 'Out -> Maybe TextEnvelopeDescr -> a -> IO (Either (FileError ()) ())
- readTextEnvelopeFromFile :: FilePath -> IO (Either (FileError TextEnvelopeError) TextEnvelope)
- readTextEnvelopeOfTypeFromFile :: TextEnvelopeType -> FilePath -> IO (Either (FileError TextEnvelopeError) TextEnvelope)
- 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
- readFileTextEnvelopeCddlAnyOf :: [FromSomeTypeCDDL TextEnvelope b] -> FilePath -> IO (Either (FileError TextEnvelopeCddlError) b)
- deserialiseFromTextEnvelopeCddlAnyOf :: [FromSomeTypeCDDL TextEnvelope b] -> TextEnvelope -> Either TextEnvelopeCddlError b
- writeTxFileTextEnvelopeCddl :: ShelleyBasedEra era -> File content 'Out -> Tx era -> IO (Either (FileError ()) ())
- writeTxFileTextEnvelopeCanonicalCddl :: ShelleyBasedEra era -> File content 'Out -> Tx era -> IO (Either (FileError ()) ())
- writeTxWitnessFileTextEnvelopeCddl :: ShelleyBasedEra era -> File () 'Out -> KeyWitness era -> IO (Either (FileError ()) ())
- deserialiseByronTxCddl :: TextEnvelope -> Either TextEnvelopeCddlError (ATxAux ByteString)
- serialiseWitnessLedgerCddl :: ShelleyBasedEra era -> KeyWitness era -> TextEnvelope
- deserialiseWitnessLedgerCddl :: ShelleyBasedEra era -> TextEnvelope -> Either TextEnvelopeCddlError (KeyWitness era)
- data TextEnvelopeCddlError
- readKeyFile :: NonEmpty (InputFormat a) -> FilePath -> IO (Either (FileError InputDecodeError) a)
- readKeyFileTextEnvelope :: HasTextEnvelope a => File content 'In -> IO (Either (FileError InputDecodeError) a)
- readKeyFileAnyOf :: forall content b. [FromSomeType SerialiseAsBech32 b] -> [FromSomeType HasTextEnvelope b] -> File content 'In -> IO (Either (FileError InputDecodeError) b)
- data FromSomeType (c :: Type -> Constraint) b where
- FromSomeType :: forall (c :: Type -> Constraint) a b. c a => AsType a -> (a -> b) -> FromSomeType c b
- deserialiseFromTextEnvelopeAnyOf :: [FromSomeType HasTextEnvelope b] -> TextEnvelope -> Either TextEnvelopeError b
- readFileTextEnvelopeAnyOf :: [FromSomeType HasTextEnvelope b] -> File content 'In -> IO (Either (FileError TextEnvelopeError) b)
- class Error e where
- prettyError :: e -> Doc ann
- throwErrorAsException :: Error e => e -> IO a
- data FileError e
- 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
- readNodeConfig :: (MonadError Text m, MonadIO m) => NodeConfigFile 'In -> m NodeConfig
- type ByronGenesisFile = File ByronGenesisConfig
- type ShelleyGenesisFile = File ShelleyGenesisConfig
- type AlonzoGenesisFile = File AlonzoGenesisConfig
- type ConwayGenesisFile = File ConwayGenesisConfig
- data GenesisConfig = GenesisCardano !NodeConfig !Config !GenesisHashShelley !(TransitionConfig LatestKnownEra)
- readCardanoGenesisConfig :: forall t (m :: Type -> Type) era. MonadIOTransError GenesisConfigError t m => Maybe (CardanoEra era) -> NodeConfig -> t m GenesisConfig
- mkProtocolInfoCardano :: GenesisConfig -> (ProtocolInfo (CardanoBlock StandardCrypto), IO [BlockForging IO (CardanoBlock StandardCrypto)])
- readByronGenesisConfig :: forall t (m :: Type -> Type). MonadIOTransError GenesisConfigError t m => NodeConfig -> t m Config
- newtype GenesisHashByron = GenesisHashByron {}
- data ShelleyConfig = ShelleyConfig {}
- newtype GenesisHashShelley = GenesisHashShelley {}
- readShelleyGenesisConfig :: forall t (m :: Type -> Type). MonadIOTransError GenesisConfigError t m => NodeConfig -> t m ShelleyConfig
- shelleyPraosNonce :: GenesisHashShelley -> Nonce
- newtype GenesisHashAlonzo = GenesisHashAlonzo {}
- readAlonzoGenesisConfig :: forall t (m :: Type -> Type) era. MonadIOTransError GenesisConfigError t m => Maybe (CardanoEra era) -> NodeConfig -> t m AlonzoGenesis
- newtype GenesisHashConway = GenesisHashConway {}
- readConwayGenesisConfig :: forall t (m :: Type -> Type). MonadIOTransError GenesisConfigError t m => NodeConfig -> t m ConwayGenesis
- data Env = Env {}
- genesisConfigToEnv :: GenesisConfig -> Either GenesisConfigError Env
- envSecurityParam :: Env -> Word64
- data LedgerState where
- LedgerState { }
- pattern LedgerStateAllegra :: LedgerState StandardAllegraBlock EmptyMK -> LedgerState
- pattern LedgerStateAlonzo :: LedgerState StandardAlonzoBlock EmptyMK -> LedgerState
- pattern LedgerStateBabbage :: LedgerState StandardBabbageBlock EmptyMK -> LedgerState
- pattern LedgerStateByron :: LedgerState ByronBlock EmptyMK -> LedgerState
- pattern LedgerStateConway :: LedgerState StandardConwayBlock EmptyMK -> LedgerState
- pattern LedgerStateMary :: LedgerState StandardMaryBlock EmptyMK -> LedgerState
- pattern LedgerStateShelley :: LedgerState StandardShelleyBlock EmptyMK -> LedgerState
- initialLedgerState :: forall t (m :: Type -> Type). MonadIOTransError InitialLedgerStateError t m => NodeConfigFile 'In -> t m (Env, LedgerState)
- encodeLedgerState :: LedgerState -> Encoding
- decodeLedgerState :: Decoder s LedgerState
- applyBlock :: Env -> LedgerState -> ValidationMode -> BlockInMode -> Either LedgerStateError (LedgerState, [LedgerEvent])
- data ValidationMode
- 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
- data FoldStatus
- 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
- 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
- data ConditionResult
- fromConditionResult :: ConditionResult -> Bool
- toConditionResult :: Bool -> ConditionResult
- data AnyNewEpochState where
- AnyNewEpochState :: forall era. ShelleyBasedEra era -> NewEpochState (ShelleyLedgerEra era) -> LedgerTables (LedgerState (CardanoBlock StandardCrypto)) ValuesMK -> AnyNewEpochState
- 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)
- getAnyNewEpochState :: ShelleyBasedEra era -> LedgerState -> Either LedgerStateError AnyNewEpochState
- getLedgerTablesUTxOValues :: ShelleyBasedEra era -> LedgerTables (LedgerState (CardanoBlock StandardCrypto)) ValuesMK -> Map TxIn (TxOut CtxUTxO era)
- data LedgerStateError
- = ApplyBlockHashMismatch Text
- | ApplyBlockError (CardanoLedgerError StandardCrypto)
- | InvalidRollback SlotNo ChainPoint
- | TerminationEpochReached EpochNo
- | UnexpectedLedgerState AnyShelleyBasedEra (NS (Current (Flip LedgerState EmptyMK)) (CardanoEras StandardCrypto))
- | ByronEraUnsupported
- | DebugError !String
- data FoldBlocksError
- data GenesisConfigError
- data InitialLedgerStateError
- connectToLocalNode :: MonadIO m => LocalNodeConnectInfo -> LocalNodeClientProtocolsInMode -> m ()
- connectToLocalNodeWithVersion :: MonadIO m => LocalNodeConnectInfo -> (NodeToClientVersion -> LocalNodeClientProtocolsInMode) -> m ()
- data LocalNodeConnectInfo = LocalNodeConnectInfo {}
- data ConsensusModeParams where
- type family ConsensusProtocol era where ...
- type family ChainDepStateProtocol era where ...
- type family ConsensusBlockForEra era where ...
- 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 ())
- data LocalNodeClientParams where
- LocalNodeClientParamsSingleBlock :: forall block. (ProtocolClient block, LedgerSupportsProtocol (ShelleyBlock (TPraos StandardCrypto) ShelleyEra)) => ProtocolClientInfoArgs block -> (NodeToClientVersion -> LocalNodeClientProtocolsForBlock block) -> LocalNodeClientParams
- LocalNodeClientParamsCardano :: forall block. (ProtocolClient block, CardanoHardForkConstraints (ConsensusCryptoForBlock block)) => ProtocolClientInfoArgs block -> (NodeToClientVersion -> LocalNodeClientProtocolsForBlock block) -> LocalNodeClientParams
- mkLocalNodeClientParams :: ConsensusModeParams -> (NodeToClientVersion -> LocalNodeClientProtocolsInMode) -> LocalNodeClientParams
- data LocalChainSyncClient block point tip (m :: Type -> Type)
- = NoLocalChainSyncClient
- | LocalChainSyncClientPipelined (ChainSyncClientPipelined block point tip m ())
- | LocalChainSyncClient (ChainSyncClient block point tip m ())
- data BlockType blk where
- data SomeBlockType where
- SomeBlockType :: forall blk. BlockType blk -> SomeBlockType
- reflBlockType :: BlockType blk -> BlockType blk' -> Maybe (blk :~: blk')
- 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
- 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)
- data BlockInMode where
- BlockInMode :: forall era. CardanoEra era -> Block era -> BlockInMode
- type LocalNodeClientProtocolsInMode = LocalNodeClientProtocols BlockInMode ChainPoint ChainTip SlotNo TxInMode TxIdInMode TxValidationErrorInCardanoMode QueryInMode IO
- newtype LocalTxSubmissionClient tx reject (m :: Type -> Type) a = LocalTxSubmissionClient {
- runLocalTxSubmissionClient :: m (LocalTxClientStIdle tx reject m a)
- data TxInMode where
- TxInMode :: forall era. ShelleyBasedEra era -> Tx era -> TxInMode
- TxInByronSpecial :: GenTx ByronBlock -> TxInMode
- data TxValidationErrorInCardanoMode where
- data SubmitResult reason
- = SubmitSuccess
- | SubmitFail reason
- submitTxToNodeLocal :: MonadIO m => LocalNodeConnectInfo -> TxInMode -> m (SubmitResult TxValidationErrorInCardanoMode)
- newtype LocalStateQueryClient block point (query :: Type -> Type) (m :: Type -> Type) a = LocalStateQueryClient {
- runLocalStateQueryClient :: m (ClientStIdle block point query m a)
- 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
- QueryLedgerConfig :: QueryInMode (HardForkLedgerConfig (CardanoEras StandardCrypto))
- newtype SystemStart = SystemStart {}
- 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))
- 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))
- QueryRatifyState :: forall era. QueryInShelleyBasedEra era (RatifyState (ShelleyLedgerEra era))
- QueryFuturePParams :: forall era. QueryInShelleyBasedEra era (Maybe (PParams (ShelleyLedgerEra era)))
- QueryDRepState :: forall era. Set (Credential 'DRepRole) -> QueryInShelleyBasedEra era (Map (Credential 'DRepRole) DRepState)
- QueryDRepStakeDistr :: forall era. Set DRep -> QueryInShelleyBasedEra era (Map DRep Coin)
- QuerySPOStakeDistr :: forall era. Set (KeyHash 'StakePool) -> QueryInShelleyBasedEra era (Map (KeyHash 'StakePool) Coin)
- QueryCommitteeMembersState :: forall era. Set (Credential 'ColdCommitteeRole) -> Set (Credential 'HotCommitteeRole) -> Set MemberStatus -> QueryInShelleyBasedEra era CommitteeMembersState
- QueryStakeVoteDelegatees :: forall era. Set StakeCredential -> QueryInShelleyBasedEra era (Map StakeCredential DRep)
- QueryProposals :: forall era. Set GovActionId -> QueryInShelleyBasedEra era (Seq (GovActionState (ShelleyLedgerEra era)))
- QueryLedgerPeerSnapshot :: forall era. QueryInShelleyBasedEra era (Serialised LedgerPeerSnapshot)
- QueryStakePoolDefaultVote :: forall era. KeyHash 'StakePool -> QueryInShelleyBasedEra era DefaultVote
- data QueryUTxOFilter
- newtype UTxO era = UTxO {}
- queryNodeLocalState :: LocalNodeConnectInfo -> Target ChainPoint -> QueryInMode result -> ExceptT AcquiringFailure IO result
- executeQueryCardanoMode :: SocketPath -> NetworkId -> QueryInMode (Either EraMismatch result) -> ExceptT QueryConvenienceError IO result
- data UnsupportedNtcVersionError = UnsupportedNtcVersionError !NodeToClientVersion ![NodeToClientVersion]
- newtype LocalTxMonitorClient txid tx slot (m :: Type -> Type) a = LocalTxMonitorClient {
- runLocalTxMonitorClient :: m (ClientStIdle txid tx slot m a)
- data LocalTxMonitoringQuery
- data LocalTxMonitoringResult
- data MempoolSizeAndCapacity = MempoolSizeAndCapacity {
- capacityInBytes :: !Word32
- sizeInBytes :: !Word32
- numberOfTxs :: !Word32
- queryTxMonitoringLocal :: MonadIO m => LocalNodeConnectInfo -> LocalTxMonitoringQuery -> m LocalTxMonitoringResult
- data TxIdInMode where
- TxIdInMode :: forall era. CardanoEra era -> TxId -> TxIdInMode
- data EraHistory where
- EraHistory :: forall (xs :: [Type]). CardanoBlock StandardCrypto ~ HardForkBlock xs => Interpreter xs -> EraHistory
- getProgress :: SlotNo -> EraHistory -> Either PastHorizonException (RelativeTime, SlotLength)
- getSlotForRelativeTime :: RelativeTime -> EraHistory -> Either PastHorizonException SlotNo
- determineEra :: LocalNodeConnectInfo -> ExceptT AcquiringFailure IO AnyCardanoEra
- getLocalChainTip :: MonadIO m => LocalNodeConnectInfo -> m ChainTip
- data OperationalCertificate
- data OperationalCertificateIssueCounter
- data OperationalCertIssueError
- getHotKey :: OperationalCertificate -> VerificationKey KesKey
- getKesPeriod :: OperationalCertificate -> Word
- getOpCertCount :: OperationalCertificate -> Word64
- issueOperationalCertificate :: VerificationKey KesKey -> Either AnyStakePoolSigningKey (SigningKey GenesisDelegateExtendedKey) -> KESPeriod -> OperationalCertificateIssueCounter -> Either OperationalCertIssueError (OperationalCertificate, OperationalCertificateIssueCounter)
- data CommitteeColdKey
- data CommitteeColdExtendedKey
- data CommitteeHotKey
- data CommitteeHotExtendedKey
- data GenesisKey
- data GenesisExtendedKey
- data GenesisDelegateKey
- data GenesisDelegateExtendedKey
- data GenesisUTxOKey
- genesisUTxOPseudoTxIn :: NetworkId -> Hash GenesisUTxOKey -> TxIn
- data GenesisParameters era = GenesisParameters {
- protocolParamSystemStart :: UTCTime
- protocolParamNetworkId :: NetworkId
- protocolParamActiveSlotsCoefficient :: Rational
- protocolParamSecurity :: NonZero Word64
- protocolParamEpochLength :: EpochSize
- protocolParamSlotLength :: NominalDiffTime
- protocolParamSlotsPerKESPeriod :: Int
- protocolParamMaxKESEvolutions :: Int
- protocolParamUpdateQuorum :: Int
- protocolParamMaxLovelaceSupply :: Coin
- protocolInitialUpdateableProtocolParameters :: PParams (ShelleyLedgerEra era)
- data GenesisKeyDelegationRequirements era where
- GenesisKeyDelegationRequirements :: forall era. ShelleyToBabbageEra era -> Hash GenesisKey -> Hash GenesisDelegateKey -> Hash VrfKey -> GenesisKeyDelegationRequirements era
- data MirCertificateRequirements era where
- MirCertificateRequirements :: forall era. ShelleyToBabbageEra era -> MIRPot -> MIRTarget -> MirCertificateRequirements era
- makeMIRCertificate :: Typeable era => MirCertificateRequirements era -> Certificate era
- makeGenesisKeyDelegationCertificate :: Typeable era => GenesisKeyDelegationRequirements era -> Certificate era
- data MIRTarget
- data MIRPot
- selectStakeCredentialWitness :: Certificate era -> Maybe StakeCredential
- data UpdateProposal = UpdateProposal !(Map (Hash GenesisKey) ProtocolParametersUpdate) !EpochNo
- 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 Word16
- 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
- makeShelleyUpdateProposal :: ProtocolParametersUpdate -> [Hash GenesisKey] -> EpochNo -> UpdateProposal
- data PraosNonce
- makePraosNonce :: ByteString -> PraosNonce
- newtype NetworkMagic = NetworkMagic {}
- data ProtocolParametersConversionError
- = PpceOutOfBounds !ProtocolParameterName !Rational
- | PpceVersionInvalid !ProtocolParameterVersion
- | PpceInvalidCostModel !CostModel !CostModelApplyError
- | PpceMissingParameter !ProtocolParameterName
- toCtxUTxOTxOut :: TxOut CtxTx era -> TxOut CtxUTxO era
- fromCtxUTxOTxOut :: TxOut CtxUTxO era -> TxOut CtxTx era
- fromNetworkMagic :: NetworkMagic -> NetworkId
- toNetworkMagic :: NetworkId -> NetworkMagic
- fromLedgerTxOuts :: ShelleyBasedEra era -> TxBody (ShelleyLedgerEra era) -> TxBodyScriptData era -> [TxOut CtxTx era]
- toLedgerUTxO :: ShelleyBasedEra era -> UTxO era -> UTxO (ShelleyLedgerEra era)
- fromLedgerUTxO :: ShelleyBasedEra era -> UTxO (ShelleyLedgerEra era) -> UTxO era
- runParsecParser :: Parser a -> Text -> Parser a
- newtype SlotsInEpoch = SlotsInEpoch Word64
- newtype SlotsToEpochEnd = SlotsToEpochEnd Word64
- slotToEpoch :: SlotNo -> EraHistory -> Either PastHorizonException (EpochNo, SlotsInEpoch, SlotsToEpochEnd)
- type SocketPath = File Socket 'InOut
- data NodeToClientVersion
- executeQueryAnyMode :: LocalNodeConnectInfo -> QueryInMode (Either EraMismatch result) -> ExceptT QueryConvenienceError IO result
- data LocalStateQueryExpr block point (query :: Type -> Type) r (m :: Type -> Type) a
- 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)
- chainPointToSlotNo :: ChainPoint -> Maybe SlotNo
- chainPointToHeaderHash :: ChainPoint -> Maybe (Hash BlockHeader)
- makeChainTip :: WithOrigin BlockNo -> ChainPoint -> ChainTip
- writeSecrets :: FilePath -> [Char] -> [Char] -> (a -> ByteString) -> [a] -> IO ()
- constructBalancedTx :: ShelleyBasedEra era -> TxBodyContent BuildTx era -> AddressInEra era -> Maybe Word -> UTxO era -> LedgerProtocolParameters era -> LedgerEpochInfo -> SystemStart -> Set PoolId -> Map StakeCredential Coin -> Map (Credential 'DRepRole) Coin -> [ShelleyWitnessSigningKey] -> Either (TxBodyErrorAutoBalance era) (Tx era)
- data QueryConvenienceError
- newtype TxCurrentTreasuryValue = TxCurrentTreasuryValue {}
- 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) Coin, Maybe (Featured ConwayEraOnwards era TxCurrentTreasuryValue)))
- renderQueryConvenienceError :: QueryConvenienceError -> Text
- newtype ScriptLockedTxInsError = ScriptLockedTxIns [TxIn]
- data TxInsExistError
- = TxInsDoNotExist [TxIn]
- | EmptyUTxO
- renderNotScriptLockedTxInsError :: ScriptLockedTxInsError -> Text
- renderTxInsExistError :: TxInsExistError -> Text
- txInsExistInUTxO :: [TxIn] -> UTxO era -> Either TxInsExistError ()
- notScriptLockedTxIns :: [TxIn] -> UTxO era -> Either ScriptLockedTxInsError ()
- textShow :: Show a => a -> Text
- 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)
- 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)
- queryDebugLedgerState :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedDebugLedgerState era)))
- queryLedgerPeerSnapshot :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Serialised LedgerPeerSnapshot)))
- queryEpoch :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch EpochNo))
- queryConstitutionHash :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SafeHash AnchorData)))
- queryEraHistory :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError EraHistory)
- queryGenesisParameters :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (GenesisParameters ShelleyEra)))
- 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)))
- queryProtocolParameters :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (PParams (ShelleyLedgerEra era))))
- 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)))
- queryStakePools :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Set PoolId)))
- queryStakeSnapshot :: BabbageEraOnwards era -> Maybe (Set PoolId) -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (SerialisedStakeSnapshots era)))
- querySystemStart :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError SystemStart)
- queryUtxo :: ShelleyBasedEra era -> QueryUTxOFilter -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (UTxO era)))
- queryConstitution :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Constitution (ShelleyLedgerEra era))))
- queryGovState :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (GovState (ShelleyLedgerEra era))))
- queryRatifyState :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (RatifyState (ShelleyLedgerEra era))))
- queryFuturePParams :: ConwayEraOnwards era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Maybe (PParams (ShelleyLedgerEra era)))))
- queryDRepState :: ConwayEraOnwards era -> Set (Credential 'DRepRole) -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map (Credential 'DRepRole) DRepState)))
- queryDRepStakeDistribution :: ConwayEraOnwards era -> Set DRep -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map DRep Coin)))
- querySPOStakeDistribution :: ConwayEraOnwards era -> Set (KeyHash 'StakePool) -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map (KeyHash 'StakePool) Coin)))
- queryProposals :: ConwayEraOnwards era -> Set GovActionId -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Seq (GovActionState (ShelleyLedgerEra era)))))
- queryCommitteeMembersState :: ConwayEraOnwards era -> Set (Credential 'ColdCommitteeRole) -> Set (Credential 'HotCommitteeRole) -> Set MemberStatus -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch CommitteeMembersState))
- queryStakeVoteDelegatees :: ConwayEraOnwards era -> Set StakeCredential -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map StakeCredential DRep)))
- queryStakePoolDefaultVote :: ConwayEraOnwards era -> KeyHash 'StakePool -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch DefaultVote))
- queryLedgerConfig :: LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (CardanoLedgerConfig StandardCrypto))
- data MemberStatus
- data CommitteeMembersState = CommitteeMembersState {}
- data DRepKey
- data DRepExtendedKey
- getAnchorDataFromGovernanceAction :: GovAction (ShelleyLedgerEra era) -> Maybe Anchor
- validateGovActionAnchorData :: FromJSON (GovActionMetadata cip) => cip -> ByteString -> Either String ()
- newtype AnchorDataHash = AnchorDataHash {}
- newtype AnchorUrl = AnchorUrl {
- unAnchorUrl :: Url
- data CommitteeColdkeyResignationRequirements era where
- CommitteeColdkeyResignationRequirements :: forall era. ConwayEraOnwards era -> Credential 'ColdCommitteeRole -> Maybe Anchor -> CommitteeColdkeyResignationRequirements era
- data CommitteeHotKeyAuthorizationRequirements era where
- CommitteeHotKeyAuthorizationRequirements :: forall era. ConwayEraOnwards era -> Credential 'ColdCommitteeRole -> Credential 'HotCommitteeRole -> CommitteeHotKeyAuthorizationRequirements era
- data DRepRegistrationRequirements era where
- DRepRegistrationRequirements :: forall era. ConwayEraOnwards era -> Credential 'DRepRole -> Coin -> DRepRegistrationRequirements era
- data DRepUnregistrationRequirements era where
- DRepUnregistrationRequirements :: forall era. ConwayEraOnwards era -> Credential 'DRepRole -> Coin -> DRepUnregistrationRequirements era
- data DRepUpdateRequirements era where
- DRepUpdateRequirements :: forall era. ConwayEraOnwards era -> Credential 'DRepRole -> DRepUpdateRequirements era
- makeCommitteeColdkeyResignationCertificate :: Typeable era => CommitteeColdkeyResignationRequirements era -> Certificate era
- makeCommitteeHotKeyAuthorizationCertificate :: Typeable era => CommitteeHotKeyAuthorizationRequirements era -> Certificate era
- makeDrepRegistrationCertificate :: Typeable era => DRepRegistrationRequirements era -> Maybe Anchor -> Certificate era
- makeDrepUnregistrationCertificate :: Typeable era => DRepUnregistrationRequirements era -> Certificate era
- makeDrepUpdateCertificate :: Typeable era => DRepUpdateRequirements era -> Maybe Anchor -> Certificate era
- 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)) -> ResolvablePointers
- unsafeBoundedRational :: (HasCallStack, Typeable r, BoundedRational r) => Rational -> r
- data DebugPlutusFailure = DebugPlutusFailure {}
- renderDebugPlutusFailure :: DebugPlutusFailure -> Text
- class Monad m => MonadIO (m :: Type -> Type) where
- class (forall (m :: Type -> Type). Monad m => Monad (t m)) => MonadTrans (t :: (Type -> Type) -> Type -> Type) where
- 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
- class Monad m => MonadError e (m :: Type -> Type) | m -> e where
- throwError :: e -> m a
- catchError :: m a -> (e -> m a) -> m a
- type Except e = ExceptT e Identity
- newtype ExceptT e (m :: Type -> Type) a = ExceptT (m (Either e 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
- throwE :: forall (m :: Type -> Type) e a. Monad m => e -> ExceptT e m a
- 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
- handleIOExceptT :: forall (m :: Type -> Type) x a. MonadIO m => (IOException -> x) -> IO a -> ExceptT x m a
- firstExceptT :: forall (m :: Type -> Type) x y a. Functor m => (x -> y) -> ExceptT x m a -> ExceptT y m a
- hoistEither :: forall (m :: Type -> Type) x a. Monad m => Either x a -> ExceptT x m a
- newExceptT :: m (Either x a) -> ExceptT x m a
- type MonadTransError e (t :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) = (Monad m, MonadTrans t, MonadError e (t m))
- type MonadIOTransError e (t :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) = (MonadIO m, MonadIO (t m), MonadCatch m, MonadTrans t, MonadError e (t m))
- liftExceptT :: forall e t (m :: Type -> Type) a. MonadTransError e t m => ExceptT e m a -> t m a
- handleIOExceptionsWith :: (MonadError e' m, MonadCatch m, Exception e) => (e -> e') -> m a -> m a
- handleIOExceptionsLiftWith :: (MonadIOTransError e' t m, Exception e) => (e -> e') -> m a -> t m a
- hoistIOEither :: forall e t (m :: Type -> Type) a. MonadIOTransError e t m => IO (Either e a) -> t m a
- liftMaybe :: MonadError e m => e -> Maybe a -> m a
- 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
- handleExceptT :: (MonadCatch m, Exception e) => (e -> x) -> m 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
- 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)
- 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
- module Cardano.Api.Internal.Pretty
Eras
A type used as a tag to distinguish the Byron era.
Instances
IsCardanoEra ByronEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Methods | |||||
HasTypeProxy ByronEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Associated Types
| |||||
data AsType ByronEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core |
data ShelleyEra Source #
A type used as a tag to distinguish the Shelley era.
Instances
IsShelleyBasedEra ShelleyEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods | |||||
IsCardanoEra ShelleyEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Methods | |||||
HasTypeProxy ShelleyEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Associated Types
Methods proxyToAsType :: Proxy ShelleyEra -> AsType ShelleyEra Source # | |||||
data AsType ShelleyEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core |
data AllegraEra Source #
A type used as a tag to distinguish the Allegra era.
Instances
IsAllegraBasedEra AllegraEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods | |||||
IsShelleyBasedEra AllegraEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods | |||||
IsCardanoEra AllegraEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Methods | |||||
HasTypeProxy AllegraEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Associated Types
Methods proxyToAsType :: Proxy AllegraEra -> AsType AllegraEra Source # | |||||
data AsType AllegraEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core |
A type used as a tag to distinguish the Mary era.
Instances
IsAllegraBasedEra MaryEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods | |||||
IsMaryBasedEra MaryEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards Methods | |||||
IsShelleyBasedEra MaryEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods | |||||
IsCardanoEra MaryEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Methods | |||||
HasTypeProxy MaryEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Associated Types
| |||||
data AsType MaryEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core |
A type used as a tag to distinguish the Alonzo era.
Instances
IsAllegraBasedEra AlonzoEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods | |||||
IsAlonzoBasedEra AlonzoEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards Methods | |||||
IsMaryBasedEra AlonzoEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards Methods | |||||
IsShelleyBasedEra AlonzoEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods | |||||
IsCardanoEra AlonzoEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Methods | |||||
HasTypeProxy AlonzoEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Associated Types
| |||||
HasScriptLanguageInEra PlutusScriptV1 AlonzoEra Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
data AsType AlonzoEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core |
data BabbageEra Source #
A type used as a tag to distinguish the Babbage era.
Instances
A type used as a tag to distinguish the Conway era.
Instances
IsAllegraBasedEra ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods | |||||
IsAlonzoBasedEra ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards Methods | |||||
IsBabbageBasedEra ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards Methods | |||||
IsConwayBasedEra ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards Methods | |||||
IsMaryBasedEra ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards Methods | |||||
IsShelleyBasedEra ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods | |||||
IsCardanoEra ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Methods | |||||
IsEra ConwayEra Source # | |||||
HasTypeProxy ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Associated Types
| |||||
HasScriptLanguageInEra PlutusScriptV1 ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
HasScriptLanguageInEra PlutusScriptV2 ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
HasScriptLanguageInEra PlutusScriptV3 ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
ToAlonzoScript PlutusScriptV1 ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Script Methods toLedgerScript :: PlutusScript PlutusScriptV1 -> AlonzoScript (ShelleyLedgerEra ConwayEra) Source # | |||||
ToAlonzoScript PlutusScriptV2 ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Script Methods toLedgerScript :: PlutusScript PlutusScriptV2 -> AlonzoScript (ShelleyLedgerEra ConwayEra) Source # | |||||
ToAlonzoScript PlutusScriptV3 ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Script Methods toLedgerScript :: PlutusScript PlutusScriptV3 -> AlonzoScript (ShelleyLedgerEra ConwayEra) Source # | |||||
data AsType ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core |
data CardanoEra era where Source #
This GADT provides a value-level representation of all the Cardano eras. This enables pattern matching on the era to allow them to be treated in a non-uniform way.
This can be used in combination with the IsCardanoEra
class to get access
to this value.
In combination this can often enable code that handles all eras, and does so uniformly where possible, and non-uniformly where necessary.
Constructors
ByronEra :: CardanoEra ByronEra | |
ShelleyEra :: CardanoEra ShelleyEra | |
AllegraEra :: CardanoEra AllegraEra | |
MaryEra :: CardanoEra MaryEra | |
AlonzoEra :: CardanoEra AlonzoEra | |
BabbageEra :: CardanoEra BabbageEra | |
ConwayEra :: CardanoEra ConwayEra |
Instances
Eon CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core Methods inEonForEra :: a -> (CardanoEra era -> a) -> CardanoEra era -> a Source # | |
ToCardanoEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core Methods toCardanoEra :: CardanoEra era -> CardanoEra era Source # | |
TestEquality CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core Methods testEquality :: CardanoEra a -> CardanoEra b -> Maybe (a :~: b) Source # | |
Convert AllegraEraOnwards CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods convert :: AllegraEraOnwards era -> CardanoEra era Source # | |
Convert AlonzoEraOnwards CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards Methods convert :: AlonzoEraOnwards era -> CardanoEra era Source # | |
Convert BabbageEraOnwards CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards Methods convert :: BabbageEraOnwards era -> CardanoEra era Source # | |
Convert ByronToAlonzoEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ByronToAlonzoEra Methods convert :: ByronToAlonzoEra era -> CardanoEra era Source # | |
Convert ConwayEraOnwards CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards Methods convert :: ConwayEraOnwards era -> CardanoEra era Source # | |
Convert MaryEraOnwards CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards Methods convert :: MaryEraOnwards era -> CardanoEra era Source # | |
Convert ShelleyBasedEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods convert :: ShelleyBasedEra era -> CardanoEra era Source # | |
Convert ShelleyEraOnly CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyEraOnly Methods convert :: ShelleyEraOnly era -> CardanoEra era Source # | |
Convert ShelleyToAllegraEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAllegraEra Methods convert :: ShelleyToAllegraEra era -> CardanoEra era Source # | |
Convert ShelleyToAlonzoEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAlonzoEra Methods convert :: ShelleyToAlonzoEra era -> CardanoEra era Source # | |
Convert ShelleyToBabbageEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToBabbageEra Methods convert :: ShelleyToBabbageEra era -> CardanoEra era Source # | |
Convert ShelleyToMaryEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToMaryEra Methods convert :: ShelleyToMaryEra era -> CardanoEra era Source # | |
Convert Era CardanoEra Source # | |
Defined in Cardano.Api.Internal.Experimental.Eras Methods convert :: Era era -> CardanoEra era Source # | |
ToJSON (CardanoEra era) Source # | |
Defined in Cardano.Api.Internal.Eras.Core Methods toJSON :: CardanoEra era -> Value toEncoding :: CardanoEra era -> Encoding toJSONList :: [CardanoEra era] -> Value toEncodingList :: [CardanoEra era] -> Encoding omitField :: CardanoEra era -> Bool | |
Show (CardanoEra era) Source # | |
Defined in Cardano.Api.Internal.Eras.Core | |
Eq (CardanoEra era) Source # | |
Defined in Cardano.Api.Internal.Eras.Core Methods (==) :: CardanoEra era -> CardanoEra era -> Bool Source # (/=) :: CardanoEra era -> CardanoEra era -> Bool Source # | |
Ord (CardanoEra era) Source # | |
Defined in Cardano.Api.Internal.Eras.Core Methods compare :: CardanoEra era -> CardanoEra era -> Ordering Source # (<) :: CardanoEra era -> CardanoEra era -> Bool Source # (<=) :: CardanoEra era -> CardanoEra era -> Bool Source # (>) :: CardanoEra era -> CardanoEra era -> Bool Source # (>=) :: CardanoEra era -> CardanoEra era -> Bool Source # max :: CardanoEra era -> CardanoEra era -> CardanoEra era Source # min :: CardanoEra era -> CardanoEra era -> CardanoEra era Source # | |
Pretty (CardanoEra era) Source # | |
Defined in Cardano.Api.Internal.Eras.Core |
class HasTypeProxy era => IsCardanoEra era where Source #
The class of Cardano eras. This allows uniform handling of all Cardano
eras, but also non-uniform by making case distinctions on the CardanoEra
constructors.
Methods
cardanoEra :: CardanoEra era Source #
Instances
IsCardanoEra AllegraEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core Methods | |
IsCardanoEra AlonzoEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core Methods | |
IsCardanoEra BabbageEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core Methods | |
IsCardanoEra ByronEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core Methods | |
IsCardanoEra ConwayEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core Methods | |
IsCardanoEra MaryEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core Methods | |
IsCardanoEra ShelleyEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core Methods |
data AnyCardanoEra where Source #
Constructors
AnyCardanoEra :: forall era. Typeable era => CardanoEra era -> AnyCardanoEra |
Instances
FromJSON AnyCardanoEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core | |
ToJSON AnyCardanoEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core Methods toJSON :: AnyCardanoEra -> Value toEncoding :: AnyCardanoEra -> Encoding toJSONList :: [AnyCardanoEra] -> Value toEncodingList :: [AnyCardanoEra] -> Encoding omitField :: AnyCardanoEra -> Bool | |
Bounded AnyCardanoEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core | |
Enum AnyCardanoEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core Methods succ :: AnyCardanoEra -> AnyCardanoEra Source # pred :: AnyCardanoEra -> AnyCardanoEra Source # toEnum :: Int -> AnyCardanoEra Source # fromEnum :: AnyCardanoEra -> Int Source # enumFrom :: AnyCardanoEra -> [AnyCardanoEra] Source # enumFromThen :: AnyCardanoEra -> AnyCardanoEra -> [AnyCardanoEra] Source # enumFromTo :: AnyCardanoEra -> AnyCardanoEra -> [AnyCardanoEra] Source # enumFromThenTo :: AnyCardanoEra -> AnyCardanoEra -> AnyCardanoEra -> [AnyCardanoEra] Source # | |
Show AnyCardanoEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core | |
Eq AnyCardanoEra Source # | Assumes that 'CardanoEra era' are singletons |
Defined in Cardano.Api.Internal.Eras.Core Methods (==) :: AnyCardanoEra -> AnyCardanoEra -> Bool Source # (/=) :: AnyCardanoEra -> AnyCardanoEra -> Bool Source # | |
Pretty AnyCardanoEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core |
anyCardanoEra :: CardanoEra era -> AnyCardanoEra Source #
Like the AnyCardanoEra
constructor but does not demand a IsCardanoEra
class constraint.
data InAnyCardanoEra (thing :: Type -> Type) where Source #
This pairs up some era-dependent type with a CardanoEra
value that tells
us what era it is, but hides the era type. This is useful when the era is
not statically known, for example when deserialising from a file.
Constructors
InAnyCardanoEra :: forall era (thing :: Type -> Type). Typeable era => CardanoEra era -> thing era -> InAnyCardanoEra thing |
Instances
Show (InAnyCardanoEra Tx) Source # | |
Defined in Cardano.Api.Internal.Tx.Sign | |
Eq (InAnyCardanoEra Tx) Source # | |
Defined in Cardano.Api.Internal.Tx.Sign Methods (==) :: InAnyCardanoEra Tx -> InAnyCardanoEra Tx -> Bool Source # (/=) :: InAnyCardanoEra Tx -> InAnyCardanoEra Tx -> Bool Source # |
inAnyCardanoEra :: CardanoEra era -> thing era -> InAnyCardanoEra thing Source #
cardanoEraConstraints :: CardanoEra era -> (CardanoEraConstraints era => a) -> a Source #
class ToCardanoEra (eon :: Type -> Type) where Source #
Methods
toCardanoEra :: eon era -> CardanoEra era Source #
Instances
ToCardanoEra AllegraEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods toCardanoEra :: AllegraEraOnwards era -> CardanoEra era Source # | |
ToCardanoEra AlonzoEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards Methods toCardanoEra :: AlonzoEraOnwards era -> CardanoEra era Source # | |
ToCardanoEra BabbageEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards Methods toCardanoEra :: BabbageEraOnwards era -> CardanoEra era Source # | |
ToCardanoEra ByronToAlonzoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ByronToAlonzoEra Methods toCardanoEra :: ByronToAlonzoEra era -> CardanoEra era Source # | |
ToCardanoEra ConwayEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards Methods toCardanoEra :: ConwayEraOnwards era -> CardanoEra era Source # | |
ToCardanoEra MaryEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards Methods toCardanoEra :: MaryEraOnwards era -> CardanoEra era Source # | |
ToCardanoEra ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods toCardanoEra :: ShelleyBasedEra era -> CardanoEra era Source # | |
ToCardanoEra ShelleyEraOnly Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyEraOnly Methods toCardanoEra :: ShelleyEraOnly era -> CardanoEra era Source # | |
ToCardanoEra ShelleyToAllegraEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAllegraEra Methods toCardanoEra :: ShelleyToAllegraEra era -> CardanoEra era Source # | |
ToCardanoEra ShelleyToAlonzoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAlonzoEra Methods toCardanoEra :: ShelleyToAlonzoEra era -> CardanoEra era Source # | |
ToCardanoEra ShelleyToBabbageEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToBabbageEra Methods toCardanoEra :: ShelleyToBabbageEra era -> CardanoEra era Source # | |
ToCardanoEra ShelleyToMaryEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToMaryEra Methods toCardanoEra :: ShelleyToMaryEra era -> CardanoEra era Source # | |
ToCardanoEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core Methods toCardanoEra :: CardanoEra era -> CardanoEra era Source # | |
ToCardanoEra Era Source # | A temporary compatibility instance for easier conversion between the experimental and old APIs. |
Defined in Cardano.Api.Internal.Experimental.Eras Methods toCardanoEra :: Era era -> CardanoEra era Source # |
Eon support
class Eon (eon :: Type -> Type) where Source #
An Eon is a span of multiple eras. Eons are used to scope functionality to particular eras such that it isn't possible construct code that uses functionality that is outside of given eras.
Methods
Arguments
:: a | Value to use if the eon does not include the era |
-> (eon era -> a) | Function to get the value to use if the eon includes the era |
-> CardanoEra era | Era to check |
-> a | The value to use |
Determine the value to use in an eon (a span of multiple eras).
Note that the negative case is the first argument, and the positive case is the second as per
the either
function convention.
Instances
Eon AllegraEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods inEonForEra :: a -> (AllegraEraOnwards era -> a) -> CardanoEra era -> a Source # | |
Eon AlonzoEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards Methods inEonForEra :: a -> (AlonzoEraOnwards era -> a) -> CardanoEra era -> a Source # | |
Eon BabbageEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards Methods inEonForEra :: a -> (BabbageEraOnwards era -> a) -> CardanoEra era -> a Source # | |
Eon ByronToAlonzoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ByronToAlonzoEra Methods inEonForEra :: a -> (ByronToAlonzoEra era -> a) -> CardanoEra era -> a Source # | |
Eon ConwayEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards Methods inEonForEra :: a -> (ConwayEraOnwards era -> a) -> CardanoEra era -> a Source # | |
Eon MaryEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards Methods inEonForEra :: a -> (MaryEraOnwards era -> a) -> CardanoEra era -> a Source # | |
Eon ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods inEonForEra :: a -> (ShelleyBasedEra era -> a) -> CardanoEra era -> a Source # | |
Eon ShelleyEraOnly Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyEraOnly Methods inEonForEra :: a -> (ShelleyEraOnly era -> a) -> CardanoEra era -> a Source # | |
Eon ShelleyToAllegraEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAllegraEra Methods inEonForEra :: a -> (ShelleyToAllegraEra era -> a) -> CardanoEra era -> a Source # | |
Eon ShelleyToAlonzoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAlonzoEra Methods inEonForEra :: a -> (ShelleyToAlonzoEra era -> a) -> CardanoEra era -> a Source # | |
Eon ShelleyToBabbageEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToBabbageEra Methods inEonForEra :: a -> (ShelleyToBabbageEra era -> a) -> CardanoEra era -> a Source # | |
Eon ShelleyToMaryEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToMaryEra Methods inEonForEra :: a -> (ShelleyToMaryEra era -> a) -> CardanoEra era -> a Source # | |
Eon CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core Methods inEonForEra :: a -> (CardanoEra era -> a) -> CardanoEra era -> a Source # | |
Eon Era Source # | A temporary compatibility instance for easier conversion between the experimental and old APIs. |
Defined in Cardano.Api.Internal.Experimental.Eras Methods inEonForEra :: a -> (Era era -> a) -> CardanoEra era -> a Source # |
data EraInEon (eon :: Type -> Type) where Source #
Constructors
EraInEon :: forall era (eon :: Type -> Type). (Typeable era, Typeable (eon era), Eon eon) => eon era -> EraInEon eon |
Arguments
:: Eon eon | |
=> (eon era -> a) | Function to get the value to use if the eon includes the era |
-> CardanoEra era | Era to check |
-> Maybe a | The value to use |
Arguments
:: Eon eon | |
=> CardanoEra era | Era to check |
-> a | Value to use if the eon does not include the era |
-> (eon era -> a) | Function to get the value to use if the eon includes the era |
-> a | The value to use |
Arguments
:: Eon eon | |
=> CardanoEra era | Era to check |
-> (eon era -> a) | Function to get the value to use if the eon includes the era |
-> Maybe a | The value to use |
Arguments
:: Eon eon | |
=> CardanoEra era | Era to check |
-> Maybe (eon era) | The eon if supported in the era |
Arguments
:: (Eon eon, IsCardanoEra era) | |
=> Maybe (eon era) | The eon if supported in the era |
monoidForEraInEon :: (Eon eon, Monoid a) => CardanoEra era -> (eon era -> a) -> a Source #
monoidForEraInEonA :: (Eon eon, Applicative f, Monoid a) => CardanoEra era -> (eon era -> f a) -> f a Source #
inEonForShelleyBasedEra :: Eon eon => a -> (eon era -> a) -> ShelleyBasedEra era -> a Source #
Determine the value to use for a feature in a given ShelleyBasedEra
.
inEonForShelleyBasedEraMaybe :: Eon eon => (eon era -> a) -> ShelleyBasedEra era -> Maybe a Source #
forShelleyBasedEraInEon :: Eon eon => ShelleyBasedEra era -> a -> (eon era -> a) -> a Source #
forShelleyBasedEraInEonMaybe :: Eon eon => ShelleyBasedEra era -> (eon era -> a) -> Maybe a Source #
forShelleyBasedEraMaybeEon :: Eon eon => ShelleyBasedEra era -> Maybe (eon era) Source #
data Featured (eon :: Type -> Type) era a where Source #
A value only if the eon includes era
Constructors
Featured | |
Arguments
:: forall (eon :: Type -> Type) era a. (IsCardanoEra era, Eon eon) | |
=> a | a value featured in eon |
-> Maybe (Featured eon era a) |
|
Create a Featured with automatic witness conjuring
asFeaturedInEra :: forall (eon :: Type -> Type) a era. Eon eon => a -> CardanoEra era -> Maybe (Featured eon era a) Source #
Attempt to construct a FeatureValue
from a value and era.
If the eon is not supported in the era, then NoFeatureValue
is returned.
asFeaturedInShelleyBasedEra :: forall (eon :: Type -> Type) a era. Eon eon => a -> ShelleyBasedEra era -> Maybe (Featured eon era a) Source #
Attempt to construct a FeatureValue
from a value and a shelley-based-era.
class Convert (f :: a -> Type) (g :: a -> Type) where Source #
The Convert class is aimed at exposing a single interface that lets us convert between eons. However this is generalizable to any injective relationship between types.
Instances
Convert AllegraEraOnwards ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods convert :: AllegraEraOnwards era -> ShelleyBasedEra era Source # | |
Convert AllegraEraOnwards CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods convert :: AllegraEraOnwards era -> CardanoEra era Source # | |
Convert AlonzoEraOnwards ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards Methods convert :: AlonzoEraOnwards era -> ShelleyBasedEra era Source # | |
Convert AlonzoEraOnwards CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards Methods convert :: AlonzoEraOnwards era -> CardanoEra era Source # | |
Convert BabbageEraOnwards AlonzoEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards Methods convert :: BabbageEraOnwards era -> AlonzoEraOnwards era Source # | |
Convert BabbageEraOnwards MaryEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards Methods convert :: BabbageEraOnwards era -> MaryEraOnwards era Source # | |
Convert BabbageEraOnwards ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards Methods convert :: BabbageEraOnwards era -> ShelleyBasedEra era Source # | |
Convert BabbageEraOnwards CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards Methods convert :: BabbageEraOnwards era -> CardanoEra era Source # | |
Convert ByronToAlonzoEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ByronToAlonzoEra Methods convert :: ByronToAlonzoEra era -> CardanoEra era Source # | |
Convert ConwayEraOnwards AllegraEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards Methods convert :: ConwayEraOnwards era -> AllegraEraOnwards era Source # | |
Convert ConwayEraOnwards BabbageEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards Methods convert :: ConwayEraOnwards era -> BabbageEraOnwards era Source # | |
Convert ConwayEraOnwards ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards Methods convert :: ConwayEraOnwards era -> ShelleyBasedEra era Source # | |
Convert ConwayEraOnwards CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards Methods convert :: ConwayEraOnwards era -> CardanoEra era Source # | |
Convert MaryEraOnwards ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards Methods convert :: MaryEraOnwards era -> ShelleyBasedEra era Source # | |
Convert MaryEraOnwards CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards Methods convert :: MaryEraOnwards era -> CardanoEra era Source # | |
Convert ShelleyBasedEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods convert :: ShelleyBasedEra era -> CardanoEra era Source # | |
Convert ShelleyEraOnly ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyEraOnly Methods convert :: ShelleyEraOnly era -> ShelleyBasedEra era Source # | |
Convert ShelleyEraOnly CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyEraOnly Methods convert :: ShelleyEraOnly era -> CardanoEra era Source # | |
Convert ShelleyToAllegraEra ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAllegraEra Methods convert :: ShelleyToAllegraEra era -> ShelleyBasedEra era Source # | |
Convert ShelleyToAllegraEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAllegraEra Methods convert :: ShelleyToAllegraEra era -> CardanoEra era Source # | |
Convert ShelleyToAlonzoEra ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAlonzoEra Methods convert :: ShelleyToAlonzoEra era -> ShelleyBasedEra era Source # | |
Convert ShelleyToAlonzoEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAlonzoEra Methods convert :: ShelleyToAlonzoEra era -> CardanoEra era Source # | |
Convert ShelleyToBabbageEra ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToBabbageEra Methods convert :: ShelleyToBabbageEra era -> ShelleyBasedEra era Source # | |
Convert ShelleyToBabbageEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToBabbageEra Methods convert :: ShelleyToBabbageEra era -> CardanoEra era Source # | |
Convert ShelleyToMaryEra ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToMaryEra Methods convert :: ShelleyToMaryEra era -> ShelleyBasedEra era Source # | |
Convert ShelleyToMaryEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToMaryEra Methods convert :: ShelleyToMaryEra era -> CardanoEra era Source # | |
Convert Era AlonzoEraOnwards Source # | |
Defined in Cardano.Api.Internal.Experimental.Eras Methods convert :: Era era -> AlonzoEraOnwards era Source # | |
Convert Era BabbageEraOnwards Source # | |
Defined in Cardano.Api.Internal.Experimental.Eras Methods convert :: Era era -> BabbageEraOnwards era Source # | |
Convert Era ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Experimental.Eras Methods convert :: Era era -> ShelleyBasedEra era Source # | |
Convert Era CardanoEra Source # | |
Defined in Cardano.Api.Internal.Experimental.Eras Methods convert :: Era era -> CardanoEra era Source # | |
Convert (a2 :: a1 -> Type) (a2 :: a1 -> Type) Source # | |
Defined in Cardano.Api.Internal.Eon.Convert |
class Inject t s where Source #
Instances
Inject Coin DeltaCoin | |
Inject Coin MaryValue | |
Inject a a | |
Defined in Cardano.Ledger.BaseTypes | |
Inject (BabbageContextError era) (ConwayContextError era) | |
Defined in Cardano.Ledger.Conway.TxInfo Methods inject :: BabbageContextError era -> ConwayContextError era Source # | |
Inject (AlonzoContextError era) (BabbageContextError era) | |
Defined in Cardano.Ledger.Babbage.TxInfo Methods inject :: AlonzoContextError era -> BabbageContextError era Source # | |
Inject (AlonzoContextError era) (ConwayContextError era) | |
Defined in Cardano.Ledger.Conway.TxInfo Methods inject :: AlonzoContextError era -> ConwayContextError era Source # |
Eons
From Byron
data ByronToAlonzoEra era where Source #
Constructors
ByronToAlonzoEraByron :: ByronToAlonzoEra ByronEra | |
ByronToAlonzoEraShelley :: ByronToAlonzoEra ShelleyEra | |
ByronToAlonzoEraAllegra :: ByronToAlonzoEra AllegraEra | |
ByronToAlonzoEraMary :: ByronToAlonzoEra MaryEra | |
ByronToAlonzoEraAlonzo :: ByronToAlonzoEra AlonzoEra |
Instances
Eon ByronToAlonzoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ByronToAlonzoEra Methods inEonForEra :: a -> (ByronToAlonzoEra era -> a) -> CardanoEra era -> a Source # | |
ToCardanoEra ByronToAlonzoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ByronToAlonzoEra Methods toCardanoEra :: ByronToAlonzoEra era -> CardanoEra era Source # | |
Convert ByronToAlonzoEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ByronToAlonzoEra Methods convert :: ByronToAlonzoEra era -> CardanoEra era Source # | |
Show (ByronToAlonzoEra era) Source # | |
Defined in Cardano.Api.Internal.Eon.ByronToAlonzoEra | |
Eq (ByronToAlonzoEra era) Source # | |
Defined in Cardano.Api.Internal.Eon.ByronToAlonzoEra Methods (==) :: ByronToAlonzoEra era -> ByronToAlonzoEra era -> Bool Source # (/=) :: ByronToAlonzoEra era -> ByronToAlonzoEra era -> Bool Source # |
byronToAlonzoEraConstraints :: ByronToAlonzoEra era -> (ByronToAlonzoEraConstraints era => a) -> a Source #
From Shelley
data ShelleyEraOnly era where Source #
Constructors
ShelleyEraOnlyShelley :: ShelleyEraOnly ShelleyEra |
Instances
Eon ShelleyEraOnly Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyEraOnly Methods inEonForEra :: a -> (ShelleyEraOnly era -> a) -> CardanoEra era -> a Source # | |
ToCardanoEra ShelleyEraOnly Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyEraOnly Methods toCardanoEra :: ShelleyEraOnly era -> CardanoEra era Source # | |
Convert ShelleyEraOnly ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyEraOnly Methods convert :: ShelleyEraOnly era -> ShelleyBasedEra era Source # | |
Convert ShelleyEraOnly CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyEraOnly Methods convert :: ShelleyEraOnly era -> CardanoEra era Source # | |
Show (ShelleyEraOnly era) Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyEraOnly | |
Eq (ShelleyEraOnly era) Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyEraOnly Methods (==) :: ShelleyEraOnly era -> ShelleyEraOnly era -> Bool Source # (/=) :: ShelleyEraOnly era -> ShelleyEraOnly era -> Bool Source # |
shelleyEraOnlyConstraints :: ShelleyEraOnly era -> (ShelleyEraOnlyConstraints era => a) -> a Source #
shelleyEraOnlyToShelleyBasedEra :: ShelleyEraOnly era -> ShelleyBasedEra era Source #
Deprecated: Use convert
instead.
data ShelleyToAllegraEra era where Source #
Constructors
ShelleyToAllegraEraShelley :: ShelleyToAllegraEra ShelleyEra | |
ShelleyToAllegraEraAllegra :: ShelleyToAllegraEra AllegraEra |
Instances
Eon ShelleyToAllegraEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAllegraEra Methods inEonForEra :: a -> (ShelleyToAllegraEra era -> a) -> CardanoEra era -> a Source # | |
ToCardanoEra ShelleyToAllegraEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAllegraEra Methods toCardanoEra :: ShelleyToAllegraEra era -> CardanoEra era Source # | |
Convert ShelleyToAllegraEra ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAllegraEra Methods convert :: ShelleyToAllegraEra era -> ShelleyBasedEra era Source # | |
Convert ShelleyToAllegraEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAllegraEra Methods convert :: ShelleyToAllegraEra era -> CardanoEra era Source # | |
Show (ShelleyToAllegraEra era) Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAllegraEra | |
Eq (ShelleyToAllegraEra era) Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAllegraEra Methods (==) :: ShelleyToAllegraEra era -> ShelleyToAllegraEra era -> Bool Source # (/=) :: ShelleyToAllegraEra era -> ShelleyToAllegraEra era -> Bool Source # |
shelleyToAllegraEraConstraints :: ShelleyToAllegraEra era -> (ShelleyToAllegraEraConstraints era => a) -> a Source #
shelleyToAllegraEraToShelleyBasedEra :: ShelleyToAllegraEra era -> ShelleyBasedEra era Source #
Deprecated: Use convert
instead.
data ShelleyToMaryEra era where Source #
Constructors
ShelleyToMaryEraShelley :: ShelleyToMaryEra ShelleyEra | |
ShelleyToMaryEraAllegra :: ShelleyToMaryEra AllegraEra | |
ShelleyToMaryEraMary :: ShelleyToMaryEra MaryEra |
Instances
Eon ShelleyToMaryEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToMaryEra Methods inEonForEra :: a -> (ShelleyToMaryEra era -> a) -> CardanoEra era -> a Source # | |
ToCardanoEra ShelleyToMaryEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToMaryEra Methods toCardanoEra :: ShelleyToMaryEra era -> CardanoEra era Source # | |
Convert ShelleyToMaryEra ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToMaryEra Methods convert :: ShelleyToMaryEra era -> ShelleyBasedEra era Source # | |
Convert ShelleyToMaryEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToMaryEra Methods convert :: ShelleyToMaryEra era -> CardanoEra era Source # | |
Show (ShelleyToMaryEra era) Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToMaryEra | |
Eq (ShelleyToMaryEra era) Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToMaryEra Methods (==) :: ShelleyToMaryEra era -> ShelleyToMaryEra era -> Bool Source # (/=) :: ShelleyToMaryEra era -> ShelleyToMaryEra era -> Bool Source # |
shelleyToMaryEraConstraints :: ShelleyToMaryEra era -> (ShelleyToMaryEraConstraints era => a) -> a Source #
shelleyToMaryEraToShelleyBasedEra :: ShelleyToMaryEra era -> ShelleyBasedEra era Source #
Deprecated: Use convert
instead.
data ShelleyToAlonzoEra era where Source #
Constructors
ShelleyToAlonzoEraShelley :: ShelleyToAlonzoEra ShelleyEra | |
ShelleyToAlonzoEraAllegra :: ShelleyToAlonzoEra AllegraEra | |
ShelleyToAlonzoEraMary :: ShelleyToAlonzoEra MaryEra | |
ShelleyToAlonzoEraAlonzo :: ShelleyToAlonzoEra AlonzoEra |
Instances
Eon ShelleyToAlonzoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAlonzoEra Methods inEonForEra :: a -> (ShelleyToAlonzoEra era -> a) -> CardanoEra era -> a Source # | |
ToCardanoEra ShelleyToAlonzoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAlonzoEra Methods toCardanoEra :: ShelleyToAlonzoEra era -> CardanoEra era Source # | |
Convert ShelleyToAlonzoEra ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAlonzoEra Methods convert :: ShelleyToAlonzoEra era -> ShelleyBasedEra era Source # | |
Convert ShelleyToAlonzoEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAlonzoEra Methods convert :: ShelleyToAlonzoEra era -> CardanoEra era Source # | |
Show (ShelleyToAlonzoEra era) Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAlonzoEra | |
Eq (ShelleyToAlonzoEra era) Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAlonzoEra Methods (==) :: ShelleyToAlonzoEra era -> ShelleyToAlonzoEra era -> Bool Source # (/=) :: ShelleyToAlonzoEra era -> ShelleyToAlonzoEra era -> Bool Source # |
shelleyToAlonzoEraConstraints :: ShelleyToAlonzoEra era -> (ShelleyToAlonzoEraConstraints era => a) -> a Source #
data ShelleyToBabbageEra era where Source #
Constructors
ShelleyToBabbageEraShelley :: ShelleyToBabbageEra ShelleyEra | |
ShelleyToBabbageEraAllegra :: ShelleyToBabbageEra AllegraEra | |
ShelleyToBabbageEraMary :: ShelleyToBabbageEra MaryEra | |
ShelleyToBabbageEraAlonzo :: ShelleyToBabbageEra AlonzoEra | |
ShelleyToBabbageEraBabbage :: ShelleyToBabbageEra BabbageEra |
Instances
Eon ShelleyToBabbageEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToBabbageEra Methods inEonForEra :: a -> (ShelleyToBabbageEra era -> a) -> CardanoEra era -> a Source # | |
ToCardanoEra ShelleyToBabbageEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToBabbageEra Methods toCardanoEra :: ShelleyToBabbageEra era -> CardanoEra era Source # | |
Convert ShelleyToBabbageEra ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToBabbageEra Methods convert :: ShelleyToBabbageEra era -> ShelleyBasedEra era Source # | |
Convert ShelleyToBabbageEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToBabbageEra Methods convert :: ShelleyToBabbageEra era -> CardanoEra era Source # | |
Show (ShelleyToBabbageEra era) Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToBabbageEra | |
Eq (ShelleyToBabbageEra era) Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToBabbageEra Methods (==) :: ShelleyToBabbageEra era -> ShelleyToBabbageEra era -> Bool Source # (/=) :: ShelleyToBabbageEra era -> ShelleyToBabbageEra era -> Bool Source # | |
Ord (ShelleyToBabbageEra era) Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToBabbageEra Methods compare :: ShelleyToBabbageEra era -> ShelleyToBabbageEra era -> Ordering Source # (<) :: ShelleyToBabbageEra era -> ShelleyToBabbageEra era -> Bool Source # (<=) :: ShelleyToBabbageEra era -> ShelleyToBabbageEra era -> Bool Source # (>) :: ShelleyToBabbageEra era -> ShelleyToBabbageEra era -> Bool Source # (>=) :: ShelleyToBabbageEra era -> ShelleyToBabbageEra era -> Bool Source # max :: ShelleyToBabbageEra era -> ShelleyToBabbageEra era -> ShelleyToBabbageEra era Source # min :: ShelleyToBabbageEra era -> ShelleyToBabbageEra era -> ShelleyToBabbageEra era Source # |
shelleyToBabbageEraConstraints :: ShelleyToBabbageEra era -> (ShelleyToBabbageEraConstraints era => a) -> a Source #
shelleyToBabbageEraToShelleyBasedEra :: ShelleyToBabbageEra era -> ShelleyBasedEra era Source #
Deprecated: Use convert
instead.
data ShelleyBasedEra era where Source #
While the Byron and Shelley eras are quite different, there are several eras that are based on Shelley with only minor differences. It is useful to be able to treat the Shelley-based eras in a mostly-uniform way.
Values of this type witness the fact that the era is Shelley-based. This can be used to constrain the era to being a Shelley-based on. It allows non-uniform handling making case distinctions on the constructor.
Constructors
ShelleyBasedEraShelley :: ShelleyBasedEra ShelleyEra | |
ShelleyBasedEraAllegra :: ShelleyBasedEra AllegraEra | |
ShelleyBasedEraMary :: ShelleyBasedEra MaryEra | |
ShelleyBasedEraAlonzo :: ShelleyBasedEra AlonzoEra | |
ShelleyBasedEraBabbage :: ShelleyBasedEra BabbageEra | |
ShelleyBasedEraConway :: ShelleyBasedEra ConwayEra |
Instances
Eon ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods inEonForEra :: a -> (ShelleyBasedEra era -> a) -> CardanoEra era -> a Source # | |
ToCardanoEra ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods toCardanoEra :: ShelleyBasedEra era -> CardanoEra era Source # | |
TestEquality ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods testEquality :: ShelleyBasedEra a -> ShelleyBasedEra b -> Maybe (a :~: b) Source # | |
Convert AllegraEraOnwards ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods convert :: AllegraEraOnwards era -> ShelleyBasedEra era Source # | |
Convert AlonzoEraOnwards ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards Methods convert :: AlonzoEraOnwards era -> ShelleyBasedEra era Source # | |
Convert BabbageEraOnwards ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards Methods convert :: BabbageEraOnwards era -> ShelleyBasedEra era Source # | |
Convert ConwayEraOnwards ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards Methods convert :: ConwayEraOnwards era -> ShelleyBasedEra era Source # | |
Convert MaryEraOnwards ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards Methods convert :: MaryEraOnwards era -> ShelleyBasedEra era Source # | |
Convert ShelleyBasedEra CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods convert :: ShelleyBasedEra era -> CardanoEra era Source # | |
Convert ShelleyEraOnly ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyEraOnly Methods convert :: ShelleyEraOnly era -> ShelleyBasedEra era Source # | |
Convert ShelleyToAllegraEra ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAllegraEra Methods convert :: ShelleyToAllegraEra era -> ShelleyBasedEra era Source # | |
Convert ShelleyToAlonzoEra ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToAlonzoEra Methods convert :: ShelleyToAlonzoEra era -> ShelleyBasedEra era Source # | |
Convert ShelleyToBabbageEra ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToBabbageEra Methods convert :: ShelleyToBabbageEra era -> ShelleyBasedEra era Source # | |
Convert ShelleyToMaryEra ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyToMaryEra Methods convert :: ShelleyToMaryEra era -> ShelleyBasedEra era Source # | |
Convert Era ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Experimental.Eras Methods convert :: Era era -> ShelleyBasedEra era Source # | |
ToJSON (ShelleyBasedEra era) Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods toJSON :: ShelleyBasedEra era -> Value toEncoding :: ShelleyBasedEra era -> Encoding toJSONList :: [ShelleyBasedEra era] -> Value toEncodingList :: [ShelleyBasedEra era] -> Encoding omitField :: ShelleyBasedEra era -> Bool | |
Show (ShelleyBasedEra era) Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra | |
NFData (ShelleyBasedEra era) Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods rnf :: ShelleyBasedEra era -> () Source # | |
Eq (ShelleyBasedEra era) Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods (==) :: ShelleyBasedEra era -> ShelleyBasedEra era -> Bool Source # (/=) :: ShelleyBasedEra era -> ShelleyBasedEra era -> Bool Source # | |
Ord (ShelleyBasedEra era) Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods compare :: ShelleyBasedEra era -> ShelleyBasedEra era -> Ordering Source # (<) :: ShelleyBasedEra era -> ShelleyBasedEra era -> Bool Source # (<=) :: ShelleyBasedEra era -> ShelleyBasedEra era -> Bool Source # (>) :: ShelleyBasedEra era -> ShelleyBasedEra era -> Bool Source # (>=) :: ShelleyBasedEra era -> ShelleyBasedEra era -> Bool Source # max :: ShelleyBasedEra era -> ShelleyBasedEra era -> ShelleyBasedEra era Source # min :: ShelleyBasedEra era -> ShelleyBasedEra era -> ShelleyBasedEra era Source # | |
Pretty (ShelleyBasedEra era) Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra |
class IsCardanoEra era => IsShelleyBasedEra era where Source #
The class of eras that are based on Shelley. This allows uniform handling
of Shelley-based eras, but also non-uniform by making case distinctions on
the ShelleyBasedEra
constructors.
Methods
shelleyBasedEra :: ShelleyBasedEra era Source #
Instances
IsShelleyBasedEra AllegraEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods | |
IsShelleyBasedEra AlonzoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods | |
IsShelleyBasedEra BabbageEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods | |
IsShelleyBasedEra ConwayEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods | |
IsShelleyBasedEra MaryEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods | |
IsShelleyBasedEra ShelleyEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods |
data AnyShelleyBasedEra where Source #
Constructors
AnyShelleyBasedEra :: forall era. Typeable era => ShelleyBasedEra era -> AnyShelleyBasedEra |
Instances
FromJSON AnyShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods parseJSON :: Value -> Parser AnyShelleyBasedEra parseJSONList :: Value -> Parser [AnyShelleyBasedEra] | |
ToJSON AnyShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods toJSON :: AnyShelleyBasedEra -> Value toEncoding :: AnyShelleyBasedEra -> Encoding toJSONList :: [AnyShelleyBasedEra] -> Value toEncodingList :: [AnyShelleyBasedEra] -> Encoding omitField :: AnyShelleyBasedEra -> Bool | |
Bounded AnyShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra | |
Enum AnyShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods succ :: AnyShelleyBasedEra -> AnyShelleyBasedEra Source # pred :: AnyShelleyBasedEra -> AnyShelleyBasedEra Source # toEnum :: Int -> AnyShelleyBasedEra Source # fromEnum :: AnyShelleyBasedEra -> Int Source # enumFrom :: AnyShelleyBasedEra -> [AnyShelleyBasedEra] Source # enumFromThen :: AnyShelleyBasedEra -> AnyShelleyBasedEra -> [AnyShelleyBasedEra] Source # enumFromTo :: AnyShelleyBasedEra -> AnyShelleyBasedEra -> [AnyShelleyBasedEra] Source # enumFromThenTo :: AnyShelleyBasedEra -> AnyShelleyBasedEra -> AnyShelleyBasedEra -> [AnyShelleyBasedEra] Source # | |
Show AnyShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra | |
Eq AnyShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ShelleyBasedEra Methods (==) :: AnyShelleyBasedEra -> AnyShelleyBasedEra -> Bool Source # (/=) :: AnyShelleyBasedEra -> AnyShelleyBasedEra -> Bool Source # |
data InAnyShelleyBasedEra (thing :: Type -> Type) where Source #
This pairs up some era-dependent type with a ShelleyBasedEra
value that
tells us what era it is, but hides the era type. This is useful when the era
is not statically known, for example when deserialising from a file.
Constructors
InAnyShelleyBasedEra :: forall era (thing :: Type -> Type). Typeable era => ShelleyBasedEra era -> thing era -> InAnyShelleyBasedEra thing |
Instances
Show (InAnyShelleyBasedEra Tx) Source # | |
Defined in Cardano.Api.Internal.Tx.Sign | |
Eq (InAnyShelleyBasedEra Tx) Source # | |
Defined in Cardano.Api.Internal.Tx.Sign Methods (==) :: InAnyShelleyBasedEra Tx -> InAnyShelleyBasedEra Tx -> Bool Source # (/=) :: InAnyShelleyBasedEra Tx -> InAnyShelleyBasedEra Tx -> Bool Source # |
inAnyShelleyBasedEra :: ShelleyBasedEra era -> thing era -> InAnyShelleyBasedEra thing Source #
shelleyBasedEraConstraints :: ShelleyBasedEra era -> (ShelleyBasedEraConstraints era => a) -> a Source #
From Allegra
data AllegraEraOnwards era where Source #
Constructors
AllegraEraOnwardsAllegra :: AllegraEraOnwards AllegraEra | |
AllegraEraOnwardsMary :: AllegraEraOnwards MaryEra | |
AllegraEraOnwardsAlonzo :: AllegraEraOnwards AlonzoEra | |
AllegraEraOnwardsBabbage :: AllegraEraOnwards BabbageEra | |
AllegraEraOnwardsConway :: AllegraEraOnwards ConwayEra |
Instances
Eon AllegraEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods inEonForEra :: a -> (AllegraEraOnwards era -> a) -> CardanoEra era -> a Source # | |
ToCardanoEra AllegraEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods toCardanoEra :: AllegraEraOnwards era -> CardanoEra era Source # | |
Convert AllegraEraOnwards ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods convert :: AllegraEraOnwards era -> ShelleyBasedEra era Source # | |
Convert AllegraEraOnwards CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods convert :: AllegraEraOnwards era -> CardanoEra era Source # | |
Convert ConwayEraOnwards AllegraEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards Methods convert :: ConwayEraOnwards era -> AllegraEraOnwards era Source # | |
Show (AllegraEraOnwards era) Source # | |
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards | |
Eq (AllegraEraOnwards era) Source # | |
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods (==) :: AllegraEraOnwards era -> AllegraEraOnwards era -> Bool Source # (/=) :: AllegraEraOnwards era -> AllegraEraOnwards era -> Bool Source # |
class IsShelleyBasedEra era => IsAllegraBasedEra era where Source #
Methods
allegraBasedEra :: AllegraEraOnwards era Source #
Instances
IsAllegraBasedEra AllegraEra Source # | |
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods | |
IsAllegraBasedEra AlonzoEra Source # | |
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods | |
IsAllegraBasedEra BabbageEra Source # | |
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods | |
IsAllegraBasedEra ConwayEra Source # | |
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods | |
IsAllegraBasedEra MaryEra Source # | |
Defined in Cardano.Api.Internal.Eon.AllegraEraOnwards Methods |
From Mary
data MaryEraOnwards era where Source #
Constructors
MaryEraOnwardsMary :: MaryEraOnwards MaryEra | |
MaryEraOnwardsAlonzo :: MaryEraOnwards AlonzoEra | |
MaryEraOnwardsBabbage :: MaryEraOnwards BabbageEra | |
MaryEraOnwardsConway :: MaryEraOnwards ConwayEra |
Instances
Eon MaryEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards Methods inEonForEra :: a -> (MaryEraOnwards era -> a) -> CardanoEra era -> a Source # | |
ToCardanoEra MaryEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards Methods toCardanoEra :: MaryEraOnwards era -> CardanoEra era Source # | |
Convert BabbageEraOnwards MaryEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards Methods convert :: BabbageEraOnwards era -> MaryEraOnwards era Source # | |
Convert MaryEraOnwards ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards Methods convert :: MaryEraOnwards era -> ShelleyBasedEra era Source # | |
Convert MaryEraOnwards CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards Methods convert :: MaryEraOnwards era -> CardanoEra era Source # | |
Show (MaryEraOnwards era) Source # | |
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards | |
Eq (MaryEraOnwards era) Source # | |
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards Methods (==) :: MaryEraOnwards era -> MaryEraOnwards era -> Bool Source # (/=) :: MaryEraOnwards era -> MaryEraOnwards era -> Bool Source # |
maryEraOnwardsConstraints :: MaryEraOnwards era -> (MaryEraOnwardsConstraints era => a) -> a Source #
maryEraOnwardsToShelleyBasedEra :: MaryEraOnwards era -> ShelleyBasedEra era Source #
Deprecated: Use convert
instead.
class IsAllegraBasedEra era => IsMaryBasedEra era where Source #
Methods
maryBasedEra :: MaryEraOnwards era Source #
Instances
IsMaryBasedEra AlonzoEra Source # | |
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards Methods | |
IsMaryBasedEra BabbageEra Source # | |
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards Methods | |
IsMaryBasedEra ConwayEra Source # | |
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards Methods | |
IsMaryBasedEra MaryEra Source # | |
Defined in Cardano.Api.Internal.Eon.MaryEraOnwards Methods |
From Alonzo
data AlonzoEraOnwards era where Source #
Constructors
AlonzoEraOnwardsAlonzo :: AlonzoEraOnwards AlonzoEra | |
AlonzoEraOnwardsBabbage :: AlonzoEraOnwards BabbageEra | |
AlonzoEraOnwardsConway :: AlonzoEraOnwards ConwayEra |
Instances
Eon AlonzoEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards Methods inEonForEra :: a -> (AlonzoEraOnwards era -> a) -> CardanoEra era -> a Source # | |
ToCardanoEra AlonzoEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards Methods toCardanoEra :: AlonzoEraOnwards era -> CardanoEra era Source # | |
Convert AlonzoEraOnwards ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards Methods convert :: AlonzoEraOnwards era -> ShelleyBasedEra era Source # | |
Convert AlonzoEraOnwards CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards Methods convert :: AlonzoEraOnwards era -> CardanoEra era Source # | |
Convert BabbageEraOnwards AlonzoEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards Methods convert :: BabbageEraOnwards era -> AlonzoEraOnwards era Source # | |
Convert Era AlonzoEraOnwards Source # | |
Defined in Cardano.Api.Internal.Experimental.Eras Methods convert :: Era era -> AlonzoEraOnwards era Source # | |
Show (AlonzoEraOnwards era) Source # | |
Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards | |
Eq (AlonzoEraOnwards era) Source # | |
Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards Methods (==) :: AlonzoEraOnwards era -> AlonzoEraOnwards era -> Bool Source # (/=) :: AlonzoEraOnwards era -> AlonzoEraOnwards era -> Bool Source # |
alonzoEraOnwardsConstraints :: AlonzoEraOnwards era -> (AlonzoEraOnwardsConstraints era => a) -> a Source #
alonzoEraOnwardsToShelleyBasedEra :: AlonzoEraOnwards era -> ShelleyBasedEra era Source #
Deprecated: Use convert
instead.
class IsMaryBasedEra era => IsAlonzoBasedEra era where Source #
Methods
alonzoBasedEra :: AlonzoEraOnwards era Source #
Instances
IsAlonzoBasedEra AlonzoEra Source # | |
Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards Methods | |
IsAlonzoBasedEra BabbageEra Source # | |
Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards Methods | |
IsAlonzoBasedEra ConwayEra Source # | |
Defined in Cardano.Api.Internal.Eon.AlonzoEraOnwards Methods |
From Babbage
data BabbageEraOnwards era where Source #
Constructors
BabbageEraOnwardsBabbage :: BabbageEraOnwards BabbageEra | |
BabbageEraOnwardsConway :: BabbageEraOnwards ConwayEra |
Instances
Eon BabbageEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards Methods inEonForEra :: a -> (BabbageEraOnwards era -> a) -> CardanoEra era -> a Source # | |
ToCardanoEra BabbageEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards Methods toCardanoEra :: BabbageEraOnwards era -> CardanoEra era Source # | |
Convert BabbageEraOnwards AlonzoEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards Methods convert :: BabbageEraOnwards era -> AlonzoEraOnwards era Source # | |
Convert BabbageEraOnwards MaryEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards Methods convert :: BabbageEraOnwards era -> MaryEraOnwards era Source # | |
Convert BabbageEraOnwards ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards Methods convert :: BabbageEraOnwards era -> ShelleyBasedEra era Source # | |
Convert BabbageEraOnwards CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards Methods convert :: BabbageEraOnwards era -> CardanoEra era Source # | |
Convert ConwayEraOnwards BabbageEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards Methods convert :: ConwayEraOnwards era -> BabbageEraOnwards era Source # | |
Convert Era BabbageEraOnwards Source # | |
Defined in Cardano.Api.Internal.Experimental.Eras Methods convert :: Era era -> BabbageEraOnwards era Source # | |
Show (BabbageEraOnwards era) Source # | |
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards | |
Eq (BabbageEraOnwards era) Source # | |
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards Methods (==) :: BabbageEraOnwards era -> BabbageEraOnwards era -> Bool Source # (/=) :: BabbageEraOnwards era -> BabbageEraOnwards era -> Bool Source # |
babbageEraOnwardsConstraints :: BabbageEraOnwards era -> (BabbageEraOnwardsConstraints era => a) -> a Source #
babbageEraOnwardsToShelleyBasedEra :: BabbageEraOnwards era -> ShelleyBasedEra era Source #
Deprecated: Use convert
instead.
class IsAlonzoBasedEra era => IsBabbageBasedEra era where Source #
Methods
babbageBasedEra :: BabbageEraOnwards era Source #
Instances
IsBabbageBasedEra BabbageEra Source # | |
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards Methods | |
IsBabbageBasedEra ConwayEra Source # | |
Defined in Cardano.Api.Internal.Eon.BabbageEraOnwards Methods |
From Conway
data ConwayEraOnwards era where Source #
Constructors
ConwayEraOnwardsConway :: ConwayEraOnwards ConwayEra |
Instances
Eon ConwayEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards Methods inEonForEra :: a -> (ConwayEraOnwards era -> a) -> CardanoEra era -> a Source # | |
ToCardanoEra ConwayEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards Methods toCardanoEra :: ConwayEraOnwards era -> CardanoEra era Source # | |
Convert ConwayEraOnwards AllegraEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards Methods convert :: ConwayEraOnwards era -> AllegraEraOnwards era Source # | |
Convert ConwayEraOnwards BabbageEraOnwards Source # | |
Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards Methods convert :: ConwayEraOnwards era -> BabbageEraOnwards era Source # | |
Convert ConwayEraOnwards ShelleyBasedEra Source # | |
Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards Methods convert :: ConwayEraOnwards era -> ShelleyBasedEra era Source # | |
Convert ConwayEraOnwards CardanoEra Source # | |
Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards Methods convert :: ConwayEraOnwards era -> CardanoEra era Source # | |
Show (ConwayEraOnwards era) Source # | |
Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards | |
Eq (ConwayEraOnwards era) Source # | |
Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards Methods (==) :: ConwayEraOnwards era -> ConwayEraOnwards era -> Bool Source # (/=) :: ConwayEraOnwards era -> ConwayEraOnwards era -> Bool Source # | |
Ord (ConwayEraOnwards era) Source # | |
Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards Methods compare :: ConwayEraOnwards era -> ConwayEraOnwards era -> Ordering Source # (<) :: ConwayEraOnwards era -> ConwayEraOnwards era -> Bool Source # (<=) :: ConwayEraOnwards era -> ConwayEraOnwards era -> Bool Source # (>) :: ConwayEraOnwards era -> ConwayEraOnwards era -> Bool Source # (>=) :: ConwayEraOnwards era -> ConwayEraOnwards era -> Bool Source # max :: ConwayEraOnwards era -> ConwayEraOnwards era -> ConwayEraOnwards era Source # min :: ConwayEraOnwards era -> ConwayEraOnwards era -> ConwayEraOnwards era Source # |
conwayEraOnwardsConstraints :: ConwayEraOnwards era -> (ConwayEraOnwardsConstraints era => a) -> a Source #
conwayEraOnwardsToShelleyBasedEra :: ConwayEraOnwards era -> ShelleyBasedEra era Source #
Deprecated: Use convert
instead.
conwayEraOnwardsToBabbageEraOnwards :: ConwayEraOnwards era -> BabbageEraOnwards era Source #
Deprecated: Use convert
instead.
class IsBabbageBasedEra era => IsConwayBasedEra era where Source #
Methods
conwayBasedEra :: ConwayEraOnwards era Source #
Instances
IsConwayBasedEra ConwayEra Source # | |
Defined in Cardano.Api.Internal.Eon.ConwayEraOnwards Methods |
Era case handling
Case on CardanoEra
caseByronOrShelleyBasedEra :: a -> (ShelleyBasedEraConstraints era => ShelleyBasedEra era -> a) -> CardanoEra era -> a Source #
caseByronOrShelleyBasedEra f g era
returns f
in Byron and applies g
to Shelley-based eras.
caseByronToAlonzoOrBabbageEraOnwards :: (ByronToAlonzoEraConstraints era => ByronToAlonzoEra era -> a) -> (BabbageEraOnwardsConstraints era => BabbageEraOnwards era -> a) -> CardanoEra era -> a Source #
caseByronToAlonzoOrBabbageEraOnwards f g era
applies f
to byron, shelley, allegra, mary, and alonzo;
and g
to babbage and later eras.
Case on ShelleyBasedEra
caseShelleyEraOnlyOrAllegraEraOnwards :: (ShelleyEraOnlyConstraints era => ShelleyEraOnly era -> a) -> (AllegraEraOnwardsConstraints era => AllegraEraOnwards era -> a) -> ShelleyBasedEra era -> a Source #
caseShelleyEraOnlyOrAllegraEraOnwards f g era
applies f
to shelley;
and applies g
to allegra and later eras.
caseShelleyToAllegraOrMaryEraOnwards :: (ShelleyToAllegraEraConstraints era => ShelleyToAllegraEra era -> a) -> (MaryEraOnwardsConstraints era => MaryEraOnwards era -> a) -> ShelleyBasedEra era -> a Source #
caseShelleyToAllegraOrMaryEraOnwards f g era
applies f
to shelley and allegra;
and applies g
to mary and later eras.
caseShelleyToMaryOrAlonzoEraOnwards :: (ShelleyToMaryEraConstraints era => ShelleyToMaryEra era -> a) -> (AlonzoEraOnwardsConstraints era => AlonzoEraOnwards era -> a) -> ShelleyBasedEra era -> a Source #
caseShelleyToMaryOrAlonzoEraOnwards f g era
applies f
to shelley, allegra, and mary;
and applies g
to alonzo and later eras.
caseShelleyToAlonzoOrBabbageEraOnwards :: (ShelleyToAlonzoEraConstraints era => ShelleyToAlonzoEra era -> a) -> (BabbageEraOnwardsConstraints era => BabbageEraOnwards era -> a) -> ShelleyBasedEra era -> a Source #
caseShelleyToAlonzoOrBabbageEraOnwards f g era
applies f
to shelley, allegra, mary, and alonzo;
and applies g
to babbage and later eras.
caseShelleyToBabbageOrConwayEraOnwards :: (ShelleyToBabbageEraConstraints era => ShelleyToBabbageEra era -> a) -> (ConwayEraOnwardsConstraints era => ConwayEraOnwards era -> a) -> ShelleyBasedEra era -> a Source #
caseShelleyToBabbageOrConwayEraOnwards f g era
applies f
to eras before conway;
and applies g
to conway and later eras.
Eon relaxation
for AlonzoEraOnly
shelleyToAlonzoEraToShelleyToBabbageEra :: ShelleyToAlonzoEra era -> ShelleyToBabbageEra era Source #
Deprecated: Use convert instead
for AlonzoEraOnwards
alonzoEraOnwardsToMaryEraOnwards :: AlonzoEraOnwards era -> MaryEraOnwards era Source #
Deprecated: Use convert instead
for BabbageEraOnwards
babbageEraOnwardsToMaryEraOnwards :: BabbageEraOnwards era -> MaryEraOnwards era Source #
Deprecated: Use convert instead
babbageEraOnwardsToAlonzoEraOnwards :: BabbageEraOnwards era -> AlonzoEraOnwards era Source #
Deprecated: Use convert instead
Assertions on era
requireShelleyBasedEra :: Applicative m => CardanoEra era -> m (Maybe (ShelleyBasedEra era)) Source #
IO
newtype File content (direction :: FileDirection) Source #
A file path with additional type information to indicate what the file is meant to contain and whether it is to be used for reading or writing.
Instances
FromJSON (File content direction) Source # | |
Defined in Cardano.Api.Internal.IO.Base Methods parseJSON :: Value -> Parser (File content direction) parseJSONList :: Value -> Parser [File content direction] omittedField :: Maybe (File content direction) | |
ToJSON (File content direction) Source # | |
Defined in Cardano.Api.Internal.IO.Base Methods toJSON :: File content direction -> Value toEncoding :: File content direction -> Encoding toJSONList :: [File content direction] -> Value toEncodingList :: [File content direction] -> Encoding | |
IsString (File content direction) Source # | |
Defined in Cardano.Api.Internal.IO.Base Methods fromString :: String -> File content direction Source # | |
Read (File content direction) Source # | |
Show (File content direction) Source # | |
Eq (File content direction) Source # | |
Ord (File content direction) Source # | |
Defined in Cardano.Api.Internal.IO.Base Methods compare :: File content direction -> File content direction -> Ordering Source # (<) :: File content direction -> File content direction -> Bool Source # (<=) :: File content direction -> File content direction -> Bool Source # (>) :: File content direction -> File content direction -> Bool Source # (>=) :: File content direction -> File content direction -> Bool Source # max :: File content direction -> File content direction -> File content direction Source # min :: File content direction -> File content direction -> File content direction Source # |
data FileDirection Source #
mapFile :: forall content (direction :: FileDirection). (FilePath -> FilePath) -> File content direction -> File content direction Source #
intoFile :: File content 'Out -> content -> (File content 'Out -> stream -> result) -> (content -> stream) -> result Source #
Given a way to serialise a value and a way to write the stream to a file, serialise a value into a stream, and write it to a file.
Whilst it is possible to call the serialisation and writing functions separately, doing so means the compiler is unable to match the content type of the file with the type of the content being serialised.
Using this function ensures that the content type of the file always matches with the content value and prevents any type mismatches.
readByteStringFile :: MonadIO m => File content 'In -> m (Either (FileError e) ByteString) Source #
readLazyByteStringFile :: MonadIO m => File content 'In -> m (Either (FileError e) ByteString) Source #
writeByteStringFileWithOwnerPermissions :: FilePath -> ByteString -> IO (Either (FileError e) ()) Source #
writeByteStringFile :: MonadIO m => File content 'Out -> ByteString -> m (Either (FileError e) ()) Source #
writeByteStringOutput :: MonadIO m => Maybe (File content 'Out) -> ByteString -> m (Either (FileError e) ()) Source #
writeLazyByteStringFileWithOwnerPermissions :: File content 'Out -> ByteString -> IO (Either (FileError e) ()) Source #
writeLazyByteStringFile :: MonadIO m => File content 'Out -> ByteString -> m (Either (FileError e) ()) Source #
writeLazyByteStringOutput :: MonadIO m => Maybe (File content 'Out) -> ByteString -> m (Either (FileError e) ()) Source #
writeTextFileWithOwnerPermissions :: File content 'Out -> Text -> IO (Either (FileError e) ()) Source #
writeTextOutput :: MonadIO m => Maybe (File content 'Out) -> Text -> m (Either (FileError e) ()) Source #
Type tags
class Typeable t => HasTypeProxy t where Source #
Associated Types
A family of singleton types used in this API to indicate which type to use where it would otherwise be ambiguous or merely unclear.
Values of this type are passed to deserialisation functions for example.
Methods
proxyToAsType :: Proxy t -> AsType t Source #
Instances
HasTypeProxy AddressAny Source # | |||||
Defined in Cardano.Api.Internal.Address Associated Types
Methods proxyToAsType :: Proxy AddressAny -> AsType AddressAny Source # | |||||
HasTypeProxy ByronAddr Source # | |||||
Defined in Cardano.Api.Internal.Address Associated Types
| |||||
HasTypeProxy ShelleyAddr Source # | |||||
Defined in Cardano.Api.Internal.Address Associated Types
Methods proxyToAsType :: Proxy ShelleyAddr -> AsType ShelleyAddr Source # | |||||
HasTypeProxy StakeAddress Source # | |||||
Defined in Cardano.Api.Internal.Address Associated Types
Methods proxyToAsType :: Proxy StakeAddress -> AsType StakeAddress Source # | |||||
HasTypeProxy BlockHeader Source # | |||||
Defined in Cardano.Api.Internal.Block Associated Types
Methods proxyToAsType :: Proxy BlockHeader -> AsType BlockHeader Source # | |||||
HasTypeProxy DRepMetadata Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata Associated Types
Methods proxyToAsType :: Proxy DRepMetadata -> AsType DRepMetadata Source # | |||||
HasTypeProxy AllegraEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Associated Types
Methods proxyToAsType :: Proxy AllegraEra -> AsType AllegraEra Source # | |||||
HasTypeProxy AlonzoEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Associated Types
| |||||
HasTypeProxy BabbageEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Associated Types
Methods proxyToAsType :: Proxy BabbageEra -> AsType BabbageEra Source # | |||||
HasTypeProxy ByronEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Associated Types
| |||||
HasTypeProxy ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Associated Types
| |||||
HasTypeProxy MaryEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Associated Types
| |||||
HasTypeProxy ShelleyEra Source # | |||||
Defined in Cardano.Api.Internal.Eras.Core Associated Types
Methods proxyToAsType :: Proxy ShelleyEra -> AsType ShelleyEra Source # | |||||
HasTypeProxy GovernancePoll Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll Associated Types
Methods proxyToAsType :: Proxy GovernancePoll -> AsType GovernancePoll Source # | |||||
HasTypeProxy GovernancePollAnswer Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll Associated Types
Methods proxyToAsType :: Proxy GovernancePollAnswer -> AsType GovernancePollAnswer Source # | |||||
HasTypeProxy ByronKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Associated Types
| |||||
HasTypeProxy ByronKeyLegacy Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Associated Types
Methods proxyToAsType :: Proxy ByronKeyLegacy -> AsType ByronKeyLegacy Source # | |||||
HasTypeProxy KesKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Associated Types
| |||||
HasTypeProxy VrfKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Associated Types
| |||||
HasTypeProxy CommitteeColdExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
| |||||
HasTypeProxy CommitteeColdKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods proxyToAsType :: Proxy CommitteeColdKey -> AsType CommitteeColdKey Source # | |||||
HasTypeProxy CommitteeHotExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
| |||||
HasTypeProxy CommitteeHotKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods proxyToAsType :: Proxy CommitteeHotKey -> AsType CommitteeHotKey Source # | |||||
HasTypeProxy DRepExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods proxyToAsType :: Proxy DRepExtendedKey -> AsType DRepExtendedKey Source # | |||||
HasTypeProxy DRepKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
| |||||
HasTypeProxy GenesisDelegateExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
| |||||
HasTypeProxy GenesisDelegateKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods proxyToAsType :: Proxy GenesisDelegateKey -> AsType GenesisDelegateKey Source # | |||||
HasTypeProxy GenesisExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods proxyToAsType :: Proxy GenesisExtendedKey -> AsType GenesisExtendedKey Source # | |||||
HasTypeProxy GenesisKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods proxyToAsType :: Proxy GenesisKey -> AsType GenesisKey Source # | |||||
HasTypeProxy GenesisUTxOKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods proxyToAsType :: Proxy GenesisUTxOKey -> AsType GenesisUTxOKey Source # | |||||
HasTypeProxy PaymentExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods proxyToAsType :: Proxy PaymentExtendedKey -> AsType PaymentExtendedKey Source # | |||||
HasTypeProxy PaymentKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods proxyToAsType :: Proxy PaymentKey -> AsType PaymentKey Source # | |||||
HasTypeProxy StakeExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods proxyToAsType :: Proxy StakeExtendedKey -> AsType StakeExtendedKey Source # | |||||
HasTypeProxy StakeKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
| |||||
HasTypeProxy StakePoolExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods proxyToAsType :: Proxy StakePoolExtendedKey -> AsType StakePoolExtendedKey Source # | |||||
HasTypeProxy StakePoolKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods proxyToAsType :: Proxy StakePoolKey -> AsType StakePoolKey Source # | |||||
HasTypeProxy OperationalCertificate Source # | |||||
Defined in Cardano.Api.Internal.OperationalCertificate Associated Types
Methods proxyToAsType :: Proxy OperationalCertificate -> AsType OperationalCertificate Source # | |||||
HasTypeProxy OperationalCertificateIssueCounter Source # | |||||
Defined in Cardano.Api.Internal.OperationalCertificate Associated Types
| |||||
HasTypeProxy PraosNonce Source # | |||||
Defined in Cardano.Api.Internal.ProtocolParameters Associated Types
Methods proxyToAsType :: Proxy PraosNonce -> AsType PraosNonce Source # | |||||
HasTypeProxy UpdateProposal Source # | |||||
Defined in Cardano.Api.Internal.ProtocolParameters Associated Types
Methods proxyToAsType :: Proxy UpdateProposal -> AsType UpdateProposal Source # | |||||
HasTypeProxy EraHistory Source # | |||||
Defined in Cardano.Api.Internal.Query Associated Types
Methods proxyToAsType :: Proxy EraHistory -> AsType EraHistory Source # | |||||
HasTypeProxy PlutusScriptV1 Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
Methods proxyToAsType :: Proxy PlutusScriptV1 -> AsType PlutusScriptV1 Source # | |||||
HasTypeProxy PlutusScriptV2 Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
Methods proxyToAsType :: Proxy PlutusScriptV2 -> AsType PlutusScriptV2 Source # | |||||
HasTypeProxy PlutusScriptV3 Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
Methods proxyToAsType :: Proxy PlutusScriptV3 -> AsType PlutusScriptV3 Source # | |||||
HasTypeProxy ScriptHash Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
Methods proxyToAsType :: Proxy ScriptHash -> AsType ScriptHash Source # | |||||
HasTypeProxy ScriptInAnyLang Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
Methods proxyToAsType :: Proxy ScriptInAnyLang -> AsType ScriptInAnyLang Source # | |||||
HasTypeProxy SimpleScript' Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
Methods proxyToAsType :: Proxy SimpleScript' -> AsType SimpleScript' Source # | |||||
HasTypeProxy HashableScriptData Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Associated Types
Methods proxyToAsType :: Proxy HashableScriptData -> AsType HashableScriptData Source # | |||||
HasTypeProxy ScriptData Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Associated Types
Methods proxyToAsType :: Proxy ScriptData -> AsType ScriptData Source # | |||||
HasTypeProxy TextEnvelope Source # | |||||
Defined in Cardano.Api.Internal.SerialiseTextEnvelope Associated Types
Methods proxyToAsType :: Proxy TextEnvelope -> AsType TextEnvelope Source # | |||||
HasTypeProxy ByronUpdateProposal Source # | |||||
Defined in Cardano.Api.Internal.SpecialByron Associated Types
Methods proxyToAsType :: Proxy ByronUpdateProposal -> AsType ByronUpdateProposal Source # | |||||
HasTypeProxy ByronVote Source # | |||||
Defined in Cardano.Api.Internal.SpecialByron Associated Types
| |||||
HasTypeProxy StakePoolMetadata Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata Associated Types
Methods proxyToAsType :: Proxy StakePoolMetadata -> AsType StakePoolMetadata Source # | |||||
HasTypeProxy TxId Source # | |||||
Defined in Cardano.Api.Internal.TxIn | |||||
HasTypeProxy TxMetadata Source # | |||||
Defined in Cardano.Api.Internal.TxMetadata Associated Types
Methods proxyToAsType :: Proxy TxMetadata -> AsType TxMetadata Source # | |||||
HasTypeProxy AssetName Source # | |||||
Defined in Cardano.Api.Internal.Value Associated Types
| |||||
HasTypeProxy PolicyId Source # | |||||
Defined in Cardano.Api.Internal.Value Associated Types
| |||||
HasTypeProxy GovActionId Source # | |||||
Defined in Cardano.Api.Internal.Orphans.Serialisation Associated Types
Methods proxyToAsType :: Proxy GovActionId -> AsType GovActionId Source # | |||||
HasTypeProxy Term Source # | |||||
HasTypeProxy addrtype => HasTypeProxy (Address addrtype) Source # | |||||
Defined in Cardano.Api.Internal.Address Associated Types
| |||||
HasTypeProxy era => HasTypeProxy (AddressInEra era) Source # | |||||
Defined in Cardano.Api.Internal.Address Associated Types
Methods proxyToAsType :: Proxy (AddressInEra era) -> AsType (AddressInEra era) Source # | |||||
Typeable era => HasTypeProxy (Certificate era) Source # | |||||
Defined in Cardano.Api.Internal.Certificate Associated Types
Methods proxyToAsType :: Proxy (Certificate era) -> AsType (Certificate era) Source # | |||||
HasTypeProxy era => HasTypeProxy (Proposal era) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Actions.ProposalProcedure Associated Types
| |||||
HasTypeProxy era => HasTypeProxy (VotingProcedure era) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure Associated Types
Methods proxyToAsType :: Proxy (VotingProcedure era) -> AsType (VotingProcedure era) Source # | |||||
HasTypeProxy era => HasTypeProxy (VotingProcedures era) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure Associated Types
Methods proxyToAsType :: Proxy (VotingProcedures era) -> AsType (VotingProcedures era) Source # | |||||
HasTypeProxy a => HasTypeProxy (Hash a) Source # | |||||
Defined in Cardano.Api.Internal.Hash Associated Types
| |||||
HasTypeProxy a => HasTypeProxy (SigningKey a) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Class Associated Types
Methods proxyToAsType :: Proxy (SigningKey a) -> AsType (SigningKey a) Source # | |||||
HasTypeProxy a => HasTypeProxy (VerificationKey a) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Class Associated Types
Methods proxyToAsType :: Proxy (VerificationKey a) -> AsType (VerificationKey a) Source # | |||||
HasTypeProxy lang => HasTypeProxy (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
Methods proxyToAsType :: Proxy (PlutusScript lang) -> AsType (PlutusScript lang) Source # | |||||
HasTypeProxy lang => HasTypeProxy (Script lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
| |||||
HasTypeProxy era => HasTypeProxy (ScriptInEra era) Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
Methods proxyToAsType :: Proxy (ScriptInEra era) -> AsType (ScriptInEra era) Source # | |||||
HasTypeProxy era => HasTypeProxy (KeyWitness era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Associated Types
Methods proxyToAsType :: Proxy (KeyWitness era) -> AsType (KeyWitness era) Source # | |||||
HasTypeProxy era => HasTypeProxy (Tx era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Associated Types
| |||||
HasTypeProxy era => HasTypeProxy (TxBody era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Associated Types
| |||||
HasTypeProxy (Credential 'ColdCommitteeRole) Source # | |||||
Defined in Cardano.Api.Internal.Orphans.Serialisation Associated Types
Methods proxyToAsType :: Proxy (Credential 'ColdCommitteeRole) -> AsType (Credential 'ColdCommitteeRole) Source # | |||||
HasTypeProxy (Credential 'DRepRole) Source # | |||||
Defined in Cardano.Api.Internal.Orphans.Serialisation Associated Types
Methods proxyToAsType :: Proxy (Credential 'DRepRole) -> AsType (Credential 'DRepRole) Source # | |||||
HasTypeProxy (Credential 'HotCommitteeRole) Source # | |||||
Defined in Cardano.Api.Internal.Orphans.Serialisation Associated Types
Methods proxyToAsType :: Proxy (Credential 'HotCommitteeRole) -> AsType (Credential 'HotCommitteeRole) Source # | |||||
(HasTypeProxy era, HasTypeProxy lang) => HasTypeProxy (PlutusScriptInEra era lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
Methods proxyToAsType :: Proxy (PlutusScriptInEra era lang) -> AsType (PlutusScriptInEra era lang) Source # |
A family of singleton types used in this API to indicate which type to use where it would otherwise be ambiguous or merely unclear.
Values of this type are passed to deserialisation functions for example.
Instances
data AsType AddressAny Source # | |
Defined in Cardano.Api.Internal.Address | |
data AsType ByronAddr Source # | |
Defined in Cardano.Api.Internal.Address | |
data AsType ShelleyAddr Source # | |
Defined in Cardano.Api.Internal.Address | |
data AsType StakeAddress Source # | |
Defined in Cardano.Api.Internal.Address | |
data AsType BlockHeader Source # | |
Defined in Cardano.Api.Internal.Block | |
data AsType DRepMetadata Source # | |
Defined in Cardano.Api.Internal.DRepMetadata | |
data AsType AllegraEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core | |
data AsType AlonzoEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core | |
data AsType BabbageEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core | |
data AsType ByronEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core | |
data AsType ConwayEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core | |
data AsType MaryEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core | |
data AsType ShelleyEra Source # | |
Defined in Cardano.Api.Internal.Eras.Core | |
data AsType GovernancePoll Source # | |
Defined in Cardano.Api.Internal.Governance.Poll | |
data AsType GovernancePollAnswer Source # | |
Defined in Cardano.Api.Internal.Governance.Poll | |
data AsType ByronKey Source # | |
Defined in Cardano.Api.Internal.Keys.Byron | |
data AsType ByronKeyLegacy Source # | |
Defined in Cardano.Api.Internal.Keys.Byron | |
data AsType KesKey Source # | |
Defined in Cardano.Api.Internal.Keys.Praos | |
data AsType VrfKey Source # | |
Defined in Cardano.Api.Internal.Keys.Praos | |
data AsType CommitteeColdExtendedKey Source # | |
data AsType CommitteeColdKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType CommitteeHotExtendedKey Source # | |
data AsType CommitteeHotKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType DRepExtendedKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType DRepKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType GenesisDelegateExtendedKey Source # | |
data AsType GenesisDelegateKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType GenesisExtendedKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType GenesisKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType GenesisUTxOKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType PaymentExtendedKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType PaymentKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType StakeExtendedKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType StakeKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType StakePoolExtendedKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType StakePoolKey Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
data AsType OperationalCertificate Source # | |
data AsType OperationalCertificateIssueCounter Source # | |
data AsType PraosNonce Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters | |
data AsType UpdateProposal Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters | |
data AsType EraHistory Source # | |
Defined in Cardano.Api.Internal.Query | |
data AsType PlutusScriptV1 Source # | |
Defined in Cardano.Api.Internal.Script | |
data AsType PlutusScriptV2 Source # | |
Defined in Cardano.Api.Internal.Script | |
data AsType PlutusScriptV3 Source # | |
Defined in Cardano.Api.Internal.Script | |
data AsType ScriptHash Source # | |
Defined in Cardano.Api.Internal.Script | |
data AsType ScriptInAnyLang Source # | |
Defined in Cardano.Api.Internal.Script | |
data AsType SimpleScript' Source # | |
Defined in Cardano.Api.Internal.Script | |
data AsType HashableScriptData Source # | |
Defined in Cardano.Api.Internal.ScriptData | |
data AsType ScriptData Source # | |
Defined in Cardano.Api.Internal.ScriptData | |
data AsType TextEnvelope Source # | |
Defined in Cardano.Api.Internal.SerialiseTextEnvelope | |
data AsType ByronUpdateProposal Source # | |
Defined in Cardano.Api.Internal.SpecialByron | |
data AsType ByronVote Source # | |
Defined in Cardano.Api.Internal.SpecialByron | |
data AsType StakePoolMetadata Source # | |
Defined in Cardano.Api.Internal.StakePoolMetadata | |
data AsType TxId Source # | |
Defined in Cardano.Api.Internal.TxIn | |
data AsType TxMetadata Source # | |
Defined in Cardano.Api.Internal.TxMetadata | |
data AsType AssetName Source # | |
Defined in Cardano.Api.Internal.Value | |
data AsType PolicyId Source # | |
Defined in Cardano.Api.Internal.Value | |
data AsType GovActionId Source # | |
Defined in Cardano.Api.Internal.Orphans.Serialisation | |
data AsType Term Source # | |
data AsType (Address addrtype) Source # | |
Defined in Cardano.Api.Internal.Address | |
data AsType (AddressInEra era) Source # | |
Defined in Cardano.Api.Internal.Address | |
data AsType (Certificate era) Source # | |
Defined in Cardano.Api.Internal.Certificate | |
data AsType (Proposal era) Source # | |
data AsType (VotingProcedure era) Source # | |
data AsType (VotingProcedures era) Source # | |
data AsType (Hash a) Source # | |
Defined in Cardano.Api.Internal.Hash | |
data AsType (SigningKey a) Source # | |
Defined in Cardano.Api.Internal.Keys.Class | |
data AsType (VerificationKey a) Source # | |
Defined in Cardano.Api.Internal.Keys.Class | |
data AsType (PlutusScript lang) Source # | |
Defined in Cardano.Api.Internal.Script | |
data AsType (Script lang) Source # | |
Defined in Cardano.Api.Internal.Script | |
data AsType (ScriptInEra era) Source # | |
Defined in Cardano.Api.Internal.Script | |
data AsType (KeyWitness era) Source # | |
Defined in Cardano.Api.Internal.Tx.Sign | |
data AsType (Tx era) Source # | |
Defined in Cardano.Api.Internal.Tx.Sign | |
data AsType (TxBody era) Source # | |
Defined in Cardano.Api.Internal.Tx.Sign | |
data AsType (Credential 'ColdCommitteeRole) Source # | |
Defined in Cardano.Api.Internal.Orphans.Serialisation | |
data AsType (Credential 'DRepRole) Source # | |
Defined in Cardano.Api.Internal.Orphans.Serialisation | |
data AsType (Credential 'HotCommitteeRole) Source # | |
Defined in Cardano.Api.Internal.Orphans.Serialisation | |
data AsType (PlutusScriptInEra era lang) Source # | |
Defined in Cardano.Api.Internal.Script |
asType :: HasTypeProxy t => AsType t Source #
Provide type proxy from the already existing HasTypeProxy
instance
Cryptographic key interface
class (Eq (VerificationKey keyrole), Show (VerificationKey keyrole), SerialiseAsRawBytes (Hash keyrole), HasTextEnvelope (VerificationKey keyrole), HasTextEnvelope (SigningKey keyrole)) => Key keyrole where Source #
An interface for cryptographic keys used for signatures with a SigningKey
and a VerificationKey
key.
This interface does not provide actual signing or verifying functions since this API is concerned with the management of keys: generating and serialising.
Associated Types
data VerificationKey keyrole Source #
The type of cryptographic verification key, for each key role.
data SigningKey keyrole Source #
The type of cryptographic signing key, for each key role.
Methods
getVerificationKey :: SigningKey keyrole -> VerificationKey keyrole Source #
Get the corresponding verification key from a signing key.
deterministicSigningKey :: AsType keyrole -> Seed -> SigningKey keyrole Source #
Generate a SigningKey
deterministically, given a Seed
. The
required size of the seed is given by deterministicSigningKeySeedSize
.
deterministicSigningKeySeedSize :: AsType keyrole -> Word Source #
verificationKeyHash :: VerificationKey keyrole -> Hash keyrole Source #
Instances
Key ByronKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Associated Types
Methods getVerificationKey :: SigningKey ByronKey -> VerificationKey ByronKey Source # deterministicSigningKey :: AsType ByronKey -> Seed -> SigningKey ByronKey Source # deterministicSigningKeySeedSize :: AsType ByronKey -> Word Source # verificationKeyHash :: VerificationKey ByronKey -> Hash ByronKey Source # | |||||||||
Key ByronKeyLegacy Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Associated Types
Methods getVerificationKey :: SigningKey ByronKeyLegacy -> VerificationKey ByronKeyLegacy Source # deterministicSigningKey :: AsType ByronKeyLegacy -> Seed -> SigningKey ByronKeyLegacy Source # deterministicSigningKeySeedSize :: AsType ByronKeyLegacy -> Word Source # verificationKeyHash :: VerificationKey ByronKeyLegacy -> Hash ByronKeyLegacy Source # | |||||||||
Key KesKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Associated Types
| |||||||||
Key VrfKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Praos Associated Types
| |||||||||
Key CommitteeColdExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey CommitteeColdExtendedKey -> VerificationKey CommitteeColdExtendedKey Source # deterministicSigningKey :: AsType CommitteeColdExtendedKey -> Seed -> SigningKey CommitteeColdExtendedKey Source # deterministicSigningKeySeedSize :: AsType CommitteeColdExtendedKey -> Word Source # verificationKeyHash :: VerificationKey CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey Source # | |||||||||
Key CommitteeColdKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey CommitteeColdKey -> VerificationKey CommitteeColdKey Source # deterministicSigningKey :: AsType CommitteeColdKey -> Seed -> SigningKey CommitteeColdKey Source # deterministicSigningKeySeedSize :: AsType CommitteeColdKey -> Word Source # verificationKeyHash :: VerificationKey CommitteeColdKey -> Hash CommitteeColdKey Source # | |||||||||
Key CommitteeHotExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey CommitteeHotExtendedKey -> VerificationKey CommitteeHotExtendedKey Source # deterministicSigningKey :: AsType CommitteeHotExtendedKey -> Seed -> SigningKey CommitteeHotExtendedKey Source # deterministicSigningKeySeedSize :: AsType CommitteeHotExtendedKey -> Word Source # verificationKeyHash :: VerificationKey CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey Source # | |||||||||
Key CommitteeHotKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey CommitteeHotKey -> VerificationKey CommitteeHotKey Source # deterministicSigningKey :: AsType CommitteeHotKey -> Seed -> SigningKey CommitteeHotKey Source # deterministicSigningKeySeedSize :: AsType CommitteeHotKey -> Word Source # verificationKeyHash :: VerificationKey CommitteeHotKey -> Hash CommitteeHotKey Source # | |||||||||
Key DRepExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey DRepExtendedKey -> VerificationKey DRepExtendedKey Source # deterministicSigningKey :: AsType DRepExtendedKey -> Seed -> SigningKey DRepExtendedKey Source # deterministicSigningKeySeedSize :: AsType DRepExtendedKey -> Word Source # verificationKeyHash :: VerificationKey DRepExtendedKey -> Hash DRepExtendedKey Source # | |||||||||
Key DRepKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey DRepKey -> VerificationKey DRepKey Source # deterministicSigningKey :: AsType DRepKey -> Seed -> SigningKey DRepKey Source # deterministicSigningKeySeedSize :: AsType DRepKey -> Word Source # verificationKeyHash :: VerificationKey DRepKey -> Hash DRepKey Source # | |||||||||
Key GenesisDelegateExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey GenesisDelegateExtendedKey -> VerificationKey GenesisDelegateExtendedKey Source # deterministicSigningKey :: AsType GenesisDelegateExtendedKey -> Seed -> SigningKey GenesisDelegateExtendedKey Source # deterministicSigningKeySeedSize :: AsType GenesisDelegateExtendedKey -> Word Source # verificationKeyHash :: VerificationKey GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey Source # | |||||||||
Key GenesisDelegateKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey GenesisDelegateKey -> VerificationKey GenesisDelegateKey Source # deterministicSigningKey :: AsType GenesisDelegateKey -> Seed -> SigningKey GenesisDelegateKey Source # deterministicSigningKeySeedSize :: AsType GenesisDelegateKey -> Word Source # verificationKeyHash :: VerificationKey GenesisDelegateKey -> Hash GenesisDelegateKey Source # | |||||||||
Key GenesisExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey GenesisExtendedKey -> VerificationKey GenesisExtendedKey Source # deterministicSigningKey :: AsType GenesisExtendedKey -> Seed -> SigningKey GenesisExtendedKey Source # deterministicSigningKeySeedSize :: AsType GenesisExtendedKey -> Word Source # verificationKeyHash :: VerificationKey GenesisExtendedKey -> Hash GenesisExtendedKey Source # | |||||||||
Key GenesisKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey GenesisKey -> VerificationKey GenesisKey Source # deterministicSigningKey :: AsType GenesisKey -> Seed -> SigningKey GenesisKey Source # deterministicSigningKeySeedSize :: AsType GenesisKey -> Word Source # verificationKeyHash :: VerificationKey GenesisKey -> Hash GenesisKey Source # | |||||||||
Key GenesisUTxOKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey GenesisUTxOKey -> VerificationKey GenesisUTxOKey Source # deterministicSigningKey :: AsType GenesisUTxOKey -> Seed -> SigningKey GenesisUTxOKey Source # deterministicSigningKeySeedSize :: AsType GenesisUTxOKey -> Word Source # verificationKeyHash :: VerificationKey GenesisUTxOKey -> Hash GenesisUTxOKey Source # | |||||||||
Key PaymentExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey PaymentExtendedKey -> VerificationKey PaymentExtendedKey Source # deterministicSigningKey :: AsType PaymentExtendedKey -> Seed -> SigningKey PaymentExtendedKey Source # deterministicSigningKeySeedSize :: AsType PaymentExtendedKey -> Word Source # verificationKeyHash :: VerificationKey PaymentExtendedKey -> Hash PaymentExtendedKey Source # | |||||||||
Key PaymentKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey PaymentKey -> VerificationKey PaymentKey Source # deterministicSigningKey :: AsType PaymentKey -> Seed -> SigningKey PaymentKey Source # deterministicSigningKeySeedSize :: AsType PaymentKey -> Word Source # verificationKeyHash :: VerificationKey PaymentKey -> Hash PaymentKey Source # | |||||||||
Key StakeExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey StakeExtendedKey -> VerificationKey StakeExtendedKey Source # deterministicSigningKey :: AsType StakeExtendedKey -> Seed -> SigningKey StakeExtendedKey Source # deterministicSigningKeySeedSize :: AsType StakeExtendedKey -> Word Source # verificationKeyHash :: VerificationKey StakeExtendedKey -> Hash StakeExtendedKey Source # | |||||||||
Key StakeKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey StakeKey -> VerificationKey StakeKey Source # deterministicSigningKey :: AsType StakeKey -> Seed -> SigningKey StakeKey Source # deterministicSigningKeySeedSize :: AsType StakeKey -> Word Source # verificationKeyHash :: VerificationKey StakeKey -> Hash StakeKey Source # | |||||||||
Key StakePoolExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey StakePoolExtendedKey -> VerificationKey StakePoolExtendedKey Source # deterministicSigningKey :: AsType StakePoolExtendedKey -> Seed -> SigningKey StakePoolExtendedKey Source # deterministicSigningKeySeedSize :: AsType StakePoolExtendedKey -> Word Source # verificationKeyHash :: VerificationKey StakePoolExtendedKey -> Hash StakePoolExtendedKey Source # | |||||||||
Key StakePoolKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey StakePoolKey -> VerificationKey StakePoolKey Source # deterministicSigningKey :: AsType StakePoolKey -> Seed -> SigningKey StakePoolKey Source # deterministicSigningKeySeedSize :: AsType StakePoolKey -> Word Source # verificationKeyHash :: VerificationKey StakePoolKey -> Hash StakePoolKey Source # |
data family SigningKey keyrole Source #
The type of cryptographic signing key, for each key role.
Instances
IsString (SigningKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods fromString :: String -> SigningKey ByronKey Source # | |||||
IsString (SigningKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods | |||||
IsString (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods fromString :: String -> SigningKey KesKey Source # | |||||
IsString (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods fromString :: String -> SigningKey VrfKey Source # | |||||
IsString (SigningKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey CommitteeColdExtendedKey Source # | |||||
IsString (SigningKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey CommitteeColdKey Source # | |||||
IsString (SigningKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey CommitteeHotExtendedKey Source # | |||||
IsString (SigningKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (SigningKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey DRepKey Source # | |||||
IsString (SigningKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey GenesisDelegateExtendedKey Source # | |||||
IsString (SigningKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey GenesisDelegateKey Source # | |||||
IsString (SigningKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey GenesisExtendedKey Source # | |||||
IsString (SigningKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey GenesisKey Source # | |||||
IsString (SigningKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (SigningKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey PaymentExtendedKey Source # | |||||
IsString (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey PaymentKey Source # | |||||
IsString (SigningKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey StakeExtendedKey Source # | |||||
IsString (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey StakeKey Source # | |||||
IsString (SigningKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey StakePoolExtendedKey Source # | |||||
IsString (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
Show (SigningKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
Show (SigningKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods showsPrec :: Int -> SigningKey ByronKeyLegacy -> ShowS Source # show :: SigningKey ByronKeyLegacy -> String Source # showList :: [SigningKey ByronKeyLegacy] -> ShowS Source # | |||||
Show (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
Show (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
Show (SigningKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey CommitteeColdExtendedKey -> ShowS Source # show :: SigningKey CommitteeColdExtendedKey -> String Source # showList :: [SigningKey CommitteeColdExtendedKey] -> ShowS Source # | |||||
Show (SigningKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey CommitteeColdKey -> ShowS Source # show :: SigningKey CommitteeColdKey -> String Source # showList :: [SigningKey CommitteeColdKey] -> ShowS Source # | |||||
Show (SigningKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey CommitteeHotExtendedKey -> ShowS Source # show :: SigningKey CommitteeHotExtendedKey -> String Source # showList :: [SigningKey CommitteeHotExtendedKey] -> ShowS Source # | |||||
Show (SigningKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey CommitteeHotKey -> ShowS Source # show :: SigningKey CommitteeHotKey -> String Source # showList :: [SigningKey CommitteeHotKey] -> ShowS Source # | |||||
Show (SigningKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey DRepExtendedKey -> ShowS Source # show :: SigningKey DRepExtendedKey -> String Source # showList :: [SigningKey DRepExtendedKey] -> ShowS Source # | |||||
Show (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (SigningKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey GenesisDelegateExtendedKey -> ShowS Source # show :: SigningKey GenesisDelegateExtendedKey -> String Source # showList :: [SigningKey GenesisDelegateExtendedKey] -> ShowS Source # | |||||
Show (SigningKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey GenesisDelegateKey -> ShowS Source # show :: SigningKey GenesisDelegateKey -> String Source # showList :: [SigningKey GenesisDelegateKey] -> ShowS Source # | |||||
Show (SigningKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey GenesisExtendedKey -> ShowS Source # show :: SigningKey GenesisExtendedKey -> String Source # showList :: [SigningKey GenesisExtendedKey] -> ShowS Source # | |||||
Show (SigningKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey GenesisKey -> ShowS Source # show :: SigningKey GenesisKey -> String Source # showList :: [SigningKey GenesisKey] -> ShowS Source # | |||||
Show (SigningKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey GenesisUTxOKey -> ShowS Source # show :: SigningKey GenesisUTxOKey -> String Source # showList :: [SigningKey GenesisUTxOKey] -> ShowS Source # | |||||
Show (SigningKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey PaymentExtendedKey -> ShowS Source # show :: SigningKey PaymentExtendedKey -> String Source # showList :: [SigningKey PaymentExtendedKey] -> ShowS Source # | |||||
Show (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey PaymentKey -> ShowS Source # show :: SigningKey PaymentKey -> String Source # showList :: [SigningKey PaymentKey] -> ShowS Source # | |||||
Show (SigningKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey StakeExtendedKey -> ShowS Source # show :: SigningKey StakeExtendedKey -> String Source # showList :: [SigningKey StakeExtendedKey] -> ShowS Source # | |||||
Show (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (SigningKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey StakePoolExtendedKey -> ShowS Source # show :: SigningKey StakePoolExtendedKey -> String Source # showList :: [SigningKey StakePoolExtendedKey] -> ShowS Source # | |||||
Show (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey StakePoolKey -> ShowS Source # show :: SigningKey StakePoolKey -> String Source # showList :: [SigningKey StakePoolKey] -> ShowS Source # | |||||
HasTypeProxy a => HasTypeProxy (SigningKey a) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Class Associated Types
Methods proxyToAsType :: Proxy (SigningKey a) -> AsType (SigningKey a) Source # | |||||
SerialiseAsCBOR (SigningKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: SigningKey ByronKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey ByronKey) -> ByteString -> Either DecoderError (SigningKey ByronKey) Source # | |||||
SerialiseAsCBOR (SigningKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: SigningKey ByronKeyLegacy -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey ByronKeyLegacy) -> ByteString -> Either DecoderError (SigningKey ByronKeyLegacy) Source # | |||||
SerialiseAsCBOR (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: SigningKey KesKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey KesKey) -> ByteString -> Either DecoderError (SigningKey KesKey) Source # | |||||
SerialiseAsCBOR (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: SigningKey VrfKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey VrfKey) -> ByteString -> Either DecoderError (SigningKey VrfKey) Source # | |||||
SerialiseAsCBOR (SigningKey CommitteeColdExtendedKey) Source # | |||||
SerialiseAsCBOR (SigningKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey CommitteeHotExtendedKey) Source # | |||||
SerialiseAsCBOR (SigningKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey DRepKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey DRepKey) -> ByteString -> Either DecoderError (SigningKey DRepKey) Source # | |||||
SerialiseAsCBOR (SigningKey GenesisDelegateExtendedKey) Source # | |||||
SerialiseAsCBOR (SigningKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey GenesisKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey GenesisKey) -> ByteString -> Either DecoderError (SigningKey GenesisKey) Source # | |||||
SerialiseAsCBOR (SigningKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey GenesisUTxOKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey GenesisUTxOKey) -> ByteString -> Either DecoderError (SigningKey GenesisUTxOKey) Source # | |||||
SerialiseAsCBOR (SigningKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey PaymentKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey PaymentKey) -> ByteString -> Either DecoderError (SigningKey PaymentKey) Source # | |||||
SerialiseAsCBOR (SigningKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey StakeKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey StakeKey) -> ByteString -> Either DecoderError (SigningKey StakeKey) Source # | |||||
SerialiseAsCBOR (SigningKey StakePoolExtendedKey) Source # | |||||
SerialiseAsCBOR (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey StakePoolKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey StakePoolKey) -> ByteString -> Either DecoderError (SigningKey StakePoolKey) Source # | |||||
SerialiseAsBech32 (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods bech32PrefixFor :: SigningKey KesKey -> Text bech32PrefixesPermitted :: AsType (SigningKey KesKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods bech32PrefixFor :: SigningKey VrfKey -> Text bech32PrefixesPermitted :: AsType (SigningKey VrfKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey CommitteeColdExtendedKey -> Text bech32PrefixesPermitted :: AsType (SigningKey CommitteeColdExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey CommitteeColdKey -> Text bech32PrefixesPermitted :: AsType (SigningKey CommitteeColdKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey CommitteeHotExtendedKey -> Text bech32PrefixesPermitted :: AsType (SigningKey CommitteeHotExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey CommitteeHotKey -> Text bech32PrefixesPermitted :: AsType (SigningKey CommitteeHotKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey DRepExtendedKey -> Text bech32PrefixesPermitted :: AsType (SigningKey DRepExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey DRepKey -> Text bech32PrefixesPermitted :: AsType (SigningKey DRepKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey PaymentExtendedKey -> Text bech32PrefixesPermitted :: AsType (SigningKey PaymentExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey PaymentKey -> Text bech32PrefixesPermitted :: AsType (SigningKey PaymentKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey StakeExtendedKey -> Text bech32PrefixesPermitted :: AsType (SigningKey StakeExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey StakeKey -> Text bech32PrefixesPermitted :: AsType (SigningKey StakeKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey StakePoolExtendedKey -> Text bech32PrefixesPermitted :: AsType (SigningKey StakePoolExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey StakePoolKey -> Text bech32PrefixesPermitted :: AsType (SigningKey StakePoolKey) -> [Text] | |||||
SerialiseAsRawBytes (SigningKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
SerialiseAsRawBytes (SigningKey ByronKeyLegacy) Source # | |||||
SerialiseAsRawBytes (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToRawBytes :: SigningKey KesKey -> ByteString Source # deserialiseFromRawBytes :: AsType (SigningKey KesKey) -> ByteString -> Either SerialiseAsRawBytesError (SigningKey KesKey) Source # | |||||
SerialiseAsRawBytes (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToRawBytes :: SigningKey VrfKey -> ByteString Source # deserialiseFromRawBytes :: AsType (SigningKey VrfKey) -> ByteString -> Either SerialiseAsRawBytesError (SigningKey VrfKey) Source # | |||||
SerialiseAsRawBytes (SigningKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (SigningKey CommitteeColdKey) Source # | |||||
SerialiseAsRawBytes (SigningKey CommitteeHotExtendedKey) Source # | |||||
SerialiseAsRawBytes (SigningKey CommitteeHotKey) Source # | |||||
SerialiseAsRawBytes (SigningKey DRepExtendedKey) Source # | |||||
SerialiseAsRawBytes (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToRawBytes :: SigningKey DRepKey -> ByteString Source # deserialiseFromRawBytes :: AsType (SigningKey DRepKey) -> ByteString -> Either SerialiseAsRawBytesError (SigningKey DRepKey) Source # | |||||
SerialiseAsRawBytes (SigningKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (SigningKey GenesisDelegateKey) Source # | |||||
SerialiseAsRawBytes (SigningKey GenesisExtendedKey) Source # | |||||
SerialiseAsRawBytes (SigningKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (SigningKey GenesisUTxOKey) Source # | |||||
SerialiseAsRawBytes (SigningKey PaymentExtendedKey) Source # | |||||
SerialiseAsRawBytes (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (SigningKey StakeExtendedKey) Source # | |||||
SerialiseAsRawBytes (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (SigningKey StakePoolExtendedKey) Source # | |||||
SerialiseAsRawBytes (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (SigningKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
HasTextEnvelope (SigningKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
HasTextEnvelope (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods textEnvelopeType :: AsType (SigningKey KesKey) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: SigningKey KesKey -> TextEnvelopeDescr Source # | |||||
HasTextEnvelope (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods textEnvelopeType :: AsType (SigningKey VrfKey) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: SigningKey VrfKey -> TextEnvelopeDescr Source # | |||||
HasTextEnvelope (SigningKey CommitteeColdExtendedKey) Source # | |||||
HasTextEnvelope (SigningKey CommitteeColdKey) Source # | |||||
HasTextEnvelope (SigningKey CommitteeHotExtendedKey) Source # | |||||
HasTextEnvelope (SigningKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (SigningKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods textEnvelopeType :: AsType (SigningKey DRepKey) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: SigningKey DRepKey -> TextEnvelopeDescr Source # | |||||
HasTextEnvelope (SigningKey GenesisDelegateExtendedKey) Source # | |||||
HasTextEnvelope (SigningKey GenesisDelegateKey) Source # | |||||
HasTextEnvelope (SigningKey GenesisExtendedKey) Source # | |||||
HasTextEnvelope (SigningKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (SigningKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (SigningKey PaymentExtendedKey) Source # | |||||
HasTextEnvelope (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (SigningKey StakeExtendedKey) Source # | |||||
HasTextEnvelope (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (SigningKey StakePoolExtendedKey) Source # | |||||
HasTextEnvelope (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (SigningKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
FromCBOR (SigningKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods fromCBOR :: Decoder s (SigningKey ByronKeyLegacy) Source # label :: Proxy (SigningKey ByronKeyLegacy) -> Text Source # | |||||
FromCBOR (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
FromCBOR (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
FromCBOR (SigningKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey CommitteeColdExtendedKey) Source # label :: Proxy (SigningKey CommitteeColdExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey CommitteeColdKey) Source # label :: Proxy (SigningKey CommitteeColdKey) -> Text Source # | |||||
FromCBOR (SigningKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey CommitteeHotExtendedKey) Source # label :: Proxy (SigningKey CommitteeHotExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey CommitteeHotKey) Source # label :: Proxy (SigningKey CommitteeHotKey) -> Text Source # | |||||
FromCBOR (SigningKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey DRepExtendedKey) Source # label :: Proxy (SigningKey DRepExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (SigningKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey GenesisDelegateExtendedKey) Source # label :: Proxy (SigningKey GenesisDelegateExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey GenesisDelegateKey) Source # label :: Proxy (SigningKey GenesisDelegateKey) -> Text Source # | |||||
FromCBOR (SigningKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey GenesisExtendedKey) Source # label :: Proxy (SigningKey GenesisExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey GenesisKey) Source # label :: Proxy (SigningKey GenesisKey) -> Text Source # | |||||
FromCBOR (SigningKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey GenesisUTxOKey) Source # label :: Proxy (SigningKey GenesisUTxOKey) -> Text Source # | |||||
FromCBOR (SigningKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey PaymentExtendedKey) Source # label :: Proxy (SigningKey PaymentExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey PaymentKey) Source # label :: Proxy (SigningKey PaymentKey) -> Text Source # | |||||
FromCBOR (SigningKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey StakeExtendedKey) Source # label :: Proxy (SigningKey StakeExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (SigningKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey StakePoolExtendedKey) Source # label :: Proxy (SigningKey StakePoolExtendedKey) -> Text Source # | |||||
FromCBOR (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey StakePoolKey) Source # label :: Proxy (SigningKey StakePoolKey) -> Text Source # | |||||
ToCBOR (SigningKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
ToCBOR (SigningKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods toCBOR :: SigningKey ByronKeyLegacy -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey ByronKeyLegacy) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey ByronKeyLegacy] -> Size Source # | |||||
ToCBOR (SigningKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
ToCBOR (SigningKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
ToCBOR (SigningKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey CommitteeColdExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeColdExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeColdExtendedKey] -> Size Source # | |||||
ToCBOR (SigningKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey CommitteeColdKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeColdKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeColdKey] -> Size Source # | |||||
ToCBOR (SigningKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey CommitteeHotExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeHotExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeHotExtendedKey] -> Size Source # | |||||
ToCBOR (SigningKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey CommitteeHotKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeHotKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeHotKey] -> Size Source # | |||||
ToCBOR (SigningKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey DRepExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey DRepExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey DRepExtendedKey] -> Size Source # | |||||
ToCBOR (SigningKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (SigningKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey GenesisDelegateExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisDelegateExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisDelegateExtendedKey] -> Size Source # | |||||
ToCBOR (SigningKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey GenesisDelegateKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisDelegateKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisDelegateKey] -> Size Source # | |||||
ToCBOR (SigningKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey GenesisExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisExtendedKey] -> Size Source # | |||||
ToCBOR (SigningKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey GenesisKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisKey] -> Size Source # | |||||
ToCBOR (SigningKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey GenesisUTxOKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisUTxOKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisUTxOKey] -> Size Source # | |||||
ToCBOR (SigningKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey PaymentExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey PaymentExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey PaymentExtendedKey] -> Size Source # | |||||
ToCBOR (SigningKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey PaymentKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey PaymentKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey PaymentKey] -> Size Source # | |||||
ToCBOR (SigningKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey StakeExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey StakeExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey StakeExtendedKey] -> Size Source # | |||||
ToCBOR (SigningKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (SigningKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey StakePoolExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey StakePoolExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey StakePoolExtendedKey] -> Size Source # | |||||
ToCBOR (SigningKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey StakePoolKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey StakePoolKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey StakePoolKey] -> Size Source # | |||||
newtype SigningKey ByronKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
newtype SigningKey ByronKeyLegacy Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
newtype SigningKey KesKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
newtype SigningKey VrfKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
newtype SigningKey CommitteeColdExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey CommitteeColdKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey CommitteeHotExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey CommitteeHotKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey DRepExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey DRepKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey GenesisDelegateExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey GenesisDelegateKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey GenesisExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey GenesisKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey GenesisUTxOKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey PaymentExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey PaymentKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey StakeExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey StakeKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey StakePoolExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype SigningKey StakePoolKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
data AsType (SigningKey a) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Class |
data family VerificationKey keyrole Source #
The type of cryptographic verification key, for each key role.
Instances
IsString (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods | |||||
IsString (VerificationKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods fromString :: String -> VerificationKey ByronKeyLegacy Source # | |||||
IsString (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods fromString :: String -> VerificationKey KesKey Source # | |||||
IsString (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods fromString :: String -> VerificationKey VrfKey Source # | |||||
IsString (VerificationKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey CommitteeColdExtendedKey Source # | |||||
IsString (VerificationKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey CommitteeColdKey Source # | |||||
IsString (VerificationKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey CommitteeHotExtendedKey Source # | |||||
IsString (VerificationKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey CommitteeHotKey Source # | |||||
IsString (VerificationKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey DRepExtendedKey Source # | |||||
IsString (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey GenesisDelegateExtendedKey Source # | |||||
IsString (VerificationKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey GenesisDelegateKey Source # | |||||
IsString (VerificationKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey GenesisExtendedKey Source # | |||||
IsString (VerificationKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (VerificationKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey GenesisUTxOKey Source # | |||||
IsString (VerificationKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey PaymentExtendedKey Source # | |||||
IsString (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (VerificationKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey StakeExtendedKey Source # | |||||
IsString (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (VerificationKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey StakePoolExtendedKey Source # | |||||
IsString (VerificationKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey StakePoolKey Source # | |||||
Show (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
Show (VerificationKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods showsPrec :: Int -> VerificationKey ByronKeyLegacy -> ShowS Source # show :: VerificationKey ByronKeyLegacy -> String Source # showList :: [VerificationKey ByronKeyLegacy] -> ShowS Source # | |||||
Show (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
Show (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
Show (VerificationKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey CommitteeColdExtendedKey -> ShowS Source # show :: VerificationKey CommitteeColdExtendedKey -> String Source # showList :: [VerificationKey CommitteeColdExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey CommitteeColdKey -> ShowS Source # show :: VerificationKey CommitteeColdKey -> String Source # showList :: [VerificationKey CommitteeColdKey] -> ShowS Source # | |||||
Show (VerificationKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey CommitteeHotExtendedKey -> ShowS Source # show :: VerificationKey CommitteeHotExtendedKey -> String Source # showList :: [VerificationKey CommitteeHotExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey CommitteeHotKey -> ShowS Source # show :: VerificationKey CommitteeHotKey -> String Source # showList :: [VerificationKey CommitteeHotKey] -> ShowS Source # | |||||
Show (VerificationKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey DRepExtendedKey -> ShowS Source # show :: VerificationKey DRepExtendedKey -> String Source # showList :: [VerificationKey DRepExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey GenesisDelegateExtendedKey -> ShowS Source # show :: VerificationKey GenesisDelegateExtendedKey -> String Source # showList :: [VerificationKey GenesisDelegateExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey GenesisDelegateKey -> ShowS Source # show :: VerificationKey GenesisDelegateKey -> String Source # showList :: [VerificationKey GenesisDelegateKey] -> ShowS Source # | |||||
Show (VerificationKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey GenesisExtendedKey -> ShowS Source # show :: VerificationKey GenesisExtendedKey -> String Source # showList :: [VerificationKey GenesisExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey GenesisKey -> ShowS Source # show :: VerificationKey GenesisKey -> String Source # showList :: [VerificationKey GenesisKey] -> ShowS Source # | |||||
Show (VerificationKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey GenesisUTxOKey -> ShowS Source # show :: VerificationKey GenesisUTxOKey -> String Source # showList :: [VerificationKey GenesisUTxOKey] -> ShowS Source # | |||||
Show (VerificationKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey PaymentExtendedKey -> ShowS Source # show :: VerificationKey PaymentExtendedKey -> String Source # showList :: [VerificationKey PaymentExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey PaymentKey -> ShowS Source # show :: VerificationKey PaymentKey -> String Source # showList :: [VerificationKey PaymentKey] -> ShowS Source # | |||||
Show (VerificationKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey StakeExtendedKey -> ShowS Source # show :: VerificationKey StakeExtendedKey -> String Source # showList :: [VerificationKey StakeExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (VerificationKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey StakePoolExtendedKey -> ShowS Source # show :: VerificationKey StakePoolExtendedKey -> String Source # showList :: [VerificationKey StakePoolExtendedKey] -> ShowS Source # | |||||
Show (VerificationKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey StakePoolKey -> ShowS Source # show :: VerificationKey StakePoolKey -> String Source # showList :: [VerificationKey StakePoolKey] -> ShowS Source # | |||||
HasTypeProxy a => HasTypeProxy (VerificationKey a) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Class Associated Types
Methods proxyToAsType :: Proxy (VerificationKey a) -> AsType (VerificationKey a) Source # | |||||
SerialiseAsCBOR (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: VerificationKey ByronKey -> ByteString Source # deserialiseFromCBOR :: AsType (VerificationKey ByronKey) -> ByteString -> Either DecoderError (VerificationKey ByronKey) Source # | |||||
SerialiseAsCBOR (VerificationKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
SerialiseAsCBOR (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: VerificationKey KesKey -> ByteString Source # deserialiseFromCBOR :: AsType (VerificationKey KesKey) -> ByteString -> Either DecoderError (VerificationKey KesKey) Source # | |||||
SerialiseAsCBOR (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: VerificationKey VrfKey -> ByteString Source # deserialiseFromCBOR :: AsType (VerificationKey VrfKey) -> ByteString -> Either DecoderError (VerificationKey VrfKey) Source # | |||||
SerialiseAsCBOR (VerificationKey CommitteeColdExtendedKey) Source # | |||||
SerialiseAsCBOR (VerificationKey CommitteeColdKey) Source # | |||||
SerialiseAsCBOR (VerificationKey CommitteeHotExtendedKey) Source # | |||||
SerialiseAsCBOR (VerificationKey CommitteeHotKey) Source # | |||||
SerialiseAsCBOR (VerificationKey DRepExtendedKey) Source # | |||||
SerialiseAsCBOR (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: VerificationKey DRepKey -> ByteString Source # deserialiseFromCBOR :: AsType (VerificationKey DRepKey) -> ByteString -> Either DecoderError (VerificationKey DRepKey) Source # | |||||
SerialiseAsCBOR (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (VerificationKey GenesisDelegateKey) Source # | |||||
SerialiseAsCBOR (VerificationKey GenesisExtendedKey) Source # | |||||
SerialiseAsCBOR (VerificationKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (VerificationKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (VerificationKey PaymentExtendedKey) Source # | |||||
SerialiseAsCBOR (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (VerificationKey StakeExtendedKey) Source # | |||||
SerialiseAsCBOR (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: VerificationKey StakeKey -> ByteString Source # deserialiseFromCBOR :: AsType (VerificationKey StakeKey) -> ByteString -> Either DecoderError (VerificationKey StakeKey) Source # | |||||
SerialiseAsCBOR (VerificationKey StakePoolExtendedKey) Source # | |||||
SerialiseAsCBOR (VerificationKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsBech32 (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods bech32PrefixFor :: VerificationKey KesKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey KesKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods bech32PrefixFor :: VerificationKey VrfKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey VrfKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsBech32 (VerificationKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey CommitteeColdKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey CommitteeColdKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsBech32 (VerificationKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey CommitteeHotKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey CommitteeHotKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey DRepExtendedKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey DRepExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey DRepKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey DRepKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey PaymentExtendedKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey PaymentExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey PaymentKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey PaymentKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey StakeExtendedKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey StakeExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey StakeKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey StakeKey) -> [Text] | |||||
SerialiseAsBech32 (VerificationKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsBech32 (VerificationKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey StakePoolKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey StakePoolKey) -> [Text] | |||||
SerialiseAsRawBytes (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
SerialiseAsRawBytes (VerificationKey ByronKeyLegacy) Source # | |||||
SerialiseAsRawBytes (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
SerialiseAsRawBytes (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
SerialiseAsRawBytes (VerificationKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (VerificationKey CommitteeColdKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (VerificationKey CommitteeHotKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey DRepExtendedKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (VerificationKey GenesisDelegateKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey GenesisExtendedKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey GenesisKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey GenesisUTxOKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey PaymentExtendedKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey PaymentKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey StakeExtendedKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey StakeKey) Source # | |||||
SerialiseAsRawBytes (VerificationKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (VerificationKey StakePoolKey) Source # | |||||
HasTextEnvelope (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
HasTextEnvelope (VerificationKey ByronKeyLegacy) Source # | |||||
HasTextEnvelope (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
HasTextEnvelope (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
HasTextEnvelope (VerificationKey CommitteeColdExtendedKey) Source # | |||||
HasTextEnvelope (VerificationKey CommitteeColdKey) Source # | |||||
HasTextEnvelope (VerificationKey CommitteeHotExtendedKey) Source # | |||||
HasTextEnvelope (VerificationKey CommitteeHotKey) Source # | |||||
HasTextEnvelope (VerificationKey DRepExtendedKey) Source # | |||||
HasTextEnvelope (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
HasTextEnvelope (VerificationKey GenesisDelegateKey) Source # | |||||
HasTextEnvelope (VerificationKey GenesisExtendedKey) Source # | |||||
HasTextEnvelope (VerificationKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (VerificationKey GenesisUTxOKey) Source # | |||||
HasTextEnvelope (VerificationKey PaymentExtendedKey) Source # | |||||
HasTextEnvelope (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (VerificationKey StakeExtendedKey) Source # | |||||
HasTextEnvelope (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
HasTextEnvelope (VerificationKey StakePoolExtendedKey) Source # | |||||
HasTextEnvelope (VerificationKey StakePoolKey) Source # | |||||
FromCBOR (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
FromCBOR (VerificationKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods fromCBOR :: Decoder s (VerificationKey ByronKeyLegacy) Source # label :: Proxy (VerificationKey ByronKeyLegacy) -> Text Source # | |||||
FromCBOR (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
FromCBOR (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
FromCBOR (VerificationKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey CommitteeColdExtendedKey) Source # label :: Proxy (VerificationKey CommitteeColdExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey CommitteeColdKey) Source # label :: Proxy (VerificationKey CommitteeColdKey) -> Text Source # | |||||
FromCBOR (VerificationKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey CommitteeHotExtendedKey) Source # label :: Proxy (VerificationKey CommitteeHotExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey CommitteeHotKey) Source # label :: Proxy (VerificationKey CommitteeHotKey) -> Text Source # | |||||
FromCBOR (VerificationKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey DRepExtendedKey) Source # label :: Proxy (VerificationKey DRepExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey GenesisDelegateExtendedKey) Source # label :: Proxy (VerificationKey GenesisDelegateExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey GenesisDelegateKey) Source # label :: Proxy (VerificationKey GenesisDelegateKey) -> Text Source # | |||||
FromCBOR (VerificationKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey GenesisExtendedKey) Source # label :: Proxy (VerificationKey GenesisExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey GenesisKey) Source # label :: Proxy (VerificationKey GenesisKey) -> Text Source # | |||||
FromCBOR (VerificationKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey GenesisUTxOKey) Source # label :: Proxy (VerificationKey GenesisUTxOKey) -> Text Source # | |||||
FromCBOR (VerificationKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey PaymentExtendedKey) Source # label :: Proxy (VerificationKey PaymentExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey PaymentKey) Source # label :: Proxy (VerificationKey PaymentKey) -> Text Source # | |||||
FromCBOR (VerificationKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey StakeExtendedKey) Source # label :: Proxy (VerificationKey StakeExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (VerificationKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey StakePoolExtendedKey) Source # label :: Proxy (VerificationKey StakePoolExtendedKey) -> Text Source # | |||||
FromCBOR (VerificationKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey StakePoolKey) Source # label :: Proxy (VerificationKey StakePoolKey) -> Text Source # | |||||
ToCBOR (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
ToCBOR (VerificationKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods toCBOR :: VerificationKey ByronKeyLegacy -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey ByronKeyLegacy) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey ByronKeyLegacy] -> Size Source # | |||||
ToCBOR (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
ToCBOR (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
ToCBOR (VerificationKey CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey CommitteeColdExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey CommitteeColdExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey CommitteeColdExtendedKey] -> Size Source # | |||||
ToCBOR (VerificationKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey CommitteeColdKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey CommitteeColdKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey CommitteeColdKey] -> Size Source # | |||||
ToCBOR (VerificationKey CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey CommitteeHotExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey CommitteeHotExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey CommitteeHotExtendedKey] -> Size Source # | |||||
ToCBOR (VerificationKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey CommitteeHotKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey CommitteeHotKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey CommitteeHotKey] -> Size Source # | |||||
ToCBOR (VerificationKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey DRepExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey DRepExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey DRepExtendedKey] -> Size Source # | |||||
ToCBOR (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey GenesisDelegateExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisDelegateExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisDelegateExtendedKey] -> Size Source # | |||||
ToCBOR (VerificationKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey GenesisDelegateKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisDelegateKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisDelegateKey] -> Size Source # | |||||
ToCBOR (VerificationKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey GenesisExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisExtendedKey] -> Size Source # | |||||
ToCBOR (VerificationKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey GenesisKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisKey] -> Size Source # | |||||
ToCBOR (VerificationKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey GenesisUTxOKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisUTxOKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisUTxOKey] -> Size Source # | |||||
ToCBOR (VerificationKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey PaymentExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey PaymentExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey PaymentExtendedKey] -> Size Source # | |||||
ToCBOR (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey PaymentKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey PaymentKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey PaymentKey] -> Size Source # | |||||
ToCBOR (VerificationKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey StakeExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey StakeExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey StakeExtendedKey] -> Size Source # | |||||
ToCBOR (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (VerificationKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey StakePoolExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey StakePoolExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey StakePoolExtendedKey] -> Size Source # | |||||
ToCBOR (VerificationKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey StakePoolKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey StakePoolKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey StakePoolKey] -> Size Source # | |||||
Eq (VerificationKey ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods (==) :: VerificationKey ByronKey -> VerificationKey ByronKey -> Bool Source # (/=) :: VerificationKey ByronKey -> VerificationKey ByronKey -> Bool Source # | |||||
Eq (VerificationKey ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods (==) :: VerificationKey ByronKeyLegacy -> VerificationKey ByronKeyLegacy -> Bool Source # (/=) :: VerificationKey ByronKeyLegacy -> VerificationKey ByronKeyLegacy -> Bool Source # | |||||
Eq (VerificationKey KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods (==) :: VerificationKey KesKey -> VerificationKey KesKey -> Bool Source # (/=) :: VerificationKey KesKey -> VerificationKey KesKey -> Bool Source # | |||||
Eq (VerificationKey VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods (==) :: VerificationKey VrfKey -> VerificationKey VrfKey -> Bool Source # (/=) :: VerificationKey VrfKey -> VerificationKey VrfKey -> Bool Source # | |||||
Eq (VerificationKey CommitteeColdExtendedKey) Source # | |||||
Eq (VerificationKey CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey CommitteeColdKey -> VerificationKey CommitteeColdKey -> Bool Source # (/=) :: VerificationKey CommitteeColdKey -> VerificationKey CommitteeColdKey -> Bool Source # | |||||
Eq (VerificationKey CommitteeHotExtendedKey) Source # | |||||
Eq (VerificationKey CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey CommitteeHotKey -> VerificationKey CommitteeHotKey -> Bool Source # (/=) :: VerificationKey CommitteeHotKey -> VerificationKey CommitteeHotKey -> Bool Source # | |||||
Eq (VerificationKey DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey DRepExtendedKey -> VerificationKey DRepExtendedKey -> Bool Source # (/=) :: VerificationKey DRepExtendedKey -> VerificationKey DRepExtendedKey -> Bool Source # | |||||
Eq (VerificationKey DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey DRepKey -> VerificationKey DRepKey -> Bool Source # (/=) :: VerificationKey DRepKey -> VerificationKey DRepKey -> Bool Source # | |||||
Eq (VerificationKey GenesisDelegateExtendedKey) Source # | |||||
Eq (VerificationKey GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Eq (VerificationKey GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Eq (VerificationKey GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey GenesisKey -> VerificationKey GenesisKey -> Bool Source # (/=) :: VerificationKey GenesisKey -> VerificationKey GenesisKey -> Bool Source # | |||||
Eq (VerificationKey GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey GenesisUTxOKey -> VerificationKey GenesisUTxOKey -> Bool Source # (/=) :: VerificationKey GenesisUTxOKey -> VerificationKey GenesisUTxOKey -> Bool Source # | |||||
Eq (VerificationKey PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Eq (VerificationKey PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey PaymentKey -> VerificationKey PaymentKey -> Bool Source # (/=) :: VerificationKey PaymentKey -> VerificationKey PaymentKey -> Bool Source # | |||||
Eq (VerificationKey StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey StakeExtendedKey -> VerificationKey StakeExtendedKey -> Bool Source # (/=) :: VerificationKey StakeExtendedKey -> VerificationKey StakeExtendedKey -> Bool Source # | |||||
Eq (VerificationKey StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey StakeKey -> VerificationKey StakeKey -> Bool Source # (/=) :: VerificationKey StakeKey -> VerificationKey StakeKey -> Bool Source # | |||||
Eq (VerificationKey StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Eq (VerificationKey StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey StakePoolKey -> VerificationKey StakePoolKey -> Bool Source # (/=) :: VerificationKey StakePoolKey -> VerificationKey StakePoolKey -> Bool Source # | |||||
newtype VerificationKey ByronKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
newtype VerificationKey ByronKeyLegacy Source # | |||||
newtype VerificationKey KesKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
newtype VerificationKey VrfKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
newtype VerificationKey CommitteeColdExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey CommitteeColdKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey CommitteeHotExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey CommitteeHotKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey DRepExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey DRepKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey GenesisDelegateExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey GenesisDelegateKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey GenesisExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey GenesisKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey GenesisUTxOKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey PaymentExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey PaymentKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey StakeExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey StakeKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey StakePoolExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype VerificationKey StakePoolKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
data AsType (VerificationKey a) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Class |
castVerificationKey :: CastVerificationKeyRole keyroleA keyroleB => VerificationKey keyroleA -> VerificationKey keyroleB Source #
Change the role of a VerificationKey
, if the representation permits.
castSigningKey :: CastSigningKeyRole keyroleA keyroleB => SigningKey keyroleA -> SigningKey keyroleB Source #
Change the role of a SigningKey
, if the representation permits.
generateSigningKey :: (MonadIO m, Key keyrole) => AsType keyrole -> m (SigningKey keyrole) Source #
Generate a SigningKey
using a seed from operating system entropy.
generateInsecureSigningKey :: (MonadIO m, Key keyrole, SerialiseAsRawBytes (SigningKey keyrole)) => StdGen -> AsType keyrole -> m (SigningKey keyrole, StdGen) Source #
Hashes
In Cardano most keys are identified by their hash, and hashes are used in many other places.
data family Hash keyrole Source #
Instances
FromJSON (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods parseJSON :: Value -> Parser (Hash BlockHeader) parseJSONList :: Value -> Parser [Hash BlockHeader] omittedField :: Maybe (Hash BlockHeader) | |||||
FromJSON (Hash DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods parseJSON :: Value -> Parser (Hash DRepKey) parseJSONList :: Value -> Parser [Hash DRepKey] omittedField :: Maybe (Hash DRepKey) | |||||
FromJSON (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods parseJSON :: Value -> Parser (Hash GenesisKey) parseJSONList :: Value -> Parser [Hash GenesisKey] omittedField :: Maybe (Hash GenesisKey) | |||||
FromJSON (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods parseJSON :: Value -> Parser (Hash PaymentKey) parseJSONList :: Value -> Parser [Hash PaymentKey] omittedField :: Maybe (Hash PaymentKey) | |||||
FromJSON (Hash StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods parseJSON :: Value -> Parser (Hash StakePoolExtendedKey) parseJSONList :: Value -> Parser [Hash StakePoolExtendedKey] | |||||
FromJSON (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods parseJSON :: Value -> Parser (Hash StakePoolKey) parseJSONList :: Value -> Parser [Hash StakePoolKey] | |||||
FromJSON (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods parseJSON :: Value -> Parser (Hash ScriptData) parseJSONList :: Value -> Parser [Hash ScriptData] omittedField :: Maybe (Hash ScriptData) | |||||
FromJSONKey (Hash ScriptData) | |||||
Defined in Cardano.Api.Internal.ScriptData Methods fromJSONKey :: FromJSONKeyFunction (Hash ScriptData) fromJSONKeyList :: FromJSONKeyFunction [Hash ScriptData] | |||||
ToJSON (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods toJSON :: Hash BlockHeader -> Value toEncoding :: Hash BlockHeader -> Encoding toJSONList :: [Hash BlockHeader] -> Value toEncodingList :: [Hash BlockHeader] -> Encoding omitField :: Hash BlockHeader -> Bool | |||||
ToJSON (Hash DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToJSON (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSON :: Hash GenesisKey -> Value toEncoding :: Hash GenesisKey -> Encoding toJSONList :: [Hash GenesisKey] -> Value toEncodingList :: [Hash GenesisKey] -> Encoding omitField :: Hash GenesisKey -> Bool | |||||
ToJSON (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSON :: Hash PaymentKey -> Value toEncoding :: Hash PaymentKey -> Encoding toJSONList :: [Hash PaymentKey] -> Value toEncodingList :: [Hash PaymentKey] -> Encoding omitField :: Hash PaymentKey -> Bool | |||||
ToJSON (Hash StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSON :: Hash StakePoolExtendedKey -> Value toEncoding :: Hash StakePoolExtendedKey -> Encoding toJSONList :: [Hash StakePoolExtendedKey] -> Value toEncodingList :: [Hash StakePoolExtendedKey] -> Encoding | |||||
ToJSON (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSON :: Hash StakePoolKey -> Value toEncoding :: Hash StakePoolKey -> Encoding toJSONList :: [Hash StakePoolKey] -> Value toEncodingList :: [Hash StakePoolKey] -> Encoding omitField :: Hash StakePoolKey -> Bool | |||||
ToJSON (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods toJSON :: Hash ScriptData -> Value toEncoding :: Hash ScriptData -> Encoding toJSONList :: [Hash ScriptData] -> Value toEncodingList :: [Hash ScriptData] -> Encoding omitField :: Hash ScriptData -> Bool | |||||
ToJSONKey (Hash DRepKey) | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToJSONKey (Hash GenesisKey) | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSONKey :: ToJSONKeyFunction (Hash GenesisKey) toJSONKeyList :: ToJSONKeyFunction [Hash GenesisKey] | |||||
ToJSONKey (Hash PaymentKey) | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSONKey :: ToJSONKeyFunction (Hash PaymentKey) toJSONKeyList :: ToJSONKeyFunction [Hash PaymentKey] | |||||
ToJSONKey (Hash StakePoolExtendedKey) | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSONKey :: ToJSONKeyFunction (Hash StakePoolExtendedKey) toJSONKeyList :: ToJSONKeyFunction [Hash StakePoolExtendedKey] | |||||
ToJSONKey (Hash StakePoolKey) | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSONKey :: ToJSONKeyFunction (Hash StakePoolKey) toJSONKeyList :: ToJSONKeyFunction [Hash StakePoolKey] | |||||
ToJSONKey (Hash ScriptData) | |||||
Defined in Cardano.Api.Internal.ScriptData Methods toJSONKey :: ToJSONKeyFunction (Hash ScriptData) toJSONKeyList :: ToJSONKeyFunction [Hash ScriptData] | |||||
IsString (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods fromString :: String -> Hash BlockHeader Source # | |||||
IsString (Hash GovernancePoll) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll Methods fromString :: String -> Hash GovernancePoll Source # | |||||
IsString (Hash ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
IsString (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods fromString :: String -> Hash ByronKeyLegacy Source # | |||||
IsString (Hash KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
IsString (Hash VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
IsString (Hash CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash CommitteeColdExtendedKey Source # | |||||
IsString (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash CommitteeColdKey Source # | |||||
IsString (Hash CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash CommitteeHotExtendedKey Source # | |||||
IsString (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash CommitteeHotKey Source # | |||||
IsString (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash DRepExtendedKey Source # | |||||
IsString (Hash DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
IsString (Hash GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash GenesisDelegateExtendedKey Source # | |||||
IsString (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash GenesisKey Source # | |||||
IsString (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash GenesisUTxOKey Source # | |||||
IsString (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||
IsString (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash PaymentKey Source # | |||||
IsString (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash StakeExtendedKey Source # | |||||
IsString (Hash StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
IsString (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash StakePoolKey Source # | |||||
IsString (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods fromString :: String -> Hash ScriptData Source # | |||||
Show (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block | |||||
Show (Hash DRepMetadata) Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata | |||||
Show (Hash GovernancePoll) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll | |||||
Show (Hash ByronKey) Source # | |||||
Show (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
Show (Hash KesKey) Source # | |||||
Show (Hash VrfKey) Source # | |||||
Show (Hash CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash DRepKey) Source # | |||||
Show (Hash GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash StakeKey) Source # | |||||
Show (Hash StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Show (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData | |||||
Show (Hash StakePoolMetadata) Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata | |||||
HasTypeProxy a => HasTypeProxy (Hash a) Source # | |||||
Defined in Cardano.Api.Internal.Hash Associated Types
| |||||
SerialiseAsCBOR (Hash ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: Hash ByronKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash ByronKey) -> ByteString -> Either DecoderError (Hash ByronKey) Source # | |||||
SerialiseAsCBOR (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: Hash ByronKeyLegacy -> ByteString Source # deserialiseFromCBOR :: AsType (Hash ByronKeyLegacy) -> ByteString -> Either DecoderError (Hash ByronKeyLegacy) Source # | |||||
SerialiseAsCBOR (Hash KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: Hash KesKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash KesKey) -> ByteString -> Either DecoderError (Hash KesKey) Source # | |||||
SerialiseAsCBOR (Hash VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: Hash VrfKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash VrfKey) -> ByteString -> Either DecoderError (Hash VrfKey) Source # | |||||
SerialiseAsCBOR (Hash CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash CommitteeColdKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash CommitteeColdKey) -> ByteString -> Either DecoderError (Hash CommitteeColdKey) Source # | |||||
SerialiseAsCBOR (Hash CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsCBOR (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash CommitteeHotKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash CommitteeHotKey) -> ByteString -> Either DecoderError (Hash CommitteeHotKey) Source # | |||||
SerialiseAsCBOR (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash DRepExtendedKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash DRepExtendedKey) -> ByteString -> Either DecoderError (Hash DRepExtendedKey) Source # | |||||
SerialiseAsCBOR (Hash DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash DRepKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash DRepKey) -> ByteString -> Either DecoderError (Hash DRepKey) Source # | |||||
SerialiseAsCBOR (Hash GenesisDelegateExtendedKey) Source # | |||||
SerialiseAsCBOR (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash GenesisDelegateKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash GenesisDelegateKey) -> ByteString -> Either DecoderError (Hash GenesisDelegateKey) Source # | |||||
SerialiseAsCBOR (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash GenesisExtendedKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash GenesisExtendedKey) -> ByteString -> Either DecoderError (Hash GenesisExtendedKey) Source # | |||||
SerialiseAsCBOR (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash GenesisKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash GenesisKey) -> ByteString -> Either DecoderError (Hash GenesisKey) Source # | |||||
SerialiseAsCBOR (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash GenesisUTxOKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash GenesisUTxOKey) -> ByteString -> Either DecoderError (Hash GenesisUTxOKey) Source # | |||||
SerialiseAsCBOR (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash PaymentExtendedKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash PaymentExtendedKey) -> ByteString -> Either DecoderError (Hash PaymentExtendedKey) Source # | |||||
SerialiseAsCBOR (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash PaymentKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash PaymentKey) -> ByteString -> Either DecoderError (Hash PaymentKey) Source # | |||||
SerialiseAsCBOR (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash StakeExtendedKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash StakeExtendedKey) -> ByteString -> Either DecoderError (Hash StakeExtendedKey) Source # | |||||
SerialiseAsCBOR (Hash StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash StakeKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash StakeKey) -> ByteString -> Either DecoderError (Hash StakeKey) Source # | |||||
SerialiseAsCBOR (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash StakePoolKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash StakePoolKey) -> ByteString -> Either DecoderError (Hash StakePoolKey) Source # | |||||
SerialiseAsBech32 (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: Hash CommitteeColdKey -> Text bech32PrefixesPermitted :: AsType (Hash CommitteeColdKey) -> [Text] | |||||
SerialiseAsBech32 (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: Hash CommitteeHotKey -> Text bech32PrefixesPermitted :: AsType (Hash CommitteeHotKey) -> [Text] | |||||
SerialiseAsBech32 (Hash DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: Hash DRepKey -> Text bech32PrefixesPermitted :: AsType (Hash DRepKey) -> [Text] | |||||
SerialiseAsBech32 (Hash StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: Hash StakePoolExtendedKey -> Text bech32PrefixesPermitted :: AsType (Hash StakePoolExtendedKey) -> [Text] | |||||
SerialiseAsBech32 (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: Hash StakePoolKey -> Text bech32PrefixesPermitted :: AsType (Hash StakePoolKey) -> [Text] | |||||
SerialiseAsRawBytes (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods serialiseToRawBytes :: Hash BlockHeader -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash BlockHeader) -> ByteString -> Either SerialiseAsRawBytesError (Hash BlockHeader) Source # | |||||
SerialiseAsRawBytes (Hash DRepMetadata) Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata Methods serialiseToRawBytes :: Hash DRepMetadata -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash DRepMetadata) -> ByteString -> Either SerialiseAsRawBytesError (Hash DRepMetadata) Source # | |||||
SerialiseAsRawBytes (Hash GovernancePoll) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll | |||||
SerialiseAsRawBytes (Hash ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToRawBytes :: Hash ByronKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash ByronKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash ByronKey) Source # | |||||
SerialiseAsRawBytes (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
SerialiseAsRawBytes (Hash KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToRawBytes :: Hash KesKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash KesKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash KesKey) Source # | |||||
SerialiseAsRawBytes (Hash VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToRawBytes :: Hash VrfKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash VrfKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash VrfKey) Source # | |||||
SerialiseAsRawBytes (Hash CommitteeColdExtendedKey) Source # | |||||
SerialiseAsRawBytes (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash CommitteeHotExtendedKey) Source # | |||||
SerialiseAsRawBytes (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToRawBytes :: Hash DRepKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash DRepKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash DRepKey) Source # | |||||
SerialiseAsRawBytes (Hash GenesisDelegateExtendedKey) Source # | |||||
SerialiseAsRawBytes (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToRawBytes :: Hash GenesisKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash GenesisKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash GenesisKey) Source # | |||||
SerialiseAsRawBytes (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToRawBytes :: Hash PaymentKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash PaymentKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash PaymentKey) Source # | |||||
SerialiseAsRawBytes (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
SerialiseAsRawBytes (Hash StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToRawBytes :: Hash StakeKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash StakeKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash StakeKey) Source # | |||||
SerialiseAsRawBytes (Hash StakePoolExtendedKey) Source # | |||||
SerialiseAsRawBytes (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToRawBytes :: Hash StakePoolKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash StakePoolKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash StakePoolKey) Source # | |||||
SerialiseAsRawBytes (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods serialiseToRawBytes :: Hash ScriptData -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash ScriptData) -> ByteString -> Either SerialiseAsRawBytesError (Hash ScriptData) Source # | |||||
SerialiseAsRawBytes (Hash StakePoolMetadata) Source # | |||||
FromCBOR (Hash ByronKey) Source # | |||||
FromCBOR (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
FromCBOR (Hash KesKey) Source # | |||||
FromCBOR (Hash VrfKey) Source # | |||||
FromCBOR (Hash CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash DRepKey) Source # | |||||
FromCBOR (Hash GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
FromCBOR (Hash StakeKey) Source # | |||||
FromCBOR (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash ByronKey) Source # | |||||
ToCBOR (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
ToCBOR (Hash KesKey) Source # | |||||
ToCBOR (Hash VrfKey) Source # | |||||
ToCBOR (Hash CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: Hash CommitteeColdExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash CommitteeColdExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash CommitteeColdExtendedKey] -> Size Source # | |||||
ToCBOR (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: Hash CommitteeHotExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash CommitteeHotExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash CommitteeHotExtendedKey] -> Size Source # | |||||
ToCBOR (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash DRepKey) Source # | |||||
ToCBOR (Hash GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: Hash GenesisDelegateExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash GenesisDelegateExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Hash GenesisDelegateExtendedKey] -> Size Source # | |||||
ToCBOR (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
ToCBOR (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
Eq (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods (==) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # (/=) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # | |||||
Eq (Hash DRepMetadata) Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata Methods (==) :: Hash DRepMetadata -> Hash DRepMetadata -> Bool Source # (/=) :: Hash DRepMetadata -> Hash DRepMetadata -> Bool Source # | |||||
Eq (Hash GovernancePoll) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll Methods (==) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # (/=) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # | |||||
Eq (Hash ByronKey) Source # | |||||
Eq (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods (==) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # (/=) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # | |||||
Eq (Hash KesKey) Source # | |||||
Eq (Hash VrfKey) Source # | |||||
Eq (Hash CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Bool Source # (/=) :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Bool Source # | |||||
Eq (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool Source # (/=) :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool Source # | |||||
Eq (Hash CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Bool Source # (/=) :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Bool Source # | |||||
Eq (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool Source # (/=) :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool Source # | |||||
Eq (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool Source # (/=) :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool Source # | |||||
Eq (Hash DRepKey) Source # | |||||
Eq (Hash GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Bool Source # (/=) :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Bool Source # | |||||
Eq (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool Source # (/=) :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool Source # | |||||
Eq (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool Source # (/=) :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool Source # | |||||
Eq (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash GenesisKey -> Hash GenesisKey -> Bool Source # (/=) :: Hash GenesisKey -> Hash GenesisKey -> Bool Source # | |||||
Eq (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool Source # (/=) :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool Source # | |||||
Eq (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # (/=) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # | |||||
Eq (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # (/=) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # | |||||
Eq (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # (/=) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # | |||||
Eq (Hash StakeKey) Source # | |||||
Eq (Hash StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool Source # (/=) :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool Source # | |||||
Eq (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # (/=) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # | |||||
Eq (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods (==) :: Hash ScriptData -> Hash ScriptData -> Bool Source # (/=) :: Hash ScriptData -> Hash ScriptData -> Bool Source # | |||||
Eq (Hash StakePoolMetadata) Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata Methods (==) :: Hash StakePoolMetadata -> Hash StakePoolMetadata -> Bool Source # (/=) :: Hash StakePoolMetadata -> Hash StakePoolMetadata -> Bool Source # | |||||
Ord (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods compare :: Hash BlockHeader -> Hash BlockHeader -> Ordering Source # (<) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # (<=) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # (>) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # (>=) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # max :: Hash BlockHeader -> Hash BlockHeader -> Hash BlockHeader Source # min :: Hash BlockHeader -> Hash BlockHeader -> Hash BlockHeader Source # | |||||
Ord (Hash GovernancePoll) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll Methods compare :: Hash GovernancePoll -> Hash GovernancePoll -> Ordering Source # (<) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # (<=) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # (>) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # (>=) :: Hash GovernancePoll -> Hash GovernancePoll -> Bool Source # max :: Hash GovernancePoll -> Hash GovernancePoll -> Hash GovernancePoll Source # min :: Hash GovernancePoll -> Hash GovernancePoll -> Hash GovernancePoll Source # | |||||
Ord (Hash ByronKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods compare :: Hash ByronKey -> Hash ByronKey -> Ordering Source # (<) :: Hash ByronKey -> Hash ByronKey -> Bool Source # (<=) :: Hash ByronKey -> Hash ByronKey -> Bool Source # (>) :: Hash ByronKey -> Hash ByronKey -> Bool Source # (>=) :: Hash ByronKey -> Hash ByronKey -> Bool Source # max :: Hash ByronKey -> Hash ByronKey -> Hash ByronKey Source # min :: Hash ByronKey -> Hash ByronKey -> Hash ByronKey Source # | |||||
Ord (Hash ByronKeyLegacy) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron Methods compare :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Ordering Source # (<) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # (<=) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # (>) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # (>=) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # max :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Hash ByronKeyLegacy Source # min :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Hash ByronKeyLegacy Source # | |||||
Ord (Hash KesKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods compare :: Hash KesKey -> Hash KesKey -> Ordering Source # (<) :: Hash KesKey -> Hash KesKey -> Bool Source # (<=) :: Hash KesKey -> Hash KesKey -> Bool Source # (>) :: Hash KesKey -> Hash KesKey -> Bool Source # (>=) :: Hash KesKey -> Hash KesKey -> Bool Source # | |||||
Ord (Hash VrfKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos Methods compare :: Hash VrfKey -> Hash VrfKey -> Ordering Source # (<) :: Hash VrfKey -> Hash VrfKey -> Bool Source # (<=) :: Hash VrfKey -> Hash VrfKey -> Bool Source # (>) :: Hash VrfKey -> Hash VrfKey -> Bool Source # (>=) :: Hash VrfKey -> Hash VrfKey -> Bool Source # | |||||
Ord (Hash CommitteeColdExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Ordering Source # (<) :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Bool Source # (<=) :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Bool Source # (>) :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Bool Source # (>=) :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Bool Source # max :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey Source # min :: Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey -> Hash CommitteeColdExtendedKey Source # | |||||
Ord (Hash CommitteeColdKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Ordering Source # (<) :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool Source # (<=) :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool Source # (>) :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool Source # (>=) :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Bool Source # max :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Hash CommitteeColdKey Source # min :: Hash CommitteeColdKey -> Hash CommitteeColdKey -> Hash CommitteeColdKey Source # | |||||
Ord (Hash CommitteeHotExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Ordering Source # (<) :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Bool Source # (<=) :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Bool Source # (>) :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Bool Source # (>=) :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Bool Source # max :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey Source # min :: Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey -> Hash CommitteeHotExtendedKey Source # | |||||
Ord (Hash CommitteeHotKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Ordering Source # (<) :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool Source # (<=) :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool Source # (>) :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool Source # (>=) :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Bool Source # max :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Hash CommitteeHotKey Source # min :: Hash CommitteeHotKey -> Hash CommitteeHotKey -> Hash CommitteeHotKey Source # | |||||
Ord (Hash DRepExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Ordering Source # (<) :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool Source # (<=) :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool Source # (>) :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool Source # (>=) :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Bool Source # max :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Hash DRepExtendedKey Source # min :: Hash DRepExtendedKey -> Hash DRepExtendedKey -> Hash DRepExtendedKey Source # | |||||
Ord (Hash DRepKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash DRepKey -> Hash DRepKey -> Ordering Source # (<) :: Hash DRepKey -> Hash DRepKey -> Bool Source # (<=) :: Hash DRepKey -> Hash DRepKey -> Bool Source # (>) :: Hash DRepKey -> Hash DRepKey -> Bool Source # (>=) :: Hash DRepKey -> Hash DRepKey -> Bool Source # max :: Hash DRepKey -> Hash DRepKey -> Hash DRepKey Source # min :: Hash DRepKey -> Hash DRepKey -> Hash DRepKey Source # | |||||
Ord (Hash GenesisDelegateExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Ordering Source # (<) :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Bool Source # (<=) :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Bool Source # (>) :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Bool Source # (>=) :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Bool Source # max :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey Source # min :: Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey -> Hash GenesisDelegateExtendedKey Source # | |||||
Ord (Hash GenesisDelegateKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Ordering Source # (<) :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool Source # (<=) :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool Source # (>) :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool Source # (>=) :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Bool Source # max :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Hash GenesisDelegateKey Source # min :: Hash GenesisDelegateKey -> Hash GenesisDelegateKey -> Hash GenesisDelegateKey Source # | |||||
Ord (Hash GenesisExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Ordering Source # (<) :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool Source # (<=) :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool Source # (>) :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool Source # (>=) :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Bool Source # max :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Hash GenesisExtendedKey Source # min :: Hash GenesisExtendedKey -> Hash GenesisExtendedKey -> Hash GenesisExtendedKey Source # | |||||
Ord (Hash GenesisKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash GenesisKey -> Hash GenesisKey -> Ordering Source # (<) :: Hash GenesisKey -> Hash GenesisKey -> Bool Source # (<=) :: Hash GenesisKey -> Hash GenesisKey -> Bool Source # (>) :: Hash GenesisKey -> Hash GenesisKey -> Bool Source # (>=) :: Hash GenesisKey -> Hash GenesisKey -> Bool Source # max :: Hash GenesisKey -> Hash GenesisKey -> Hash GenesisKey Source # min :: Hash GenesisKey -> Hash GenesisKey -> Hash GenesisKey Source # | |||||
Ord (Hash GenesisUTxOKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Ordering Source # (<) :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool Source # (<=) :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool Source # (>) :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool Source # (>=) :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Bool Source # max :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Hash GenesisUTxOKey Source # min :: Hash GenesisUTxOKey -> Hash GenesisUTxOKey -> Hash GenesisUTxOKey Source # | |||||
Ord (Hash PaymentExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Ordering Source # (<) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # (<=) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # (>) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # (>=) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # max :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Hash PaymentExtendedKey Source # min :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Hash PaymentExtendedKey Source # | |||||
Ord (Hash PaymentKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash PaymentKey -> Hash PaymentKey -> Ordering Source # (<) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # (<=) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # (>) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # (>=) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # max :: Hash PaymentKey -> Hash PaymentKey -> Hash PaymentKey Source # min :: Hash PaymentKey -> Hash PaymentKey -> Hash PaymentKey Source # | |||||
Ord (Hash StakeExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Ordering Source # (<) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # (<=) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # (>) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # (>=) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # max :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Hash StakeExtendedKey Source # min :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Hash StakeExtendedKey Source # | |||||
Ord (Hash StakeKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash StakeKey -> Hash StakeKey -> Ordering Source # (<) :: Hash StakeKey -> Hash StakeKey -> Bool Source # (<=) :: Hash StakeKey -> Hash StakeKey -> Bool Source # (>) :: Hash StakeKey -> Hash StakeKey -> Bool Source # (>=) :: Hash StakeKey -> Hash StakeKey -> Bool Source # max :: Hash StakeKey -> Hash StakeKey -> Hash StakeKey Source # min :: Hash StakeKey -> Hash StakeKey -> Hash StakeKey Source # | |||||
Ord (Hash StakePoolExtendedKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Ordering Source # (<) :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool Source # (<=) :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool Source # (>) :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool Source # (>=) :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Bool Source # max :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey Source # min :: Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey -> Hash StakePoolExtendedKey Source # | |||||
Ord (Hash StakePoolKey) Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash StakePoolKey -> Hash StakePoolKey -> Ordering Source # (<) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # (<=) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # (>) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # (>=) :: Hash StakePoolKey -> Hash StakePoolKey -> Bool Source # max :: Hash StakePoolKey -> Hash StakePoolKey -> Hash StakePoolKey Source # min :: Hash StakePoolKey -> Hash StakePoolKey -> Hash StakePoolKey Source # | |||||
Ord (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods compare :: Hash ScriptData -> Hash ScriptData -> Ordering Source # (<) :: Hash ScriptData -> Hash ScriptData -> Bool Source # (<=) :: Hash ScriptData -> Hash ScriptData -> Bool Source # (>) :: Hash ScriptData -> Hash ScriptData -> Bool Source # (>=) :: Hash ScriptData -> Hash ScriptData -> Bool Source # max :: Hash ScriptData -> Hash ScriptData -> Hash ScriptData Source # min :: Hash ScriptData -> Hash ScriptData -> Hash ScriptData Source # | |||||
newtype Hash BlockHeader Source # | For now at least we use a fixed concrete hash type for all modes and era. The different eras do use different types, but it's all the same underlying representation. | ||||
Defined in Cardano.Api.Internal.Block | |||||
newtype Hash DRepMetadata Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata | |||||
newtype Hash GovernancePoll Source # | |||||
Defined in Cardano.Api.Internal.Governance.Poll | |||||
newtype Hash ByronKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
newtype Hash ByronKeyLegacy Source # | |||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||
newtype Hash KesKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
newtype Hash VrfKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Praos | |||||
newtype Hash CommitteeColdExtendedKey Source # | |||||
newtype Hash CommitteeColdKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash CommitteeHotExtendedKey Source # | |||||
newtype Hash CommitteeHotKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash DRepExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash DRepKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash GenesisDelegateExtendedKey Source # | |||||
newtype Hash GenesisDelegateKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash GenesisExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash GenesisKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash GenesisUTxOKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash PaymentExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash PaymentKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash StakeExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash StakeKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash StakePoolExtendedKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash StakePoolKey Source # | |||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||
newtype Hash ScriptData Source # | |||||
Defined in Cardano.Api.Internal.ScriptData | |||||
newtype Hash StakePoolMetadata Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata | |||||
data AsType (Hash a) Source # | |||||
Defined in Cardano.Api.Internal.Hash |
renderSafeHashAsHex :: SafeHash tag -> Text Source #
Mnemonics
Functions for working with mnemonics ** Mnemonics generation
data MnemonicSize Source #
The size of a mnemonic sentence. The size is given in the number of words in the sentence. The allowed sizes are 12, 15, 18, 21, and 24.
Instances
Show MnemonicSize Source # | |
Defined in Cardano.Api.Internal.Keys.Mnemonics | |
Eq MnemonicSize Source # | |
Defined in Cardano.Api.Internal.Keys.Mnemonics Methods (==) :: MnemonicSize -> MnemonicSize -> Bool Source # (/=) :: MnemonicSize -> MnemonicSize -> Bool Source # |
Arguments
:: MonadIO m | |
=> MnemonicSize | The size of the mnemonic sentence to generate. Must be one of 12, 15, 18, 21, or 24. |
-> m [Text] |
Generate a mnemonic sentence of the given size.
Key derivation from mnemonics
data MnemonicToSigningKeyError Source #
Errors that can occur when converting a mnemonic sentence to a signing key
Constructors
InvalidMnemonicError String | |
InvalidAccountNumberError Word32 | |
InvalidPaymentKeyNoError Word32 |
Instances
Show MnemonicToSigningKeyError Source # | |
Defined in Cardano.Api.Internal.Keys.Mnemonics | |
Error MnemonicToSigningKeyError Source # | |
Defined in Cardano.Api.Internal.Keys.Mnemonics Methods prettyError :: MnemonicToSigningKeyError -> Doc ann Source # | |
Eq MnemonicToSigningKeyError Source # | |
Defined in Cardano.Api.Internal.Keys.Mnemonics Methods (==) :: MnemonicToSigningKeyError -> MnemonicToSigningKeyError -> Bool Source # (/=) :: MnemonicToSigningKeyError -> MnemonicToSigningKeyError -> Bool Source # |
signingKeyFromMnemonic Source #
Arguments
:: SigningKeyFromRootKey keyrole | |
=> AsType keyrole | Type of the extended signing key to generate. |
-> [Text] | The mnemonic sentence. The length must be one of 12, 15, 18, 21, or 24. Each element of the list must be a single word. |
-> Word32 | The account number in the derivation path. First account is 0. |
-> Either MnemonicToSigningKeyError (SigningKey keyrole) |
Generate a signing key from a mnemonic sentence for a key role that
accepts only one payment key from an account number (DRep and committee keys).
For other key roles (extended payment and stake keys), see signingKeyFromMnemonicWithPaymentKeyIndex
.
We derive one key per account following the advice in https://cips.cardano.org/cip/CIP-0105: "Since it is best practice to use a single cryptographic key for a single purpose, we opt to keep DRep and committee keys separate from other keys in Cardano."
A derivation path is like a file path in a file system. It specifies the location of a key in the key tree. The path is a list of indices, one for each level of the tree. The indices are separated by a forward slash (/). In this function we only ask for one index: the account number.
For more information about address derivation check: * https://cips.cardano.org/cip/CIP-1852 * https://github.com/uniVocity/cardano-tutorials/blob/master/cardano-addresses.md#understanding-the-hd-wallet-address-format-bip-44 * https://cips.cardano.org/cip/CIP-0105
signingKeyFromMnemonicWithPaymentKeyIndex Source #
Arguments
:: IndexedSigningKeyFromRootKey keyrole | |
=> AsType keyrole | Type of the extended signing key to generate. |
-> [Text] | The mnemonic sentence. The length must be one of 12, 15, 18, 21, or 24. Each element of the list must be a single word. |
-> Word32 | The account number in the derivation path. The first account is 0. |
-> Word32 | The payment key number in the derivation path. Consider that wallets following the BIP-44 standard only check 20 addresses without transactions before giving up. For example, if you have a fresh wallet and receive a payment on the address generated with address_index = 6, your wallet may only display the money received on addresses from 0 to 26. If you receive payment on an address with address_index = 30, the funds may not be displayed to you even though it's on the blockchain. It will only appear once there is a transaction in some address where address_index is between 10 and 29. The gap limit can be customized on some wallets, but increasing it reduces synchronization performance. |
-> Either MnemonicToSigningKeyError (SigningKey keyrole) |
Generate a signing key from a mnemonic sentence for a key role that
accepts several payment keys from an account number (extended payment and stake keys).
For other key roles (DRep and committee keys), see signingKeyFromMnemonic
.
A derivation path is like a file path in a file system. It specifies the location of a key in the key tree. The path is a list of indices, one for each level of the tree. The indices are separated by a forward slash (/). In this function, we only ask for two indices: the account number and the payment key number. Each account can have multiple payment keys.
For more information about address derivation, check: * https://cips.cardano.org/cip/CIP-1852 * https://github.com/uniVocity/cardano-tutorials/blob/master/cardano-addresses.md#understanding-the-hd-wallet-address-format-bip-44 * https://cips.cardano.org/cip/CIP-0105
Mnemonic word queries
findMnemonicWordsWithPrefix :: Text -> [(Text, Int)] Source #
Obtain the list of all mnemonic words that start with the given prefix and their index in the dictionary. For example: >>> findMnemonicWordsWithPrefix "cha" [("chair",302),("chalk",303),("champion",304),("change",305),("chaos",306),("chapter",307),("charge",308),("chase",309),("chat",310)]
autocompleteMnemonicPrefix :: Text -> Maybe Text Source #
Autocomplete the prefix of the mnemonic word as much as possible. In other words, find the longest common prefix for all the words that start with the given prefix. For example: >>> autocompleteMnemonicPrefix "ty" Just "typ"
Because "type" and "typical" are the only words that start with "ty".
>>>
autocompleteMnemonicPrefix "vani"
Just "vanish"
Because "vanish" is the only word that starts with "vani".
>>>
autocompleteMnemonicPrefix "medo"
Nothing
Because there are no words that start with "medo".
Payment addresses
Constructing and inspecting normal payment addresses
data Address addrtype where Source #
Addresses are used as locations where assets live. The address determines the rights needed to spend assets at the address: in particular holding some signing key or being able to satisfy the conditions of a script.
There are currently two types of address:
- Byron addresses, which use the type tag
ByronAddr
; and - Shelley addresses, which use the type tag
ShelleyAddr
. Notably, Shelley addresses support scripts and stake delegation.
The address type is subtly from the ledger era in which each
address type is valid: while Byron addresses are the only choice in the
Byron era, the Shelley era and all subsequent eras support both Byron and
Shelley addresses. The Address
type param only says the type of the address
(either Byron or Shelley). The AddressInEra
type connects the address type
with the era in which it is supported.
Constructors
ByronAddress :: Address -> Address ByronAddr | Byron addresses were the only supported address type in the original Byron era. |
ShelleyAddress :: Network -> PaymentCredential -> StakeReference -> Address ShelleyAddr | Shelley addresses allow delegation. Shelley addresses were introduced in Shelley era and are thus supported from the Shelley era onwards |
Instances
FromJSON (Address ByronAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address | |||||
FromJSON (Address ShelleyAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods parseJSON :: Value -> Parser (Address ShelleyAddr) parseJSONList :: Value -> Parser [Address ShelleyAddr] | |||||
ToJSON (Address ByronAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address | |||||
ToJSON (Address ShelleyAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods toJSON :: Address ShelleyAddr -> Value toEncoding :: Address ShelleyAddr -> Encoding toJSONList :: [Address ShelleyAddr] -> Value toEncodingList :: [Address ShelleyAddr] -> Encoding omitField :: Address ShelleyAddr -> Bool | |||||
Show (Address addrtype) Source # | |||||
SerialiseAddress (Address ByronAddr) Source # | |||||
SerialiseAddress (Address ShelleyAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods serialiseAddress :: Address ShelleyAddr -> Text Source # deserialiseAddress :: AsType (Address ShelleyAddr) -> Text -> Maybe (Address ShelleyAddr) Source # | |||||
HasTypeProxy addrtype => HasTypeProxy (Address addrtype) Source # | |||||
Defined in Cardano.Api.Internal.Address Associated Types
| |||||
SerialiseAsBech32 (Address ShelleyAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods bech32PrefixFor :: Address ShelleyAddr -> Text bech32PrefixesPermitted :: AsType (Address ShelleyAddr) -> [Text] | |||||
SerialiseAsRawBytes (Address ByronAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods serialiseToRawBytes :: Address ByronAddr -> ByteString Source # deserialiseFromRawBytes :: AsType (Address ByronAddr) -> ByteString -> Either SerialiseAsRawBytesError (Address ByronAddr) Source # | |||||
SerialiseAsRawBytes (Address ShelleyAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address | |||||
NFData (Address addrtype) Source # | |||||
Defined in Cardano.Api.Internal.Address | |||||
Eq (Address addrtype) Source # | |||||
Ord (Address addrtype) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods compare :: Address addrtype -> Address addrtype -> Ordering Source # (<) :: Address addrtype -> Address addrtype -> Bool Source # (<=) :: Address addrtype -> Address addrtype -> Bool Source # (>) :: Address addrtype -> Address addrtype -> Bool Source # (>=) :: Address addrtype -> Address addrtype -> Bool Source # max :: Address addrtype -> Address addrtype -> Address addrtype Source # min :: Address addrtype -> Address addrtype -> Address addrtype Source # | |||||
data AsType (Address addrtype) Source # | |||||
Defined in Cardano.Api.Internal.Address |
A type used as a tag to distinguish Byron addresses.
Instances
HasTypeProxy ByronAddr Source # | |||||
Defined in Cardano.Api.Internal.Address Associated Types
| |||||
FromJSON (Address ByronAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address | |||||
ToJSON (Address ByronAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address | |||||
SerialiseAddress (Address ByronAddr) Source # | |||||
SerialiseAsRawBytes (Address ByronAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods serialiseToRawBytes :: Address ByronAddr -> ByteString Source # deserialiseFromRawBytes :: AsType (Address ByronAddr) -> ByteString -> Either SerialiseAsRawBytesError (Address ByronAddr) Source # | |||||
data AsType ByronAddr Source # | |||||
Defined in Cardano.Api.Internal.Address |
data ShelleyAddr Source #
A type used as a tag to distinguish Shelley addresses.
Instances
HasTypeProxy ShelleyAddr Source # | |||||
Defined in Cardano.Api.Internal.Address Associated Types
Methods proxyToAsType :: Proxy ShelleyAddr -> AsType ShelleyAddr Source # | |||||
FromJSON (Address ShelleyAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods parseJSON :: Value -> Parser (Address ShelleyAddr) parseJSONList :: Value -> Parser [Address ShelleyAddr] | |||||
ToJSON (Address ShelleyAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods toJSON :: Address ShelleyAddr -> Value toEncoding :: Address ShelleyAddr -> Encoding toJSONList :: [Address ShelleyAddr] -> Value toEncodingList :: [Address ShelleyAddr] -> Encoding omitField :: Address ShelleyAddr -> Bool | |||||
SerialiseAddress (Address ShelleyAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods serialiseAddress :: Address ShelleyAddr -> Text Source # deserialiseAddress :: AsType (Address ShelleyAddr) -> Text -> Maybe (Address ShelleyAddr) Source # | |||||
SerialiseAsBech32 (Address ShelleyAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods bech32PrefixFor :: Address ShelleyAddr -> Text bech32PrefixesPermitted :: AsType (Address ShelleyAddr) -> [Text] | |||||
SerialiseAsRawBytes (Address ShelleyAddr) Source # | |||||
Defined in Cardano.Api.Internal.Address | |||||
data AsType ShelleyAddr Source # | |||||
Defined in Cardano.Api.Internal.Address |
Byron addresses
Byron-era payment keys. Used for Byron addresses and witnessing transactions that spend from these addresses.
These use Ed25519 but with a 32byte "chaincode" used in HD derivation.
The inclusion of the chaincode is a design mistake but one that cannot
be corrected for the Byron era. The Shelley era PaymentKey
s do not include
a chaincode. It is safe to use a zero or random chaincode for new Byron keys.
This is a type level tag, used with other interfaces like Key
.
Instances
HasTypeProxy ByronKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Associated Types
| |||||||||
Key ByronKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Associated Types
Methods getVerificationKey :: SigningKey ByronKey -> VerificationKey ByronKey Source # deterministicSigningKey :: AsType ByronKey -> Seed -> SigningKey ByronKey Source # deterministicSigningKeySeedSize :: AsType ByronKey -> Word Source # verificationKeyHash :: VerificationKey ByronKey -> Hash ByronKey Source # | |||||||||
IsString (Hash ByronKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||||||
IsString (SigningKey ByronKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Methods fromString :: String -> SigningKey ByronKey Source # | |||||||||
IsString (VerificationKey ByronKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Methods | |||||||||
Show (Hash ByronKey) Source # | |||||||||
Show (SigningKey ByronKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||||||
Show (VerificationKey ByronKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||||||
SerialiseAsCBOR (Hash ByronKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: Hash ByronKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash ByronKey) -> ByteString -> Either DecoderError (Hash ByronKey) Source # | |||||||||
SerialiseAsCBOR (SigningKey ByronKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: SigningKey ByronKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey ByronKey) -> ByteString -> Either DecoderError (SigningKey ByronKey) Source # | |||||||||
SerialiseAsCBOR (VerificationKey ByronKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: VerificationKey ByronKey -> ByteString Source # deserialiseFromCBOR :: AsType (VerificationKey ByronKey) -> ByteString -> Either DecoderError (VerificationKey ByronKey) Source # | |||||||||
SerialiseAsRawBytes (Hash ByronKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToRawBytes :: Hash ByronKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash ByronKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash ByronKey) Source # | |||||||||
SerialiseAsRawBytes (SigningKey ByronKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||||||
SerialiseAsRawBytes (VerificationKey ByronKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||||||
HasTextEnvelope (SigningKey ByronKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||||||
HasTextEnvelope (VerificationKey ByronKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||||||
FromCBOR (Hash ByronKey) Source # | |||||||||
FromCBOR (SigningKey ByronKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||||||
FromCBOR (VerificationKey ByronKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||||||
ToCBOR (Hash ByronKey) Source # | |||||||||
ToCBOR (SigningKey ByronKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||||||
ToCBOR (VerificationKey ByronKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||||||
Eq (Hash ByronKey) Source # | |||||||||
Eq (VerificationKey ByronKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Methods (==) :: VerificationKey ByronKey -> VerificationKey ByronKey -> Bool Source # (/=) :: VerificationKey ByronKey -> VerificationKey ByronKey -> Bool Source # | |||||||||
Ord (Hash ByronKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Methods compare :: Hash ByronKey -> Hash ByronKey -> Ordering Source # (<) :: Hash ByronKey -> Hash ByronKey -> Bool Source # (<=) :: Hash ByronKey -> Hash ByronKey -> Bool Source # (>) :: Hash ByronKey -> Hash ByronKey -> Bool Source # (>=) :: Hash ByronKey -> Hash ByronKey -> Bool Source # max :: Hash ByronKey -> Hash ByronKey -> Hash ByronKey Source # min :: Hash ByronKey -> Hash ByronKey -> Hash ByronKey Source # | |||||||||
data AsType ByronKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||||||
newtype Hash ByronKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||||||
newtype SigningKey ByronKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||||||
newtype VerificationKey ByronKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron |
data ByronKeyLegacy Source #
Instances
HasTypeProxy ByronKeyLegacy Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Associated Types
Methods proxyToAsType :: Proxy ByronKeyLegacy -> AsType ByronKeyLegacy Source # | |||||||||
Key ByronKeyLegacy Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Associated Types
Methods getVerificationKey :: SigningKey ByronKeyLegacy -> VerificationKey ByronKeyLegacy Source # deterministicSigningKey :: AsType ByronKeyLegacy -> Seed -> SigningKey ByronKeyLegacy Source # deterministicSigningKeySeedSize :: AsType ByronKeyLegacy -> Word Source # verificationKeyHash :: VerificationKey ByronKeyLegacy -> Hash ByronKeyLegacy Source # | |||||||||
IsString (Hash ByronKeyLegacy) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Methods fromString :: String -> Hash ByronKeyLegacy Source # | |||||||||
IsString (SigningKey ByronKeyLegacy) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Methods | |||||||||
IsString (VerificationKey ByronKeyLegacy) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Methods fromString :: String -> VerificationKey ByronKeyLegacy Source # | |||||||||
Show (Hash ByronKeyLegacy) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||||||
Show (SigningKey ByronKeyLegacy) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Methods showsPrec :: Int -> SigningKey ByronKeyLegacy -> ShowS Source # show :: SigningKey ByronKeyLegacy -> String Source # showList :: [SigningKey ByronKeyLegacy] -> ShowS Source # | |||||||||
Show (VerificationKey ByronKeyLegacy) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Methods showsPrec :: Int -> VerificationKey ByronKeyLegacy -> ShowS Source # show :: VerificationKey ByronKeyLegacy -> String Source # showList :: [VerificationKey ByronKeyLegacy] -> ShowS Source # | |||||||||
SerialiseAsCBOR (Hash ByronKeyLegacy) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: Hash ByronKeyLegacy -> ByteString Source # deserialiseFromCBOR :: AsType (Hash ByronKeyLegacy) -> ByteString -> Either DecoderError (Hash ByronKeyLegacy) Source # | |||||||||
SerialiseAsCBOR (SigningKey ByronKeyLegacy) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: SigningKey ByronKeyLegacy -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey ByronKeyLegacy) -> ByteString -> Either DecoderError (SigningKey ByronKeyLegacy) Source # | |||||||||
SerialiseAsCBOR (VerificationKey ByronKeyLegacy) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||||||
SerialiseAsRawBytes (Hash ByronKeyLegacy) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||||||
SerialiseAsRawBytes (SigningKey ByronKeyLegacy) Source # | |||||||||
SerialiseAsRawBytes (VerificationKey ByronKeyLegacy) Source # | |||||||||
HasTextEnvelope (SigningKey ByronKeyLegacy) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||||||
HasTextEnvelope (VerificationKey ByronKeyLegacy) Source # | |||||||||
FromCBOR (Hash ByronKeyLegacy) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||||||
FromCBOR (SigningKey ByronKeyLegacy) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Methods fromCBOR :: Decoder s (SigningKey ByronKeyLegacy) Source # label :: Proxy (SigningKey ByronKeyLegacy) -> Text Source # | |||||||||
FromCBOR (VerificationKey ByronKeyLegacy) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Methods fromCBOR :: Decoder s (VerificationKey ByronKeyLegacy) Source # label :: Proxy (VerificationKey ByronKeyLegacy) -> Text Source # | |||||||||
ToCBOR (Hash ByronKeyLegacy) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||||||
ToCBOR (SigningKey ByronKeyLegacy) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Methods toCBOR :: SigningKey ByronKeyLegacy -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey ByronKeyLegacy) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey ByronKeyLegacy] -> Size Source # | |||||||||
ToCBOR (VerificationKey ByronKeyLegacy) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Methods toCBOR :: VerificationKey ByronKeyLegacy -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey ByronKeyLegacy) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey ByronKeyLegacy] -> Size Source # | |||||||||
Eq (Hash ByronKeyLegacy) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Methods (==) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # (/=) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # | |||||||||
Eq (VerificationKey ByronKeyLegacy) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Methods (==) :: VerificationKey ByronKeyLegacy -> VerificationKey ByronKeyLegacy -> Bool Source # (/=) :: VerificationKey ByronKeyLegacy -> VerificationKey ByronKeyLegacy -> Bool Source # | |||||||||
Ord (Hash ByronKeyLegacy) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron Methods compare :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Ordering Source # (<) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # (<=) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # (>) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # (>=) :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Bool Source # max :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Hash ByronKeyLegacy Source # min :: Hash ByronKeyLegacy -> Hash ByronKeyLegacy -> Hash ByronKeyLegacy Source # | |||||||||
data AsType ByronKeyLegacy Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||||||
newtype Hash ByronKeyLegacy Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||||||
newtype SigningKey ByronKeyLegacy Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Byron | |||||||||
newtype VerificationKey ByronKeyLegacy Source # | |||||||||
Shelley addresses
makeShelleyAddress :: NetworkId -> PaymentCredential -> StakeAddressReference -> Address ShelleyAddr Source #
data PaymentCredential Source #
Constructors
PaymentCredentialByKey (Hash PaymentKey) | |
PaymentCredentialByScript ScriptHash |
Instances
Show PaymentCredential Source # | |
Defined in Cardano.Api.Internal.Address | |
Eq PaymentCredential Source # | |
Defined in Cardano.Api.Internal.Address Methods (==) :: PaymentCredential -> PaymentCredential -> Bool Source # (/=) :: PaymentCredential -> PaymentCredential -> Bool Source # | |
Ord PaymentCredential Source # | |
Defined in Cardano.Api.Internal.Address Methods compare :: PaymentCredential -> PaymentCredential -> Ordering Source # (<) :: PaymentCredential -> PaymentCredential -> Bool Source # (<=) :: PaymentCredential -> PaymentCredential -> Bool Source # (>) :: PaymentCredential -> PaymentCredential -> Bool Source # (>=) :: PaymentCredential -> PaymentCredential -> Bool Source # max :: PaymentCredential -> PaymentCredential -> PaymentCredential Source # min :: PaymentCredential -> PaymentCredential -> PaymentCredential Source # |
newtype StakeAddressPointer Source #
Constructors
StakeAddressPointer | |
Fields |
Instances
Show StakeAddressPointer Source # | |
Defined in Cardano.Api.Internal.Address | |
Eq StakeAddressPointer Source # | |
Defined in Cardano.Api.Internal.Address Methods (==) :: StakeAddressPointer -> StakeAddressPointer -> Bool Source # (/=) :: StakeAddressPointer -> StakeAddressPointer -> Bool Source # |
data StakeAddressReference Source #
Constructors
StakeAddressByValue StakeCredential | |
StakeAddressByPointer StakeAddressPointer | |
NoStakeAddress |
Instances
Show StakeAddressReference Source # | |
Defined in Cardano.Api.Internal.Address | |
Eq StakeAddressReference Source # | |
Defined in Cardano.Api.Internal.Address Methods (==) :: StakeAddressReference -> StakeAddressReference -> Bool Source # (/=) :: StakeAddressReference -> StakeAddressReference -> Bool Source # |
data PaymentKey Source #
Shelley-era payment keys. Used for Shelley payment addresses and witnessing transactions that spend from these addresses.
This is a type level tag, used with other interfaces like Key
.
Instances
HasTypeProxy PaymentKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods proxyToAsType :: Proxy PaymentKey -> AsType PaymentKey Source # | |||||||||
Key PaymentKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey PaymentKey -> VerificationKey PaymentKey Source # deterministicSigningKey :: AsType PaymentKey -> Seed -> SigningKey PaymentKey Source # deterministicSigningKeySeedSize :: AsType PaymentKey -> Word Source # verificationKeyHash :: VerificationKey PaymentKey -> Hash PaymentKey Source # | |||||||||
FromJSON (Hash PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods parseJSON :: Value -> Parser (Hash PaymentKey) parseJSONList :: Value -> Parser [Hash PaymentKey] omittedField :: Maybe (Hash PaymentKey) | |||||||||
ToJSON (Hash PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSON :: Hash PaymentKey -> Value toEncoding :: Hash PaymentKey -> Encoding toJSONList :: [Hash PaymentKey] -> Value toEncodingList :: [Hash PaymentKey] -> Encoding omitField :: Hash PaymentKey -> Bool | |||||||||
ToJSONKey (Hash PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toJSONKey :: ToJSONKeyFunction (Hash PaymentKey) toJSONKeyList :: ToJSONKeyFunction [Hash PaymentKey] | |||||||||
IsString (Hash PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash PaymentKey Source # | |||||||||
IsString (SigningKey PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey PaymentKey Source # | |||||||||
IsString (VerificationKey PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||||||
Show (Hash PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
Show (SigningKey PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey PaymentKey -> ShowS Source # show :: SigningKey PaymentKey -> String Source # showList :: [SigningKey PaymentKey] -> ShowS Source # | |||||||||
Show (VerificationKey PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey PaymentKey -> ShowS Source # show :: VerificationKey PaymentKey -> String Source # showList :: [VerificationKey PaymentKey] -> ShowS Source # | |||||||||
SerialiseAsCBOR (Hash PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash PaymentKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash PaymentKey) -> ByteString -> Either DecoderError (Hash PaymentKey) Source # | |||||||||
SerialiseAsCBOR (SigningKey PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey PaymentKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey PaymentKey) -> ByteString -> Either DecoderError (SigningKey PaymentKey) Source # | |||||||||
SerialiseAsCBOR (VerificationKey PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
SerialiseAsBech32 (SigningKey PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey PaymentKey -> Text bech32PrefixesPermitted :: AsType (SigningKey PaymentKey) -> [Text] | |||||||||
SerialiseAsBech32 (VerificationKey PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey PaymentKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey PaymentKey) -> [Text] | |||||||||
SerialiseAsRawBytes (Hash PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToRawBytes :: Hash PaymentKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash PaymentKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash PaymentKey) Source # | |||||||||
SerialiseAsRawBytes (SigningKey PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
SerialiseAsRawBytes (VerificationKey PaymentKey) Source # | |||||||||
HasTextEnvelope (SigningKey PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
HasTextEnvelope (VerificationKey PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
FromCBOR (Hash PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
FromCBOR (SigningKey PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey PaymentKey) Source # label :: Proxy (SigningKey PaymentKey) -> Text Source # | |||||||||
FromCBOR (VerificationKey PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey PaymentKey) Source # label :: Proxy (VerificationKey PaymentKey) -> Text Source # | |||||||||
ToCBOR (Hash PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
ToCBOR (SigningKey PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey PaymentKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey PaymentKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey PaymentKey] -> Size Source # | |||||||||
ToCBOR (VerificationKey PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey PaymentKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey PaymentKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey PaymentKey] -> Size Source # | |||||||||
Eq (Hash PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # (/=) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # | |||||||||
Eq (VerificationKey PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey PaymentKey -> VerificationKey PaymentKey -> Bool Source # (/=) :: VerificationKey PaymentKey -> VerificationKey PaymentKey -> Bool Source # | |||||||||
Ord (Hash PaymentKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash PaymentKey -> Hash PaymentKey -> Ordering Source # (<) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # (<=) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # (>) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # (>=) :: Hash PaymentKey -> Hash PaymentKey -> Bool Source # max :: Hash PaymentKey -> Hash PaymentKey -> Hash PaymentKey Source # min :: Hash PaymentKey -> Hash PaymentKey -> Hash PaymentKey Source # | |||||||||
data AsType PaymentKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
newtype Hash PaymentKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
newtype SigningKey PaymentKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
newtype VerificationKey PaymentKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley |
data PaymentExtendedKey Source #
Shelley-era payment keys using extended ed25519 cryptographic keys.
They can be used for Shelley payment addresses and witnessing transactions that spend from these addresses.
These extended keys are used by HD wallets. So this type provides interoperability with HD wallets. The ITN CLI also supported this key type.
The extended verification keys can be converted (via castVerificationKey
)
to ordinary keys (i.e. VerificationKey
PaymentKey
) but this is not the
case for the signing keys. The signing keys can be used to witness
transactions directly, with verification via their non-extended verification
key (VerificationKey
PaymentKey
).
This is a type level tag, used with other interfaces like Key
.
Instances
HasTypeProxy PaymentExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods proxyToAsType :: Proxy PaymentExtendedKey -> AsType PaymentExtendedKey Source # | |||||||||
Key PaymentExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey PaymentExtendedKey -> VerificationKey PaymentExtendedKey Source # deterministicSigningKey :: AsType PaymentExtendedKey -> Seed -> SigningKey PaymentExtendedKey Source # deterministicSigningKeySeedSize :: AsType PaymentExtendedKey -> Word Source # verificationKeyHash :: VerificationKey PaymentExtendedKey -> Hash PaymentExtendedKey Source # | |||||||||
IsString (Hash PaymentExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||||||
IsString (SigningKey PaymentExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey PaymentExtendedKey Source # | |||||||||
IsString (VerificationKey PaymentExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey PaymentExtendedKey Source # | |||||||||
Show (Hash PaymentExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
Show (SigningKey PaymentExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey PaymentExtendedKey -> ShowS Source # show :: SigningKey PaymentExtendedKey -> String Source # showList :: [SigningKey PaymentExtendedKey] -> ShowS Source # | |||||||||
Show (VerificationKey PaymentExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey PaymentExtendedKey -> ShowS Source # show :: VerificationKey PaymentExtendedKey -> String Source # showList :: [VerificationKey PaymentExtendedKey] -> ShowS Source # | |||||||||
SerialiseAsCBOR (Hash PaymentExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash PaymentExtendedKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash PaymentExtendedKey) -> ByteString -> Either DecoderError (Hash PaymentExtendedKey) Source # | |||||||||
SerialiseAsCBOR (SigningKey PaymentExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
SerialiseAsCBOR (VerificationKey PaymentExtendedKey) Source # | |||||||||
SerialiseAsBech32 (SigningKey PaymentExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey PaymentExtendedKey -> Text bech32PrefixesPermitted :: AsType (SigningKey PaymentExtendedKey) -> [Text] | |||||||||
SerialiseAsBech32 (VerificationKey PaymentExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey PaymentExtendedKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey PaymentExtendedKey) -> [Text] | |||||||||
SerialiseAsRawBytes (Hash PaymentExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
SerialiseAsRawBytes (SigningKey PaymentExtendedKey) Source # | |||||||||
SerialiseAsRawBytes (VerificationKey PaymentExtendedKey) Source # | |||||||||
HasTextEnvelope (SigningKey PaymentExtendedKey) Source # | |||||||||
HasTextEnvelope (VerificationKey PaymentExtendedKey) Source # | |||||||||
FromCBOR (Hash PaymentExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
FromCBOR (SigningKey PaymentExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey PaymentExtendedKey) Source # label :: Proxy (SigningKey PaymentExtendedKey) -> Text Source # | |||||||||
FromCBOR (VerificationKey PaymentExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey PaymentExtendedKey) Source # label :: Proxy (VerificationKey PaymentExtendedKey) -> Text Source # | |||||||||
ToCBOR (Hash PaymentExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
ToCBOR (SigningKey PaymentExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey PaymentExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey PaymentExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey PaymentExtendedKey] -> Size Source # | |||||||||
ToCBOR (VerificationKey PaymentExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey PaymentExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey PaymentExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey PaymentExtendedKey] -> Size Source # | |||||||||
Eq (Hash PaymentExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # (/=) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # | |||||||||
Eq (VerificationKey PaymentExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
Ord (Hash PaymentExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Ordering Source # (<) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # (<=) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # (>) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # (>=) :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Bool Source # max :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Hash PaymentExtendedKey Source # min :: Hash PaymentExtendedKey -> Hash PaymentExtendedKey -> Hash PaymentExtendedKey Source # | |||||||||
data AsType PaymentExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
newtype Hash PaymentExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
newtype SigningKey PaymentExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
newtype VerificationKey PaymentExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley |
Addresses in any era
data AddressAny Source #
Either a Byron address or a Shelley address.
Sometimes we need to be able to work with either of the two types of address (Byron or Shelley addresses), but without reference to an era in which the address will be used. This type serves that purpose.
Constructors
AddressByron !(Address ByronAddr) | |
AddressShelley !(Address ShelleyAddr) |
Instances
Show AddressAny Source # | |||||
Defined in Cardano.Api.Internal.Address | |||||
SerialiseAddress AddressAny Source # | |||||
Defined in Cardano.Api.Internal.Address Methods serialiseAddress :: AddressAny -> Text Source # deserialiseAddress :: AsType AddressAny -> Text -> Maybe AddressAny Source # | |||||
HasTypeProxy AddressAny Source # | |||||
Defined in Cardano.Api.Internal.Address Associated Types
Methods proxyToAsType :: Proxy AddressAny -> AsType AddressAny Source # | |||||
SerialiseAsRawBytes AddressAny Source # | |||||
Defined in Cardano.Api.Internal.Address | |||||
Eq AddressAny Source # | |||||
Defined in Cardano.Api.Internal.Address Methods (==) :: AddressAny -> AddressAny -> Bool Source # (/=) :: AddressAny -> AddressAny -> Bool Source # | |||||
Ord AddressAny Source # | |||||
Defined in Cardano.Api.Internal.Address Methods compare :: AddressAny -> AddressAny -> Ordering Source # (<) :: AddressAny -> AddressAny -> Bool Source # (<=) :: AddressAny -> AddressAny -> Bool Source # (>) :: AddressAny -> AddressAny -> Bool Source # (>=) :: AddressAny -> AddressAny -> Bool Source # max :: AddressAny -> AddressAny -> AddressAny Source # min :: AddressAny -> AddressAny -> AddressAny Source # | |||||
data AsType AddressAny Source # | |||||
Defined in Cardano.Api.Internal.Address |
parseAddressAny :: SerialiseAddress addr => Parser addr Source #
Addresses in specific eras
data AddressInEra era where Source #
An Address
that can be used in a particular ledger era.
All current ledger eras support Byron addresses. Shelley addresses are
supported in the ShelleyEra
and later eras.
Constructors
AddressInEra :: forall addrtype era. AddressTypeInEra addrtype era -> Address addrtype -> AddressInEra era |
Instances
IsShelleyBasedEra era => FromJSON (AddressInEra era) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods parseJSON :: Value -> Parser (AddressInEra era) parseJSONList :: Value -> Parser [AddressInEra era] omittedField :: Maybe (AddressInEra era) | |||||
IsCardanoEra era => ToJSON (AddressInEra era) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods toJSON :: AddressInEra era -> Value toEncoding :: AddressInEra era -> Encoding toJSONList :: [AddressInEra era] -> Value toEncodingList :: [AddressInEra era] -> Encoding omitField :: AddressInEra era -> Bool | |||||
Show (AddressInEra era) Source # | |||||
Defined in Cardano.Api.Internal.Address | |||||
IsCardanoEra era => SerialiseAddress (AddressInEra era) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods serialiseAddress :: AddressInEra era -> Text Source # deserialiseAddress :: AsType (AddressInEra era) -> Text -> Maybe (AddressInEra era) Source # | |||||
HasTypeProxy era => HasTypeProxy (AddressInEra era) Source # | |||||
Defined in Cardano.Api.Internal.Address Associated Types
Methods proxyToAsType :: Proxy (AddressInEra era) -> AsType (AddressInEra era) Source # | |||||
IsCardanoEra era => SerialiseAsRawBytes (AddressInEra era) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods serialiseToRawBytes :: AddressInEra era -> ByteString Source # deserialiseFromRawBytes :: AsType (AddressInEra era) -> ByteString -> Either SerialiseAsRawBytesError (AddressInEra era) Source # | |||||
NFData (AddressInEra era) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods rnf :: AddressInEra era -> () Source # | |||||
Eq (AddressInEra era) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods (==) :: AddressInEra era -> AddressInEra era -> Bool Source # (/=) :: AddressInEra era -> AddressInEra era -> Bool Source # | |||||
Ord (AddressInEra era) Source # | |||||
Defined in Cardano.Api.Internal.Address Methods compare :: AddressInEra era -> AddressInEra era -> Ordering Source # (<) :: AddressInEra era -> AddressInEra era -> Bool Source # (<=) :: AddressInEra era -> AddressInEra era -> Bool Source # (>) :: AddressInEra era -> AddressInEra era -> Bool Source # (>=) :: AddressInEra era -> AddressInEra era -> Bool Source # max :: AddressInEra era -> AddressInEra era -> AddressInEra era Source # min :: AddressInEra era -> AddressInEra era -> AddressInEra era Source # | |||||
data AsType (AddressInEra era) Source # | |||||
Defined in Cardano.Api.Internal.Address |
isKeyAddress :: AddressInEra era -> Bool Source #
Is the UTxO at the address only spendable via a key witness.
data AddressTypeInEra addrtype era where Source #
Constructors
ByronAddressInAnyEra :: forall era. AddressTypeInEra ByronAddr era | |
ShelleyAddressInEra :: forall era. ShelleyBasedEra era -> AddressTypeInEra ShelleyAddr era |
Instances
Show (AddressTypeInEra addrtype era) Source # | |
Defined in Cardano.Api.Internal.Address | |
NFData (AddressTypeInEra addrtype era) Source # | |
Defined in Cardano.Api.Internal.Address Methods rnf :: AddressTypeInEra addrtype era -> () Source # |
byronAddressInEra :: Address ByronAddr -> AddressInEra era Source #
shelleyAddressInEra :: ShelleyBasedEra era -> Address ShelleyAddr -> AddressInEra era Source #
anyAddressInShelleyBasedEra :: ShelleyBasedEra era -> AddressAny -> AddressInEra era Source #
anyAddressInEra :: CardanoEra era -> AddressAny -> Either String (AddressInEra era) Source #
toAddressAny :: Address addr -> AddressAny Source #
makeByronAddressInEra :: NetworkId -> VerificationKey ByronKey -> AddressInEra era Source #
makeShelleyAddressInEra :: ShelleyBasedEra era -> NetworkId -> PaymentCredential -> StakeAddressReference -> AddressInEra era Source #
Stake addresses
Constructing and inspecting stake addresses
data StakeAddress Source #
Instances
FromJSON StakeAddress Source # | |||||
Defined in Cardano.Api.Internal.Address | |||||
ToJSON StakeAddress Source # | |||||
Defined in Cardano.Api.Internal.Address Methods toJSON :: StakeAddress -> Value toEncoding :: StakeAddress -> Encoding toJSONList :: [StakeAddress] -> Value toEncodingList :: [StakeAddress] -> Encoding omitField :: StakeAddress -> Bool | |||||
Show StakeAddress Source # | |||||
Defined in Cardano.Api.Internal.Address | |||||
SerialiseAddress StakeAddress Source # | |||||
Defined in Cardano.Api.Internal.Address Methods serialiseAddress :: StakeAddress -> Text Source # deserialiseAddress :: AsType StakeAddress -> Text -> Maybe StakeAddress Source # | |||||
HasTypeProxy StakeAddress Source # | |||||
Defined in Cardano.Api.Internal.Address Associated Types
Methods proxyToAsType :: Proxy StakeAddress -> AsType StakeAddress Source # | |||||
SerialiseAsBech32 StakeAddress Source # | |||||
Defined in Cardano.Api.Internal.Address Methods bech32PrefixFor :: StakeAddress -> Text | |||||
SerialiseAsRawBytes StakeAddress Source # | |||||
Defined in Cardano.Api.Internal.Address | |||||
Eq StakeAddress Source # | |||||
Defined in Cardano.Api.Internal.Address Methods (==) :: StakeAddress -> StakeAddress -> Bool Source # (/=) :: StakeAddress -> StakeAddress -> Bool Source # | |||||
Ord StakeAddress Source # | |||||
Defined in Cardano.Api.Internal.Address Methods compare :: StakeAddress -> StakeAddress -> Ordering Source # (<) :: StakeAddress -> StakeAddress -> Bool Source # (<=) :: StakeAddress -> StakeAddress -> Bool Source # (>) :: StakeAddress -> StakeAddress -> Bool Source # (>=) :: StakeAddress -> StakeAddress -> Bool Source # max :: StakeAddress -> StakeAddress -> StakeAddress Source # min :: StakeAddress -> StakeAddress -> StakeAddress Source # | |||||
data AsType StakeAddress Source # | |||||
Defined in Cardano.Api.Internal.Address |
data StakeCredential Source #
Instances
ToJSON StakeCredential Source # | |
Defined in Cardano.Api.Internal.Address Methods toJSON :: StakeCredential -> Value toEncoding :: StakeCredential -> Encoding toJSONList :: [StakeCredential] -> Value toEncodingList :: [StakeCredential] -> Encoding omitField :: StakeCredential -> Bool | |
Show StakeCredential Source # | |
Defined in Cardano.Api.Internal.Address | |
Eq StakeCredential Source # | |
Defined in Cardano.Api.Internal.Address Methods (==) :: StakeCredential -> StakeCredential -> Bool Source # (/=) :: StakeCredential -> StakeCredential -> Bool Source # | |
Ord StakeCredential Source # | |
Defined in Cardano.Api.Internal.Address Methods compare :: StakeCredential -> StakeCredential -> Ordering Source # (<) :: StakeCredential -> StakeCredential -> Bool Source # (<=) :: StakeCredential -> StakeCredential -> Bool Source # (>) :: StakeCredential -> StakeCredential -> Bool Source # (>=) :: StakeCredential -> StakeCredential -> Bool Source # max :: StakeCredential -> StakeCredential -> StakeCredential Source # min :: StakeCredential -> StakeCredential -> StakeCredential Source # |
stakeAddressCredential :: StakeAddress -> StakeCredential Source #
Get a stake credential from a stake address. This drops the network information.
Instances
HasTypeProxy StakeKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
| |||||||||
Key StakeKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey StakeKey -> VerificationKey StakeKey Source # deterministicSigningKey :: AsType StakeKey -> Seed -> SigningKey StakeKey Source # deterministicSigningKeySeedSize :: AsType StakeKey -> Word Source # verificationKeyHash :: VerificationKey StakeKey -> Hash StakeKey Source # | |||||||||
IsString (Hash StakeKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
IsString (SigningKey StakeKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey StakeKey Source # | |||||||||
IsString (VerificationKey StakeKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods | |||||||||
Show (Hash StakeKey) Source # | |||||||||
Show (SigningKey StakeKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
Show (VerificationKey StakeKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
SerialiseAsCBOR (Hash StakeKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash StakeKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash StakeKey) -> ByteString -> Either DecoderError (Hash StakeKey) Source # | |||||||||
SerialiseAsCBOR (SigningKey StakeKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey StakeKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey StakeKey) -> ByteString -> Either DecoderError (SigningKey StakeKey) Source # | |||||||||
SerialiseAsCBOR (VerificationKey StakeKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: VerificationKey StakeKey -> ByteString Source # deserialiseFromCBOR :: AsType (VerificationKey StakeKey) -> ByteString -> Either DecoderError (VerificationKey StakeKey) Source # | |||||||||
SerialiseAsBech32 (SigningKey StakeKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey StakeKey -> Text bech32PrefixesPermitted :: AsType (SigningKey StakeKey) -> [Text] | |||||||||
SerialiseAsBech32 (VerificationKey StakeKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey StakeKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey StakeKey) -> [Text] | |||||||||
SerialiseAsRawBytes (Hash StakeKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToRawBytes :: Hash StakeKey -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash StakeKey) -> ByteString -> Either SerialiseAsRawBytesError (Hash StakeKey) Source # | |||||||||
SerialiseAsRawBytes (SigningKey StakeKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
SerialiseAsRawBytes (VerificationKey StakeKey) Source # | |||||||||
HasTextEnvelope (SigningKey StakeKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
HasTextEnvelope (VerificationKey StakeKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
FromCBOR (Hash StakeKey) Source # | |||||||||
FromCBOR (SigningKey StakeKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
FromCBOR (VerificationKey StakeKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
ToCBOR (Hash StakeKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
ToCBOR (SigningKey StakeKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
ToCBOR (VerificationKey StakeKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
Eq (Hash StakeKey) Source # | |||||||||
Eq (VerificationKey StakeKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey StakeKey -> VerificationKey StakeKey -> Bool Source # (/=) :: VerificationKey StakeKey -> VerificationKey StakeKey -> Bool Source # | |||||||||
Ord (Hash StakeKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash StakeKey -> Hash StakeKey -> Ordering Source # (<) :: Hash StakeKey -> Hash StakeKey -> Bool Source # (<=) :: Hash StakeKey -> Hash StakeKey -> Bool Source # (>) :: Hash StakeKey -> Hash StakeKey -> Bool Source # (>=) :: Hash StakeKey -> Hash StakeKey -> Bool Source # max :: Hash StakeKey -> Hash StakeKey -> Hash StakeKey Source # min :: Hash StakeKey -> Hash StakeKey -> Hash StakeKey Source # | |||||||||
data AsType StakeKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
newtype Hash StakeKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
newtype SigningKey StakeKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
newtype VerificationKey StakeKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley |
data StakeExtendedKey Source #
Shelley-era stake keys using extended ed25519 cryptographic keys.
They can be used for Shelley stake addresses and witnessing transactions that use stake addresses.
These extended keys are used by HD wallets. So this type provides interoperability with HD wallets. The ITN CLI also supported this key type.
The extended verification keys can be converted (via castVerificationKey
)
to ordinary keys (i.e. VerificationKey
StakeKey
) but this is not the
case for the signing keys. The signing keys can be used to witness
transactions directly, with verification via their non-extended verification
key (VerificationKey
StakeKey
).
This is a type level tag, used with other interfaces like Key
.
Instances
HasTypeProxy StakeExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods proxyToAsType :: Proxy StakeExtendedKey -> AsType StakeExtendedKey Source # | |||||||||
Key StakeExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Associated Types
Methods getVerificationKey :: SigningKey StakeExtendedKey -> VerificationKey StakeExtendedKey Source # deterministicSigningKey :: AsType StakeExtendedKey -> Seed -> SigningKey StakeExtendedKey Source # deterministicSigningKeySeedSize :: AsType StakeExtendedKey -> Word Source # verificationKeyHash :: VerificationKey StakeExtendedKey -> Hash StakeExtendedKey Source # | |||||||||
IsString (Hash StakeExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> Hash StakeExtendedKey Source # | |||||||||
IsString (SigningKey StakeExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> SigningKey StakeExtendedKey Source # | |||||||||
IsString (VerificationKey StakeExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromString :: String -> VerificationKey StakeExtendedKey Source # | |||||||||
Show (Hash StakeExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
Show (SigningKey StakeExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> SigningKey StakeExtendedKey -> ShowS Source # show :: SigningKey StakeExtendedKey -> String Source # showList :: [SigningKey StakeExtendedKey] -> ShowS Source # | |||||||||
Show (VerificationKey StakeExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods showsPrec :: Int -> VerificationKey StakeExtendedKey -> ShowS Source # show :: VerificationKey StakeExtendedKey -> String Source # showList :: [VerificationKey StakeExtendedKey] -> ShowS Source # | |||||||||
SerialiseAsCBOR (Hash StakeExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash StakeExtendedKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash StakeExtendedKey) -> ByteString -> Either DecoderError (Hash StakeExtendedKey) Source # | |||||||||
SerialiseAsCBOR (SigningKey StakeExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
SerialiseAsCBOR (VerificationKey StakeExtendedKey) Source # | |||||||||
SerialiseAsBech32 (SigningKey StakeExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: SigningKey StakeExtendedKey -> Text bech32PrefixesPermitted :: AsType (SigningKey StakeExtendedKey) -> [Text] | |||||||||
SerialiseAsBech32 (VerificationKey StakeExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods bech32PrefixFor :: VerificationKey StakeExtendedKey -> Text bech32PrefixesPermitted :: AsType (VerificationKey StakeExtendedKey) -> [Text] | |||||||||
SerialiseAsRawBytes (Hash StakeExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
SerialiseAsRawBytes (SigningKey StakeExtendedKey) Source # | |||||||||
SerialiseAsRawBytes (VerificationKey StakeExtendedKey) Source # | |||||||||
HasTextEnvelope (SigningKey StakeExtendedKey) Source # | |||||||||
HasTextEnvelope (VerificationKey StakeExtendedKey) Source # | |||||||||
FromCBOR (Hash StakeExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
FromCBOR (SigningKey StakeExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (SigningKey StakeExtendedKey) Source # label :: Proxy (SigningKey StakeExtendedKey) -> Text Source # | |||||||||
FromCBOR (VerificationKey StakeExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods fromCBOR :: Decoder s (VerificationKey StakeExtendedKey) Source # label :: Proxy (VerificationKey StakeExtendedKey) -> Text Source # | |||||||||
ToCBOR (Hash StakeExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
ToCBOR (SigningKey StakeExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: SigningKey StakeExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey StakeExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey StakeExtendedKey] -> Size Source # | |||||||||
ToCBOR (VerificationKey StakeExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods toCBOR :: VerificationKey StakeExtendedKey -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey StakeExtendedKey) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey StakeExtendedKey] -> Size Source # | |||||||||
Eq (Hash StakeExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # (/=) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # | |||||||||
Eq (VerificationKey StakeExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods (==) :: VerificationKey StakeExtendedKey -> VerificationKey StakeExtendedKey -> Bool Source # (/=) :: VerificationKey StakeExtendedKey -> VerificationKey StakeExtendedKey -> Bool Source # | |||||||||
Ord (Hash StakeExtendedKey) Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley Methods compare :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Ordering Source # (<) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # (<=) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # (>) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # (>=) :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Bool Source # max :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Hash StakeExtendedKey Source # min :: Hash StakeExtendedKey -> Hash StakeExtendedKey -> Hash StakeExtendedKey Source # | |||||||||
data AsType StakeExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
newtype Hash StakeExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
newtype SigningKey StakeExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley | |||||||||
newtype VerificationKey StakeExtendedKey Source # | |||||||||
Defined in Cardano.Api.Internal.Keys.Shelley |
Multi-asset values
Instances
FromJSON Quantity Source # | |
Defined in Cardano.Api.Internal.Value | |
ToJSON Quantity Source # | |
Defined in Cardano.Api.Internal.Value Methods toEncoding :: Quantity -> Encoding toJSONList :: [Quantity] -> Value toEncodingList :: [Quantity] -> Encoding | |
Data Quantity Source # | |
Defined in Cardano.Api.Internal.Value Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Quantity -> c Quantity Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Quantity Source # toConstr :: Quantity -> Constr Source # dataTypeOf :: Quantity -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Quantity) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Quantity) Source # gmapT :: (forall b. Data b => b -> b) -> Quantity -> Quantity Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Quantity -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Quantity -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Quantity -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Quantity -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Quantity -> m Quantity Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Quantity -> m Quantity Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Quantity -> m Quantity Source # | |
Monoid Quantity Source # | |
Semigroup Quantity Source # | |
Num Quantity Source # | |
Defined in Cardano.Api.Internal.Value Methods (+) :: Quantity -> Quantity -> Quantity Source # (-) :: Quantity -> Quantity -> Quantity Source # (*) :: Quantity -> Quantity -> Quantity Source # negate :: Quantity -> Quantity Source # abs :: Quantity -> Quantity Source # signum :: Quantity -> Quantity Source # fromInteger :: Integer -> Quantity Source # | |
Show Quantity Source # | |
Eq Quantity Source # | |
Ord Quantity Source # | |
Defined in Cardano.Api.Internal.Value |
Constructors
PolicyId | |
Fields |
Instances
FromJSON PolicyId Source # | |||||
Defined in Cardano.Api.Internal.Value | |||||
ToJSON PolicyId Source # | |||||
Defined in Cardano.Api.Internal.Value Methods toEncoding :: PolicyId -> Encoding toJSONList :: [PolicyId] -> Value toEncodingList :: [PolicyId] -> Encoding | |||||
IsString PolicyId Source # | |||||
Defined in Cardano.Api.Internal.Value Methods fromString :: String -> PolicyId Source # | |||||
Show PolicyId Source # | |||||
HasTypeProxy PolicyId Source # | |||||
Defined in Cardano.Api.Internal.Value Associated Types
| |||||
SerialiseAsRawBytes PolicyId Source # | |||||
Defined in Cardano.Api.Internal.Value Methods serialiseToRawBytes :: PolicyId -> ByteString Source # deserialiseFromRawBytes :: AsType PolicyId -> ByteString -> Either SerialiseAsRawBytesError PolicyId Source # | |||||
Eq PolicyId Source # | |||||
Ord PolicyId Source # | |||||
Defined in Cardano.Api.Internal.Value | |||||
data AsType PolicyId Source # | |||||
Defined in Cardano.Api.Internal.Value |
scriptPolicyId :: Script lang -> PolicyId Source #
Constructors
AssetName ByteString |
Instances
FromJSON AssetName Source # | |||||
Defined in Cardano.Api.Internal.Value | |||||
FromJSONKey AssetName Source # | |||||
Defined in Cardano.Api.Internal.Value Methods fromJSONKey :: FromJSONKeyFunction AssetName fromJSONKeyList :: FromJSONKeyFunction [AssetName] | |||||
ToJSON AssetName Source # | |||||
Defined in Cardano.Api.Internal.Value Methods toEncoding :: AssetName -> Encoding toJSONList :: [AssetName] -> Value toEncodingList :: [AssetName] -> Encoding | |||||
ToJSONKey AssetName Source # | |||||
Defined in Cardano.Api.Internal.Value | |||||
IsString AssetName Source # | |||||
Defined in Cardano.Api.Internal.Value Methods fromString :: String -> AssetName Source # | |||||
Show AssetName Source # | |||||
HasTypeProxy AssetName Source # | |||||
Defined in Cardano.Api.Internal.Value Associated Types
| |||||
SerialiseAsRawBytes AssetName Source # | |||||
Defined in Cardano.Api.Internal.Value | |||||
Eq AssetName Source # | |||||
Ord AssetName Source # | |||||
Defined in Cardano.Api.Internal.Value | |||||
data AsType AssetName Source # | |||||
Defined in Cardano.Api.Internal.Value |
Constructors
AdaAssetId | |
AssetId !PolicyId !AssetName |
Instances
Show AssetId Source # | |
Eq AssetId Source # | |
Ord AssetId Source # | |
Defined in Cardano.Api.Internal.Value |
Instances
FromJSON Value Source # | |
Defined in Cardano.Api.Internal.Value | |
ToJSON Value Source # | |
Defined in Cardano.Api.Internal.Value Methods toEncoding :: Value -> Encoding toJSONList :: [Value] -> Value toEncodingList :: [Value] -> Encoding | |
Monoid Value Source # | |
Semigroup Value Source # | |
IsList Value Source # | |
Show Value Source # | |
Eq Value Source # | |
type Item Value Source # | |
Defined in Cardano.Api.Internal.Value |
parsePolicyId :: Parser PolicyId Source #
Policy ID parser.
parseAssetName :: Parser AssetName Source #
Asset name parser.
parseTxOutMultiAssetValue :: Parser Value Source #
Parse a Value
from its string representation. The resulting amounts must be positive for the parser
to succeed.
parseMintingMultiAssetValue :: MaryEraOnwards era -> Parser MultiAsset Source #
Parse a MintValue
from its string representation. The string representation cannot contain ADA.
parseUTxOValue :: Parser Value Source #
Parse a Value
from its string representation. The resulting amounts must be positive for the parser
to succeed.
negateValue :: Value -> Value Source #
This lets you write a - b
as a <> negateValue b
.
newtype ValueNestedRep Source #
Constructors
ValueNestedRep [ValueNestedBundle] |
Instances
FromJSON ValueNestedRep Source # | |
Defined in Cardano.Api.Internal.Value | |
ToJSON ValueNestedRep Source # | |
Defined in Cardano.Api.Internal.Value Methods toJSON :: ValueNestedRep -> Value toEncoding :: ValueNestedRep -> Encoding toJSONList :: [ValueNestedRep] -> Value toEncodingList :: [ValueNestedRep] -> Encoding omitField :: ValueNestedRep -> Bool | |
Show ValueNestedRep Source # | |
Defined in Cardano.Api.Internal.Value | |
Eq ValueNestedRep Source # | |
Defined in Cardano.Api.Internal.Value Methods (==) :: ValueNestedRep -> ValueNestedRep -> Bool Source # (/=) :: ValueNestedRep -> ValueNestedRep -> Bool Source # | |
Ord ValueNestedRep Source # | |
Defined in Cardano.Api.Internal.Value Methods compare :: ValueNestedRep -> ValueNestedRep -> Ordering Source # (<) :: ValueNestedRep -> ValueNestedRep -> Bool Source # (<=) :: ValueNestedRep -> ValueNestedRep -> Bool Source # (>) :: ValueNestedRep -> ValueNestedRep -> Bool Source # (>=) :: ValueNestedRep -> ValueNestedRep -> Bool Source # max :: ValueNestedRep -> ValueNestedRep -> ValueNestedRep Source # min :: ValueNestedRep -> ValueNestedRep -> ValueNestedRep Source # |
data ValueNestedBundle Source #
A bundle within a ValueNestedRep
for a single PolicyId
, or for the
special case of ada.
Constructors
ValueNestedBundleAda Quantity | |
ValueNestedBundle PolicyId (Map AssetName Quantity) |
Instances
Show ValueNestedBundle Source # | |
Defined in Cardano.Api.Internal.Value | |
Eq ValueNestedBundle Source # | |
Defined in Cardano.Api.Internal.Value Methods (==) :: ValueNestedBundle -> ValueNestedBundle -> Bool Source # (/=) :: ValueNestedBundle -> ValueNestedBundle -> Bool Source # | |
Ord ValueNestedBundle Source # | |
Defined in Cardano.Api.Internal.Value Methods compare :: ValueNestedBundle -> ValueNestedBundle -> Ordering Source # (<) :: ValueNestedBundle -> ValueNestedBundle -> Bool Source # (<=) :: ValueNestedBundle -> ValueNestedBundle -> Bool Source # (>) :: ValueNestedBundle -> ValueNestedBundle -> Bool Source # (>=) :: ValueNestedBundle -> ValueNestedBundle -> Bool Source # max :: ValueNestedBundle -> ValueNestedBundle -> ValueNestedBundle Source # min :: ValueNestedBundle -> ValueNestedBundle -> ValueNestedBundle Source # |
renderMultiAsset :: MultiAsset -> Text Source #
toLedgerValue :: MaryEraOnwards era -> Value -> Value (ShelleyLedgerEra era) Source #
fromLedgerValue :: ShelleyBasedEra era -> Value (ShelleyLedgerEra era) -> Value Source #
newtype PolicyAssets Source #
Map of non-ADA assets with their quantity, for a single policy
Constructors
PolicyAssets (Map AssetName Quantity) |
Instances
Monoid PolicyAssets Source # | |||||
Defined in Cardano.Api.Internal.Value Methods mempty :: PolicyAssets Source # mappend :: PolicyAssets -> PolicyAssets -> PolicyAssets Source # mconcat :: [PolicyAssets] -> PolicyAssets Source # | |||||
Semigroup PolicyAssets Source # | |||||
Defined in Cardano.Api.Internal.Value Methods (<>) :: PolicyAssets -> PolicyAssets -> PolicyAssets Source # sconcat :: NonEmpty PolicyAssets -> PolicyAssets Source # stimes :: Integral b => b -> PolicyAssets -> PolicyAssets Source # | |||||
IsList PolicyAssets Source # | |||||
Defined in Cardano.Api.Internal.Value Associated Types
Methods fromList :: [Item PolicyAssets] -> PolicyAssets Source # fromListN :: Int -> [Item PolicyAssets] -> PolicyAssets Source # toList :: PolicyAssets -> [Item PolicyAssets] Source # | |||||
Show PolicyAssets Source # | |||||
Defined in Cardano.Api.Internal.Value | |||||
Eq PolicyAssets Source # | |||||
Defined in Cardano.Api.Internal.Value Methods (==) :: PolicyAssets -> PolicyAssets -> Bool Source # (/=) :: PolicyAssets -> PolicyAssets -> Bool Source # | |||||
MonoFunctor PolicyAssets Source # | |||||
Defined in Cardano.Api.Internal.Value Methods omap :: (Element PolicyAssets -> Element PolicyAssets) -> PolicyAssets -> PolicyAssets | |||||
type Item PolicyAssets Source # | |||||
Defined in Cardano.Api.Internal.Value | |||||
type Element PolicyAssets Source # | |||||
Defined in Cardano.Api.Internal.Value |
policyAssetsToValue :: PolicyId -> PolicyAssets -> Value Source #
valueToPolicyAssets :: Value -> Map PolicyId PolicyAssets Source #
Converts Value
to PolicyAssets
. Discards any ADA value stored in Value
.
multiAssetToPolicyAssets :: MultiAsset -> Map PolicyId PolicyAssets Source #
Convert cardano-ledger's MultiAsset
to a map of PolicyAssets
Ada / Lovelace within multi-asset values
selectLovelace :: Value -> Lovelace Source #
lovelaceToValue :: Lovelace -> Value Source #
valueToLovelace :: Value -> Maybe Lovelace Source #
Check if the Value
consists of only Lovelace
and no other assets,
and if so then return the Lovelace
See also selectLovelace
to select the Lovelace quantity from the Value,
ignoring other assets.
Blocks
Blocks in the context of an era
Deprecated: Use getBlockHeader instead
A blockchain block in a particular Cardano era.
Constructors
ByronBlock :: ByronBlock -> Block ByronEra | |
ShelleyBlock :: forall era. ShelleyBasedEra era -> ShelleyBlock (ConsensusProtocol era) (ShelleyLedgerEra era) -> Block era |
pattern Block :: BlockHeader -> [Tx era] -> Block era Source #
Deprecated: Use getBlockHeader instead
A block consists of a header and a body containing transactions.
data BlockHeader Source #
Constructors
BlockHeader !SlotNo !(Hash BlockHeader) !BlockNo |
Instances
HasTypeProxy BlockHeader Source # | |||||
Defined in Cardano.Api.Internal.Block Associated Types
Methods proxyToAsType :: Proxy BlockHeader -> AsType BlockHeader Source # | |||||
FromJSON (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods parseJSON :: Value -> Parser (Hash BlockHeader) parseJSONList :: Value -> Parser [Hash BlockHeader] omittedField :: Maybe (Hash BlockHeader) | |||||
ToJSON (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods toJSON :: Hash BlockHeader -> Value toEncoding :: Hash BlockHeader -> Encoding toJSONList :: [Hash BlockHeader] -> Value toEncodingList :: [Hash BlockHeader] -> Encoding omitField :: Hash BlockHeader -> Bool | |||||
IsString (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods fromString :: String -> Hash BlockHeader Source # | |||||
Show (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block | |||||
SerialiseAsRawBytes (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods serialiseToRawBytes :: Hash BlockHeader -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash BlockHeader) -> ByteString -> Either SerialiseAsRawBytesError (Hash BlockHeader) Source # | |||||
Eq (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods (==) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # (/=) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # | |||||
Ord (Hash BlockHeader) Source # | |||||
Defined in Cardano.Api.Internal.Block Methods compare :: Hash BlockHeader -> Hash BlockHeader -> Ordering Source # (<) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # (<=) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # (>) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # (>=) :: Hash BlockHeader -> Hash BlockHeader -> Bool Source # max :: Hash BlockHeader -> Hash BlockHeader -> Hash BlockHeader Source # min :: Hash BlockHeader -> Hash BlockHeader -> Hash BlockHeader Source # | |||||
data AsType BlockHeader Source # | |||||
Defined in Cardano.Api.Internal.Block | |||||
newtype Hash BlockHeader Source # | For now at least we use a fixed concrete hash type for all modes and era. The different eras do use different types, but it's all the same underlying representation. | ||||
Defined in Cardano.Api.Internal.Block |
getBlockHeader :: Block era -> BlockHeader Source #
getBlockTxs :: Block era -> [Tx era] Source #
Points on the chain
data ChainPoint Source #
Constructors
ChainPointAtGenesis | |
ChainPoint !SlotNo !(Hash BlockHeader) |
Instances
FromJSON ChainPoint Source # | |
Defined in Cardano.Api.Internal.Block | |
ToJSON ChainPoint Source # | |
Defined in Cardano.Api.Internal.Block Methods toJSON :: ChainPoint -> Value toEncoding :: ChainPoint -> Encoding toJSONList :: [ChainPoint] -> Value toEncodingList :: [ChainPoint] -> Encoding omitField :: ChainPoint -> Bool | |
Show ChainPoint Source # | |
Defined in Cardano.Api.Internal.Block | |
Eq ChainPoint Source # | |
Defined in Cardano.Api.Internal.Block Methods (==) :: ChainPoint -> ChainPoint -> Bool Source # (/=) :: ChainPoint -> ChainPoint -> Bool Source # | |
Ord ChainPoint Source # | |
Defined in Cardano.Api.Internal.Block Methods compare :: ChainPoint -> ChainPoint -> Ordering Source # (<) :: ChainPoint -> ChainPoint -> Bool Source # (<=) :: ChainPoint -> ChainPoint -> Bool Source # (>) :: ChainPoint -> ChainPoint -> Bool Source # (>=) :: ChainPoint -> ChainPoint -> Bool Source # max :: ChainPoint -> ChainPoint -> ChainPoint Source # min :: ChainPoint -> ChainPoint -> ChainPoint Source # |
An epoch, i.e. the number of the epoch.
Instances
FromJSON EpochNo | |||||
Defined in Cardano.Slotting.Slot | |||||
ToJSON EpochNo | |||||
Defined in Cardano.Slotting.Slot Methods toEncoding :: EpochNo -> Encoding toJSONList :: [EpochNo] -> Value toEncodingList :: [EpochNo] -> Encoding | |||||
Enum EpochNo | |||||
Defined in Cardano.Slotting.Slot Methods succ :: EpochNo -> EpochNo Source # pred :: EpochNo -> EpochNo Source # toEnum :: Int -> EpochNo Source # fromEnum :: EpochNo -> Int Source # enumFrom :: EpochNo -> [EpochNo] Source # enumFromThen :: EpochNo -> EpochNo -> [EpochNo] Source # enumFromTo :: EpochNo -> EpochNo -> [EpochNo] Source # enumFromThenTo :: EpochNo -> EpochNo -> EpochNo -> [EpochNo] Source # | |||||
Generic EpochNo | |||||
Defined in Cardano.Slotting.Slot Associated Types
| |||||
Show EpochNo | |||||
FromCBOR EpochNo | |||||
ToCBOR EpochNo | |||||
DecCBOR EpochNo | |||||
EncCBOR EpochNo | |||||
NFData EpochNo | |||||
Defined in Cardano.Slotting.Slot | |||||
Eq EpochNo | |||||
Ord EpochNo | |||||
Defined in Cardano.Slotting.Slot | |||||
NoThunks EpochNo | |||||
Condense EpochNo | |||||
Serialise EpochNo | |||||
Defined in Cardano.Slotting.Slot | |||||
type Rep EpochNo | |||||
Defined in Cardano.Slotting.Slot type Rep EpochNo = D1 ('MetaData "EpochNo" "Cardano.Slotting.Slot" "cardano-slotting-0.2.0.0-1062762da5e24b3256026b7bf7ed7ea570deea61ae8ec963e4334bb658f0121b" 'True) (C1 ('MetaCons "EpochNo" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEpochNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64))) |
Tip of the chain
This is like a ChainPoint
but is conventionally used for the tip of the
chain: that is the most recent block at the end of the chain.
It also carries the BlockNo
of the chain tip.
Constructors
ChainTipAtGenesis | |
ChainTip !SlotNo !(Hash BlockHeader) !BlockNo |
Instances
ToJSON ChainTip Source # | |
Defined in Cardano.Api.Internal.Block Methods toEncoding :: ChainTip -> Encoding toJSONList :: [ChainTip] -> Value toEncodingList :: [ChainTip] -> Encoding | |
Show ChainTip Source # | |
Eq ChainTip Source # | |
The 0-based index of the block in the blockchain. BlockNo is <= SlotNo and is only equal at slot N if there is a block for every slot where N <= SlotNo.
Instances
FromJSON BlockNo | |||||
Defined in Cardano.Slotting.Block | |||||
ToJSON BlockNo | |||||
Defined in Cardano.Slotting.Block Methods toEncoding :: BlockNo -> Encoding toJSONList :: [BlockNo] -> Value toEncodingList :: [BlockNo] -> Encoding | |||||
Bounded BlockNo | |||||
Enum BlockNo | |||||
Defined in Cardano.Slotting.Block Methods succ :: BlockNo -> BlockNo Source # pred :: BlockNo -> BlockNo Source # toEnum :: Int -> BlockNo Source # fromEnum :: BlockNo -> Int Source # enumFrom :: BlockNo -> [BlockNo] Source # enumFromThen :: BlockNo -> BlockNo -> [BlockNo] Source # enumFromTo :: BlockNo -> BlockNo -> [BlockNo] Source # enumFromThenTo :: BlockNo -> BlockNo -> BlockNo -> [BlockNo] Source # | |||||
Generic BlockNo | |||||
Defined in Cardano.Slotting.Block Associated Types
| |||||
Num BlockNo | |||||
Defined in Cardano.Slotting.Block | |||||
Show BlockNo | |||||
FromCBOR BlockNo | |||||
ToCBOR BlockNo | |||||
DecCBOR BlockNo | |||||
EncCBOR BlockNo | |||||
NFData BlockNo | |||||
Defined in Cardano.Slotting.Block | |||||
Eq BlockNo | |||||
Ord BlockNo | |||||
Defined in Cardano.Slotting.Block | |||||
NoThunks BlockNo | |||||
ChainOrder BlockNo | |||||
Defined in Ouroboros.Consensus.Protocol.Abstract Associated Types
Methods preferCandidate :: ChainOrderConfig BlockNo -> BlockNo -> BlockNo -> Bool Source # | |||||
Condense BlockNo | |||||
Serialise BlockNo | |||||
Defined in Cardano.Slotting.Block | |||||
type Rep BlockNo | |||||
Defined in Cardano.Slotting.Block type Rep BlockNo = D1 ('MetaData "BlockNo" "Cardano.Slotting.Block" "cardano-slotting-0.2.0.0-1062762da5e24b3256026b7bf7ed7ea570deea61ae8ec963e4334bb658f0121b" 'True) (C1 ('MetaCons "BlockNo" 'PrefixI 'True) (S1 ('MetaSel ('Just "unBlockNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64))) | |||||
type ChainOrderConfig BlockNo | |||||
Defined in Ouroboros.Consensus.Protocol.Abstract |
Building transactions
Building transactions
Constructing and inspecting transactions
Transaction bodies
data TxBody era where Source #
Constructors
ShelleyTxBody | |
Fields
|
Bundled Patterns
pattern TxBody :: TxBodyContent ViewTx era -> TxBody era | Deprecated: Use getTxBodyContent $ getTxBody instead |
Instances
Show (TxBody era) Source # | |||||
HasTypeProxy era => HasTypeProxy (TxBody era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Associated Types
| |||||
IsShelleyBasedEra era => SerialiseAsCBOR (TxBody era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Methods serialiseToCBOR :: TxBody era -> ByteString Source # deserialiseFromCBOR :: AsType (TxBody era) -> ByteString -> Either DecoderError (TxBody era) Source # | |||||
IsShelleyBasedEra era => HasTextEnvelope (TxBody era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Methods textEnvelopeType :: AsType (TxBody era) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: TxBody era -> TextEnvelopeDescr Source # | |||||
Eq (TxBody era) Source # | |||||
data AsType (TxBody era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign |
createTransactionBody :: HasCallStack => ShelleyBasedEra era -> TxBodyContent BuildTx era -> Either TxBodyError (TxBody era) Source #
createAndValidateTransactionBody :: ShelleyBasedEra era -> TxBodyContent BuildTx era -> Either TxBodyError (TxBody era) Source #
Deprecated: Use createTransactionBody instead
makeByronTransactionBody :: TxIns BuildTx ByronEra -> [TxOut CtxTx ByronEra] -> Either TxBodyError (Annotated Tx ByteString) Source #
data TxBodyContent build era Source #
Constructors
TxBodyContent | |
Fields
|
Instances
IsShelleyBasedEra era => Show (TxBodyContent build era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body | |
IsShelleyBasedEra era => Eq (TxBodyContent build era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods (==) :: TxBodyContent build era -> TxBodyContent build era -> Bool Source # (/=) :: TxBodyContent build era -> TxBodyContent build era -> Bool Source # |
getTxBodyContent :: TxBody era -> TxBodyContent ViewTx era Source #
Transaction body builders
defaultTxBodyContent :: ShelleyBasedEra era -> TxBodyContent BuildTx era Source #
defaultTxFee :: ShelleyBasedEra era -> TxFee era Source #
defaultTxValidityUpperBound :: ShelleyBasedEra era -> TxValidityUpperBound era Source #
setTxIns :: TxIns build era -> TxBodyContent build era -> TxBodyContent build era Source #
modTxIns :: (TxIns build era -> TxIns build era) -> TxBodyContent build era -> TxBodyContent build era Source #
addTxIns :: TxIns build era -> TxBodyContent build era -> TxBodyContent build era Source #
addTxIn :: (TxIn, BuildTxWith build (Witness WitCtxTxIn era)) -> TxBodyContent build era -> TxBodyContent build era Source #
setTxInsCollateral :: TxInsCollateral era -> TxBodyContent build era -> TxBodyContent build era Source #
modTxInsCollateral :: (TxInsCollateral era -> TxInsCollateral era) -> TxBodyContent build era -> TxBodyContent build era Source #
addTxInsCollateral :: IsAlonzoBasedEra era => [TxIn] -> TxBodyContent build era -> TxBodyContent build era Source #
addTxInCollateral :: IsAlonzoBasedEra era => TxIn -> TxBodyContent build era -> TxBodyContent build era Source #
setTxInsReference :: TxInsReference build era -> TxBodyContent build era -> TxBodyContent build era Source #
modTxInsReference :: (TxInsReference build era -> TxInsReference build era) -> TxBodyContent build era -> TxBodyContent build era Source #
addTxInsReference :: (Applicative (BuildTxWith build), IsBabbageBasedEra era) => [TxIn] -> Set HashableScriptData -> TxBodyContent build era -> TxBodyContent build era Source #
addTxInReference :: (Applicative (BuildTxWith build), IsBabbageBasedEra era) => TxIn -> Maybe HashableScriptData -> TxBodyContent build era -> TxBodyContent build era Source #
setTxOuts :: [TxOut CtxTx era] -> TxBodyContent build era -> TxBodyContent build era Source #
modTxOuts :: ([TxOut CtxTx era] -> [TxOut CtxTx era]) -> TxBodyContent build era -> TxBodyContent build era Source #
addTxOuts :: [TxOut CtxTx era] -> TxBodyContent build era -> TxBodyContent build era Source #
addTxOut :: TxOut CtxTx era -> TxBodyContent build era -> TxBodyContent build era Source #
setTxTotalCollateral :: TxTotalCollateral era -> TxBodyContent build era -> TxBodyContent build era Source #
modTxTotalCollateral :: (TxTotalCollateral era -> TxTotalCollateral era) -> TxBodyContent build era -> TxBodyContent build era Source #
setTxReturnCollateral :: TxReturnCollateral CtxTx era -> TxBodyContent build era -> TxBodyContent build era Source #
modTxReturnCollateral :: (TxReturnCollateral CtxTx era -> TxReturnCollateral CtxTx era) -> TxBodyContent build era -> TxBodyContent build era Source #
setTxFee :: TxFee era -> TxBodyContent build era -> TxBodyContent build era Source #
modTxFee :: (TxFee era -> TxFee era) -> TxBodyContent build era -> TxBodyContent build era Source #
setTxValidityLowerBound :: TxValidityLowerBound era -> TxBodyContent build era -> TxBodyContent build era Source #
modTxValidityLowerBound :: (TxValidityLowerBound era -> TxValidityLowerBound era) -> TxBodyContent build era -> TxBodyContent build era Source #
setTxValidityUpperBound :: TxValidityUpperBound era -> TxBodyContent build era -> TxBodyContent build era Source #
modTxValidityUpperBound :: (TxValidityUpperBound era -> TxValidityUpperBound era) -> TxBodyContent build era -> TxBodyContent build era Source #
setTxMetadata :: TxMetadataInEra era -> TxBodyContent build era -> TxBodyContent build era Source #
modTxMetadata :: (TxMetadataInEra era -> TxMetadataInEra era) -> TxBodyContent build era -> TxBodyContent build era Source #
setTxAuxScripts :: TxAuxScripts era -> TxBodyContent build era -> TxBodyContent build era Source #
modTxAuxScripts :: (TxAuxScripts era -> TxAuxScripts era) -> TxBodyContent build era -> TxBodyContent build era Source #
setTxExtraKeyWits :: TxExtraKeyWitnesses era -> TxBodyContent build era -> TxBodyContent build era Source #
modTxExtraKeyWits :: (TxExtraKeyWitnesses era -> TxExtraKeyWitnesses era) -> TxBodyContent build era -> TxBodyContent build era Source #
addTxExtraKeyWits :: IsAlonzoBasedEra era => [Hash PaymentKey] -> TxBodyContent build era -> TxBodyContent build era Source #
setTxProtocolParams :: BuildTxWith build (Maybe (LedgerProtocolParameters era)) -> TxBodyContent build era -> TxBodyContent build era Source #
setTxWithdrawals :: TxWithdrawals build era -> TxBodyContent build era -> TxBodyContent build era Source #
modTxWithdrawals :: (TxWithdrawals build era -> TxWithdrawals build era) -> TxBodyContent build era -> TxBodyContent build era Source #
setTxCertificates :: TxCertificates build era -> TxBodyContent build era -> TxBodyContent build era Source #
modTxCertificates :: (TxCertificates build era -> TxCertificates build era) -> TxBodyContent build era -> TxBodyContent build era Source #
setTxUpdateProposal :: TxUpdateProposal era -> TxBodyContent build era -> TxBodyContent build era Source #
modTxUpdateProposal :: (TxUpdateProposal era -> TxUpdateProposal era) -> TxBodyContent build era -> TxBodyContent build era Source #
setTxMintValue :: TxMintValue build era -> TxBodyContent build era -> TxBodyContent build era Source #
modTxMintValue :: (TxMintValue build era -> TxMintValue build era) -> TxBodyContent build era -> TxBodyContent build era Source #
addTxMintValue :: IsMaryBasedEra era => Map PolicyId (PolicyAssets, BuildTxWith build (ScriptWitness WitCtxMint era)) -> TxBodyContent build era -> TxBodyContent build era Source #
subtractTxMintValue :: IsMaryBasedEra era => Map PolicyId (PolicyAssets, BuildTxWith build (ScriptWitness WitCtxMint era)) -> TxBodyContent build era -> TxBodyContent build era Source #
Adds the negation of the provided assets and quantities to the txMintValue field of the TxBodyContent
.
setTxScriptValidity :: TxScriptValidity era -> TxBodyContent build era -> TxBodyContent build era Source #
modTxScriptValidity :: (TxScriptValidity era -> TxScriptValidity era) -> TxBodyContent build era -> TxBodyContent build era Source #
setTxProposalProcedures :: Maybe (Featured ConwayEraOnwards era (TxProposalProcedures build era)) -> TxBodyContent build era -> TxBodyContent build era Source #
setTxVotingProcedures :: Maybe (Featured ConwayEraOnwards era (TxVotingProcedures build era)) -> TxBodyContent build era -> TxBodyContent build era Source #
setTxCurrentTreasuryValue :: Maybe (Featured ConwayEraOnwards era (Maybe Coin)) -> TxBodyContent build era -> TxBodyContent build era Source #
setTxTreasuryDonation :: Maybe (Featured ConwayEraOnwards era Coin) -> TxBodyContent build era -> TxBodyContent build era Source #
data TxBodyError Source #
Constructors
TxBodyPlutusScriptDecodeError DecoderError | |
TxBodyEmptyTxIns | |
TxBodyEmptyTxInsCollateral | |
TxBodyEmptyTxOuts | |
TxBodyOutputError !TxOutputError | |
TxBodyMetadataError ![(Word64, TxMetadataRangeError)] | |
TxBodyInIxOverflow !TxIn | |
TxBodyMissingProtocolParams | |
TxBodyProtocolParamsConversionError !ProtocolParametersConversionError |
Instances
Show TxBodyError Source # | |
Defined in Cardano.Api.Internal.Tx.Body | |
Error TxBodyError Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods prettyError :: TxBodyError -> Doc ann Source # | |
Eq TxBodyError Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods (==) :: TxBodyError -> TxBodyError -> Bool Source # (/=) :: TxBodyError -> TxBodyError -> Bool Source # |
data TxOutputError Source #
Constructors
TxOutputNegative !Quantity !TxOutInAnyEra | |
TxOutputOverflow !Quantity !TxOutInAnyEra |
Instances
Show TxOutputError Source # | |
Defined in Cardano.Api.Internal.Tx.Output | |
Error TxOutputError Source # | |
Defined in Cardano.Api.Internal.Tx.Output Methods prettyError :: TxOutputError -> Doc ann Source # | |
Eq TxOutputError Source # | |
Defined in Cardano.Api.Internal.Tx.Output Methods (==) :: TxOutputError -> TxOutputError -> Bool Source # (/=) :: TxOutputError -> TxOutputError -> Bool Source # |
data TxBodyScriptData era where Source #
Constructors
TxBodyNoScriptData :: forall era. TxBodyScriptData era | |
TxBodyScriptData :: forall era. AlonzoEraOnwardsConstraints era => AlonzoEraOnwards era -> TxDats (ShelleyLedgerEra era) -> Redeemers (ShelleyLedgerEra era) -> TxBodyScriptData era |
Instances
Show (TxBodyScriptData era) Source # | |
Defined in Cardano.Api.Internal.Tx.Sign | |
Eq (TxBodyScriptData era) Source # | |
Defined in Cardano.Api.Internal.Tx.Sign Methods (==) :: TxBodyScriptData era -> TxBodyScriptData era -> Bool Source # (/=) :: TxBodyScriptData era -> TxBodyScriptData era -> Bool Source # |
Transaction Ids
Constructors
TxId (Hash HASH EraIndependentTxBody) |
Instances
FromJSON TxId Source # | |
Defined in Cardano.Api.Internal.TxIn | |
FromJSONKey TxId Source # | |
Defined in Cardano.Api.Internal.TxIn | |
ToJSON TxId Source # | |
Defined in Cardano.Api.Internal.TxIn Methods toEncoding :: TxId -> Encoding toJSONList :: [TxId] -> Value toEncodingList :: [TxId] -> Encoding | |
ToJSONKey TxId Source # | |
Defined in Cardano.Api.Internal.TxIn | |
IsString TxId Source # | |
Defined in Cardano.Api.Internal.TxIn Methods fromString :: String -> TxId Source # | |
Show TxId Source # | |
HasTypeProxy TxId Source # | |
Defined in Cardano.Api.Internal.TxIn | |
SerialiseAsRawBytes TxId Source # | |
Defined in Cardano.Api.Internal.TxIn Methods serialiseToRawBytes :: TxId -> ByteString Source # deserialiseFromRawBytes :: AsType TxId -> ByteString -> Either SerialiseAsRawBytesError TxId Source # | |
Eq TxId Source # | |
Ord TxId Source # | |
Defined in Cardano.Api.Internal.TxIn | |
data AsType TxId Source # | |
Defined in Cardano.Api.Internal.TxIn |
getTxIdByron :: ATxAux ByteString -> TxId Source #
Transaction inputs
Instances
FromJSON TxIn Source # | |
Defined in Cardano.Api.Internal.TxIn | |
FromJSONKey TxIn Source # | |
Defined in Cardano.Api.Internal.TxIn | |
ToJSON TxIn Source # | |
Defined in Cardano.Api.Internal.TxIn Methods toEncoding :: TxIn -> Encoding toJSONList :: [TxIn] -> Value toEncodingList :: [TxIn] -> Encoding | |
ToJSONKey TxIn Source # | |
Defined in Cardano.Api.Internal.TxIn | |
Show TxIn Source # | |
Eq TxIn Source # | |
Ord TxIn Source # | |
Defined in Cardano.Api.Internal.TxIn | |
Pretty TxIn Source # | |
Defined in Cardano.Api.Internal.TxIn |
type TxIns build era = [(TxIn, BuildTxWith build (Witness WitCtxTxIn era))] Source #
Instances
FromJSON TxIx Source # | |
Defined in Cardano.Api.Internal.TxIn | |
ToJSON TxIx Source # | |
Defined in Cardano.Api.Internal.TxIn Methods toEncoding :: TxIx -> Encoding toJSONList :: [TxIx] -> Value toEncodingList :: [TxIx] -> Encoding | |
Enum TxIx Source # | |
Show TxIx Source # | |
Eq TxIx Source # | |
Ord TxIx Source # | |
Defined in Cardano.Api.Internal.TxIn |
renderTxIn :: TxIn -> Text Source #
getReferenceInputsSizeForTxIds :: ShelleyLedgerEra era ~ ledgerera => BabbageEraOnwards era -> UTxO ledgerera -> Set TxIn -> Int Source #
Calculate the reference inputs size in bytes for provided set of transaction IDs and UTXOs.
Transaction outputs
The context is a transaction body
Instances
IsShelleyBasedEra era => FromJSON (TxOut CtxTx era) Source # | |
Defined in Cardano.Api.Internal.Tx.Output Methods parseJSON :: Value -> Parser (TxOut CtxTx era) parseJSONList :: Value -> Parser [TxOut CtxTx era] omittedField :: Maybe (TxOut CtxTx era) |
The context is the UTxO
Instances
IsShelleyBasedEra era => FromJSON (TxOut CtxUTxO era) Source # | |
Defined in Cardano.Api.Internal.Tx.Output Methods parseJSON :: Value -> Parser (TxOut CtxUTxO era) parseJSONList :: Value -> Parser [TxOut CtxUTxO era] omittedField :: Maybe (TxOut CtxUTxO era) |
Constructors
TxOut (AddressInEra era) (TxOutValue era) (TxOutDatum ctx era) (ReferenceScript era) |
Instances
IsShelleyBasedEra era => FromJSON (TxOut CtxTx era) Source # | |
Defined in Cardano.Api.Internal.Tx.Output Methods parseJSON :: Value -> Parser (TxOut CtxTx era) parseJSONList :: Value -> Parser [TxOut CtxTx era] omittedField :: Maybe (TxOut CtxTx era) | |
IsShelleyBasedEra era => FromJSON (TxOut CtxUTxO era) Source # | |
Defined in Cardano.Api.Internal.Tx.Output Methods parseJSON :: Value -> Parser (TxOut CtxUTxO era) parseJSONList :: Value -> Parser [TxOut CtxUTxO era] omittedField :: Maybe (TxOut CtxUTxO era) | |
IsCardanoEra era => ToJSON (TxOut ctx era) Source # | |
Defined in Cardano.Api.Internal.Tx.Output Methods toJSON :: TxOut ctx era -> Value toEncoding :: TxOut ctx era -> Encoding toJSONList :: [TxOut ctx era] -> Value toEncodingList :: [TxOut ctx era] -> Encoding | |
Show (TxOut ctx era) Source # | |
Eq (TxOut ctx era) Source # | |
data TxOutValue era where Source #
Constructors
TxOutValueByron :: Coin -> TxOutValue ByronEra | |
TxOutValueShelleyBased :: forall era. (Eq (Value (ShelleyLedgerEra era)), Show (Value (ShelleyLedgerEra era))) => ShelleyBasedEra era -> Value (ShelleyLedgerEra era) -> TxOutValue era |
Instances
IsShelleyBasedEra era => FromJSON (TxOutValue era) Source # | |
Defined in Cardano.Api.Internal.Tx.Output Methods parseJSON :: Value -> Parser (TxOutValue era) parseJSONList :: Value -> Parser [TxOutValue era] omittedField :: Maybe (TxOutValue era) | |
IsCardanoEra era => ToJSON (TxOutValue era) Source # | |
Defined in Cardano.Api.Internal.Tx.Output Methods toJSON :: TxOutValue era -> Value toEncoding :: TxOutValue era -> Encoding toJSONList :: [TxOutValue era] -> Value toEncodingList :: [TxOutValue era] -> Encoding omitField :: TxOutValue era -> Bool | |
Show (TxOutValue era) Source # | |
Defined in Cardano.Api.Internal.Tx.Output | |
Eq (TxOutValue era) Source # | |
Defined in Cardano.Api.Internal.Tx.Output Methods (==) :: TxOutValue era -> TxOutValue era -> Bool Source # (/=) :: TxOutValue era -> TxOutValue era -> Bool Source # |
data TxOutInAnyEra where Source #
Constructors
TxOutInAnyEra :: forall era. CardanoEra era -> TxOut CtxTx era -> TxOutInAnyEra |
Instances
Show TxOutInAnyEra Source # | |
Defined in Cardano.Api.Internal.Tx.Output | |
Eq TxOutInAnyEra Source # | |
Defined in Cardano.Api.Internal.Tx.Output Methods (==) :: TxOutInAnyEra -> TxOutInAnyEra -> Bool Source # (/=) :: TxOutInAnyEra -> TxOutInAnyEra -> Bool Source # | |
Pretty TxOutInAnyEra Source # | |
Defined in Cardano.Api.Internal.Tx.Output |
txOutInAnyEra :: CardanoEra era -> TxOut CtxTx era -> TxOutInAnyEra Source #
Convenience constructor for TxOutInAnyEra
txOutValueToLovelace :: TxOutValue era -> Coin Source #
txOutValueToValue :: TxOutValue era -> Value Source #
lovelaceToTxOutValue :: ShelleyBasedEra era -> Coin -> TxOutValue era Source #
data TxOutDatum ctx era where Source #
Constructors
TxOutDatumNone :: forall ctx era. TxOutDatum ctx era | |
TxOutDatumHash :: forall era ctx. AlonzoEraOnwards era -> Hash ScriptData -> TxOutDatum ctx era | A transaction output that only specifies the hash of the datum, but not the full datum value. |
TxOutSupplementalDatum :: forall era. AlonzoEraOnwards era -> HashableScriptData -> TxOutDatum CtxTx era | A transaction output that specifies the whole datum value. This can only be used in the context of the transaction body (i.e this is a supplemental datum), and does not occur in the UTxO. The UTxO only contains the datum hash. |
TxOutDatumInline :: forall era ctx. BabbageEraOnwards era -> HashableScriptData -> TxOutDatum ctx era | A transaction output that specifies the whole datum instead of the datum hash. Note that the datum map will not be updated with this datum, it only exists at the transaction output. |
Instances
Show (TxOutDatum ctx era) Source # | |
Defined in Cardano.Api.Internal.Tx.Output | |
Eq (TxOutDatum ctx era) Source # | |
Defined in Cardano.Api.Internal.Tx.Output Methods (==) :: TxOutDatum ctx era -> TxOutDatum ctx era -> Bool Source # (/=) :: TxOutDatum ctx era -> TxOutDatum ctx era -> Bool Source # |
Other transaction body types
data TxInsCollateral era where Source #
Constructors
TxInsCollateralNone :: forall era. TxInsCollateral era | |
TxInsCollateral :: forall era. AlonzoEraOnwards era -> [TxIn] -> TxInsCollateral era |
Instances
Show (TxInsCollateral era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body | |
Eq (TxInsCollateral era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods (==) :: TxInsCollateral era -> TxInsCollateral era -> Bool Source # (/=) :: TxInsCollateral era -> TxInsCollateral era -> Bool Source # |
data TxInsReference build era where Source #
Constructors
TxInsReferenceNone :: forall build era. TxInsReference build era | |
TxInsReference | |
Fields
|
Instances
Show (TxInsReference build era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body | |
Eq (TxInsReference build era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods (==) :: TxInsReference build era -> TxInsReference build era -> Bool Source # (/=) :: TxInsReference build era -> TxInsReference build era -> Bool Source # |
data TxTotalCollateral era where Source #
Constructors
TxTotalCollateralNone :: forall era. TxTotalCollateral era | |
TxTotalCollateral :: forall era. BabbageEraOnwards era -> Coin -> TxTotalCollateral era |
Instances
Show (TxTotalCollateral era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body | |
Eq (TxTotalCollateral era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods (==) :: TxTotalCollateral era -> TxTotalCollateral era -> Bool Source # (/=) :: TxTotalCollateral era -> TxTotalCollateral era -> Bool Source # |
data TxReturnCollateral ctx era where Source #
Constructors
TxReturnCollateralNone :: forall ctx era. TxReturnCollateral ctx era | |
TxReturnCollateral :: forall era ctx. BabbageEraOnwards era -> TxOut ctx era -> TxReturnCollateral ctx era |
Instances
Show (TxReturnCollateral ctx era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body | |
Eq (TxReturnCollateral ctx era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods (==) :: TxReturnCollateral ctx era -> TxReturnCollateral ctx era -> Bool Source # (/=) :: TxReturnCollateral ctx era -> TxReturnCollateral ctx era -> Bool Source # |
Constructors
TxFeeExplicit :: forall era. ShelleyBasedEra era -> Coin -> TxFee era |
data TxValidityLowerBound era where Source #
Constructors
TxValidityNoLowerBound :: forall era. TxValidityLowerBound era | |
TxValidityLowerBound :: forall era. AllegraEraOnwards era -> SlotNo -> TxValidityLowerBound era |
Instances
Show (TxValidityLowerBound era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body | |
Eq (TxValidityLowerBound era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods (==) :: TxValidityLowerBound era -> TxValidityLowerBound era -> Bool Source # (/=) :: TxValidityLowerBound era -> TxValidityLowerBound era -> Bool Source # |
data TxValidityUpperBound era where Source #
This was formerly known as the TTL.
Constructors
TxValidityUpperBound :: forall era. ShelleyBasedEra era -> Maybe SlotNo -> TxValidityUpperBound era |
Instances
Show (TxValidityUpperBound era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body | |
Eq (TxValidityUpperBound era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods (==) :: TxValidityUpperBound era -> TxValidityUpperBound era -> Bool Source # (/=) :: TxValidityUpperBound era -> TxValidityUpperBound era -> Bool Source # |
The 0-based index for the Ourboros time slot.
Instances
FromJSON SlotNo | |||||
Defined in Cardano.Slotting.Slot | |||||
ToJSON SlotNo | |||||
Defined in Cardano.Slotting.Slot Methods toEncoding :: SlotNo -> Encoding toJSONList :: [SlotNo] -> Value toEncodingList :: [SlotNo] -> Encoding | |||||
Bounded SlotNo | |||||
Enum SlotNo | |||||
Defined in Cardano.Slotting.Slot Methods succ :: SlotNo -> SlotNo Source # pred :: SlotNo -> SlotNo Source # toEnum :: Int -> SlotNo Source # fromEnum :: SlotNo -> Int Source # enumFrom :: SlotNo -> [SlotNo] Source # enumFromThen :: SlotNo -> SlotNo -> [SlotNo] Source # enumFromTo :: SlotNo -> SlotNo -> [SlotNo] Source # enumFromThenTo :: SlotNo -> SlotNo -> SlotNo -> [SlotNo] Source # | |||||
Generic SlotNo | |||||
Defined in Cardano.Slotting.Slot Associated Types
| |||||
Num SlotNo | |||||
Defined in Cardano.Slotting.Slot | |||||
Show SlotNo | |||||
FromCBOR SlotNo | |||||
ToCBOR SlotNo | |||||
DecCBOR SlotNo | |||||
EncCBOR SlotNo | |||||
NFData SlotNo | |||||
Defined in Cardano.Slotting.Slot | |||||
Eq SlotNo | |||||
Ord SlotNo | |||||
NoThunks SlotNo | |||||
Condense SlotNo | |||||
Serialise SlotNo | |||||
Defined in Cardano.Slotting.Slot | |||||
ShowProxy SlotNo | |||||
(Condense block, HasHeader block, Condense (HeaderHash block)) => Condense (AnchoredFragment block) | |||||
Defined in Ouroboros.Consensus.Util.Condense Methods condense :: AnchoredFragment block -> String Source # | |||||
HasHeader block => Anchorable (WithOrigin SlotNo) (Anchor block) block | |||||
Defined in Ouroboros.Network.AnchoredFragment | |||||
Anchorable (WithOrigin SlotNo) (HeaderStateWithTime blk) (HeaderStateWithTime blk) | |||||
Defined in Ouroboros.Consensus.HeaderStateHistory Methods asAnchor :: HeaderStateWithTime blk -> HeaderStateWithTime blk Source # getAnchorMeasure :: Proxy (HeaderStateWithTime blk) -> HeaderStateWithTime blk -> WithOrigin SlotNo Source # | |||||
GetTip l => Anchorable (WithOrigin SlotNo) (StateRef m l) (StateRef m l) | |||||
type Rep SlotNo | |||||
Defined in Cardano.Slotting.Slot type Rep SlotNo = D1 ('MetaData "SlotNo" "Cardano.Slotting.Slot" "cardano-slotting-0.2.0.0-1062762da5e24b3256026b7bf7ed7ea570deea61ae8ec963e4334bb658f0121b" 'True) (C1 ('MetaCons "SlotNo" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSlotNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64))) |
newtype EpochSlots Source #
The number of slots per epoch.
Constructors
EpochSlots | |
Fields |
Instances
Data EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> EpochSlots -> c EpochSlots Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c EpochSlots Source # toConstr :: EpochSlots -> Constr Source # dataTypeOf :: EpochSlots -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c EpochSlots) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c EpochSlots) Source # gmapT :: (forall b. Data b => b -> b) -> EpochSlots -> EpochSlots Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> EpochSlots -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> EpochSlots -> r Source # gmapQ :: (forall d. Data d => d -> u) -> EpochSlots -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> EpochSlots -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> EpochSlots -> m EpochSlots Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> EpochSlots -> m EpochSlots Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> EpochSlots -> m EpochSlots Source # | |||||
Generic EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots Associated Types
| |||||
Read EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots | |||||
Show EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots | |||||
FromCBOR EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots | |||||
ToCBOR EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots Methods toCBOR :: EpochSlots -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy EpochSlots -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [EpochSlots] -> Size Source # | |||||
DecCBOR EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots | |||||
EncCBOR EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots Methods encCBOR :: EpochSlots -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy EpochSlots -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [EpochSlots] -> Size Source # | |||||
Buildable EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots Methods build :: EpochSlots -> Builder | |||||
Eq EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots Methods (==) :: EpochSlots -> EpochSlots -> Bool Source # (/=) :: EpochSlots -> EpochSlots -> Bool Source # | |||||
Ord EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots Methods compare :: EpochSlots -> EpochSlots -> Ordering Source # (<) :: EpochSlots -> EpochSlots -> Bool Source # (<=) :: EpochSlots -> EpochSlots -> Bool Source # (>) :: EpochSlots -> EpochSlots -> Bool Source # (>=) :: EpochSlots -> EpochSlots -> Bool Source # max :: EpochSlots -> EpochSlots -> EpochSlots Source # min :: EpochSlots -> EpochSlots -> EpochSlots Source # | |||||
NoThunks EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots Methods noThunks :: Context -> EpochSlots -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> EpochSlots -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy EpochSlots -> String # | |||||
type Rep EpochSlots | |||||
Defined in Cardano.Chain.Slotting.EpochSlots type Rep EpochSlots = D1 ('MetaData "EpochSlots" "Cardano.Chain.Slotting.EpochSlots" "cardano-ledger-byron-1.1.0.0-7fb551a04b7ebd202180a636c363fd4c69d431c37908920ba820fedd2c0d0ade" 'True) (C1 ('MetaCons "EpochSlots" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEpochSlots") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64))) |
data TxMetadataInEra era where Source #
Constructors
TxMetadataNone :: forall era. TxMetadataInEra era | |
TxMetadataInEra :: forall era. ShelleyBasedEra era -> TxMetadata -> TxMetadataInEra era |
Instances
Show (TxMetadataInEra era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body | |
Eq (TxMetadataInEra era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods (==) :: TxMetadataInEra era -> TxMetadataInEra era -> Bool Source # (/=) :: TxMetadataInEra era -> TxMetadataInEra era -> Bool Source # |
data TxAuxScripts era where Source #
Constructors
TxAuxScriptsNone :: forall era. TxAuxScripts era | |
TxAuxScripts :: forall era. AllegraEraOnwards era -> [ScriptInEra era] -> TxAuxScripts era |
Instances
Show (TxAuxScripts era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body | |
Eq (TxAuxScripts era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods (==) :: TxAuxScripts era -> TxAuxScripts era -> Bool Source # (/=) :: TxAuxScripts era -> TxAuxScripts era -> Bool Source # |
data TxExtraKeyWitnesses era where Source #
Constructors
TxExtraKeyWitnessesNone :: forall era. TxExtraKeyWitnesses era | |
TxExtraKeyWitnesses :: forall era. AlonzoEraOnwards era -> [Hash PaymentKey] -> TxExtraKeyWitnesses era |
Instances
Show (TxExtraKeyWitnesses era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body | |
Eq (TxExtraKeyWitnesses era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods (==) :: TxExtraKeyWitnesses era -> TxExtraKeyWitnesses era -> Bool Source # (/=) :: TxExtraKeyWitnesses era -> TxExtraKeyWitnesses era -> Bool Source # |
data TxWithdrawals build era where Source #
Constructors
TxWithdrawalsNone :: forall build era. TxWithdrawals build era | |
TxWithdrawals :: forall era build. ShelleyBasedEra era -> [(StakeAddress, Coin, BuildTxWith build (Witness WitCtxStake era))] -> TxWithdrawals build era |
Instances
Show (TxWithdrawals build era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body | |
Eq (TxWithdrawals build era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods (==) :: TxWithdrawals build era -> TxWithdrawals build era -> Bool Source # (/=) :: TxWithdrawals build era -> TxWithdrawals build era -> Bool Source # |
data TxCertificates build era where Source #
Constructors
TxCertificatesNone :: forall build era. TxCertificates build era | No certificates |
TxCertificates :: forall era build. ShelleyBasedEra era -> OMap (Certificate era) (BuildTxWith build (Maybe (StakeCredential, Witness WitCtxStake era))) -> TxCertificates build era | Represents certificates present in transaction. Prefer using |
Instances
Show (TxCertificates build era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body | |
Eq (TxCertificates build era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods (==) :: TxCertificates build era -> TxCertificates build era -> Bool Source # (/=) :: TxCertificates build era -> TxCertificates build era -> Bool Source # |
mkTxCertificates :: Applicative (BuildTxWith build) => ShelleyBasedEra era -> [(Certificate era, Maybe (ScriptWitness WitCtxStake era))] -> TxCertificates build era Source #
Create TxCertificates
. Note that 'Certificate era' will be deduplicated. Only Certificates with a
stake credential will be in the result.
Note that, when building a transaction in Conway era, a witness is not required for staking credential registration, but this is only the case during the transitional period of Conway era and only for staking credential registration certificates without a deposit. Future eras will require a witness for registration certificates, because the one without a deposit will be removed.
data TxUpdateProposal era where Source #
Constructors
TxUpdateProposalNone :: forall era. TxUpdateProposal era | |
TxUpdateProposal :: forall era. ShelleyToBabbageEra era -> UpdateProposal -> TxUpdateProposal era |
Instances
Show (TxUpdateProposal era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body | |
Eq (TxUpdateProposal era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods (==) :: TxUpdateProposal era -> TxUpdateProposal era -> Bool Source # (/=) :: TxUpdateProposal era -> TxUpdateProposal era -> Bool Source # |
data TxMintValue build era where Source #
Constructors
TxMintNone :: forall build era. TxMintValue build era | |
TxMintValue :: forall era build. MaryEraOnwards era -> Map PolicyId (PolicyAssets, BuildTxWith build (ScriptWitness WitCtxMint era)) -> TxMintValue build era |
Instances
Monoid (TxMintValue build era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods mempty :: TxMintValue build era Source # mappend :: TxMintValue build era -> TxMintValue build era -> TxMintValue build era Source # mconcat :: [TxMintValue build era] -> TxMintValue build era Source # | |
Semigroup (TxMintValue build era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods (<>) :: TxMintValue build era -> TxMintValue build era -> TxMintValue build era Source # sconcat :: NonEmpty (TxMintValue build era) -> TxMintValue build era Source # stimes :: Integral b => b -> TxMintValue build era -> TxMintValue build era Source # | |
Show (TxMintValue build era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body | |
Eq (TxMintValue build era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods (==) :: TxMintValue build era -> TxMintValue build era -> Bool Source # (/=) :: TxMintValue build era -> TxMintValue build era -> Bool Source # |
mkTxMintValue :: MaryEraOnwards era -> [(PolicyId, PolicyAssets, BuildTxWith build (ScriptWitness WitCtxMint era))] -> TxMintValue build era Source #
A helper function for building TxMintValue
with present witnesses. Only the first witness
in the argument will be used for each policy id.
txMintValueToValue :: TxMintValue build era -> Value Source #
Convert TxMintValue
to a more handy Value
.
indexTxMintValue :: TxMintValue build era -> [(ScriptWitnessIndex, PolicyId, PolicyAssets, BuildTxWith build (ScriptWitness WitCtxMint era))] Source #
Index the assets with witnesses in the order of policy ids. See section 4.1 of https://github.com/intersectmbo/cardano-ledger/releases/latest/download/alonzo-ledger.pdf
data TxVotingProcedures build era where Source #
Constructors
TxVotingProceduresNone :: forall build era. TxVotingProcedures build era | |
TxVotingProcedures :: forall era build. VotingProcedures (ShelleyLedgerEra era) -> BuildTxWith build (Map Voter (ScriptWitness WitCtxStake era)) -> TxVotingProcedures build era |
Instances
Show (TxVotingProcedures build era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body | |
Eq (TxVotingProcedures build era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods (==) :: TxVotingProcedures build era -> TxVotingProcedures build era -> Bool Source # (/=) :: TxVotingProcedures build era -> TxVotingProcedures build era -> Bool Source # |
mkTxVotingProcedures :: Applicative (BuildTxWith build) => [(VotingProcedures era, Maybe (ScriptWitness WitCtxStake era))] -> Either (VotesMergingConflict era) (TxVotingProcedures build era) Source #
Create voting procedures from map of voting procedures and optional witnesses.
Validates the function argument, to make sure the list of votes is legal.
See mergeVotingProcedures
for validation rules.
data TxProposalProcedures build era where Source #
Constructors
TxProposalProceduresNone :: forall build era. TxProposalProcedures build era | No proposals in transaction.. |
TxProposalProcedures :: forall era build. EraPParams (ShelleyLedgerEra era) => OMap (ProposalProcedure (ShelleyLedgerEra era)) (BuildTxWith build (Maybe (ScriptWitness WitCtxStake era))) -> TxProposalProcedures build era | Represents proposal procedures present in transaction. |
Instances
Show (TxProposalProcedures build era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body | |
Eq (TxProposalProcedures build era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods (==) :: TxProposalProcedures build era -> TxProposalProcedures build era -> Bool Source # (/=) :: TxProposalProcedures build era -> TxProposalProcedures build era -> Bool Source # |
mkTxProposalProcedures :: forall era build. (Applicative (BuildTxWith build), IsShelleyBasedEra era) => [(ProposalProcedure (ShelleyLedgerEra era), Maybe (ScriptWitness WitCtxStake era))] -> TxProposalProcedures build era Source #
A smart constructor for TxProposalProcedures
. It makes sure that the value produced is consistent - the
witnessed proposals are also present in the first constructor parameter.
convProposalProcedures :: TxProposalProcedures build era -> OSet (ProposalProcedure (ShelleyLedgerEra era)) Source #
Returns an OSet of proposals from TxProposalProcedures
.
Building vs viewing transactions
data BuildTxWith build a where Source #
Constructors
ViewTx :: forall a. BuildTxWith ViewTx a | |
BuildTxWith :: forall a. a -> BuildTxWith BuildTx a |
Instances
Applicative (BuildTxWith BuildTx) Source # | |
Defined in Cardano.Api.Internal.Tx.BuildTxWith Methods pure :: a -> BuildTxWith BuildTx a Source # (<*>) :: BuildTxWith BuildTx (a -> b) -> BuildTxWith BuildTx a -> BuildTxWith BuildTx b Source # liftA2 :: (a -> b -> c) -> BuildTxWith BuildTx a -> BuildTxWith BuildTx b -> BuildTxWith BuildTx c Source # (*>) :: BuildTxWith BuildTx a -> BuildTxWith BuildTx b -> BuildTxWith BuildTx b Source # (<*) :: BuildTxWith BuildTx a -> BuildTxWith BuildTx b -> BuildTxWith BuildTx a Source # | |
Applicative (BuildTxWith ViewTx) Source # | |
Defined in Cardano.Api.Internal.Tx.BuildTxWith Methods pure :: a -> BuildTxWith ViewTx a Source # (<*>) :: BuildTxWith ViewTx (a -> b) -> BuildTxWith ViewTx a -> BuildTxWith ViewTx b Source # liftA2 :: (a -> b -> c) -> BuildTxWith ViewTx a -> BuildTxWith ViewTx b -> BuildTxWith ViewTx c Source # (*>) :: BuildTxWith ViewTx a -> BuildTxWith ViewTx b -> BuildTxWith ViewTx b Source # (<*) :: BuildTxWith ViewTx a -> BuildTxWith ViewTx b -> BuildTxWith ViewTx a Source # | |
Functor (BuildTxWith build) Source # | |
Defined in Cardano.Api.Internal.Tx.BuildTxWith Methods fmap :: (a -> b) -> BuildTxWith build a -> BuildTxWith build b Source # (<$) :: a -> BuildTxWith build b -> BuildTxWith build a Source # | |
(Applicative (BuildTxWith build), Monoid a) => Monoid (BuildTxWith build a) Source # | |
Defined in Cardano.Api.Internal.Tx.BuildTxWith Methods mempty :: BuildTxWith build a Source # mappend :: BuildTxWith build a -> BuildTxWith build a -> BuildTxWith build a Source # mconcat :: [BuildTxWith build a] -> BuildTxWith build a Source # | |
Semigroup a => Semigroup (BuildTxWith build a) Source # | |
Defined in Cardano.Api.Internal.Tx.BuildTxWith Methods (<>) :: BuildTxWith build a -> BuildTxWith build a -> BuildTxWith build a Source # sconcat :: NonEmpty (BuildTxWith build a) -> BuildTxWith build a Source # stimes :: Integral b => b -> BuildTxWith build a -> BuildTxWith build a Source # | |
Show a => Show (BuildTxWith build a) Source # | |
Defined in Cardano.Api.Internal.Tx.BuildTxWith | |
Eq a => Eq (BuildTxWith build a) Source # | |
Defined in Cardano.Api.Internal.Tx.BuildTxWith Methods (==) :: BuildTxWith build a -> BuildTxWith build a -> Bool Source # (/=) :: BuildTxWith build a -> BuildTxWith build a -> Bool Source # |
Instances
Applicative (BuildTxWith BuildTx) Source # | |
Defined in Cardano.Api.Internal.Tx.BuildTxWith Methods pure :: a -> BuildTxWith BuildTx a Source # (<*>) :: BuildTxWith BuildTx (a -> b) -> BuildTxWith BuildTx a -> BuildTxWith BuildTx b Source # liftA2 :: (a -> b -> c) -> BuildTxWith BuildTx a -> BuildTxWith BuildTx b -> BuildTxWith BuildTx c Source # (*>) :: BuildTxWith BuildTx a -> BuildTxWith BuildTx b -> BuildTxWith BuildTx b Source # (<*) :: BuildTxWith BuildTx a -> BuildTxWith BuildTx b -> BuildTxWith BuildTx a Source # |
Instances
Applicative (BuildTxWith ViewTx) Source # | |
Defined in Cardano.Api.Internal.Tx.BuildTxWith Methods pure :: a -> BuildTxWith ViewTx a Source # (<*>) :: BuildTxWith ViewTx (a -> b) -> BuildTxWith ViewTx a -> BuildTxWith ViewTx b Source # liftA2 :: (a -> b -> c) -> BuildTxWith ViewTx a -> BuildTxWith ViewTx b -> BuildTxWith ViewTx c Source # (*>) :: BuildTxWith ViewTx a -> BuildTxWith ViewTx b -> BuildTxWith ViewTx b Source # (<*) :: BuildTxWith ViewTx a -> BuildTxWith ViewTx b -> BuildTxWith ViewTx a Source # |
buildTxWithToMaybe :: BuildTxWith build a -> Maybe a Source #
Fee calculation
newtype LedgerEpochInfo Source #
Constructors
LedgerEpochInfo | |
Fields |
evaluateTransactionFee Source #
Arguments
:: ShelleyBasedEra era | |
-> PParams (ShelleyLedgerEra era) | |
-> TxBody era | |
-> Word | The number of Shelley key witnesses |
-> Word | The number of Byron key witnesses |
-> Int | Reference script size in bytes |
-> Coin |
Transaction fees can be computed for a proposed transaction based on the expected number of key witnesses (i.e. signatures).
When possible, use calculateMinTxFee
, as it provides a more accurate
estimate:
Arguments
:: ShelleyBasedEra era | |
-> PParams (ShelleyLedgerEra era) | |
-> UTxO era | |
-> TxBody era | |
-> Word | The number of Shelley key witnesses |
-> Coin |
Estimate the minimum transaction fee by analyzing the transaction structure and determining the required number and type of key witnesses.
It requires access to the relevant portion of the UTXO set to look up any transaction inputs (txins) included in the transaction. However, it cannot reliably determine the number of witnesses required for native scripts.
Therefore, the number of witnesses needed for native scripts must be provided as an additional argument.
estimateTransactionKeyWitnessCount :: TxBodyContent BuildTx era -> Word Source #
Provide and approximate count of the key witnesses (i.e. signatures) required for a transaction.
This estimate is not exact and may overestimate the required number of witnesses. The function makes conservative assumptions, including:
- Treating all inputs as originating from distinct addresses. In reality, multiple inputs may share the same address, requiring only one witness per address.
- Assuming regular and collateral inputs are distinct, even though they may overlap.
TODO: Consider implementing a more precise calculation that leverages the UTXO set to determine which inputs correspond to distinct addresses. Additionally, the estimate can be refined by distinguishing between Shelley and Byron-style witnesses.
Minimum required UTxO calculation
calculateMinimumUTxO :: HasCallStack => ShelleyBasedEra era -> PParams (ShelleyLedgerEra era) -> TxOut CtxTx era -> Coin Source #
Script execution units
evaluateTransactionExecutionUnits :: CardanoEra era -> SystemStart -> LedgerEpochInfo -> LedgerProtocolParameters era -> UTxO era -> TxBody era -> Map ScriptWitnessIndex (Either ScriptExecutionError (EvalTxExecutionUnitsLog, ExecutionUnits)) Source #
Compute the ExecutionUnits
required for each script in the transaction.
This process involves executing all scripts and counting the actual execution units consumed.
data ScriptExecutionError Source #
This data type represents the possible reasons for a script’s execution
failure, as reported by the evaluateTransactionExecutionUnits
function.
The first three errors relate to issues before executing the script, while the last two arise during script execution.
TODO: Consider replacing ScriptWitnessIndex
with the ledger’s PlutusPurpose
AsIx ledgerera
. This change would require parameterizing the
ScriptExecutionError
.
Constructors
ScriptErrorMissingTxIn TxIn | The script depends on a |
ScriptErrorTxInWithoutDatum TxIn | The |
ScriptErrorWrongDatum (Hash ScriptData) | The |
ScriptErrorEvaluationFailed DebugPlutusFailure | The script evaluation failed. This usually means it evaluated to an
error value. This is not a case of running out of execution units
(which is not possible for |
ScriptErrorExecutionUnitsOverflow | The execution units overflowed a 64bit word. Congratulations if you encounter this error. With the current style of cost model this would need a script to run for over 7 months, which is somewhat more than the expected maximum of a few milliseconds. |
ScriptErrorNotPlutusWitnessedTxIn ScriptWitnessIndex ScriptHash | An attempt was made to spend a key witnessed tx input with a script witness. |
ScriptErrorRedeemerPointsToUnknownScriptHash ScriptWitnessIndex | The redeemer pointer points to a script hash that does not exist in the transaction nor in the UTxO as a reference script" |
ScriptErrorMissingScript ScriptWitnessIndex ResolvablePointers | A redeemer pointer points to a script that does not exist. |
ScriptErrorMissingCostModel Language | A cost model was missing for a language which was used. |
(EraPlutusContext (ShelleyLedgerEra era), Show (ContextError (ShelleyLedgerEra era))) => ScriptErrorTranslationError (ContextError (ShelleyLedgerEra era)) |
Instances
Show ScriptExecutionError Source # | |
Defined in Cardano.Api.Internal.Fees | |
Error ScriptExecutionError Source # | |
Defined in Cardano.Api.Internal.Fees Methods prettyError :: ScriptExecutionError -> Doc ann Source # |
data TransactionValidityError era where Source #
Constructors
TransactionValidityIntervalError :: forall era. PastHorizonException -> TransactionValidityError era | The transaction validity interval is too far into the future. Transactions containing Plutus scripts must have a validity interval that is not excessively far in the future. This ensures that the UTC corresponding to the validity interval expressed in slot numbers, can be reliably determined. Plutus scripts are given the transaction validity interval in UTC to prevent sensitivity to variations in slot lengths. If either end of the validity interval exceeds the "time horizon", the consensus algorithm cannot reliably establish the relationship between slots and time. This error occurs when thevalidity interval exceeds the time horizon. For the Cardano mainnet, the time horizon is set to 36 hours beyond the current time. This effectively restricts the submission and validation of transactions that include Plutus scripts if the end of their validity interval extends more than 36 hours into the future. |
TransactionValidityCostModelError :: forall era. Map AnyPlutusScriptVersion CostModel -> String -> TransactionValidityError era |
Instances
Show (TransactionValidityError era) Source # | |
Defined in Cardano.Api.Internal.Fees | |
Error (TransactionValidityError era) Source # | |
Defined in Cardano.Api.Internal.Fees Methods prettyError :: TransactionValidityError era -> Doc ann Source # |
Transaction balance
evaluateTransactionBalance :: ShelleyBasedEra era -> PParams (ShelleyLedgerEra era) -> Set PoolId -> Map StakeCredential Coin -> Map (Credential 'DRepRole) Coin -> UTxO era -> TxBody era -> TxOutValue era Source #
Compute the total balance of the proposed transaction. Ultimately, a valid transaction must be fully balanced, which means that it has a total value of zero.
Finding the (non-zero) balance of a partially constructed transaction is useful for adjusting a transaction to be fully balanced.
Building transactions with automated fees and balancing
estimateBalancedTxBody Source #
Arguments
:: HasCallStack | |
=> MaryEraOnwards era | |
-> TxBodyContent BuildTx era | |
-> PParams (ShelleyLedgerEra era) | |
-> Set PoolId | The set of registered stake pools, being unregistered in this transaction. |
-> Map StakeCredential Coin | A map of all deposits for stake credentials that are being unregistered in this transaction. |
-> Map (Credential 'DRepRole) Coin | A map of all deposits for DRep credentials that are being unregistered in this transaction. |
-> Map ScriptWitnessIndex ExecutionUnits | Plutus script execution units. |
-> Coin | Total potential collateral amount. |
-> Int | The number of key witnesses to be added to the transaction. |
-> Int | The number of Byron key witnesses to be added to the transaction. |
-> Int | The size of all reference scripts in bytes. |
-> AddressInEra era | Change address. |
-> Value | Total value of UTXOs being spent. |
-> Either (TxFeeEstimationError era) (BalancedTxBody era) |
Use when you do not have access to the UTxOs you intend to spend
estimateOrCalculateBalancedTxBody :: ShelleyBasedEra era -> FeeEstimationMode era -> PParams (ShelleyLedgerEra era) -> TxBodyContent BuildTx era -> Set PoolId -> Map StakeCredential Coin -> Map (Credential 'DRepRole) Coin -> AddressInEra era -> Either (AutoBalanceError era) (BalancedTxBody era) Source #
makeTransactionBodyAutoBalance Source #
Arguments
:: HasCallStack | |
=> ShelleyBasedEra era | |
-> SystemStart | |
-> LedgerEpochInfo | |
-> LedgerProtocolParameters era | |
-> Set PoolId | The set of registered stake pools, being unregistered in this transaction. |
-> Map StakeCredential Coin | The map of all deposits for stake credentials that are being unregistered in this transaction |
-> Map (Credential 'DRepRole) Coin | The map of all deposits for DRep credentials that are being unregistered in this transaction |
-> UTxO era | The transaction inputs (including reference and collateral ones), not the entire |
-> TxBodyContent BuildTx era | |
-> AddressInEra era | Change address |
-> Maybe Word | Override key witnesses |
-> Either (TxBodyErrorAutoBalance era) (BalancedTxBody era) |
This is similar to makeTransactionBody
but with greater automation to
calculate suitable values for several things.
In particular:
- It calculates the correct script
ExecutionUnits
(ignoring the provided values, which can thus be zero). - It calculates the transaction fees based on the script
ExecutionUnits
, the currentProtocolParameters
, and an estimate of the number of key witnesses (i.e. signatures). There is an override for the number of key witnesses. - It accepts a change address, calculates the balance of the transaction and puts the excess change into the change output.
- It also checks that the balance is positive and the change is above the minimum threshold.
To do this, it requires more information than makeTransactionBody
, all of
which can be queried from a local node.
data AutoBalanceError era Source #
Constructors
AutoBalanceEstimationError (TxFeeEstimationError era) | |
AutoBalanceCalculationError (TxBodyErrorAutoBalance era) |
Instances
Show (AutoBalanceError era) Source # | |
Defined in Cardano.Api.Internal.Fees | |
Error (AutoBalanceError era) Source # | |
Defined in Cardano.Api.Internal.Fees Methods prettyError :: AutoBalanceError era -> Doc ann Source # |
data BalancedTxBody era Source #
Constructors
BalancedTxBody | |
Instances
IsShelleyBasedEra era => Show (BalancedTxBody era) Source # | |
Defined in Cardano.Api.Internal.Fees |
data FeeEstimationMode era Source #
Constructors
CalculateWithSpendableUTxO | Accurate fee calculation. |
Fields
| |
EstimateWithoutSpendableUTxO | Less accurate fee estimation. |
Fields
|
newtype RequiredShelleyKeyWitnesses Source #
Constructors
RequiredShelleyKeyWitnesses | |
Fields |
Instances
newtype RequiredByronKeyWitnesses Source #
Constructors
RequiredByronKeyWitnesses | |
Fields |
Instances
newtype TotalReferenceScriptsSize Source #
Constructors
TotalReferenceScriptsSize | |
Fields |
Instances
data TxFeeEstimationError era Source #
Constructors
TxFeeEstimationTransactionTranslationError (TransactionValidityError era) | |
TxFeeEstimationScriptExecutionError (TxBodyErrorAutoBalance era) | |
TxFeeEstimationBalanceError (TxBodyErrorAutoBalance era) | |
TxFeeEstimationxBodyError TxBodyError | |
TxFeeEstimationFinalConstructionError TxBodyError | |
TxFeeEstimationOnlyMaryOnwardsSupportedError |
Instances
Show (TxFeeEstimationError era) Source # | |
Defined in Cardano.Api.Internal.Fees | |
Error (TxFeeEstimationError era) Source # | |
Defined in Cardano.Api.Internal.Fees Methods prettyError :: TxFeeEstimationError era -> Doc ann Source # |
data TxBodyErrorAutoBalance era Source #
The possible errors that can arise from makeTransactionBodyAutoBalance
.
Constructors
TxBodyError TxBodyError | The same errors that can arise from |
TxBodyScriptExecutionError [(ScriptWitnessIndex, ScriptExecutionError)] | One or more scripts failed to execute correctly. |
TxBodyScriptBadScriptValidity | One or more scripts were expected to fail validation, but none did. |
TxBodyErrorBalanceNegative Coin MultiAsset | There is not enough ada and non-ada to cover both the outputs and the fees. The transaction should be changed to provide more input assets, or otherwise adjusted to need less (e.g. outputs, script etc). |
TxBodyErrorAdaBalanceTooSmall | There is enough ada to cover both the outputs and the fees, but the resulting change is too small: it is under the minimum value for new UTXO entries. The transaction should be changed to provide more input ada. |
Fields
| |
TxBodyErrorByronEraNotSupported |
|
TxBodyErrorMissingParamMinUTxO | The |
TxBodyErrorMinUTxONotMet | The minimum spendable UTxO threshold has not been met. |
Fields
| |
TxBodyErrorNonAdaAssetsUnbalanced Value | |
TxBodyErrorScriptWitnessIndexMissingFromExecUnitsMap ScriptWitnessIndex (Map ScriptWitnessIndex ExecutionUnits) |
Instances
Show (TxBodyErrorAutoBalance era) Source # | |
Defined in Cardano.Api.Internal.Fees | |
Error (TxBodyErrorAutoBalance era) Source # | |
Defined in Cardano.Api.Internal.Fees Methods prettyError :: TxBodyErrorAutoBalance era -> Doc ann Source # |
data TxScriptValidity era where Source #
A representation of whether the era supports tx script validity.
The Alonzo and subsequent eras support script validity.
Constructors
TxScriptValidityNone :: forall era. TxScriptValidity era | |
TxScriptValidity :: forall era. AlonzoEraOnwards era -> ScriptValidity -> TxScriptValidity era | Tx script validity is supported in transactions in the |
Instances
Show (TxScriptValidity era) Source # | |
Defined in Cardano.Api.Internal.Tx.Sign | |
Eq (TxScriptValidity era) Source # | |
Defined in Cardano.Api.Internal.Tx.Sign Methods (==) :: TxScriptValidity era -> TxScriptValidity era -> Bool Source # (/=) :: TxScriptValidity era -> TxScriptValidity era -> Bool Source # |
data ScriptValidity Source #
Indicates whether a script is expected to fail or pass validation.
Constructors
ScriptInvalid | Script is expected to fail validation. Transactions marked as such can include scripts that fail validation. Such transactions may be submitted to the chain, in which case the collateral will be taken upon on chain script validation failure. |
ScriptValid | Script is expected to pass validation. Transactions marked as such cannot include scripts that fail validation. |
Instances
Show ScriptValidity Source # | |
Defined in Cardano.Api.Internal.Tx.Sign | |
DecCBOR ScriptValidity Source # | |
Defined in Cardano.Api.Internal.Tx.Sign | |
EncCBOR ScriptValidity Source # | |
Defined in Cardano.Api.Internal.Tx.Sign Methods encCBOR :: ScriptValidity -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy ScriptValidity -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ScriptValidity] -> Size Source # | |
Eq ScriptValidity Source # | |
Defined in Cardano.Api.Internal.Tx.Sign Methods (==) :: ScriptValidity -> ScriptValidity -> Bool Source # (/=) :: ScriptValidity -> ScriptValidity -> Bool Source # |
Signing transactions
Creating transaction witnesses one by one, or all in one go.
Bundled Patterns
pattern Tx :: TxBody era -> [KeyWitness era] -> Tx era | This pattern will be deprecated in the future. We advise against introducing new usage of it. |
Instances
Show (InAnyShelleyBasedEra Tx) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign | |||||
Show (InAnyCardanoEra Tx) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign | |||||
Show (Tx era) Source # | |||||
HasTypeProxy era => HasTypeProxy (Tx era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Associated Types
| |||||
IsShelleyBasedEra era => SerialiseAsCBOR (Tx era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Methods serialiseToCBOR :: Tx era -> ByteString Source # deserialiseFromCBOR :: AsType (Tx era) -> ByteString -> Either DecoderError (Tx era) Source # | |||||
IsShelleyBasedEra era => HasTextEnvelope (Tx era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Methods textEnvelopeType :: AsType (Tx era) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: Tx era -> TextEnvelopeDescr Source # | |||||
Eq (InAnyShelleyBasedEra Tx) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Methods (==) :: InAnyShelleyBasedEra Tx -> InAnyShelleyBasedEra Tx -> Bool Source # (/=) :: InAnyShelleyBasedEra Tx -> InAnyShelleyBasedEra Tx -> Bool Source # | |||||
Eq (InAnyCardanoEra Tx) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Methods (==) :: InAnyCardanoEra Tx -> InAnyCardanoEra Tx -> Bool Source # (/=) :: InAnyCardanoEra Tx -> InAnyCardanoEra Tx -> Bool Source # | |||||
Eq (Tx era) Source # | |||||
data AsType (Tx era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign |
getTxWitnesses :: Tx era -> [KeyWitness era] Source #
Signing in one go
signByronTransaction :: NetworkId -> Annotated Tx ByteString -> [SigningKey ByronKey] -> ATxAux ByteString Source #
signShelleyTransaction :: ShelleyBasedEra era -> TxBody era -> [ShelleyWitnessSigningKey] -> Tx era Source #
Incremental signing and separate witnesses
makeSignedByronTransaction :: [KeyWitness era] -> Annotated Tx ByteString -> ATxAux ByteString Source #
makeSignedTransaction :: [KeyWitness era] -> TxBody era -> Tx era Source #
data KeyWitness era Source #
Instances
Show (KeyWitness era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign | |||||
HasTypeProxy era => HasTypeProxy (KeyWitness era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Associated Types
Methods proxyToAsType :: Proxy (KeyWitness era) -> AsType (KeyWitness era) Source # | |||||
IsCardanoEra era => SerialiseAsCBOR (KeyWitness era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Methods serialiseToCBOR :: KeyWitness era -> ByteString Source # deserialiseFromCBOR :: AsType (KeyWitness era) -> ByteString -> Either DecoderError (KeyWitness era) Source # | |||||
IsCardanoEra era => HasTextEnvelope (KeyWitness era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Methods textEnvelopeType :: AsType (KeyWitness era) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: KeyWitness era -> TextEnvelopeDescr Source # | |||||
Eq (KeyWitness era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign Methods (==) :: KeyWitness era -> KeyWitness era -> Bool Source # (/=) :: KeyWitness era -> KeyWitness era -> Bool Source # | |||||
data AsType (KeyWitness era) Source # | |||||
Defined in Cardano.Api.Internal.Tx.Sign |
makeByronKeyWitness :: IsByronKey key => NetworkId -> Annotated Tx ByteString -> SigningKey key -> KeyWitness ByronEra Source #
data ShelleyWitnessSigningKey Source #
Constructors
WitnessPaymentKey (SigningKey PaymentKey) | |
WitnessPaymentExtendedKey (SigningKey PaymentExtendedKey) | |
WitnessStakeKey (SigningKey StakeKey) | |
WitnessStakeExtendedKey (SigningKey StakeExtendedKey) | |
WitnessStakePoolKey (SigningKey StakePoolKey) | |
WitnessStakePoolExtendedKey (SigningKey StakePoolExtendedKey) | |
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) |
makeShelleyKeyWitness :: ShelleyBasedEra era -> TxBody era -> ShelleyWitnessSigningKey -> KeyWitness era Source #
makeShelleyKeyWitness' :: ShelleyBasedEra era -> TxBody (ShelleyLedgerEra era) -> ShelleyWitnessSigningKey -> KeyWitness era Source #
makeShelleyBootstrapWitness :: ShelleyBasedEra era -> WitnessNetworkIdOrByronAddress -> TxBody era -> SigningKey ByronKey -> KeyWitness era Source #
makeShelleyBasedBootstrapWitness :: ShelleyBasedEra era -> WitnessNetworkIdOrByronAddress -> TxBody (ShelleyLedgerEra era) -> SigningKey ByronKey -> KeyWitness era Source #
Transaction metadata
Embedding additional structured data within transactions.
newtype TxMetadata Source #
Constructors
TxMetadata | |
Fields |
Instances
Monoid TxMetadata Source # | |||||
Defined in Cardano.Api.Internal.TxMetadata Methods mempty :: TxMetadata Source # mappend :: TxMetadata -> TxMetadata -> TxMetadata Source # mconcat :: [TxMetadata] -> TxMetadata Source # | |||||
Semigroup TxMetadata Source # | Merge metadata maps. When there are clashing entries the left hand side takes precedence. | ||||
Defined in Cardano.Api.Internal.TxMetadata Methods (<>) :: TxMetadata -> TxMetadata -> TxMetadata Source # sconcat :: NonEmpty TxMetadata -> TxMetadata Source # stimes :: Integral b => b -> TxMetadata -> TxMetadata Source # | |||||
Show TxMetadata Source # | |||||
Defined in Cardano.Api.Internal.TxMetadata | |||||
HasTypeProxy TxMetadata Source # | |||||
Defined in Cardano.Api.Internal.TxMetadata Associated Types
Methods proxyToAsType :: Proxy TxMetadata -> AsType TxMetadata Source # | |||||
SerialiseAsCBOR TxMetadata Source # | |||||
Defined in Cardano.Api.Internal.TxMetadata Methods serialiseToCBOR :: TxMetadata -> ByteString Source # deserialiseFromCBOR :: AsType TxMetadata -> ByteString -> Either DecoderError TxMetadata Source # | |||||
Eq TxMetadata Source # | |||||
Defined in Cardano.Api.Internal.TxMetadata Methods (==) :: TxMetadata -> TxMetadata -> Bool Source # (/=) :: TxMetadata -> TxMetadata -> Bool Source # | |||||
data AsType TxMetadata Source # | |||||
Defined in Cardano.Api.Internal.TxMetadata |
class AsTxMetadata a where Source #
Methods
asTxMetadata :: a -> TxMetadata Source #
Instances
AsTxMetadata GovernancePoll Source # | |
Defined in Cardano.Api.Internal.Governance.Poll Methods | |
AsTxMetadata GovernancePollAnswer Source # | |
Defined in Cardano.Api.Internal.Governance.Poll Methods |
Constructing metadata
data TxMetadataValue Source #
Constructors
TxMetaMap [(TxMetadataValue, TxMetadataValue)] | |
TxMetaList [TxMetadataValue] | |
TxMetaNumber Integer | |
TxMetaBytes ByteString | |
TxMetaText Text |
Instances
Show TxMetadataValue Source # | |
Defined in Cardano.Api.Internal.TxMetadata | |
Eq TxMetadataValue Source # | |
Defined in Cardano.Api.Internal.TxMetadata Methods (==) :: TxMetadataValue -> TxMetadataValue -> Bool Source # (/=) :: TxMetadataValue -> TxMetadataValue -> Bool Source # | |
Ord TxMetadataValue Source # | |
Defined in Cardano.Api.Internal.TxMetadata Methods compare :: TxMetadataValue -> TxMetadataValue -> Ordering Source # (<) :: TxMetadataValue -> TxMetadataValue -> Bool Source # (<=) :: TxMetadataValue -> TxMetadataValue -> Bool Source # (>) :: TxMetadataValue -> TxMetadataValue -> Bool Source # (>=) :: TxMetadataValue -> TxMetadataValue -> Bool Source # max :: TxMetadataValue -> TxMetadataValue -> TxMetadataValue Source # min :: TxMetadataValue -> TxMetadataValue -> TxMetadataValue Source # |
mergeTransactionMetadata :: (TxMetadataValue -> TxMetadataValue -> TxMetadataValue) -> TxMetadata -> TxMetadata -> TxMetadata Source #
metaTextChunks :: Text -> TxMetadataValue Source #
Create a TxMetadataValue
from a Text
as a list of chunks of an
acceptable size.
metaBytesChunks :: ByteString -> TxMetadataValue Source #
Create a TxMetadataValue
from a ByteString
as a list of chunks of an
accaptable size.
Validating metadata
validateTxMetadata :: TxMetadata -> Either [(Word64, TxMetadataRangeError)] () Source #
Validate transaction metadata. This is for use with existing constructed metadata values, e.g. constructed manually or decoded from CBOR directly.
data TxMetadataRangeError Source #
An error in transaction metadata due to an out-of-range value.
Constructors
TxMetadataNumberOutOfRange !Integer | The number is outside the maximum range of |
TxMetadataTextTooLong !Int | The length of a text string metadatum value exceeds the maximum of 64 bytes as UTF8. |
TxMetadataBytesTooLong !Int | The length of a byte string metadatum value exceeds the maximum of 64 bytes. |
Instances
Data TxMetadataRangeError Source # | |
Defined in Cardano.Api.Internal.TxMetadata Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TxMetadataRangeError -> c TxMetadataRangeError Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TxMetadataRangeError Source # toConstr :: TxMetadataRangeError -> Constr Source # dataTypeOf :: TxMetadataRangeError -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TxMetadataRangeError) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TxMetadataRangeError) Source # gmapT :: (forall b. Data b => b -> b) -> TxMetadataRangeError -> TxMetadataRangeError Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TxMetadataRangeError -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TxMetadataRangeError -> r Source # gmapQ :: (forall d. Data d => d -> u) -> TxMetadataRangeError -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> TxMetadataRangeError -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TxMetadataRangeError -> m TxMetadataRangeError Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TxMetadataRangeError -> m TxMetadataRangeError Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TxMetadataRangeError -> m TxMetadataRangeError Source # | |
Show TxMetadataRangeError Source # | |
Defined in Cardano.Api.Internal.TxMetadata | |
Error TxMetadataRangeError Source # | |
Defined in Cardano.Api.Internal.TxMetadata Methods prettyError :: TxMetadataRangeError -> Doc ann Source # | |
Eq TxMetadataRangeError Source # | |
Defined in Cardano.Api.Internal.TxMetadata Methods (==) :: TxMetadataRangeError -> TxMetadataRangeError -> Bool Source # (/=) :: TxMetadataRangeError -> TxMetadataRangeError -> Bool Source # |
Conversion to/from JSON
data TxMetadataJsonSchema Source #
Tx metadata is similar to JSON but not exactly the same. It has some deliberate limitations such as no support for floating point numbers or special forms for null or boolean values. It also has limitations on the length of strings. On the other hand, unlike JSON, it distinguishes between byte strings and text strings. It also supports any value as map keys rather than just string.
We provide two different mappings between tx metadata and JSON, useful for different purposes:
- A mapping that allows almost any JSON value to be converted into tx metadata. This does not require a specific JSON schema for the input. It does not expose the full representation capability of tx metadata.
- A mapping that exposes the full representation capability of tx metadata, but relies on a specific JSON schema for the input JSON.
In the "no schema" mapping, the idea is that (almost) any JSON can be turned into tx metadata and then converted back, without loss. That is, we can round-trip the JSON.
The subset of JSON supported is all JSON except: * No null or bool values * No floating point, only integers in the range of a 64bit signed integer * A limitation on string lengths
The approach for this mapping is to use whichever representation as tx metadata is most compact. In particular:
- JSON lists and maps represented as CBOR lists and maps
- JSON strings represented as CBOR strings
- JSON hex strings with "0x" prefix represented as CBOR byte strings
- JSON integer numbers represented as CBOR signed or unsigned numbers
- JSON maps with string keys that parse as numbers or hex byte strings, represented as CBOR map keys that are actually numbers or byte strings.
The string length limit depends on whether the hex string representation is used or not. For text strings the limit is 64 bytes for the UTF8 representation of the text string. For byte strings the limit is 64 bytes for the raw byte form (ie not the input hex, but after hex decoding).
In the "detailed schema" mapping, the idea is that we expose the full representation capability of the tx metadata in the form of a JSON schema. This means the full representation is available and can be controlled precisely. It also means any tx metadata can be converted into the JSON and back without loss. That is we can round-trip the tx metadata via the JSON and also round-trip schema-compliant JSON via tx metadata.
Constructors
TxMetadataJsonNoSchema | Use the "no schema" mapping between JSON and tx metadata as described above. |
TxMetadataJsonDetailedSchema | Use the "detailed schema" mapping between JSON and tx metadata as described above. |
Instances
Show TxMetadataJsonSchema Source # | |
Defined in Cardano.Api.Internal.TxMetadata | |
Eq TxMetadataJsonSchema Source # | |
Defined in Cardano.Api.Internal.TxMetadata Methods (==) :: TxMetadataJsonSchema -> TxMetadataJsonSchema -> Bool Source # (/=) :: TxMetadataJsonSchema -> TxMetadataJsonSchema -> Bool Source # |
metadataFromJson :: TxMetadataJsonSchema -> Value -> Either TxMetadataJsonError TxMetadata Source #
Convert a value from JSON into tx metadata, using the given choice of mapping between JSON and tx metadata.
This may fail with a conversion error if the JSON is outside the supported
subset for the chosen mapping. See TxMetadataJsonSchema
for the details.
metadataToJson :: TxMetadataJsonSchema -> TxMetadata -> Value Source #
Convert a tx metadata value into JSON , using the given choice of mapping between JSON and tx metadata.
This conversion is total but is not necessarily invertible.
See TxMetadataJsonSchema
for the details.
metadataValueToJsonNoSchema :: TxMetadataValue -> Value Source #
data TxMetadataJsonError Source #
Constructors
TxMetadataJsonToplevelNotMap | |
TxMetadataJsonToplevelBadKey !Text | |
TxMetadataJsonSchemaError !Word64 !Value !TxMetadataJsonSchemaError | |
TxMetadataRangeError !Word64 !Value !TxMetadataRangeError |
Instances
Data TxMetadataJsonError Source # | |
Defined in Cardano.Api.Internal.TxMetadata Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TxMetadataJsonError -> c TxMetadataJsonError Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TxMetadataJsonError Source # toConstr :: TxMetadataJsonError -> Constr Source # dataTypeOf :: TxMetadataJsonError -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TxMetadataJsonError) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TxMetadataJsonError) Source # gmapT :: (forall b. Data b => b -> b) -> TxMetadataJsonError -> TxMetadataJsonError Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TxMetadataJsonError -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TxMetadataJsonError -> r Source # gmapQ :: (forall d. Data d => d -> u) -> TxMetadataJsonError -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> TxMetadataJsonError -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TxMetadataJsonError -> m TxMetadataJsonError Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TxMetadataJsonError -> m TxMetadataJsonError Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TxMetadataJsonError -> m TxMetadataJsonError Source # | |
Show TxMetadataJsonError Source # | |
Defined in Cardano.Api.Internal.TxMetadata | |
Error TxMetadataJsonError Source # | |
Defined in Cardano.Api.Internal.TxMetadata Methods prettyError :: TxMetadataJsonError -> Doc ann Source # | |
Eq TxMetadataJsonError Source # | |
Defined in Cardano.Api.Internal.TxMetadata Methods (==) :: TxMetadataJsonError -> TxMetadataJsonError -> Bool Source # (/=) :: TxMetadataJsonError -> TxMetadataJsonError -> Bool Source # |
data TxMetadataJsonSchemaError Source #
Constructors
TxMetadataJsonNullNotAllowed | |
TxMetadataJsonBoolNotAllowed | |
TxMetadataJsonNumberNotInteger !Double | |
TxMetadataJsonNotObject !Value | |
TxMetadataJsonBadObject ![(Text, Value)] | |
TxMetadataJsonBadMapPair !Value | |
TxMetadataJsonTypeMismatch !Text !Value |
Instances
Data TxMetadataJsonSchemaError Source # | |
Defined in Cardano.Api.Internal.TxMetadata Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TxMetadataJsonSchemaError -> c TxMetadataJsonSchemaError Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TxMetadataJsonSchemaError Source # toConstr :: TxMetadataJsonSchemaError -> Constr Source # dataTypeOf :: TxMetadataJsonSchemaError -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TxMetadataJsonSchemaError) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TxMetadataJsonSchemaError) Source # gmapT :: (forall b. Data b => b -> b) -> TxMetadataJsonSchemaError -> TxMetadataJsonSchemaError Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TxMetadataJsonSchemaError -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TxMetadataJsonSchemaError -> r Source # gmapQ :: (forall d. Data d => d -> u) -> TxMetadataJsonSchemaError -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> TxMetadataJsonSchemaError -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TxMetadataJsonSchemaError -> m TxMetadataJsonSchemaError Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TxMetadataJsonSchemaError -> m TxMetadataJsonSchemaError Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TxMetadataJsonSchemaError -> m TxMetadataJsonSchemaError Source # | |
Show TxMetadataJsonSchemaError Source # | |
Defined in Cardano.Api.Internal.TxMetadata | |
Error TxMetadataJsonSchemaError Source # | |
Defined in Cardano.Api.Internal.TxMetadata Methods prettyError :: TxMetadataJsonSchemaError -> Doc ann Source # | |
Eq TxMetadataJsonSchemaError Source # | |
Defined in Cardano.Api.Internal.TxMetadata Methods (==) :: TxMetadataJsonSchemaError -> TxMetadataJsonSchemaError -> Bool Source # (/=) :: TxMetadataJsonSchemaError -> TxMetadataJsonSchemaError -> Bool Source # |
Governance action metadata
Constructors
BaseGovActionMetadata |
Instances
FromJSON (Authors CIP108) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.GovAction Methods parseJSON :: Value -> Parser (Authors CIP108) parseJSONList :: Value -> Parser [Authors CIP108] omittedField :: Maybe (Authors CIP108) | |||||
FromJSON (Body CIP108) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.GovAction Methods parseJSON :: Value -> Parser (Body CIP108) parseJSONList :: Value -> Parser [Body CIP108] omittedField :: Maybe (Body CIP108) | |||||
FromJSON (GovActionMetadata CIP108) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.GovAction Methods parseJSON :: Value -> Parser (GovActionMetadata CIP108) parseJSONList :: Value -> Parser [GovActionMetadata CIP108] | |||||
FromJSON (HashAlgorithm CIP108) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.GovAction Methods parseJSON :: Value -> Parser (HashAlgorithm CIP108) parseJSONList :: Value -> Parser [HashAlgorithm CIP108] | |||||
Generic (Authors CIP108) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.GovAction Associated Types
| |||||
Generic (Body CIP108) Source # | |||||
Generic (HashAlgorithm CIP108) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.GovAction Associated Types
Methods from :: HashAlgorithm CIP108 -> Rep (HashAlgorithm CIP108) x Source # to :: Rep (HashAlgorithm CIP108) x -> HashAlgorithm CIP108 Source # | |||||
Show (Authors CIP108) Source # | |||||
Show (Body CIP108) Source # | |||||
Show (HashAlgorithm CIP108) Source # | |||||
newtype Authors CIP108 Source # | |||||
data Body CIP108 Source # | |||||
data HashAlgorithm CIP108 Source # | |||||
type Rep (Authors CIP108) Source # | |||||
type Rep (Body CIP108) Source # | |||||
type Rep (HashAlgorithm CIP108) Source # | |||||
DRep Metadata
data DRepMetadata Source #
A representation of the required fields for off-chain drep metadata.
Instances
Show DRepMetadata Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata | |||||
HasTypeProxy DRepMetadata Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata Associated Types
Methods proxyToAsType :: Proxy DRepMetadata -> AsType DRepMetadata Source # | |||||
Eq DRepMetadata Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata Methods (==) :: DRepMetadata -> DRepMetadata -> Bool Source # (/=) :: DRepMetadata -> DRepMetadata -> Bool Source # | |||||
Show (Hash DRepMetadata) Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata | |||||
SerialiseAsRawBytes (Hash DRepMetadata) Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata Methods serialiseToRawBytes :: Hash DRepMetadata -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash DRepMetadata) -> ByteString -> Either SerialiseAsRawBytesError (Hash DRepMetadata) Source # | |||||
Eq (Hash DRepMetadata) Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata Methods (==) :: Hash DRepMetadata -> Hash DRepMetadata -> Bool Source # (/=) :: Hash DRepMetadata -> Hash DRepMetadata -> Bool Source # | |||||
data AsType DRepMetadata Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata | |||||
newtype Hash DRepMetadata Source # | |||||
Defined in Cardano.Api.Internal.DRepMetadata |
data DRepMetadataReference Source #
Instances
Show DRepMetadataReference Source # | |
Defined in Cardano.Api.Internal.Certificate | |
Eq DRepMetadataReference Source # | |
Defined in Cardano.Api.Internal.Certificate Methods (==) :: DRepMetadataReference -> DRepMetadataReference -> Bool Source # (/=) :: DRepMetadataReference -> DRepMetadataReference -> Bool Source # |
hashDRepMetadata :: ByteString -> (DRepMetadata, Hash DRepMetadata) Source #
Return the decoded metadata and the hash of the original bytes.
Constructors
DrepRegistrationMetadata |
Instances
FromJSON (Body CIP119) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.DrepRegistration Methods parseJSON :: Value -> Parser (Body CIP119) parseJSONList :: Value -> Parser [Body CIP119] omittedField :: Maybe (Body CIP119) | |||||
FromJSON (GovActionMetadata CIP119) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.DrepRegistration Methods parseJSON :: Value -> Parser (GovActionMetadata CIP119) parseJSONList :: Value -> Parser [GovActionMetadata CIP119] | |||||
FromJSON (HashAlgorithm CIP119) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.DrepRegistration Methods parseJSON :: Value -> Parser (HashAlgorithm CIP119) parseJSONList :: Value -> Parser [HashAlgorithm CIP119] | |||||
Generic (Body CIP119) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.DrepRegistration Associated Types
| |||||
Generic (HashAlgorithm CIP119) Source # | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.DrepRegistration Associated Types
Methods from :: HashAlgorithm CIP119 -> Rep (HashAlgorithm CIP119) x Source # to :: Rep (HashAlgorithm CIP119) x -> HashAlgorithm CIP119 Source # | |||||
Show (Body CIP119) Source # | |||||
Show (HashAlgorithm CIP119) Source # | |||||
data Authors CIP119 Source # | |||||
data Body CIP119 Source # | |||||
Defined in Cardano.Api.Internal.Governance.Metadata.DrepRegistration data Body CIP119 = Body {
| |||||
data HashAlgorithm CIP119 Source # | |||||
type Rep (Body CIP119) Source # | |||||
type Rep (HashAlgorithm CIP119) Source # | |||||
Certificates
data Certificate era where Source #
Constructors
ShelleyRelatedCertificate :: forall era. Typeable era => ShelleyToBabbageEra era -> ShelleyTxCert (ShelleyLedgerEra era) -> Certificate era | |
ConwayCertificate :: forall era. Typeable era => ConwayEraOnwards era -> ConwayTxCert (ShelleyLedgerEra era) -> Certificate era |
Instances
TestEquality Certificate Source # | |||||
Defined in Cardano.Api.Internal.Certificate Methods testEquality :: Certificate a -> Certificate b -> Maybe (a :~: b) Source # | |||||
Show (Certificate era) Source # | |||||
Defined in Cardano.Api.Internal.Certificate | |||||
Typeable era => HasTypeProxy (Certificate era) Source # | |||||
Defined in Cardano.Api.Internal.Certificate Associated Types
Methods proxyToAsType :: Proxy (Certificate era) -> AsType (Certificate era) Source # | |||||
IsShelleyBasedEra era => SerialiseAsCBOR (Certificate era) Source # | |||||
Defined in Cardano.Api.Internal.Certificate Methods serialiseToCBOR :: Certificate era -> ByteString Source # deserialiseFromCBOR :: AsType (Certificate era) -> ByteString -> Either DecoderError (Certificate era) Source # | |||||
IsShelleyBasedEra era => HasTextEnvelope (Certificate era) Source # | |||||
Defined in Cardano.Api.Internal.Certificate Methods textEnvelopeType :: AsType (Certificate era) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: Certificate era -> TextEnvelopeDescr Source # | |||||
IsShelleyBasedEra era => FromCBOR (Certificate era) Source # | |||||
Defined in Cardano.Api.Internal.Certificate | |||||
IsShelleyBasedEra era => ToCBOR (Certificate era) Source # | |||||
Defined in Cardano.Api.Internal.Certificate Methods toCBOR :: Certificate era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Certificate era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Certificate era] -> Size Source # | |||||
Eq (Certificate era) Source # | |||||
Defined in Cardano.Api.Internal.Certificate Methods (==) :: Certificate era -> Certificate era -> Bool Source # (/=) :: Certificate era -> Certificate era -> Bool Source # | |||||
Ord (Certificate era) Source # | |||||
Defined in Cardano.Api.Internal.Certificate Methods compare :: Certificate era -> Certificate era -> Ordering Source # (<) :: Certificate era -> Certificate era -> Bool Source # (<=) :: Certificate era -> Certificate era -> Bool Source # (>) :: Certificate era -> Certificate era -> Bool Source # (>=) :: Certificate era -> Certificate era -> Bool Source # max :: Certificate era -> Certificate era -> Certificate era Source # min :: Certificate era -> Certificate era -> Certificate era Source # | |||||
data AsType (Certificate era) Source # | |||||
Defined in Cardano.Api.Internal.Certificate |
Registering stake address and delegating
Certificates that are embedded in transactions for registering and unregistering stake address, and for setting the stake pool delegation choice for a stake address.
data StakeAddressRequirements era where Source #
Constructors
StakeAddrRegistrationConway :: forall era. ConwayEraOnwards era -> Coin -> StakeCredential -> StakeAddressRequirements era | |
StakeAddrRegistrationPreConway :: forall era. ShelleyToBabbageEra era -> StakeCredential -> StakeAddressRequirements era |
data StakeDelegationRequirements era where Source #
Constructors
StakeDelegationRequirementsConwayOnwards :: forall era. ConwayEraOnwards era -> StakeCredential -> Delegatee -> StakeDelegationRequirements era | |
StakeDelegationRequirementsPreConway :: forall era. ShelleyToBabbageEra era -> StakeCredential -> PoolId -> StakeDelegationRequirements era |
makeStakeAddressDelegationCertificate :: StakeDelegationRequirements era -> Certificate era Source #
makeStakeAddressUnregistrationCertificate :: StakeAddressRequirements era -> Certificate era Source #
makeStakeAddressAndDRepDelegationCertificate :: ConwayEraOnwards era -> StakeCredential -> Delegatee -> Coin -> Certificate era Source #
Registering stake pools
Certificates that are embedded in transactions for registering and retiring stake pools. This includes updating the stake pool parameters.
data StakePoolRegistrationRequirements era where Source #
Constructors
StakePoolRegistrationRequirementsConwayOnwards :: forall era. ConwayEraOnwards era -> PoolParams -> StakePoolRegistrationRequirements era | |
StakePoolRegistrationRequirementsPreConway :: forall era. ShelleyToBabbageEra era -> PoolParams -> StakePoolRegistrationRequirements era |
data StakePoolRetirementRequirements era where Source #
Constructors
StakePoolRetirementRequirementsConwayOnwards :: forall era. ConwayEraOnwards era -> PoolId -> EpochNo -> StakePoolRetirementRequirements era | |
StakePoolRetirementRequirementsPreConway :: forall era. ShelleyToBabbageEra era -> PoolId -> EpochNo -> StakePoolRetirementRequirements era |
makeStakePoolRegistrationCertificate :: StakePoolRegistrationRequirements era -> Certificate era Source #
makeStakePoolRetirementCertificate :: StakePoolRetirementRequirements era -> Certificate era Source #
data StakePoolParameters Source #
Instances
Show StakePoolParameters Source # | |
Defined in Cardano.Api.Internal.Certificate | |
Eq StakePoolParameters Source # | |
Defined in Cardano.Api.Internal.Certificate Methods (==) :: StakePoolParameters -> StakePoolParameters -> Bool Source # (/=) :: StakePoolParameters -> StakePoolParameters -> Bool Source # |
data StakePoolRelay Source #
Instances
Show StakePoolRelay Source # | |
Defined in Cardano.Api.Internal.Certificate | |
Eq StakePoolRelay Source # | |
Defined in Cardano.Api.Internal.Certificate Methods (==) :: StakePoolRelay -> StakePoolRelay -> Bool Source # (/=) :: StakePoolRelay -> StakePoolRelay -> Bool Source # |
data StakePoolMetadataReference Source #
Instances
Show StakePoolMetadataReference Source # | |
Defined in Cardano.Api.Internal.Certificate | |
Eq StakePoolMetadataReference Source # | |
Defined in Cardano.Api.Internal.Certificate Methods (==) :: StakePoolMetadataReference -> StakePoolMetadataReference -> Bool Source # (/=) :: StakePoolMetadataReference -> StakePoolMetadataReference -> Bool Source # |
Anchor data
data AnchorDataFromCertificateError Source #
Constructors
InvalidPoolMetadataHashError Url ByteString |
Instances
Show AnchorDataFromCertificateError Source # | |
Defined in Cardano.Api.Internal.Certificate | |
Error AnchorDataFromCertificateError Source # | |
Defined in Cardano.Api.Internal.Certificate Methods prettyError :: AnchorDataFromCertificateError -> Doc ann Source # | |
Eq AnchorDataFromCertificateError Source # | |
Defined in Cardano.Api.Internal.Certificate |
getAnchorDataFromCertificate :: Certificate era -> Either AnchorDataFromCertificateError (Maybe Anchor) Source #
Get anchor data url and hash from a certificate. A return value of Nothing
means that the certificate does not contain anchor data.
isDRepRegOrUpdateCert :: Certificate era -> Bool Source #
Rewards
newtype DelegationsAndRewards Source #
A mapping of Shelley reward accounts to both the stake pool that they delegate to and their reward account balance. TODO: Move to cardano-api
Constructors
DelegationsAndRewards (Map StakeAddress Coin, Map StakeAddress PoolId) |
Instances
FromJSON DelegationsAndRewards Source # | |
Defined in Cardano.Api.Internal.Rewards Methods parseJSON :: Value -> Parser DelegationsAndRewards parseJSONList :: Value -> Parser [DelegationsAndRewards] | |
ToJSON DelegationsAndRewards Source # | |
Defined in Cardano.Api.Internal.Rewards Methods toJSON :: DelegationsAndRewards -> Value toEncoding :: DelegationsAndRewards -> Encoding toJSONList :: [DelegationsAndRewards] -> Value toEncodingList :: [DelegationsAndRewards] -> Encoding | |
Show DelegationsAndRewards Source # | |
Defined in Cardano.Api.Internal.Rewards | |
Eq DelegationsAndRewards Source # | |
Defined in Cardano.Api.Internal.Rewards Methods (==) :: DelegationsAndRewards -> DelegationsAndRewards -> Bool Source # (/=) :: DelegationsAndRewards -> DelegationsAndRewards -> Bool Source # |
mergeDelegsAndRewards :: DelegationsAndRewards -> [(StakeAddress, Maybe Coin, Maybe PoolId)] Source #
Stake pool off-chain metadata
data StakePoolMetadata Source #
A representation of the required fields for off-chain stake pool metadata.
Instances
FromJSON StakePoolMetadata Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata Methods parseJSON :: Value -> Parser StakePoolMetadata parseJSONList :: Value -> Parser [StakePoolMetadata] | |||||
Show StakePoolMetadata Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata | |||||
HasTypeProxy StakePoolMetadata Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata Associated Types
Methods proxyToAsType :: Proxy StakePoolMetadata -> AsType StakePoolMetadata Source # | |||||
Eq StakePoolMetadata Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata Methods (==) :: StakePoolMetadata -> StakePoolMetadata -> Bool Source # (/=) :: StakePoolMetadata -> StakePoolMetadata -> Bool Source # | |||||
Show (Hash StakePoolMetadata) Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata | |||||
SerialiseAsRawBytes (Hash StakePoolMetadata) Source # | |||||
Eq (Hash StakePoolMetadata) Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata Methods (==) :: Hash StakePoolMetadata -> Hash StakePoolMetadata -> Bool Source # (/=) :: Hash StakePoolMetadata -> Hash StakePoolMetadata -> Bool Source # | |||||
data AsType StakePoolMetadata Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata | |||||
newtype Hash StakePoolMetadata Source # | |||||
Defined in Cardano.Api.Internal.StakePoolMetadata |
validateAndHashStakePoolMetadata :: ByteString -> Either StakePoolMetadataValidationError (StakePoolMetadata, Hash StakePoolMetadata) Source #
Decode and validate the provided JSON-encoded bytes as StakePoolMetadata
.
Return the decoded metadata and the hash of the original bytes.
data StakePoolMetadataValidationError Source #
A stake pool metadata validation error.
Constructors
StakePoolMetadataJsonDecodeError !String | |
StakePoolMetadataInvalidLengthError | The length of the JSON-encoded stake pool metadata exceeds the maximum. |
Instances
Data StakePoolMetadataValidationError Source # | |
Defined in Cardano.Api.Internal.StakePoolMetadata Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StakePoolMetadataValidationError -> c StakePoolMetadataValidationError Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StakePoolMetadataValidationError Source # toConstr :: StakePoolMetadataValidationError -> Constr Source # dataTypeOf :: StakePoolMetadataValidationError -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c StakePoolMetadataValidationError) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StakePoolMetadataValidationError) Source # gmapT :: (forall b. Data b => b -> b) -> StakePoolMetadataValidationError -> StakePoolMetadataValidationError Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StakePoolMetadataValidationError -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StakePoolMetadataValidationError -> r Source # gmapQ :: (forall d. Data d => d -> u) -> StakePoolMetadataValidationError -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> StakePoolMetadataValidationError -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> StakePoolMetadataValidationError -> m StakePoolMetadataValidationError Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StakePoolMetadataValidationError -> m StakePoolMetadataValidationError Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StakePoolMetadataValidationError -> m StakePoolMetadataValidationError Source # | |
Show StakePoolMetadataValidationError Source # | |
Defined in Cardano.Api.Internal.StakePoolMetadata | |
Error StakePoolMetadataValidationError Source # | |
Defined in Cardano.Api.Internal.StakePoolMetadata Methods prettyError :: StakePoolMetadataValidationError -> Doc ann Source # | |
Eq StakePoolMetadataValidationError Source # | |
Scripts
Both PaymentCredential
s and StakeCredential
s can use scripts.
Script languages
data SimpleScript' Source #
Instances
HasTypeProxy SimpleScript' Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
Methods proxyToAsType :: Proxy SimpleScript' -> AsType SimpleScript' Source # | |||||
IsScriptLanguage SimpleScript' Source # | |||||
Defined in Cardano.Api.Internal.Script Methods | |||||
data AsType SimpleScript' Source # | |||||
Defined in Cardano.Api.Internal.Script |
data PlutusScriptV1 Source #
The original simple script language which supports
- require a signature from a given key (by verification key hash)
- n-way and combinator
- n-way or combinator
- m-of-n combinator
This version of the language was introduced in the ShelleyEra
.
The second version of the simple script language. It has all the features of the original simple script language plus new atomic predicates:
- require the time be before a given slot number
- require the time be after a given slot number
This version of the language was introduced in the AllegraEra
.
However we opt for a single type level tag SimpleScript'
as the second version of
of the language introduced in the Allegra era is a superset of the language introduced
in the Shelley era.
Place holder type to show what the pattern is to extend to multiple languages, not just multiple versions of a single language.
Instances
HasTypeProxy PlutusScriptV1 Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
Methods proxyToAsType :: Proxy PlutusScriptV1 -> AsType PlutusScriptV1 Source # | |||||
IsPlutusScriptLanguage PlutusScriptV1 Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
IsScriptLanguage PlutusScriptV1 Source # | |||||
Defined in Cardano.Api.Internal.Script Methods | |||||
HasScriptLanguageInEra PlutusScriptV1 AlonzoEra Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
HasScriptLanguageInEra PlutusScriptV1 BabbageEra Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
HasScriptLanguageInEra PlutusScriptV1 ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
ToAlonzoScript PlutusScriptV1 BabbageEra Source # | |||||
Defined in Cardano.Api.Internal.Script Methods toLedgerScript :: PlutusScript PlutusScriptV1 -> AlonzoScript (ShelleyLedgerEra BabbageEra) Source # | |||||
ToAlonzoScript PlutusScriptV1 ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Script Methods toLedgerScript :: PlutusScript PlutusScriptV1 -> AlonzoScript (ShelleyLedgerEra ConwayEra) Source # | |||||
data AsType PlutusScriptV1 Source # | |||||
Defined in Cardano.Api.Internal.Script |
data PlutusScriptV2 Source #
Instances
HasTypeProxy PlutusScriptV2 Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
Methods proxyToAsType :: Proxy PlutusScriptV2 -> AsType PlutusScriptV2 Source # | |||||
IsPlutusScriptLanguage PlutusScriptV2 Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
IsScriptLanguage PlutusScriptV2 Source # | |||||
Defined in Cardano.Api.Internal.Script Methods | |||||
HasScriptLanguageInEra PlutusScriptV2 BabbageEra Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
HasScriptLanguageInEra PlutusScriptV2 ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
ToAlonzoScript PlutusScriptV2 BabbageEra Source # | |||||
Defined in Cardano.Api.Internal.Script Methods toLedgerScript :: PlutusScript PlutusScriptV2 -> AlonzoScript (ShelleyLedgerEra BabbageEra) Source # | |||||
ToAlonzoScript PlutusScriptV2 ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Script Methods toLedgerScript :: PlutusScript PlutusScriptV2 -> AlonzoScript (ShelleyLedgerEra ConwayEra) Source # | |||||
data AsType PlutusScriptV2 Source # | |||||
Defined in Cardano.Api.Internal.Script |
data PlutusScriptV3 Source #
Instances
HasTypeProxy PlutusScriptV3 Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
Methods proxyToAsType :: Proxy PlutusScriptV3 -> AsType PlutusScriptV3 Source # | |||||
IsPlutusScriptLanguage PlutusScriptV3 Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
IsScriptLanguage PlutusScriptV3 Source # | |||||
Defined in Cardano.Api.Internal.Script Methods | |||||
HasScriptLanguageInEra PlutusScriptV3 ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
ToAlonzoScript PlutusScriptV3 ConwayEra Source # | |||||
Defined in Cardano.Api.Internal.Script Methods toLedgerScript :: PlutusScript PlutusScriptV3 -> AlonzoScript (ShelleyLedgerEra ConwayEra) Source # | |||||
data AsType PlutusScriptV3 Source # | |||||
Defined in Cardano.Api.Internal.Script |
data ScriptLanguage lang where Source #
Constructors
SimpleScriptLanguage :: ScriptLanguage SimpleScript' | |
PlutusScriptLanguage :: forall lang. IsPlutusScriptLanguage lang => PlutusScriptVersion lang -> ScriptLanguage lang |
Instances
TestEquality ScriptLanguage Source # | |
Defined in Cardano.Api.Internal.Script Methods testEquality :: ScriptLanguage a -> ScriptLanguage b -> Maybe (a :~: b) Source # | |
Show (ScriptLanguage lang) Source # | |
Defined in Cardano.Api.Internal.Script | |
Eq (ScriptLanguage lang) Source # | |
Defined in Cardano.Api.Internal.Script Methods (==) :: ScriptLanguage lang -> ScriptLanguage lang -> Bool Source # (/=) :: ScriptLanguage lang -> ScriptLanguage lang -> Bool Source # |
data PlutusScriptVersion lang where Source #
Constructors
PlutusScriptV1 :: PlutusScriptVersion PlutusScriptV1 | |
PlutusScriptV2 :: PlutusScriptVersion PlutusScriptV2 | |
PlutusScriptV3 :: PlutusScriptVersion PlutusScriptV3 |
Instances
TestEquality PlutusScriptVersion Source # | |
Defined in Cardano.Api.Internal.Script Methods testEquality :: PlutusScriptVersion a -> PlutusScriptVersion b -> Maybe (a :~: b) Source # | |
Show (PlutusScriptVersion lang) Source # | |
Defined in Cardano.Api.Internal.Script | |
Eq (PlutusScriptVersion lang) Source # | |
Defined in Cardano.Api.Internal.Script Methods (==) :: PlutusScriptVersion lang -> PlutusScriptVersion lang -> Bool Source # (/=) :: PlutusScriptVersion lang -> PlutusScriptVersion lang -> Bool Source # |
data AnyScriptLanguage where Source #
Constructors
AnyScriptLanguage :: forall lang. ScriptLanguage lang -> AnyScriptLanguage |
Instances
Bounded AnyScriptLanguage Source # | |
Defined in Cardano.Api.Internal.Script | |
Enum AnyScriptLanguage Source # | |
Defined in Cardano.Api.Internal.Script Methods succ :: AnyScriptLanguage -> AnyScriptLanguage Source # pred :: AnyScriptLanguage -> AnyScriptLanguage Source # toEnum :: Int -> AnyScriptLanguage Source # fromEnum :: AnyScriptLanguage -> Int Source # enumFrom :: AnyScriptLanguage -> [AnyScriptLanguage] Source # enumFromThen :: AnyScriptLanguage -> AnyScriptLanguage -> [AnyScriptLanguage] Source # enumFromTo :: AnyScriptLanguage -> AnyScriptLanguage -> [AnyScriptLanguage] Source # enumFromThenTo :: AnyScriptLanguage -> AnyScriptLanguage -> AnyScriptLanguage -> [AnyScriptLanguage] Source # | |
Show AnyScriptLanguage Source # | |
Defined in Cardano.Api.Internal.Script | |
Eq AnyScriptLanguage Source # | |
Defined in Cardano.Api.Internal.Script Methods (==) :: AnyScriptLanguage -> AnyScriptLanguage -> Bool Source # (/=) :: AnyScriptLanguage -> AnyScriptLanguage -> Bool Source # | |
Ord AnyScriptLanguage Source # | |
Defined in Cardano.Api.Internal.Script Methods compare :: AnyScriptLanguage -> AnyScriptLanguage -> Ordering Source # (<) :: AnyScriptLanguage -> AnyScriptLanguage -> Bool Source # (<=) :: AnyScriptLanguage -> AnyScriptLanguage -> Bool Source # (>) :: AnyScriptLanguage -> AnyScriptLanguage -> Bool Source # (>=) :: AnyScriptLanguage -> AnyScriptLanguage -> Bool Source # max :: AnyScriptLanguage -> AnyScriptLanguage -> AnyScriptLanguage Source # min :: AnyScriptLanguage -> AnyScriptLanguage -> AnyScriptLanguage Source # |
data AnyPlutusScriptVersion where Source #
Constructors
AnyPlutusScriptVersion :: forall lang. IsPlutusScriptLanguage lang => PlutusScriptVersion lang -> AnyPlutusScriptVersion |
Instances
FromJSON AnyPlutusScriptVersion Source # | |
Defined in Cardano.Api.Internal.Script Methods parseJSON :: Value -> Parser AnyPlutusScriptVersion parseJSONList :: Value -> Parser [AnyPlutusScriptVersion] | |
FromJSONKey AnyPlutusScriptVersion Source # | |
Defined in Cardano.Api.Internal.Script Methods fromJSONKey :: FromJSONKeyFunction AnyPlutusScriptVersion fromJSONKeyList :: FromJSONKeyFunction [AnyPlutusScriptVersion] | |
ToJSON AnyPlutusScriptVersion Source # | |
Defined in Cardano.Api.Internal.Script Methods toJSON :: AnyPlutusScriptVersion -> Value toEncoding :: AnyPlutusScriptVersion -> Encoding toJSONList :: [AnyPlutusScriptVersion] -> Value toEncodingList :: [AnyPlutusScriptVersion] -> Encoding | |
ToJSONKey AnyPlutusScriptVersion Source # | |
Defined in Cardano.Api.Internal.Script Methods toJSONKey :: ToJSONKeyFunction AnyPlutusScriptVersion toJSONKeyList :: ToJSONKeyFunction [AnyPlutusScriptVersion] | |
Bounded AnyPlutusScriptVersion Source # | |
Defined in Cardano.Api.Internal.Script | |
Enum AnyPlutusScriptVersion Source # | |
Defined in Cardano.Api.Internal.Script Methods succ :: AnyPlutusScriptVersion -> AnyPlutusScriptVersion Source # pred :: AnyPlutusScriptVersion -> AnyPlutusScriptVersion Source # toEnum :: Int -> AnyPlutusScriptVersion Source # fromEnum :: AnyPlutusScriptVersion -> Int Source # enumFrom :: AnyPlutusScriptVersion -> [AnyPlutusScriptVersion] Source # enumFromThen :: AnyPlutusScriptVersion -> AnyPlutusScriptVersion -> [AnyPlutusScriptVersion] Source # enumFromTo :: AnyPlutusScriptVersion -> AnyPlutusScriptVersion -> [AnyPlutusScriptVersion] Source # enumFromThenTo :: AnyPlutusScriptVersion -> AnyPlutusScriptVersion -> AnyPlutusScriptVersion -> [AnyPlutusScriptVersion] Source # | |
Show AnyPlutusScriptVersion Source # | |
Defined in Cardano.Api.Internal.Script | |
FromCBOR AnyPlutusScriptVersion Source # | |
Defined in Cardano.Api.Internal.Script | |
ToCBOR AnyPlutusScriptVersion Source # | |
Defined in Cardano.Api.Internal.Script Methods toCBOR :: AnyPlutusScriptVersion -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy AnyPlutusScriptVersion -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [AnyPlutusScriptVersion] -> Size Source # | |
Eq AnyPlutusScriptVersion Source # | |
Defined in Cardano.Api.Internal.Script Methods (==) :: AnyPlutusScriptVersion -> AnyPlutusScriptVersion -> Bool Source # (/=) :: AnyPlutusScriptVersion -> AnyPlutusScriptVersion -> Bool Source # | |
Ord AnyPlutusScriptVersion Source # | |
Defined in Cardano.Api.Internal.Script Methods compare :: AnyPlutusScriptVersion -> AnyPlutusScriptVersion -> Ordering Source # (<) :: AnyPlutusScriptVersion -> AnyPlutusScriptVersion -> Bool Source # (<=) :: AnyPlutusScriptVersion -> AnyPlutusScriptVersion -> Bool Source # (>) :: AnyPlutusScriptVersion -> AnyPlutusScriptVersion -> Bool Source # (>=) :: AnyPlutusScriptVersion -> AnyPlutusScriptVersion -> Bool Source # max :: AnyPlutusScriptVersion -> AnyPlutusScriptVersion -> AnyPlutusScriptVersion Source # min :: AnyPlutusScriptVersion -> AnyPlutusScriptVersion -> AnyPlutusScriptVersion Source # |
class IsScriptLanguage lang => IsPlutusScriptLanguage lang where Source #
Methods
Instances
class HasTypeProxy lang => IsScriptLanguage lang where Source #
Methods
scriptLanguage :: ScriptLanguage lang Source #
Instances
IsScriptLanguage PlutusScriptV1 Source # | |
Defined in Cardano.Api.Internal.Script Methods | |
IsScriptLanguage PlutusScriptV2 Source # | |
Defined in Cardano.Api.Internal.Script Methods | |
IsScriptLanguage PlutusScriptV3 Source # | |
Defined in Cardano.Api.Internal.Script Methods | |
IsScriptLanguage SimpleScript' Source # | |
Defined in Cardano.Api.Internal.Script Methods |
Scripts in a specific language
data Script lang where Source #
A script in a particular language.
See also ScriptInAnyLang
for a script in any of the known languages.
See also ScriptInEra
for a script in a language that is available within
a particular era.
Note that some but not all scripts have an external JSON syntax, hence this
type has no JSON serialisation instances. The SimpleScript
family of
languages do have a JSON syntax and thus have ToJSON
/FromJSON
instances.
Constructors
SimpleScript :: !SimpleScript -> Script SimpleScript' | |
PlutusScript :: forall lang. IsPlutusScriptLanguage lang => !(PlutusScriptVersion lang) -> !(PlutusScript lang) -> Script lang |
Instances
Show (Script lang) Source # | |||||
HasTypeProxy lang => HasTypeProxy (Script lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
| |||||
IsScriptLanguage lang => SerialiseAsCBOR (Script lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Methods serialiseToCBOR :: Script lang -> ByteString Source # deserialiseFromCBOR :: AsType (Script lang) -> ByteString -> Either DecoderError (Script lang) Source # | |||||
IsScriptLanguage lang => HasTextEnvelope (Script lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Methods textEnvelopeType :: AsType (Script lang) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: Script lang -> TextEnvelopeDescr Source # | |||||
Eq (Script lang) Source # | |||||
data AsType (Script lang) Source # | |||||
Defined in Cardano.Api.Internal.Script |
data PlutusScriptInEra era lang where Source #
Constructors
PlutusScriptInEra :: forall lang era. PlutusScript lang -> PlutusScriptInEra era lang |
Instances
Show (PlutusScriptInEra era lang) Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
(HasTypeProxy era, HasTypeProxy lang) => HasTypeProxy (PlutusScriptInEra era lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
Methods proxyToAsType :: Proxy (PlutusScriptInEra era lang) -> AsType (PlutusScriptInEra era lang) Source # | |||||
(Era (ShelleyLedgerEra era), HasTypeProxy (PlutusScriptInEra era lang), PlutusLanguage (ToLedgerPlutusLanguage lang)) => SerialiseAsCBOR (PlutusScriptInEra era lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Methods serialiseToCBOR :: PlutusScriptInEra era lang -> ByteString Source # deserialiseFromCBOR :: AsType (PlutusScriptInEra era lang) -> ByteString -> Either DecoderError (PlutusScriptInEra era lang) Source # | |||||
Eq (PlutusScriptInEra era lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Methods (==) :: PlutusScriptInEra era lang -> PlutusScriptInEra era lang -> Bool Source # (/=) :: PlutusScriptInEra era lang -> PlutusScriptInEra era lang -> Bool Source # | |||||
data AsType (PlutusScriptInEra era lang) Source # | |||||
Defined in Cardano.Api.Internal.Script |
Scripts in any language
data ScriptInAnyLang where Source #
Sometimes it is necessary to handle all languages without making static type distinctions between languages. For example, when reading external input, or before the era context is known.
Use toScriptInEra
to convert to a script in the context of an era.
Constructors
ScriptInAnyLang :: forall lang. ScriptLanguage lang -> Script lang -> ScriptInAnyLang |
Instances
FromJSON ScriptInAnyLang Source # | |||||
Defined in Cardano.Api.Internal.Script Methods parseJSON :: Value -> Parser ScriptInAnyLang parseJSONList :: Value -> Parser [ScriptInAnyLang] | |||||
ToJSON ScriptInAnyLang Source # | |||||
Defined in Cardano.Api.Internal.Script Methods toJSON :: ScriptInAnyLang -> Value toEncoding :: ScriptInAnyLang -> Encoding toJSONList :: [ScriptInAnyLang] -> Value toEncodingList :: [ScriptInAnyLang] -> Encoding omitField :: ScriptInAnyLang -> Bool | |||||
Show ScriptInAnyLang Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
HasTypeProxy ScriptInAnyLang Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
Methods proxyToAsType :: Proxy ScriptInAnyLang -> AsType ScriptInAnyLang Source # | |||||
Eq ScriptInAnyLang Source # | |||||
Defined in Cardano.Api.Internal.Script Methods (==) :: ScriptInAnyLang -> ScriptInAnyLang -> Bool Source # (/=) :: ScriptInAnyLang -> ScriptInAnyLang -> Bool Source # | |||||
data AsType ScriptInAnyLang Source # | |||||
Defined in Cardano.Api.Internal.Script |
toScriptInAnyLang :: Script lang -> ScriptInAnyLang Source #
Convert a script in a specific statically-known language to a
ScriptInAnyLang
.
No inverse to this is provided, just do case analysis on the ScriptLanguage
field within the ScriptInAnyLang
constructor.
Scripts in a specific era
data ScriptInEra era where Source #
Constructors
ScriptInEra :: forall lang era. ScriptLanguageInEra lang era -> Script lang -> ScriptInEra era |
Instances
Show (ScriptInEra era) Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
HasTypeProxy era => HasTypeProxy (ScriptInEra era) Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
Methods proxyToAsType :: Proxy (ScriptInEra era) -> AsType (ScriptInEra era) Source # | |||||
Eq (ScriptInEra era) Source # | |||||
Defined in Cardano.Api.Internal.Script Methods (==) :: ScriptInEra era -> ScriptInEra era -> Bool Source # (/=) :: ScriptInEra era -> ScriptInEra era -> Bool Source # | |||||
data AsType (ScriptInEra era) Source # | |||||
Defined in Cardano.Api.Internal.Script |
toScriptInEra :: ShelleyBasedEra era -> ScriptInAnyLang -> Maybe (ScriptInEra era) Source #
Given a target era and a script in some language, check if the language is
supported in that era, and if so return a ScriptInEra
.
eraOfScriptInEra :: ScriptInEra era -> ShelleyBasedEra era Source #
class HasScriptLanguageInEra lang era where Source #
Smart-constructor for ScriptLanguageInEra
to write functions
manipulating scripts that do not commit to a particular era.
Methods
scriptLanguageInEra :: ScriptLanguageInEra lang era Source #
Instances
HasScriptLanguageInEra PlutusScriptV1 AlonzoEra Source # | |
Defined in Cardano.Api.Internal.Script | |
HasScriptLanguageInEra PlutusScriptV1 BabbageEra Source # | |
Defined in Cardano.Api.Internal.Script | |
HasScriptLanguageInEra PlutusScriptV1 ConwayEra Source # | |
Defined in Cardano.Api.Internal.Script | |
HasScriptLanguageInEra PlutusScriptV2 BabbageEra Source # | |
Defined in Cardano.Api.Internal.Script | |
HasScriptLanguageInEra PlutusScriptV2 ConwayEra Source # | |
Defined in Cardano.Api.Internal.Script | |
HasScriptLanguageInEra PlutusScriptV3 ConwayEra Source # | |
Defined in Cardano.Api.Internal.Script |
class ToAlonzoScript lang era where Source #
Methods
toLedgerScript :: PlutusScript lang -> AlonzoScript (ShelleyLedgerEra era) Source #
Instances
ToAlonzoScript PlutusScriptV1 BabbageEra Source # | |
Defined in Cardano.Api.Internal.Script Methods toLedgerScript :: PlutusScript PlutusScriptV1 -> AlonzoScript (ShelleyLedgerEra BabbageEra) Source # | |
ToAlonzoScript PlutusScriptV1 ConwayEra Source # | |
Defined in Cardano.Api.Internal.Script Methods toLedgerScript :: PlutusScript PlutusScriptV1 -> AlonzoScript (ShelleyLedgerEra ConwayEra) Source # | |
ToAlonzoScript PlutusScriptV2 BabbageEra Source # | |
Defined in Cardano.Api.Internal.Script Methods toLedgerScript :: PlutusScript PlutusScriptV2 -> AlonzoScript (ShelleyLedgerEra BabbageEra) Source # | |
ToAlonzoScript PlutusScriptV2 ConwayEra Source # | |
Defined in Cardano.Api.Internal.Script Methods toLedgerScript :: PlutusScript PlutusScriptV2 -> AlonzoScript (ShelleyLedgerEra ConwayEra) Source # | |
ToAlonzoScript PlutusScriptV3 ConwayEra Source # | |
Defined in Cardano.Api.Internal.Script Methods toLedgerScript :: PlutusScript PlutusScriptV3 -> AlonzoScript (ShelleyLedgerEra ConwayEra) Source # |
type AlonzoEraOnwardsConstraints era = (HashAlgorithm HASH, Signable (VRF StandardCrypto) Seed, PraosProtocolSupportsNode (ConsensusProtocol era), ShelleyBlock (ConsensusProtocol era) (ShelleyLedgerEra era) ~ ConsensusBlockForEra era, ShelleyCompatible (ConsensusProtocol era) (ShelleyLedgerEra era), ADDRHASH ~ Blake2b_224, AlonzoEraPParams (ShelleyLedgerEra era), AlonzoEraTx (ShelleyLedgerEra era), AlonzoEraTxBody (ShelleyLedgerEra era), AlonzoEraTxOut (ShelleyLedgerEra era), AlonzoEraTxWits (ShelleyLedgerEra era), Era (ShelleyLedgerEra era), EraPParams (ShelleyLedgerEra era), EraTx (ShelleyLedgerEra era), EraTxBody (ShelleyLedgerEra era), EraTxOut (ShelleyLedgerEra era), EraUTxO (ShelleyLedgerEra era), HashAnnotated (TxBody (ShelleyLedgerEra era)) EraIndependentTxBody, MaryEraTxBody (ShelleyLedgerEra era), NativeScript (ShelleyLedgerEra era) ~ Timelock (ShelleyLedgerEra era), EraPlutusContext (ShelleyLedgerEra era), Script (ShelleyLedgerEra era) ~ AlonzoScript (ShelleyLedgerEra era), ScriptsNeeded (ShelleyLedgerEra era) ~ AlonzoScriptsNeeded (ShelleyLedgerEra era), ShelleyEraTxCert (ShelleyLedgerEra era), Value (ShelleyLedgerEra era) ~ MaryValue, FromCBOR (ChainDepState (ConsensusProtocol era)), FromCBOR (DebugLedgerState era), IsCardanoEra era, IsShelleyBasedEra era, ToJSON (ChainDepState (ConsensusProtocol era)), ToJSON (DebugLedgerState era), Typeable era, (era == ByronEra) ~ 'False) Source #
Use of a script in an era as a witness
data WitCtxTxIn Source #
A tag type for the context in which a script is used in a transaction.
This type tags the context as being to witness a transaction input.
Instances
IsScriptWitnessInCtx WitCtxTxIn Source # | |
Defined in Cardano.Api.Internal.Script Methods scriptWitnessInCtx :: ScriptWitnessInCtx WitCtxTxIn Source # |
data WitCtxMint Source #
A tag type for the context in which a script is used in a transaction.
This type tags the context as being to witness minting.
Instances
IsScriptWitnessInCtx WitCtxMint Source # | |
Defined in Cardano.Api.Internal.Script Methods scriptWitnessInCtx :: ScriptWitnessInCtx WitCtxMint Source # |
data WitCtxStake Source #
A tag type for the context in which a script is used in a transaction.
This type tags the context as being to witness the use of stake addresses in certificates, withdrawals, voting and proposals.
Instances
IsScriptWitnessInCtx WitCtxStake Source # | |
Defined in Cardano.Api.Internal.Script Methods scriptWitnessInCtx :: ScriptWitnessInCtx WitCtxStake Source # |
data WitCtx witctx where Source #
This GADT provides a value-level representation of all the witness contexts. This enables pattern matching on the context to allow them to be treated in a non-uniform way.
Constructors
WitCtxTxIn :: WitCtx WitCtxTxIn | |
WitCtxMint :: WitCtx WitCtxMint | |
WitCtxStake :: WitCtx WitCtxStake |
data ScriptWitness witctx era where Source #
A use of a script within a transaction body to witness that something is being used in an authorised manner. That can be
- spending a transaction input
- minting tokens
- using a certificate (stake address certs specifically)
- withdrawing from a reward account
For simple script languages, the use of the script is the same in all contexts. For Plutus scripts, using a script involves supplying a redeemer. In addition, Plutus scripts used for spending inputs must also supply the datum value used when originally creating the TxOut that is now being spent.
Constructors
SimpleScriptWitness :: forall era witctx. ScriptLanguageInEra SimpleScript' era -> SimpleScriptOrReferenceInput SimpleScript' -> ScriptWitness witctx era | |
PlutusScriptWitness :: forall lang era witctx. IsPlutusScriptLanguage lang => ScriptLanguageInEra lang era -> PlutusScriptVersion lang -> PlutusScriptOrReferenceInput lang -> ScriptDatum witctx -> ScriptRedeemer -> ExecutionUnits -> ScriptWitness witctx era |
Instances
Show (ScriptWitness witctx era) Source # | |
Defined in Cardano.Api.Internal.Script | |
Eq (ScriptWitness witctx era) Source # | |
Defined in Cardano.Api.Internal.Script Methods (==) :: ScriptWitness witctx era -> ScriptWitness witctx era -> Bool Source # (/=) :: ScriptWitness witctx era -> ScriptWitness witctx era -> Bool Source # |
getScriptWitnessScript :: ScriptWitness witctx era -> Maybe (ScriptInEra era) Source #
getScriptWitnessReferenceInput :: ScriptWitness witctx era -> Maybe TxIn Source #
getScriptWitnessReferenceInputOrScript :: ScriptWitness witctx era -> Either (ScriptInEra era) TxIn Source #
We cannot always extract a script from a script witness due to reference scripts.
Reference scripts exist in the UTxO, so without access to the UTxO we cannot
retrieve the script.
So in the cases for script reference, the result contains Right TxIn
.
data Witness witctx era where Source #
Constructors
KeyWitness :: forall witctx era. KeyWitnessInCtx witctx -> Witness witctx era | |
ScriptWitness :: forall witctx era. ScriptWitnessInCtx witctx -> ScriptWitness witctx era -> Witness witctx era |
data KeyWitnessInCtx witctx where Source #
Constructors
KeyWitnessForSpending :: KeyWitnessInCtx WitCtxTxIn | |
KeyWitnessForStakeAddr :: KeyWitnessInCtx WitCtxStake |
Instances
Show (KeyWitnessInCtx witctx) Source # | |
Defined in Cardano.Api.Internal.Script | |
Eq (KeyWitnessInCtx witctx) Source # | |
Defined in Cardano.Api.Internal.Script Methods (==) :: KeyWitnessInCtx witctx -> KeyWitnessInCtx witctx -> Bool Source # (/=) :: KeyWitnessInCtx witctx -> KeyWitnessInCtx witctx -> Bool Source # |
data ScriptWitnessInCtx witctx where Source #
Constructors
ScriptWitnessForSpending :: ScriptWitnessInCtx WitCtxTxIn | |
ScriptWitnessForMinting :: ScriptWitnessInCtx WitCtxMint | |
ScriptWitnessForStakeAddr :: ScriptWitnessInCtx WitCtxStake |
Instances
Show (ScriptWitnessInCtx witctx) Source # | |
Defined in Cardano.Api.Internal.Script | |
Eq (ScriptWitnessInCtx witctx) Source # | |
Defined in Cardano.Api.Internal.Script Methods (==) :: ScriptWitnessInCtx witctx -> ScriptWitnessInCtx witctx -> Bool Source # (/=) :: ScriptWitnessInCtx witctx -> ScriptWitnessInCtx witctx -> Bool Source # |
class IsScriptWitnessInCtx ctx where Source #
Methods
Instances
IsScriptWitnessInCtx WitCtxMint Source # | |
Defined in Cardano.Api.Internal.Script Methods scriptWitnessInCtx :: ScriptWitnessInCtx WitCtxMint Source # | |
IsScriptWitnessInCtx WitCtxStake Source # | |
Defined in Cardano.Api.Internal.Script Methods scriptWitnessInCtx :: ScriptWitnessInCtx WitCtxStake Source # | |
IsScriptWitnessInCtx WitCtxTxIn Source # | |
Defined in Cardano.Api.Internal.Script Methods scriptWitnessInCtx :: ScriptWitnessInCtx WitCtxTxIn Source # |
data ScriptDatum witctx where Source #
Constructors
ScriptDatumForTxIn :: Maybe HashableScriptData -> ScriptDatum WitCtxTxIn | |
InlineScriptDatum :: ScriptDatum WitCtxTxIn | |
NoScriptDatumForMint :: ScriptDatum WitCtxMint | |
NoScriptDatumForStake :: ScriptDatum WitCtxStake |
Instances
Show (ScriptDatum witctx) Source # | |
Defined in Cardano.Api.Internal.Script | |
Eq (ScriptDatum witctx) Source # | |
Defined in Cardano.Api.Internal.Script Methods (==) :: ScriptDatum witctx -> ScriptDatum witctx -> Bool Source # (/=) :: ScriptDatum witctx -> ScriptDatum witctx -> Bool Source # |
type ScriptRedeemer = HashableScriptData Source #
Inspecting ScriptWitness
es
data AnyScriptWitness era where Source #
A ScriptWitness
in any WitCtx
. This lets us handle heterogeneous
collections of script witnesses from multiple contexts.
Constructors
AnyScriptWitness :: forall witctx era. Typeable witctx => ScriptWitness witctx era -> AnyScriptWitness era |
Instances
Show (AnyScriptWitness era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body | |
Eq (AnyScriptWitness era) Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods (==) :: AnyScriptWitness era -> AnyScriptWitness era -> Bool Source # (/=) :: AnyScriptWitness era -> AnyScriptWitness era -> Bool Source # |
data ScriptWitnessIndex Source #
Identify the location of a ScriptWitness
within the context of a
TxBody
. These are indexes of the objects within the transaction that
need or can use script witnesses: inputs, minted assets, withdrawals and
certificates. These are simple numeric indices, enumerated from zero.
Thus the indices are not stable if the transaction body is modified.
Constructors
ScriptWitnessIndexTxIn !Word32 | The n'th transaction input, in the order of the |
ScriptWitnessIndexMint !Word32 | |
ScriptWitnessIndexCertificate !Word32 | The n'th certificate, in the list order of the certificates. |
ScriptWitnessIndexWithdrawal !Word32 | The n'th withdrawal, in the order of the |
ScriptWitnessIndexVoting !Word32 | The n'th vote, in the order of the votes. |
ScriptWitnessIndexProposing !Word32 | The n'th proposal, in the order of the proposals. |
Instances
ToJSON ScriptWitnessIndex Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods toJSON :: ScriptWitnessIndex -> Value toEncoding :: ScriptWitnessIndex -> Encoding toJSONList :: [ScriptWitnessIndex] -> Value toEncodingList :: [ScriptWitnessIndex] -> Encoding omitField :: ScriptWitnessIndex -> Bool | |
Show ScriptWitnessIndex Source # | |
Defined in Cardano.Api.Internal.Tx.Body | |
Eq ScriptWitnessIndex Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods (==) :: ScriptWitnessIndex -> ScriptWitnessIndex -> Bool Source # (/=) :: ScriptWitnessIndex -> ScriptWitnessIndex -> Bool Source # | |
Ord ScriptWitnessIndex Source # | |
Defined in Cardano.Api.Internal.Tx.Body Methods compare :: ScriptWitnessIndex -> ScriptWitnessIndex -> Ordering Source # (<) :: ScriptWitnessIndex -> ScriptWitnessIndex -> Bool Source # (<=) :: ScriptWitnessIndex -> ScriptWitnessIndex -> Bool Source # (>) :: ScriptWitnessIndex -> ScriptWitnessIndex -> Bool Source # (>=) :: ScriptWitnessIndex -> ScriptWitnessIndex -> Bool Source # max :: ScriptWitnessIndex -> ScriptWitnessIndex -> ScriptWitnessIndex Source # min :: ScriptWitnessIndex -> ScriptWitnessIndex -> ScriptWitnessIndex Source # |
collectTxBodyScriptWitnesses :: ShelleyBasedEra era -> TxBodyContent BuildTx era -> [(ScriptWitnessIndex, AnyScriptWitness era)] Source #
Languages supported in each era
data ScriptLanguageInEra lang era where Source #
Constructors
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 |
Instances
ToJSON (ScriptLanguageInEra lang era) Source # | |
Defined in Cardano.Api.Internal.Script Methods toJSON :: ScriptLanguageInEra lang era -> Value toEncoding :: ScriptLanguageInEra lang era -> Encoding toJSONList :: [ScriptLanguageInEra lang era] -> Value toEncodingList :: [ScriptLanguageInEra lang era] -> Encoding omitField :: ScriptLanguageInEra lang era -> Bool | |
Show (ScriptLanguageInEra lang era) Source # | |
Defined in Cardano.Api.Internal.Script | |
Eq (ScriptLanguageInEra lang era) Source # | |
Defined in Cardano.Api.Internal.Script Methods (==) :: ScriptLanguageInEra lang era -> ScriptLanguageInEra lang era -> Bool Source # (/=) :: ScriptLanguageInEra lang era -> ScriptLanguageInEra lang era -> Bool Source # | |
Ord (ScriptLanguageInEra lang era) Source # | |
Defined in Cardano.Api.Internal.Script Methods compare :: ScriptLanguageInEra lang era -> ScriptLanguageInEra lang era -> Ordering Source # (<) :: ScriptLanguageInEra lang era -> ScriptLanguageInEra lang era -> Bool Source # (<=) :: ScriptLanguageInEra lang era -> ScriptLanguageInEra lang era -> Bool Source # (>) :: ScriptLanguageInEra lang era -> ScriptLanguageInEra lang era -> Bool Source # (>=) :: ScriptLanguageInEra lang era -> ScriptLanguageInEra lang era -> Bool Source # max :: ScriptLanguageInEra lang era -> ScriptLanguageInEra lang era -> ScriptLanguageInEra lang era Source # min :: ScriptLanguageInEra lang era -> ScriptLanguageInEra lang era -> ScriptLanguageInEra lang era Source # |
scriptLanguageSupportedInEra :: ShelleyBasedEra era -> ScriptLanguage lang -> Maybe (ScriptLanguageInEra lang era) Source #
Check if a given script language is supported in a given era, and if so return the evidence.
sbeToSimpleScriptLanguageInEra :: ShelleyBasedEra era -> ScriptLanguageInEra SimpleScript' era Source #
languageOfScriptLanguageInEra :: ScriptLanguageInEra lang era -> ScriptLanguage lang Source #
eraOfScriptLanguageInEra :: ScriptLanguageInEra lang era -> ShelleyBasedEra era Source #
Simple scripts
Making multi-signature and time-lock scripts.
data SimpleScript Source #
Constructors
RequireSignature !(Hash PaymentKey) | |
RequireTimeBefore !SlotNo | |
RequireTimeAfter !SlotNo | |
RequireAllOf ![SimpleScript] | |
RequireAnyOf ![SimpleScript] | |
RequireMOf !Int ![SimpleScript] |
Instances
FromJSON SimpleScript Source # | |
Defined in Cardano.Api.Internal.Script | |
ToJSON SimpleScript Source # | |
Defined in Cardano.Api.Internal.Script Methods toJSON :: SimpleScript -> Value toEncoding :: SimpleScript -> Encoding toJSONList :: [SimpleScript] -> Value toEncodingList :: [SimpleScript] -> Encoding omitField :: SimpleScript -> Bool | |
Show SimpleScript Source # | |
Defined in Cardano.Api.Internal.Script | |
Eq SimpleScript Source # | |
Defined in Cardano.Api.Internal.Script Methods (==) :: SimpleScript -> SimpleScript -> Bool Source # (/=) :: SimpleScript -> SimpleScript -> Bool Source # |
Plutus scripts
data PlutusScript lang Source #
Plutus scripts.
Note that Plutus scripts have a binary serialisation but no JSON serialisation.
Instances
Show (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
HasTypeProxy lang => HasTypeProxy (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
Methods proxyToAsType :: Proxy (PlutusScript lang) -> AsType (PlutusScript lang) Source # | |||||
HasTypeProxy lang => SerialiseAsCBOR (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Methods serialiseToCBOR :: PlutusScript lang -> ByteString Source # deserialiseFromCBOR :: AsType (PlutusScript lang) -> ByteString -> Either DecoderError (PlutusScript lang) Source # | |||||
HasTypeProxy lang => SerialiseAsRawBytes (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Methods serialiseToRawBytes :: PlutusScript lang -> ByteString Source # deserialiseFromRawBytes :: AsType (PlutusScript lang) -> ByteString -> Either SerialiseAsRawBytesError (PlutusScript lang) Source # | |||||
IsPlutusScriptLanguage lang => HasTextEnvelope (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Methods textEnvelopeType :: AsType (PlutusScript lang) -> TextEnvelopeType Source # textEnvelopeDefaultDescr :: PlutusScript lang -> TextEnvelopeDescr Source # | |||||
Eq (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Methods (==) :: PlutusScript lang -> PlutusScript lang -> Bool Source # (/=) :: PlutusScript lang -> PlutusScript lang -> Bool Source # | |||||
Ord (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script Methods compare :: PlutusScript lang -> PlutusScript lang -> Ordering Source # (<) :: PlutusScript lang -> PlutusScript lang -> Bool Source # (<=) :: PlutusScript lang -> PlutusScript lang -> Bool Source # (>) :: PlutusScript lang -> PlutusScript lang -> Bool Source # (>=) :: PlutusScript lang -> PlutusScript lang -> Bool Source # max :: PlutusScript lang -> PlutusScript lang -> PlutusScript lang Source # min :: PlutusScript lang -> PlutusScript lang -> PlutusScript lang Source # | |||||
data AsType (PlutusScript lang) Source # | |||||
Defined in Cardano.Api.Internal.Script |
examplePlutusScriptAlwaysSucceeds :: WitCtx witctx -> PlutusScript PlutusScriptV1 Source #
An example Plutus script that always succeeds, irrespective of inputs.
For example, if one were to use this for a payment address then it would allow anyone to spend from it.
The exact script depends on the context in which it is to be used.
examplePlutusScriptAlwaysFails :: WitCtx witctx -> PlutusScript PlutusScriptV1 Source #
An example Plutus script that always fails, irrespective of inputs.
For example, if one were to use this for a payment address then it would be impossible for anyone to ever spend from it.
The exact script depends on the context in which it is to be used.
Script data
collectPlutusScriptHashes :: AlonzoEraOnwards era -> Tx era -> UTxO era -> Map ScriptWitnessIndex ScriptHash Source #
Collect all plutus script hashes that are needed to validate the given transaction
and return them in a map with their corresponding ScriptWitnessIndex
as key.
data HashableScriptData Source #
Instances
Show HashableScriptData Source # | |||||
Defined in Cardano.Api.Internal.ScriptData | |||||
HasTypeProxy HashableScriptData Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Associated Types
Methods proxyToAsType :: Proxy HashableScriptData -> AsType HashableScriptData Source # | |||||
SerialiseAsCBOR HashableScriptData Source # | |||||
Defined in Cardano.Api.Internal.ScriptData | |||||
Eq HashableScriptData Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods (==) :: HashableScriptData -> HashableScriptData -> Bool Source # (/=) :: HashableScriptData -> HashableScriptData -> Bool Source # | |||||
Ord HashableScriptData Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods compare :: HashableScriptData -> HashableScriptData -> Ordering Source # (<) :: HashableScriptData -> HashableScriptData -> Bool Source # (<=) :: HashableScriptData -> HashableScriptData -> Bool Source # (>) :: HashableScriptData -> HashableScriptData -> Bool Source # (>=) :: HashableScriptData -> HashableScriptData -> Bool Source # max :: HashableScriptData -> HashableScriptData -> HashableScriptData Source # min :: HashableScriptData -> HashableScriptData -> HashableScriptData Source # | |||||
data AsType HashableScriptData Source # | |||||
Defined in Cardano.Api.Internal.ScriptData |
unsafeHashableScriptData :: ScriptData -> HashableScriptData Source #
Warning: Creating HashableScriptData
from a ScriptData
value pretty
much guarantees the original bytes used to create the ScriptData
value will be different if we serialize HashableScriptData
again.
Do not use this.
data ScriptData Source #
Constructors
ScriptDataConstructor | |
Fields
| |
ScriptDataMap [(ScriptData, ScriptData)] | Key value pairs |
ScriptDataList [ScriptData] | Elements |
ScriptDataNumber Integer | |
ScriptDataBytes ByteString |
Instances
Show ScriptData Source # | |||||
Defined in Cardano.Api.Internal.ScriptData | |||||
HasTypeProxy ScriptData Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Associated Types
Methods proxyToAsType :: Proxy ScriptData -> AsType ScriptData Source # | |||||
SerialiseAsCBOR ScriptData Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods serialiseToCBOR :: ScriptData -> ByteString Source # deserialiseFromCBOR :: AsType ScriptData -> ByteString -> Either DecoderError ScriptData Source # | |||||
FromCBOR ScriptData Source # | |||||
Defined in Cardano.Api.Internal.ScriptData | |||||
ToCBOR ScriptData Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods toCBOR :: ScriptData -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ScriptData -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ScriptData] -> Size Source # | |||||
Eq ScriptData Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods (==) :: ScriptData -> ScriptData -> Bool Source # (/=) :: ScriptData -> ScriptData -> Bool Source # | |||||
Ord ScriptData Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods compare :: ScriptData -> ScriptData -> Ordering Source # (<) :: ScriptData -> ScriptData -> Bool Source # (<=) :: ScriptData -> ScriptData -> Bool Source # (>) :: ScriptData -> ScriptData -> Bool Source # (>=) :: ScriptData -> ScriptData -> Bool Source # max :: ScriptData -> ScriptData -> ScriptData Source # min :: ScriptData -> ScriptData -> ScriptData Source # | |||||
FromJSON (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods parseJSON :: Value -> Parser (Hash ScriptData) parseJSONList :: Value -> Parser [Hash ScriptData] omittedField :: Maybe (Hash ScriptData) | |||||
FromJSONKey (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods fromJSONKey :: FromJSONKeyFunction (Hash ScriptData) fromJSONKeyList :: FromJSONKeyFunction [Hash ScriptData] | |||||
ToJSON (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods toJSON :: Hash ScriptData -> Value toEncoding :: Hash ScriptData -> Encoding toJSONList :: [Hash ScriptData] -> Value toEncodingList :: [Hash ScriptData] -> Encoding omitField :: Hash ScriptData -> Bool | |||||
ToJSONKey (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods toJSONKey :: ToJSONKeyFunction (Hash ScriptData) toJSONKeyList :: ToJSONKeyFunction [Hash ScriptData] | |||||
IsString (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods fromString :: String -> Hash ScriptData Source # | |||||
Show (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData | |||||
SerialiseAsRawBytes (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods serialiseToRawBytes :: Hash ScriptData -> ByteString Source # deserialiseFromRawBytes :: AsType (Hash ScriptData) -> ByteString -> Either SerialiseAsRawBytesError (Hash ScriptData) Source # | |||||
Eq (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods (==) :: Hash ScriptData -> Hash ScriptData -> Bool Source # (/=) :: Hash ScriptData -> Hash ScriptData -> Bool Source # | |||||
Ord (Hash ScriptData) Source # | |||||
Defined in Cardano.Api.Internal.ScriptData Methods compare :: Hash ScriptData -> Hash ScriptData -> Ordering Source # (<) :: Hash ScriptData -> Hash ScriptData -> Bool Source # (<=) :: Hash ScriptData -> Hash ScriptData -> Bool Source # (>) :: Hash ScriptData -> Hash ScriptData -> Bool Source # (>=) :: Hash ScriptData -> Hash ScriptData -> Bool Source # max :: Hash ScriptData -> Hash ScriptData -> Hash ScriptData Source # min :: Hash ScriptData -> Hash ScriptData -> Hash ScriptData Source # | |||||
data AsType ScriptData Source # | |||||
Defined in Cardano.Api.Internal.ScriptData | |||||
newtype Hash ScriptData Source # | |||||
Defined in Cardano.Api.Internal.ScriptData |
Validation
newtype ScriptDataRangeError Source #
An error in script data due to an out-of-range value.
Constructors
ScriptDataConstructorOutOfRange Integer | The constructor number is outside the maximum range of |
Instances
Data ScriptDataRangeError Source # | |
Defined in Cardano.Api.Internal.ScriptData Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ScriptDataRangeError -> c ScriptDataRangeError Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ScriptDataRangeError Source # toConstr :: ScriptDataRangeError -> Constr Source # dataTypeOf :: ScriptDataRangeError -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ScriptDataRangeError) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ScriptDataRangeError) Source # gmapT :: (forall b. Data b => b -> b) -> ScriptDataRangeError -> ScriptDataRangeError Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ScriptDataRangeError -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ScriptDataRangeError -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ScriptDataRangeError -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ScriptDataRangeError -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ScriptDataRangeError -> m ScriptDataRangeError Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ScriptDataRangeError -> m ScriptDataRangeError Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ScriptDataRangeError -> m ScriptDataRangeError Source # | |
Show ScriptDataRangeError Source # | |
Defined in Cardano.Api.Internal.ScriptData | |
Error ScriptDataRangeError Source # | |
Defined in Cardano.Api.Internal.ScriptData Methods prettyError :: ScriptDataRangeError -> Doc ann Source # | |
Eq ScriptDataRangeError Source # | |
Defined in Cardano.Api.Internal.ScriptData Methods (==) :: ScriptDataRangeError -> ScriptDataRangeError -> Bool Source # (/=) :: ScriptDataRangeError -> ScriptDataRangeError -> Bool Source # |
validateScriptData :: ScriptData -> Either ScriptDataRangeError () Source #
Validate script data. This is for use with existing constructed script data values, e.g. constructed manually or decoded from CBOR directly.
Conversion to/from JSON
data ScriptDataJsonSchema Source #
Script data is similar to JSON but not exactly the same. It has some deliberate limitations such as no support for floating point numbers or special forms for null or boolean values. It also has limitations on the length of strings. On the other hand, unlike JSON, it distinguishes between byte strings and text strings. It also supports any value as map keys rather than just string. It also supports alternatives / tagged unions, used for representing constructors for Plutus data values.
We provide two different mappings between script data and JSON, useful for different purposes:
- A mapping that allows almost any JSON value to be converted into script data. This does not require a specific JSON schema for the input. It does not expose the full representation capability of script data.
- A mapping that exposes the full representation capability of script data, but relies on a specific JSON schema for the input JSON.
In the "no schema" mapping, the idea is that (almost) any JSON can be turned into script data and then converted back, without loss. That is, we can round-trip the JSON.
The subset of JSON supported is all JSON except:
- No null or bool values
- No floating point, only integers in the range of a 64bit signed integer
- A limitation on string lengths
The approach for this mapping is to use whichever representation as script data is most compact. In particular:
- JSON lists and maps represented as CBOR lists and maps
- JSON strings represented as CBOR strings
- JSON hex strings with "0x" prefix represented as CBOR byte strings
- JSON integer numbers represented as CBOR signed or unsigned numbers
- JSON maps with string keys that parse as numbers or hex byte strings, represented as CBOR map keys that are actually numbers or byte strings.
The string length limit depends on whether the hex string representation is used or not. For text strings the limit is 64 bytes for the UTF8 representation of the text string. For byte strings the limit is 64 bytes for the raw byte form (ie not the input hex, but after hex decoding).
In the "detailed schema" mapping, the idea is that we expose the full representation capability of the script data in the form of a JSON schema. This means the full representation is available and can be controlled precisely. It also means any script data can be converted into the JSON and back without loss. That is we can round-trip the script data via the JSON and also round-trip schema-compliant JSON via script data.
- Warning*: While the JSON representation does round-trip, the CBOR through
JSON does not. When serialising and deserialising
HashableScriptData
through JSON e.g:CBOR -> HashableScriptData -> JSON -> HashableScriptData -> CBOR
the original CBOR representation is lost and the resulting CBOR *will* be different resulting in a different script data hash, which is calculated from CBOR. This is because cardano-ledger does not canonicalise CBOR representation, so you can have few slightly different serialised representations of a data structure, which represent the same value.
See: https://github.com/IntersectMBO/cardano-api/issues/612#issuecomment-2701256007
Constructors
ScriptDataJsonNoSchema | Use the "no schema" mapping between JSON and script data as described above. |
ScriptDataJsonDetailedSchema | Use the "detailed schema" mapping between JSON and script data as described above. |
Instances
Show ScriptDataJsonSchema Source # | |
Defined in Cardano.Api.Internal.ScriptData | |
Eq ScriptDataJsonSchema Source # | |
Defined in Cardano.Api.Internal.ScriptData Methods (==) :: ScriptDataJsonSchema -> ScriptDataJsonSchema -> Bool Source # (/=) :: ScriptDataJsonSchema -> ScriptDataJsonSchema -> Bool Source # |
scriptDataFromJson :: ScriptDataJsonSchema -> Value -> Either ScriptDataJsonError HashableScriptData Source #
Convert a value from JSON into script data, using the given choice of mapping between JSON and script data.
This may fail with a conversion error if the JSON is outside the supported
subset for the chosen mapping. See ScriptDataJsonSchema
for the details.
scriptDataToJson :: ScriptDataJsonSchema -> HashableScriptData -> Value Source #
Convert a script data value into JSON , using the given choice of mapping between JSON and script data.
This conversion is total but is not necessarily invertible.
See ScriptDataJsonSchema
for the details.
data ScriptDataJsonError Source #
Constructors
ScriptDataJsonSchemaError !Value !ScriptDataJsonSchemaError | |
ScriptDataRangeError !Value !ScriptDataRangeError |
Instances
Data ScriptDataJsonError Source # | |
Defined in Cardano.Api.Internal.ScriptData Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ScriptDataJsonError -> c ScriptDataJsonError Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ScriptDataJsonError Source # toConstr :: ScriptDataJsonError -> Constr Source # dataTypeOf :: ScriptDataJsonError -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ScriptDataJsonError) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ScriptDataJsonError) Source # gmapT :: (forall b. Data b => b -> b) -> ScriptDataJsonError -> ScriptDataJsonError Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ScriptDataJsonError -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ScriptDataJsonError -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ScriptDataJsonError -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ScriptDataJsonError -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ScriptDataJsonError -> m ScriptDataJsonError Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ScriptDataJsonError -> m ScriptDataJsonError Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ScriptDataJsonError -> m ScriptDataJsonError Source # | |
Show ScriptDataJsonError Source # | |
Defined in Cardano.Api.Internal.ScriptData | |
Error ScriptDataJsonError Source # | |
Defined in Cardano.Api.Internal.ScriptData Methods prettyError :: ScriptDataJsonError -> Doc ann Source # | |
Eq ScriptDataJsonError Source # | |
Defined in Cardano.Api.Internal.ScriptData Methods (==) :: ScriptDataJsonError -> ScriptDataJsonError -> Bool Source # (/=) :: ScriptDataJsonError -> ScriptDataJsonError -> Bool Source # |
data ScriptDataJsonSchemaError Source #
Constructors
ScriptDataJsonNullNotAllowed | |
ScriptDataJsonBoolNotAllowed | |
ScriptDataJsonNumberNotInteger !Double | |
ScriptDataJsonNotObject !Value | |
ScriptDataJsonBadObject ![(Text, Value)] | |
ScriptDataJsonBadMapPair !Value | |
ScriptDataJsonTypeMismatch !Text !Value |
Instances
Data ScriptDataJsonSchemaError Source # | |
Defined in Cardano.Api.Internal.ScriptData Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ScriptDataJsonSchemaError -> c ScriptDataJsonSchemaError Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ScriptDataJsonSchemaError Source # toConstr :: ScriptDataJsonSchemaError -> Constr Source # dataTypeOf :: ScriptDataJsonSchemaError -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ScriptDataJsonSchemaError) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ScriptDataJsonSchemaError) Source # gmapT :: (forall b. Data b => b -> b) -> ScriptDataJsonSchemaError -> ScriptDataJsonSchemaError Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ScriptDataJsonSchemaError -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ScriptDataJsonSchemaError -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ScriptDataJsonSchemaError -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ScriptDataJsonSchemaError -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ScriptDataJsonSchemaError -> m ScriptDataJsonSchemaError Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ScriptDataJsonSchemaError -> m ScriptDataJsonSchemaError Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ScriptDataJsonSchemaError -> m ScriptDataJsonSchemaError Source # | |
Show ScriptDataJsonSchemaError Source # | |
Defined in Cardano.Api.Internal.ScriptData | |
Error ScriptDataJsonSchemaError Source # | |
Defined in Cardano.Api.Internal.ScriptData Methods prettyError :: ScriptDataJsonSchemaError -> Doc ann Source # | |
Eq ScriptDataJsonSchemaError Source # | |
Defined in Cardano.Api.Internal.ScriptData Methods (==) :: ScriptDataJsonSchemaError -> ScriptDataJsonSchemaError -> Bool Source # (/=) :: ScriptDataJsonSchemaError -> ScriptDataJsonSchemaError -> Bool Source # |
data ScriptDataJsonBytesError Source #
Constructors
ScriptDataJsonBytesErrorValue ScriptDataJsonError | |
ScriptDataJsonBytesErrorInvalid ScriptDataRangeError |
Instances
Data ScriptDataJsonBytesError Source # | |
Defined in Cardano.Api.Internal.ScriptData Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ScriptDataJsonBytesError -> c ScriptDataJsonBytesError Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ScriptDataJsonBytesError Source # toConstr :: ScriptDataJsonBytesError -> Constr Source # dataTypeOf :: ScriptDataJsonBytesError -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ScriptDataJsonBytesError) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ScriptDataJsonBytesError) Source # gmapT :: (forall b. Data b => b -> b) -> ScriptDataJsonBytesError -> ScriptDataJsonBytesError Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ScriptDataJsonBytesError -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ScriptDataJsonBytesError -> r Source # gmapQ :: (forall d. Data d => d -> u) -> ScriptDataJsonBytesError -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> ScriptDataJsonBytesError -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ScriptDataJsonBytesError -> m ScriptDataJsonBytesError Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ScriptDataJsonBytesError -> m ScriptDataJsonBytesError Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ScriptDataJsonBytesError -> m ScriptDataJsonBytesError Source # | |
Show ScriptDataJsonBytesError Source # | |
Defined in Cardano.Api.Internal.ScriptData | |
Error ScriptDataJsonBytesError Source # | |
Defined in Cardano.Api.Internal.ScriptData Methods prettyError :: ScriptDataJsonBytesError -> Doc ann Source # |
scriptDataJsonToHashable Source #
Arguments
:: ScriptDataJsonSchema | |
-> Value | ScriptData Value |
-> Either ScriptDataJsonBytesError HashableScriptData |
This allows us to take JSON formatted ScriptData and encode it in the CDDL format whilst preserving the original bytes.
Script execution units
data ExecutionUnits Source #
The units for how long a script executes for and how much memory it uses. This is used to declare the resources used by a particular use of a script.
This type is also used to describe the limits for the maximum overall execution units per transaction or per block.
Constructors
ExecutionUnits | |
Fields
|
Instances
FromJSON ExecutionUnits Source # | |
Defined in Cardano.Api.Internal.Script | |
ToJSON ExecutionUnits Source # | |
Defined in Cardano.Api.Internal.Script Methods toJSON :: ExecutionUnits -> Value toEncoding :: ExecutionUnits -> Encoding toJSONList :: [ExecutionUnits] -> Value toEncodingList :: [ExecutionUnits] -> Encoding omitField :: ExecutionUnits -> Bool | |
Show ExecutionUnits Source # | |
Defined in Cardano.Api.Internal.Script | |
FromCBOR ExecutionUnits Source # | |
Defined in Cardano.Api.Internal.Script | |
ToCBOR ExecutionUnits Source # | |
Defined in Cardano.Api.Internal.Script Methods toCBOR :: ExecutionUnits -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ExecutionUnits -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ExecutionUnits] -> Size Source # | |
Eq ExecutionUnits Source # | |
Defined in Cardano.Api.Internal.Script Methods (==) :: ExecutionUnits -> ExecutionUnits -> Bool Source # (/=) :: ExecutionUnits -> ExecutionUnits -> Bool Source # |
data ExecutionUnitPrices Source #
The prices for ExecutionUnits
as a fraction of a Coin
.
These are used to determine the fee for the use of a script within a
transaction, based on the ExecutionUnits
needed by the use of the script.
Constructors
ExecutionUnitPrices | |
Fields |
Instances
FromJSON ExecutionUnitPrices Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters Methods parseJSON :: Value -> Parser ExecutionUnitPrices parseJSONList :: Value -> Parser [ExecutionUnitPrices] | |
ToJSON ExecutionUnitPrices Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters Methods toJSON :: ExecutionUnitPrices -> Value toEncoding :: ExecutionUnitPrices -> Encoding toJSONList :: [ExecutionUnitPrices] -> Value toEncodingList :: [ExecutionUnitPrices] -> Encoding omitField :: ExecutionUnitPrices -> Bool | |
Show ExecutionUnitPrices Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters | |
FromCBOR ExecutionUnitPrices Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters | |
ToCBOR ExecutionUnitPrices Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters Methods toCBOR :: ExecutionUnitPrices -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ExecutionUnitPrices -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ExecutionUnitPrices] -> Size Source # | |
Eq ExecutionUnitPrices Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters Methods (==) :: ExecutionUnitPrices -> ExecutionUnitPrices -> Bool Source # (/=) :: ExecutionUnitPrices -> ExecutionUnitPrices -> Bool Source # |
Instances
Data CostModel Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CostModel -> c CostModel Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CostModel Source # toConstr :: CostModel -> Constr Source # dataTypeOf :: CostModel -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CostModel) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CostModel) Source # gmapT :: (forall b. Data b => b -> b) -> CostModel -> CostModel Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CostModel -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CostModel -> r Source # gmapQ :: (forall d. Data d => d -> u) -> CostModel -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> CostModel -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CostModel -> m CostModel Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CostModel -> m CostModel Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CostModel -> m CostModel Source # | |
Show CostModel Source # | |
FromCBOR CostModel Source # | |
ToCBOR CostModel Source # | |
Eq CostModel Source # | |
toAlonzoCostModel :: CostModel -> Language -> Either ProtocolParametersConversionError CostModel Source #
toAlonzoCostModels :: Map AnyPlutusScriptVersion CostModel -> Either ProtocolParametersConversionError CostModels Source #
Script addresses
Making addresses from scripts.
newtype ScriptHash Source #
We have this type separate from the Hash
type to avoid the script
hash type being parametrised by the era. The representation is era
independent, and there are many places where we want to use a script
hash where we don't want things to be era-parametrised.
Constructors
ScriptHash ScriptHash |
Instances
FromJSON ScriptHash Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
ToJSON ScriptHash Source # | |||||
Defined in Cardano.Api.Internal.Script Methods toJSON :: ScriptHash -> Value toEncoding :: ScriptHash -> Encoding toJSONList :: [ScriptHash] -> Value toEncodingList :: [ScriptHash] -> Encoding omitField :: ScriptHash -> Bool | |||||
IsString ScriptHash Source # | |||||
Defined in Cardano.Api.Internal.Script Methods fromString :: String -> ScriptHash Source # | |||||
Show ScriptHash Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
HasTypeProxy ScriptHash Source # | |||||
Defined in Cardano.Api.Internal.Script Associated Types
Methods proxyToAsType :: Proxy ScriptHash -> AsType ScriptHash Source # | |||||
SerialiseAsRawBytes ScriptHash Source # | |||||
Defined in Cardano.Api.Internal.Script | |||||
Eq ScriptHash Source # | |||||
Defined in Cardano.Api.Internal.Script Methods (==) :: ScriptHash -> ScriptHash -> Bool Source # (/=) :: ScriptHash -> ScriptHash -> Bool Source # | |||||
Ord ScriptHash Source # | |||||
Defined in Cardano.Api.Internal.Script Methods compare :: ScriptHash -> ScriptHash -> Ordering Source # (<) :: ScriptHash -> ScriptHash -> Bool Source # (<=) :: ScriptHash -> ScriptHash -> Bool Source # (>) :: ScriptHash -> ScriptHash -> Bool Source # (>=) :: ScriptHash -> ScriptHash -> Bool Source # max :: ScriptHash -> ScriptHash -> ScriptHash Source # min :: ScriptHash -> ScriptHash -> ScriptHash Source # | |||||
data AsType ScriptHash Source # | |||||
Defined in Cardano.Api.Internal.Script |
hashScript :: Script lang -> ScriptHash Source #
Serialisation
Support for serialising data in JSON, CBOR and text files.
data InputFormat a where Source #
Input format/encoding.
Constructors
InputFormatBech32 :: forall a. SerialiseAsBech32 a => InputFormat a | Bech32 encoding. |
InputFormatHex :: forall a. SerialiseAsRawBytes a => InputFormat a | Hex/Base16 encoding. |
InputFormatTextEnvelope :: forall a. HasTextEnvelope a => InputFormat a | Text envelope format. |
data InputDecodeError Source #
Input decoding error.
Constructors
InputTextEnvelopeError !TextEnvelopeError | The provided data seems to be a valid text envelope, but some error occurred in deserialising it. |
InputBech32DecodeError !Bech32DecodeError | The provided data is valid Bech32, but some error occurred in deserialising it. |
InputInvalidError | The provided data does not represent a valid value of the provided type. |
Instances
Data InputDecodeError Source # | |
Defined in Cardano.Api.Internal.DeserialiseAnyOf Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InputDecodeError -> c InputDecodeError Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InputDecodeError Source # toConstr :: InputDecodeError -> Constr Source # dataTypeOf :: InputDecodeError -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InputDecodeError) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InputDecodeError) Source # gmapT :: (forall b. Data b => b -> b) -> InputDecodeError -> InputDecodeError Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InputDecodeError -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InputDecodeError -> r Source # gmapQ :: (forall d. Data d => d -> u) -> InputDecodeError -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> InputDecodeError -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> InputDecodeError -> m InputDecodeError Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InputDecodeError -> m InputDecodeError Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InputDecodeError -> m InputDecodeError Source # | |
Show InputDecodeError Source # | |
Defined in Cardano.Api.Internal.DeserialiseAnyOf | |
Error InputDecodeError Source # | |
Defined in Cardano.Api.Internal.DeserialiseAnyOf Methods prettyError :: InputDecodeError -> Doc ann Source # | |
Eq InputDecodeError Source # | |
Defined in Cardano.Api.Internal.DeserialiseAnyOf Methods (==) :: InputDecodeError -> InputDecodeError -> Bool Source # (/=) :: InputDecodeError -> InputDecodeError -> Bool Source # |
deserialiseInput :: NonEmpty (InputFormat a) -> ByteString -> Either InputDecodeError a Source #
Deserialise an input of some type that is formatted in some way.
deserialiseInputAnyOf :: [FromSomeType SerialiseAsBech32 b] -> [FromSomeType HasTextEnvelope b] -> ByteString -> Either InputDecodeError b Source #
Deserialise an input of some type that is formatted in some way.
The provided ByteString
can either be Bech32-encoded or in the text
envelope format.
renderInputDecodeError :: InputDecodeError -> Doc ann Source #
Render an error message for a InputDecodeError
.
data SomeAddressVerificationKey Source #
Constructors
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) | |
AStakePoolVerificationKey (VerificationKey StakePoolKey) | |
AStakePoolExtendedVerificationKey (VerificationKey StakePoolExtendedKey) | |
ADRepVerificationKey (VerificationKey DRepKey) | |
ADRepExtendedVerificationKey (VerificationKey DRepExtendedKey) | |
ACommitteeColdVerificationKey (VerificationKey CommitteeColdKey) | |
ACommitteeColdExtendedVerificationKey (VerificationKey CommitteeColdExtendedKey) | |
ACommitteeHotVerificationKey (VerificationKey CommitteeHotKey) | |
ACommitteeHotExtendedVerificationKey (VerificationKey CommitteeHotExtendedKey) |
Instances
deserialiseAnyVerificationKey :: ByteString -> Either InputDecodeError SomeAddressVerificationKey Source #
deserialiseAnyVerificationKeyBech32 :: ByteString -> Either Bech32DecodeError SomeAddressVerificationKey Source #
deserialiseAnyVerificationKeyTextEnvelope :: ByteString -> Either TextEnvelopeError SomeAddressVerificationKey Source #
mapSomeAddressVerificationKey :: (forall keyrole. Key keyrole => VerificationKey keyrole -> a) -> SomeAddressVerificationKey -> a Source #
CBOR
class HasTypeProxy a => SerialiseAsCBOR a Source #
Instances
SerialiseAsCBOR GovernancePoll Source # | |
Defined in Cardano.Api.Internal.Governance.Poll Methods serialiseToCBOR :: GovernancePoll -> ByteString Source # deserialiseFromCBOR :: AsType GovernancePoll -> ByteString -> Either DecoderError GovernancePoll Source # | |
SerialiseAsCBOR GovernancePollAnswer Source # | |
SerialiseAsCBOR OperationalCertificate Source # | |
SerialiseAsCBOR OperationalCertificateIssueCounter Source # | |
SerialiseAsCBOR UpdateProposal Source # | |
Defined in Cardano.Api.Internal.ProtocolParameters Methods serialiseToCBOR :: UpdateProposal -> ByteString Source # deserialiseFromCBOR :: AsType UpdateProposal -> ByteString -> Either DecoderError UpdateProposal Source # | |
SerialiseAsCBOR EraHistory Source # | |
Defined in Cardano.Api.Internal.Query Methods serialiseToCBOR :: EraHistory -> ByteString Source # deserialiseFromCBOR :: AsType EraHistory -> ByteString -> Either DecoderError EraHistory Source # | |
SerialiseAsCBOR HashableScriptData Source # | |
Defined in Cardano.Api.Internal.ScriptData | |
SerialiseAsCBOR ScriptData Source # | |
Defined in Cardano.Api.Internal.ScriptData Methods serialiseToCBOR :: ScriptData -> ByteString Source # deserialiseFromCBOR :: AsType ScriptData -> ByteString -> Either DecoderError ScriptData Source # | |
SerialiseAsCBOR TxMetadata Source # | |
Defined in Cardano.Api.Internal.TxMetadata Methods serialiseToCBOR :: TxMetadata -> ByteString Source # deserialiseFromCBOR :: AsType TxMetadata -> ByteString -> Either DecoderError TxMetadata Source # | |
SerialiseAsCBOR Term Source # | |
Defined in Cardano.Api.Internal.Serialise.Cbor.Canonical Methods serialiseToCBOR :: Term -> ByteString Source # deserialiseFromCBOR :: AsType Term -> ByteString -> Either DecoderError Term Source # | |
IsShelleyBasedEra era => SerialiseAsCBOR (Certificate era) Source # | |
Defined in Cardano.Api.Internal.Certificate Methods serialiseToCBOR :: Certificate era -> ByteString Source # deserialiseFromCBOR :: AsType (Certificate era) -> ByteString -> Either DecoderError (Certificate era) Source # | |
IsShelleyBasedEra era => SerialiseAsCBOR (Proposal era) Source # | |
Defined in Cardano.Api.Internal.Governance.Actions.ProposalProcedure Methods serialiseToCBOR :: Proposal era -> ByteString Source # deserialiseFromCBOR :: AsType (Proposal era) -> ByteString -> Either DecoderError (Proposal era) Source # | |
IsShelleyBasedEra era => SerialiseAsCBOR (VotingProcedure era) Source # | |
Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure Methods serialiseToCBOR :: VotingProcedure era -> ByteString Source # deserialiseFromCBOR :: AsType (VotingProcedure era) -> ByteString -> Either DecoderError (VotingProcedure era) Source # | |
IsShelleyBasedEra era => SerialiseAsCBOR (VotingProcedures era) Source # | |
Defined in Cardano.Api.Internal.Governance.Actions.VotingProcedure Methods serialiseToCBOR :: VotingProcedures era -> ByteString Source # deserialiseFromCBOR :: AsType (VotingProcedures era) -> ByteString -> Either DecoderError (VotingProcedures era) Source # | |
SerialiseAsCBOR (Hash ByronKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: Hash ByronKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash ByronKey) -> ByteString -> Either DecoderError (Hash ByronKey) Source # | |
SerialiseAsCBOR (Hash ByronKeyLegacy) Source # | |
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: Hash ByronKeyLegacy -> ByteString Source # deserialiseFromCBOR :: AsType (Hash ByronKeyLegacy) -> ByteString -> Either DecoderError (Hash ByronKeyLegacy) Source # | |
SerialiseAsCBOR (Hash KesKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: Hash KesKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash KesKey) -> ByteString -> Either DecoderError (Hash KesKey) Source # | |
SerialiseAsCBOR (Hash VrfKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: Hash VrfKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash VrfKey) -> ByteString -> Either DecoderError (Hash VrfKey) Source # | |
SerialiseAsCBOR (Hash CommitteeColdExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
SerialiseAsCBOR (Hash CommitteeColdKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash CommitteeColdKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash CommitteeColdKey) -> ByteString -> Either DecoderError (Hash CommitteeColdKey) Source # | |
SerialiseAsCBOR (Hash CommitteeHotExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
SerialiseAsCBOR (Hash CommitteeHotKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash CommitteeHotKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash CommitteeHotKey) -> ByteString -> Either DecoderError (Hash CommitteeHotKey) Source # | |
SerialiseAsCBOR (Hash DRepExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash DRepExtendedKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash DRepExtendedKey) -> ByteString -> Either DecoderError (Hash DRepExtendedKey) Source # | |
SerialiseAsCBOR (Hash DRepKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash DRepKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash DRepKey) -> ByteString -> Either DecoderError (Hash DRepKey) Source # | |
SerialiseAsCBOR (Hash GenesisDelegateExtendedKey) Source # | |
SerialiseAsCBOR (Hash GenesisDelegateKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash GenesisDelegateKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash GenesisDelegateKey) -> ByteString -> Either DecoderError (Hash GenesisDelegateKey) Source # | |
SerialiseAsCBOR (Hash GenesisExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash GenesisExtendedKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash GenesisExtendedKey) -> ByteString -> Either DecoderError (Hash GenesisExtendedKey) Source # | |
SerialiseAsCBOR (Hash GenesisKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash GenesisKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash GenesisKey) -> ByteString -> Either DecoderError (Hash GenesisKey) Source # | |
SerialiseAsCBOR (Hash GenesisUTxOKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash GenesisUTxOKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash GenesisUTxOKey) -> ByteString -> Either DecoderError (Hash GenesisUTxOKey) Source # | |
SerialiseAsCBOR (Hash PaymentExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash PaymentExtendedKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash PaymentExtendedKey) -> ByteString -> Either DecoderError (Hash PaymentExtendedKey) Source # | |
SerialiseAsCBOR (Hash PaymentKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash PaymentKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash PaymentKey) -> ByteString -> Either DecoderError (Hash PaymentKey) Source # | |
SerialiseAsCBOR (Hash StakeExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash StakeExtendedKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash StakeExtendedKey) -> ByteString -> Either DecoderError (Hash StakeExtendedKey) Source # | |
SerialiseAsCBOR (Hash StakeKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash StakeKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash StakeKey) -> ByteString -> Either DecoderError (Hash StakeKey) Source # | |
SerialiseAsCBOR (Hash StakePoolKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: Hash StakePoolKey -> ByteString Source # deserialiseFromCBOR :: AsType (Hash StakePoolKey) -> ByteString -> Either DecoderError (Hash StakePoolKey) Source # | |
SerialiseAsCBOR (SigningKey ByronKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: SigningKey ByronKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey ByronKey) -> ByteString -> Either DecoderError (SigningKey ByronKey) Source # | |
SerialiseAsCBOR (SigningKey ByronKeyLegacy) Source # | |
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: SigningKey ByronKeyLegacy -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey ByronKeyLegacy) -> ByteString -> Either DecoderError (SigningKey ByronKeyLegacy) Source # | |
SerialiseAsCBOR (SigningKey KesKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: SigningKey KesKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey KesKey) -> ByteString -> Either DecoderError (SigningKey KesKey) Source # | |
SerialiseAsCBOR (SigningKey VrfKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: SigningKey VrfKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey VrfKey) -> ByteString -> Either DecoderError (SigningKey VrfKey) Source # | |
SerialiseAsCBOR (SigningKey CommitteeColdExtendedKey) Source # | |
SerialiseAsCBOR (SigningKey CommitteeColdKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
SerialiseAsCBOR (SigningKey CommitteeHotExtendedKey) Source # | |
SerialiseAsCBOR (SigningKey CommitteeHotKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
SerialiseAsCBOR (SigningKey DRepExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
SerialiseAsCBOR (SigningKey DRepKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey DRepKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey DRepKey) -> ByteString -> Either DecoderError (SigningKey DRepKey) Source # | |
SerialiseAsCBOR (SigningKey GenesisDelegateExtendedKey) Source # | |
SerialiseAsCBOR (SigningKey GenesisDelegateKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
SerialiseAsCBOR (SigningKey GenesisExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
SerialiseAsCBOR (SigningKey GenesisKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey GenesisKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey GenesisKey) -> ByteString -> Either DecoderError (SigningKey GenesisKey) Source # | |
SerialiseAsCBOR (SigningKey GenesisUTxOKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey GenesisUTxOKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey GenesisUTxOKey) -> ByteString -> Either DecoderError (SigningKey GenesisUTxOKey) Source # | |
SerialiseAsCBOR (SigningKey PaymentExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
SerialiseAsCBOR (SigningKey PaymentKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey PaymentKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey PaymentKey) -> ByteString -> Either DecoderError (SigningKey PaymentKey) Source # | |
SerialiseAsCBOR (SigningKey StakeExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
SerialiseAsCBOR (SigningKey StakeKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey StakeKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey StakeKey) -> ByteString -> Either DecoderError (SigningKey StakeKey) Source # | |
SerialiseAsCBOR (SigningKey StakePoolExtendedKey) Source # | |
SerialiseAsCBOR (SigningKey StakePoolKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: SigningKey StakePoolKey -> ByteString Source # deserialiseFromCBOR :: AsType (SigningKey StakePoolKey) -> ByteString -> Either DecoderError (SigningKey StakePoolKey) Source # | |
SerialiseAsCBOR (VerificationKey ByronKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Byron Methods serialiseToCBOR :: VerificationKey ByronKey -> ByteString Source # deserialiseFromCBOR :: AsType (VerificationKey ByronKey) -> ByteString -> Either DecoderError (VerificationKey ByronKey) Source # | |
SerialiseAsCBOR (VerificationKey ByronKeyLegacy) Source # | |
Defined in Cardano.Api.Internal.Keys.Byron | |
SerialiseAsCBOR (VerificationKey KesKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: VerificationKey KesKey -> ByteString Source # deserialiseFromCBOR :: AsType (VerificationKey KesKey) -> ByteString -> Either DecoderError (VerificationKey KesKey) Source # | |
SerialiseAsCBOR (VerificationKey VrfKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Praos Methods serialiseToCBOR :: VerificationKey VrfKey -> ByteString Source # deserialiseFromCBOR :: AsType (VerificationKey VrfKey) -> ByteString -> Either DecoderError (VerificationKey VrfKey) Source # | |
SerialiseAsCBOR (VerificationKey CommitteeColdExtendedKey) Source # | |
SerialiseAsCBOR (VerificationKey CommitteeColdKey) Source # | |
SerialiseAsCBOR (VerificationKey CommitteeHotExtendedKey) Source # | |
SerialiseAsCBOR (VerificationKey CommitteeHotKey) Source # | |
SerialiseAsCBOR (VerificationKey DRepExtendedKey) Source # | |
SerialiseAsCBOR (VerificationKey DRepKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: VerificationKey DRepKey -> ByteString Source # deserialiseFromCBOR :: AsType (VerificationKey DRepKey) -> ByteString -> Either DecoderError (VerificationKey DRepKey) Source # | |
SerialiseAsCBOR (VerificationKey GenesisDelegateExtendedKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley | |
SerialiseAsCBOR (VerificationKey GenesisDelegateKey) Source # | |
Defined in Cardano.Api.Internal.Keys.Shelley Methods serialiseToCBOR :: VerificationKey GenesisDelegateKey -> ByteString Source |