Safe Haskell | None |
---|---|
Language | Haskell2010 |
Cardano.Api.Ledger
Synopsis
- data Data era where
- data Decoder s a
- newtype VKey (kd :: KeyRole) = VKey {}
- newtype PParams era = PParams (PParamsHKD Identity era)
- data ProtVer = ProtVer {}
- data Vote
- class (EraTxBody era, EraTxWits era, EraTxAuxData era, EraPParams era, NoThunks (Tx era), DecCBOR (Annotator (Tx era)), EncCBOR (Tx era), ToCBOR (Tx era), Show (Tx era), Eq (Tx era), EqRaw (Tx era)) => EraTx era where
- type family Tx era = (r :: Type) | r -> era
- data TxIn = TxIn !TxId !TxIx
- newtype TxId = TxId {}
- fromCBOR :: FromCBOR a => Decoder s a
- toCBOR :: ToCBOR a => a -> Encoding
- serialize' :: EncCBOR a => Version -> a -> ByteString
- slice :: ByteString -> ByteSpan -> ByteString
- hashFromBytes :: HashAlgorithm h => ByteString -> Maybe (Hash h a)
- hashToBytes :: Hash h a -> ByteString
- hashWithSerialiser :: HashAlgorithm h => (a -> Encoding) -> a -> Hash h a
- hashVerKeyVRF :: forall c (r :: KeyRoleVRF). Crypto c => VerKeyVRF (VRF c) -> VRFVerKeyHash r
- data StrictMaybe a
- showTimelock :: AllegraEraScript era => NativeScript era -> String
- fromEraCBOR :: (Era era, DecCBOR t) => Decoder s t
- toEraCBOR :: (Era era, EncCBOR t) => t -> Encoding
- ppMinFeeAL :: EraPParams era => Lens' (PParams era) Coin
- ppMinUTxOValueL :: (EraPParams era, ProtVerAtMost era 4) => Lens' (PParams era) Coin
- pattern RegPoolTxCert :: EraTxCert era => PoolParams -> TxCert era
- pattern RetirePoolTxCert :: EraTxCert era => KeyHash 'StakePool -> EpochNo -> TxCert era
- castSafeHash :: SafeHash i -> SafeHash j
- extractHash :: SafeHash i -> Hash HASH i
- fromVRFVerKeyHash :: forall (r :: KeyRoleVRF) v. VRFVerKeyHash r -> Hash HASH (VerKeyVRF v)
- hashKey :: forall (kd :: KeyRole). VKey kd -> KeyHash kd
- toVRFVerKeyHash :: forall v (r :: KeyRoleVRF). Hash HASH (VerKeyVRF v) -> VRFVerKeyHash r
- pattern DelegStakeTxCert :: ShelleyEraTxCert era => StakeCredential -> KeyHash 'StakePool -> TxCert era
- pattern GenesisDelegTxCert :: (ShelleyEraTxCert era, ProtVerAtMost era 8) => KeyHash 'Genesis -> KeyHash 'GenesisDelegate -> VRFVerKeyHash 'GenDelegVRF -> TxCert era
- pattern MirTxCert :: (ShelleyEraTxCert era, ProtVerAtMost era 8) => MIRCert -> TxCert era
- pattern RegTxCert :: ShelleyEraTxCert era => StakeCredential -> TxCert era
- pattern UnRegTxCert :: ShelleyEraTxCert era => StakeCredential -> TxCert era
- type family Script era = (r :: Type) | r -> era
- getNativeScript :: EraScript era => Script era -> Maybe (NativeScript era)
- type family Script era = (r :: Type) | r -> era
- class (Val (Value era), ToJSON (TxOut era), DecCBOR (Value era), DecCBOR (CompactForm (Value era)), MemPack (CompactForm (Value era)), EncCBOR (Value era), ToCBOR (TxOut era), EncCBOR (TxOut era), DecCBOR (TxOut era), DecShareCBOR (TxOut era), Share (TxOut era) ~ Interns (Credential 'Staking), NoThunks (TxOut era), NFData (TxOut era), Show (TxOut era), Eq (TxOut era), MemPack (TxOut era), EraPParams era) => EraTxOut era
- class (EraScript era, Eq (TxWits era), EqRaw (TxWits era), Show (TxWits era), Monoid (TxWits era), NoThunks (TxWits era), ToCBOR (TxWits era), EncCBOR (TxWits era), DecCBOR (Annotator (TxWits era))) => EraTxWits era where
- type TxWits era = (r :: Type) | r -> era
- mkBasicTxWits :: TxWits era
- addrTxWitsL :: Lens' (TxWits era) (Set (WitVKey 'Witness))
- bootAddrTxWitsL :: Lens' (TxWits era) (Set BootstrapWitness)
- scriptTxWitsL :: Lens' (TxWits era) (Map ScriptHash (Script era))
- upgradeTxWits :: TxWits (PreviousEra era) -> TxWits era
- type family TxWits era = (r :: Type) | r -> era
- type family Value era
- class (Typeable era, KnownNat (ProtVerLow era), KnownNat (ProtVerHigh era), ProtVerLow era <= ProtVerHigh era, MinVersion <= ProtVerLow era, MinVersion <= ProtVerHigh era, CmpNat (ProtVerLow era) MaxVersion ~ 'LT, CmpNat (ProtVerHigh era) MaxVersion ~ 'LT, ProtVerLow era <= MaxVersion, ProtVerHigh era <= MaxVersion) => Era era where
- type PreviousEra era = (r :: Type) | r -> era
- type ProtVerLow era :: Nat
- type ProtVerHigh era :: Nat
- eraName :: String
- type family PreviousEra era = (r :: Type) | r -> era
- type family ProtVerHigh era :: Nat
- type family ProtVerLow era :: Nat
- class (Era era, Eq (PParamsHKD Identity era), Ord (PParamsHKD Identity era), Show (PParamsHKD Identity era), NFData (PParamsHKD Identity era), EncCBOR (PParamsHKD Identity era), DecCBOR (PParamsHKD Identity era), ToCBOR (PParamsHKD Identity era), FromCBOR (PParamsHKD Identity era), NoThunks (PParamsHKD Identity era), ToJSON (PParamsHKD Identity era), FromJSON (PParamsHKD Identity era), Eq (PParamsHKD StrictMaybe era), Ord (PParamsHKD StrictMaybe era), Show (PParamsHKD StrictMaybe era), NFData (PParamsHKD StrictMaybe era), EncCBOR (PParamsHKD StrictMaybe era), DecCBOR (PParamsHKD StrictMaybe era), ToCBOR (PParamsHKD StrictMaybe era), FromCBOR (PParamsHKD StrictMaybe era), NoThunks (PParamsHKD StrictMaybe era), ToJSON (PParamsHKD StrictMaybe era)) => EraPParams era where
- type PParamsHKD (f :: Type -> Type) era = (r :: Type) | r -> era
- type UpgradePParams (f :: Type -> Type) era
- type DowngradePParams (f :: Type -> Type) era
- applyPPUpdates :: PParams era -> PParamsUpdate era -> PParams era
- emptyPParamsIdentity :: PParamsHKD Identity era
- emptyPParamsStrictMaybe :: PParamsHKD StrictMaybe era
- upgradePParamsHKD :: forall (f :: Type -> Type). (HKDApplicative f, EraPParams (PreviousEra era)) => UpgradePParams f era -> PParamsHKD f (PreviousEra era) -> PParamsHKD f era
- downgradePParamsHKD :: forall (f :: Type -> Type). (HKDFunctor f, EraPParams (PreviousEra era)) => DowngradePParams f era -> PParamsHKD f era -> PParamsHKD f (PreviousEra era)
- hkdMinFeeAL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f Coin)
- hkdMinFeeBL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f Coin)
- hkdMaxBBSizeL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f Word32)
- hkdMaxTxSizeL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f Word32)
- hkdMaxBHSizeL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f Word16)
- hkdKeyDepositL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f Coin)
- hkdPoolDepositL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f Coin)
- hkdEMaxL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f EpochInterval)
- hkdNOptL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f Word16)
- hkdA0L :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f NonNegativeInterval)
- hkdRhoL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f UnitInterval)
- hkdTauL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f UnitInterval)
- hkdDL :: forall (f :: Type -> Type). (HKDFunctor f, ProtVerAtMost era 6) => Lens' (PParamsHKD f era) (HKD f UnitInterval)
- ppDG :: SimpleGetter (PParams era) UnitInterval
- hkdExtraEntropyL :: forall (f :: Type -> Type). (HKDFunctor f, ProtVerAtMost era 6) => Lens' (PParamsHKD f era) (HKD f Nonce)
- hkdProtocolVersionL :: forall (f :: Type -> Type). (HKDFunctor f, ProtVerAtMost era 8) => Lens' (PParamsHKD f era) (HKD f ProtVer)
- ppProtocolVersionL :: Lens' (PParams era) ProtVer
- ppuProtocolVersionL :: Lens' (PParamsUpdate era) (StrictMaybe ProtVer)
- hkdMinUTxOValueL :: forall (f :: Type -> Type). (HKDFunctor f, ProtVerAtMost era 4) => Lens' (PParamsHKD f era) (HKD f Coin)
- hkdMinPoolCostL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f Coin)
- type family DowngradePParams (f :: Type -> Type) era
- type family PParamsHKD (f :: Type -> Type) era = (r :: Type) | r -> era
- type family UpgradePParams (f :: Type -> Type) era
- data PParamsUpdate era
- class (Era era, ToJSON (TxCert era), DecCBOR (TxCert era), EncCBOR (TxCert era), ToCBOR (TxCert era), FromCBOR (TxCert era), NoThunks (TxCert era), NFData (TxCert era), Show (TxCert era), Ord (TxCert era), Eq (TxCert era)) => EraTxCert era where
- type TxCert era = (r :: Type) | r -> era
- type TxCertUpgradeError era
- upgradeTxCert :: TxCert (PreviousEra era) -> Either (TxCertUpgradeError era) (TxCert era)
- getVKeyWitnessTxCert :: TxCert era -> Maybe (KeyHash 'Witness)
- getScriptWitnessTxCert :: TxCert era -> Maybe ScriptHash
- mkRegPoolTxCert :: PoolParams -> TxCert era
- getRegPoolTxCert :: TxCert era -> Maybe PoolParams
- mkRetirePoolTxCert :: KeyHash 'StakePool -> EpochNo -> TxCert era
- getRetirePoolTxCert :: TxCert era -> Maybe (KeyHash 'StakePool, EpochNo)
- lookupRegStakeTxCert :: TxCert era -> Maybe (Credential 'Staking)
- lookupUnRegStakeTxCert :: TxCert era -> Maybe (Credential 'Staking)
- getTotalDepositsTxCerts :: Foldable f => PParams era -> (KeyHash 'StakePool -> Bool) -> f (TxCert era) -> Coin
- getTotalRefundsTxCerts :: Foldable f => PParams era -> (Credential 'Staking -> Maybe Coin) -> (Credential 'DRepRole -> Maybe Coin) -> f (TxCert era) -> Coin
- type family TxCert era = (r :: Type) | r -> era
- type family TxCertUpgradeError era
- data PoolCert
- = RegPool !PoolParams
- | RetirePool !(KeyHash 'StakePool) !EpochNo
- type ADDRHASH = Blake2b_224
- newtype KeyHash (r :: KeyRole) = KeyHash {}
- data SafeHash i
- data KeyRole
- class (EraPParams era, Eq (GovState era), Show (GovState era), NoThunks (GovState era), NFData (GovState era), EncCBOR (GovState era), DecCBOR (GovState era), DecShareCBOR (GovState era), Share (GovState era) ~ (Interns (Credential 'Staking), Interns (KeyHash 'StakePool), Interns (Credential 'DRepRole), Interns (Credential 'HotCommitteeRole)), ToCBOR (GovState era), FromCBOR (GovState era), Default (GovState era), ToJSON (GovState era)) => EraGov era where
- type family GovState era = (r :: Type) | r -> era
- data MIRCert = MIRCert {
- mirPot :: !MIRPot
- mirRewards :: !MIRTarget
- data MIRPot
- data MIRTarget
- class EraTxCert era => ShelleyEraTxCert era where
- mkRegTxCert :: StakeCredential -> TxCert era
- getRegTxCert :: TxCert era -> Maybe StakeCredential
- mkUnRegTxCert :: StakeCredential -> TxCert era
- getUnRegTxCert :: TxCert era -> Maybe StakeCredential
- mkDelegStakeTxCert :: StakeCredential -> KeyHash 'StakePool -> TxCert era
- getDelegStakeTxCert :: TxCert era -> Maybe (StakeCredential, KeyHash 'StakePool)
- mkGenesisDelegTxCert :: GenesisDelegCert -> TxCert era
- getGenesisDelegTxCert :: TxCert era -> Maybe GenesisDelegCert
- mkMirTxCert :: MIRCert -> TxCert era
- getMirTxCert :: TxCert era -> Maybe MIRCert
- data AccountState = AccountState {
- asTreasury :: !Coin
- asReserves :: !Coin
- ppPricesL :: AlonzoEraPParams era => Lens' (PParams era) Prices
- newtype CoinPerWord = CoinPerWord {}
- plutusScriptLanguage :: AlonzoEraScript era => PlutusScript era -> Language
- class (EraScript era, Eq (PlutusScript era), Ord (PlutusScript era), Show (PlutusScript era), NoThunks (PlutusScript era), NFData (PlutusScript era), SafeToHash (PlutusScript era), Eq (PlutusPurpose AsItem era), Show (PlutusPurpose AsItem era), EncCBOR (PlutusPurpose AsItem era), DecCBOR (PlutusPurpose AsItem era), NoThunks (PlutusPurpose AsItem era), NFData (PlutusPurpose AsItem era), Eq (PlutusPurpose AsIx era), Ord (PlutusPurpose AsIx era), Show (PlutusPurpose AsIx era), EncCBOR (PlutusPurpose AsIx era), DecCBOR (PlutusPurpose AsIx era), EncCBORGroup (PlutusPurpose AsIx era), DecCBORGroup (PlutusPurpose AsIx era), NoThunks (PlutusPurpose AsIx era), NFData (PlutusPurpose AsIx era), Eq (PlutusPurpose AsIxItem era), Show (PlutusPurpose AsIxItem era), NoThunks (PlutusPurpose AsIxItem era), NFData (PlutusPurpose AsIxItem era), AllegraEraScript era) => AlonzoEraScript era where
- data PlutusScript era
- type PlutusPurpose (f :: Type -> Type -> Type) era = (r :: Type) | r -> era
- eraMaxLanguage :: Language
- toPlutusScript :: Script era -> Maybe (PlutusScript era)
- fromPlutusScript :: PlutusScript era -> Script era
- mkPlutusScript :: forall (l :: Language). PlutusLanguage l => Plutus l -> Maybe (PlutusScript era)
- withPlutusScript :: PlutusScript era -> (forall (l :: Language). PlutusLanguage l => Plutus l -> a) -> a
- hoistPlutusPurpose :: (forall ix it. g ix it -> f ix it) -> PlutusPurpose g era -> PlutusPurpose f era
- mkSpendingPurpose :: f Word32 TxIn -> PlutusPurpose f era
- toSpendingPurpose :: PlutusPurpose f era -> Maybe (f Word32 TxIn)
- mkMintingPurpose :: f Word32 PolicyID -> PlutusPurpose f era
- toMintingPurpose :: PlutusPurpose f era -> Maybe (f Word32 PolicyID)
- mkCertifyingPurpose :: f Word32 (TxCert era) -> PlutusPurpose f era
- toCertifyingPurpose :: PlutusPurpose f era -> Maybe (f Word32 (TxCert era))
- mkRewardingPurpose :: f Word32 RewardAccount -> PlutusPurpose f era
- toRewardingPurpose :: PlutusPurpose f era -> Maybe (f Word32 RewardAccount)
- upgradePlutusPurposeAsIx :: PlutusPurpose AsIx (PreviousEra era) -> PlutusPurpose AsIx era
- type family PlutusPurpose (f :: Type -> Type -> Type) era = (r :: Type) | r -> era
- data family PlutusScript era
- data AlonzoPlutusPurpose (f :: Type -> Type -> Type) era
- = AlonzoSpending !(f Word32 TxIn)
- | AlonzoMinting !(f Word32 PolicyID)
- | AlonzoCertifying !(f Word32 (TxCert era))
- | AlonzoRewarding !(f Word32 RewardAccount)
- newtype AsIx ix it = AsIx {
- unAsIx :: ix
- data AsIxItem ix it = AsIxItem !ix !it
- data AlonzoGenesis
- class (MaryEraTxBody era, AlonzoEraTxOut era) => AlonzoEraTxBody era where
- collateralInputsTxBodyL :: Lens' (TxBody era) (Set TxIn)
- reqSignerHashesTxBodyL :: Lens' (TxBody era) (Set (KeyHash 'Witness))
- scriptIntegrityHashTxBodyL :: Lens' (TxBody era) (StrictMaybe ScriptIntegrityHash)
- networkIdTxBodyL :: Lens' (TxBody era) (StrictMaybe Network)
- redeemerPointer :: TxBody era -> PlutusPurpose AsItem era -> StrictMaybe (PlutusPurpose AsIx era)
- redeemerPointerInverse :: TxBody era -> PlutusPurpose AsIx era -> StrictMaybe (PlutusPurpose AsIxItem era)
- unRedeemers :: Redeemers era -> Map (PlutusPurpose AsIx era) (Data era, ExUnits)
- class (EraTxWits era, AlonzoEraScript era) => AlonzoEraTxWits era where
- datsTxWitsL :: Lens' (TxWits era) (TxDats era)
- rdmrsTxWitsL :: Lens' (TxWits era) (Redeemers era)
- data TxDats era where
- newtype ExUnits where
- WrapExUnits { }
- pattern ExUnits :: Natural -> Natural -> ExUnits
- data Plutus (l :: Language)
- data CostModels
- data Prices = Prices {}
- newtype CoinPerByte = CoinPerByte {}
- data Anchor = Anchor {
- anchorUrl :: !Url
- anchorDataHash :: !(SafeHash AnchorData)
- newtype AnchorData = AnchorData ByteString
- data Constitution era = Constitution {}
- data GovAction era
- = ParameterChange !(StrictMaybe (GovPurposeId 'PParamUpdatePurpose era)) !(PParamsUpdate era) !(StrictMaybe ScriptHash)
- | HardForkInitiation !(StrictMaybe (GovPurposeId 'HardForkPurpose era)) !ProtVer
- | TreasuryWithdrawals !(Map RewardAccount Coin) !(StrictMaybe ScriptHash)
- | NoConfidence !(StrictMaybe (GovPurposeId 'CommitteePurpose era))
- | UpdateCommittee !(StrictMaybe (GovPurposeId 'CommitteePurpose era)) !(Set (Credential 'ColdCommitteeRole)) !(Map (Credential 'ColdCommitteeRole) EpochNo) !UnitInterval
- | NewConstitution !(StrictMaybe (GovPurposeId 'ConstitutionPurpose era)) !(Constitution era)
- | InfoAction
- data GovActionId = GovActionId {
- gaidTxId :: !TxId
- gaidGovActionIx :: !GovActionIx
- newtype GovActionIx = GovActionIx {}
- data GovActionState era = GovActionState {
- gasId :: !GovActionId
- gasCommitteeVotes :: !(Map (Credential 'HotCommitteeRole) Vote)
- gasDRepVotes :: !(Map (Credential 'DRepRole) Vote)
- gasStakePoolVotes :: !(Map (KeyHash 'StakePool) Vote)
- gasProposalProcedure :: !(ProposalProcedure era)
- gasProposedIn :: !EpochNo
- gasExpiresAfter :: !EpochNo
- data ProposalProcedure era = ProposalProcedure {
- pProcDeposit :: !Coin
- pProcReturnAddr :: !RewardAccount
- pProcGovAction :: !(GovAction era)
- pProcAnchor :: !Anchor
- data Voter
- data VotingProcedure era = VotingProcedure {
- vProcVote :: !Vote
- vProcAnchor :: !(StrictMaybe Anchor)
- newtype VotingProcedures era = VotingProcedures {
- unVotingProcedures :: Map Voter (Map GovActionId (VotingProcedure era))
- pattern AuthCommitteeHotKeyTxCert :: ConwayEraTxCert era => Credential 'ColdCommitteeRole -> Credential 'HotCommitteeRole -> TxCert era
- pattern DelegTxCert :: ConwayEraTxCert era => StakeCredential -> Delegatee -> TxCert era
- pattern RegDRepTxCert :: ConwayEraTxCert era => Credential 'DRepRole -> Coin -> StrictMaybe Anchor -> TxCert era
- pattern RegDepositDelegTxCert :: ConwayEraTxCert era => StakeCredential -> Delegatee -> Coin -> TxCert era
- pattern RegDepositTxCert :: ConwayEraTxCert era => StakeCredential -> Coin -> TxCert era
- pattern ResignCommitteeColdTxCert :: ConwayEraTxCert era => Credential 'ColdCommitteeRole -> StrictMaybe Anchor -> TxCert era
- pattern UnRegDRepTxCert :: ConwayEraTxCert era => Credential 'DRepRole -> Coin -> TxCert era
- pattern UnRegDepositTxCert :: ConwayEraTxCert era => StakeCredential -> Coin -> TxCert era
- class ShelleyEraTxCert era => ConwayEraTxCert era where
- mkRegDepositTxCert :: StakeCredential -> Coin -> TxCert era
- getRegDepositTxCert :: TxCert era -> Maybe (StakeCredential, Coin)
- mkUnRegDepositTxCert :: StakeCredential -> Coin -> TxCert era
- getUnRegDepositTxCert :: TxCert era -> Maybe (StakeCredential, Coin)
- mkDelegTxCert :: StakeCredential -> Delegatee -> TxCert era
- getDelegTxCert :: TxCert era -> Maybe (StakeCredential, Delegatee)
- mkRegDepositDelegTxCert :: StakeCredential -> Delegatee -> Coin -> TxCert era
- getRegDepositDelegTxCert :: TxCert era -> Maybe (StakeCredential, Delegatee, Coin)
- mkAuthCommitteeHotKeyTxCert :: Credential 'ColdCommitteeRole -> Credential 'HotCommitteeRole -> TxCert era
- getAuthCommitteeHotKeyTxCert :: TxCert era -> Maybe (Credential 'ColdCommitteeRole, Credential 'HotCommitteeRole)
- mkResignCommitteeColdTxCert :: Credential 'ColdCommitteeRole -> StrictMaybe Anchor -> TxCert era
- getResignCommitteeColdTxCert :: TxCert era -> Maybe (Credential 'ColdCommitteeRole, StrictMaybe Anchor)
- mkRegDRepTxCert :: Credential 'DRepRole -> Coin -> StrictMaybe Anchor -> TxCert era
- getRegDRepTxCert :: TxCert era -> Maybe (Credential 'DRepRole, Coin, StrictMaybe Anchor)
- mkUnRegDRepTxCert :: Credential 'DRepRole -> Coin -> TxCert era
- getUnRegDRepTxCert :: TxCert era -> Maybe (Credential 'DRepRole, Coin)
- mkUpdateDRepTxCert :: Credential 'DRepRole -> StrictMaybe Anchor -> TxCert era
- getUpdateDRepTxCert :: TxCert era -> Maybe (Credential 'DRepRole, StrictMaybe Anchor)
- data Delegatee
- = DelegStake !(KeyHash 'StakePool)
- | DelegVote !DRep
- | DelegStakeVote !(KeyHash 'StakePool) !DRep
- data ConwayPlutusPurpose (f :: Type -> Type -> Type) era
- = ConwaySpending !(f Word32 TxIn)
- | ConwayMinting !(f Word32 PolicyID)
- | ConwayCertifying !(f Word32 (TxCert era))
- | ConwayRewarding !(f Word32 RewardAccount)
- | ConwayVoting !(f Word32 Voter)
- | ConwayProposing !(f Word32 (ProposalProcedure era))
- data ConwayGenesis = ConwayGenesis {}
- data WitVKey (kr :: KeyRole) where
- pattern WitVKey :: Typeable kr => VKey kr -> SignedDSIGN DSIGN (Hash HASH EraIndependentTxBody) -> WitVKey kr
- hashAnchorData :: AnchorData -> SafeHash AnchorData
- txIxToInt :: TxIx -> Int
- data RewardAccount = RewardAccount {
- raNetwork :: !Network
- raCredential :: !(Credential 'Staking)
- data NewEpochState era = NewEpochState {
- nesEL :: !EpochNo
- nesBprev :: !BlocksMade
- nesBcur :: !BlocksMade
- nesEs :: !(EpochState era)
- nesRu :: !(StrictMaybe PulsingRewUpdate)
- nesPd :: !PoolDistr
- stashedAVVMAddresses :: !(StashedAVVMAddresses era)
- newtype Coin = Coin {}
- serializeAsHexText :: ToCBOR a => a -> Text
- byronProtVer :: Version
- mkVersion :: (Integral i, MonadFail m) => i -> m Version
- toPlainDecoder :: Maybe ByteString -> Version -> Decoder s a -> Decoder s a
- data Annotated b a = Annotated {
- unAnnotated :: !b
- annotation :: !a
- data ByteSpan = ByteSpan !ByteOffset !ByteOffset
- class (UnsoundPureKESAlgorithm (KES c), VRFAlgorithm (VRF c), ContextKES (KES c) ~ (), ContextVRF (VRF c) ~ (), Typeable c) => Crypto c
- data Committee era = Committee {}
- dvtPPEconomicGroupL :: Lens' DRepVotingThresholds UnitInterval
- dvtPPGovGroupL :: Lens' DRepVotingThresholds UnitInterval
- dvtPPNetworkGroupL :: Lens' DRepVotingThresholds UnitInterval
- dvtPPTechnicalGroupL :: Lens' DRepVotingThresholds UnitInterval
- dvtUpdateToConstitutionL :: Lens' DRepVotingThresholds UnitInterval
- data DRepVotingThresholds = DRepVotingThresholds {
- dvtMotionNoConfidence :: !UnitInterval
- dvtCommitteeNormal :: !UnitInterval
- dvtCommitteeNoConfidence :: !UnitInterval
- dvtUpdateToConstitution :: !UnitInterval
- dvtHardForkInitiation :: !UnitInterval
- dvtPPNetworkGroup :: !UnitInterval
- dvtPPEconomicGroup :: !UnitInterval
- dvtPPTechnicalGroup :: !UnitInterval
- dvtPPGovGroup :: !UnitInterval
- dvtTreasuryWithdrawal :: !UnitInterval
- data PoolVotingThresholds = PoolVotingThresholds {}
- data UpgradeConwayPParams (f :: Type -> Type) = UpgradeConwayPParams {
- ucppPoolVotingThresholds :: !(HKD f PoolVotingThresholds)
- ucppDRepVotingThresholds :: !(HKD f DRepVotingThresholds)
- ucppCommitteeMinSize :: !(HKD f Word16)
- ucppCommitteeMaxTermLength :: !(HKD f EpochInterval)
- ucppGovActionLifetime :: !(HKD f EpochInterval)
- ucppGovActionDeposit :: !(HKD f Coin)
- ucppDRepDeposit :: !(HKD f Coin)
- ucppDRepActivity :: !(HKD f EpochInterval)
- ucppMinFeeRefScriptCostPerByte :: !(HKD f NonNegativeInterval)
- ucppPlutusV3CostModel :: !(HKD f CostModel)
- pattern UpdateDRepTxCert :: ConwayEraTxCert era => Credential 'DRepRole -> StrictMaybe Anchor -> TxCert era
- data ConwayDelegCert
- data ConwayGovCert
- = ConwayRegDRep !(Credential 'DRepRole) !Coin !(StrictMaybe Anchor)
- | ConwayUnRegDRep !(Credential 'DRepRole) !Coin
- | ConwayUpdateDRep !(Credential 'DRepRole) !(StrictMaybe Anchor)
- | ConwayAuthCommitteeHotKey !(Credential 'ColdCommitteeRole) !(Credential 'HotCommitteeRole)
- | ConwayResignCommitteeColdKey !(Credential 'ColdCommitteeRole) !(StrictMaybe Anchor)
- data ConwayTxCert era
- newtype EpochInterval = EpochInterval {}
- newtype EpochNo = EpochNo {}
- class HasKeyRole (a :: KeyRole -> Type)
- unsafeMakeSafeHash :: Hash HASH i -> SafeHash i
- data GenDelegPair = GenDelegPair {}
- data StandardCrypto
- textToDns :: MonadFail m => Int -> Text -> m DnsName
- textToUrl :: MonadFail m => Int -> Text -> m Url
- boundRational :: BoundedRational r => Rational -> Maybe r
- unboundRational :: BoundedRational r => r -> Rational
- data DnsName
- data Network
- data NonNegativeInterval
- portToWord16 :: Port -> Word16
- data UnitInterval
- data Url
- credToText :: forall (kr :: KeyRole). Credential kr -> Text
- data Credential (kr :: KeyRole)
- = ScriptHashObj !ScriptHash
- | KeyHashObj !(KeyHash kr)
- data StakeReference
- addDeltaCoin :: Coin -> DeltaCoin -> Coin
- toDeltaCoin :: Coin -> DeltaCoin
- drepAnchorL :: Lens' DRepState (StrictMaybe Anchor)
- drepDepositL :: Lens' DRepState Coin
- drepExpiryL :: Lens' DRepState EpochNo
- data DRep where
- data DRepState = DRepState {
- drepExpiry :: !EpochNo
- drepAnchor :: !(StrictMaybe Anchor)
- drepDeposit :: !Coin
- drepDelegs :: !(Set (Credential 'Staking))
- languageToText :: Language -> Text
- data Language
- data PoolMetadata = PoolMetadata {
- pmUrl :: !Url
- pmHash :: !ByteString
- data PoolParams = PoolParams {
- ppId :: !(KeyHash 'StakePool)
- ppVrf :: !(VRFVerKeyHash 'StakePoolVRF)
- ppPledge :: !Coin
- ppCost :: !Coin
- ppMargin :: !UnitInterval
- ppRewardAccount :: !RewardAccount
- ppOwners :: !(Set (KeyHash 'Staking))
- ppRelays :: !(StrictSeq StakePoolRelay)
- ppMetadata :: !(StrictMaybe PoolMetadata)
- data StakePoolRelay
- = SingleHostAddr !(StrictMaybe Port) !(StrictMaybe IPv4) !(StrictMaybe IPv6)
- | SingleHostName !(StrictMaybe Port) !DnsName
- | MultiHostName !DnsName
- unData :: Data era -> Data
- csCommitteeCredsL :: forall era f. Functor f => (Map (Credential 'ColdCommitteeRole) CommitteeAuthorization -> f (Map (Credential 'ColdCommitteeRole) CommitteeAuthorization)) -> CommitteeState era -> f (CommitteeState era)
- data PState era = PState {
- psStakePoolParams :: !(Map (KeyHash 'StakePool) PoolParams)
- psFutureStakePoolParams :: !(Map (KeyHash 'StakePool) PoolParams)
- psRetiring :: !(Map (KeyHash 'StakePool) EpochNo)
- psDeposits :: !(Map (KeyHash 'StakePool) Coin)
- maybeToStrictMaybe :: Maybe a -> StrictMaybe a
- strictMaybeToMaybe :: StrictMaybe a -> Maybe a
- newtype MultiAsset = MultiAsset (Map PolicyID (Map AssetName Integer))
- secondsToNominalDiffTimeMicro :: Micro -> NominalDiffTimeMicro
- data ShelleyGenesisStaking = ShelleyGenesisStaking {}
- data GenesisDelegCert = GenesisDelegCert !(KeyHash 'Genesis) !(KeyHash 'GenesisDelegate) !(VRFVerKeyHash 'GenDelegVRF)
- data ShelleyDelegCert
- data ShelleyTxCert era
Documentation
Instances
Instances
MonadFail (Decoder s) | |
Applicative (Decoder s) | |
Defined in Codec.CBOR.Decoding | |
Functor (Decoder s) | |
Monad (Decoder s) | |
newtype VKey (kd :: KeyRole) Source #
Discriminated verification key
We wrap the basic VerKeyDSIGN
in order to add the key role.
Constructors
VKey | |
Fields |
Instances
HasKeyRole VKey | |||||
Defined in Cardano.Ledger.Keys.Internal | |||||
ToJSON (VKey 'Witness) Source # | |||||
Defined in Cardano.Api.Internal.Orphans | |||||
Generic (VKey kd) | |||||
Defined in Cardano.Ledger.Keys.Internal Associated Types
| |||||
Show (VKey kd) | |||||
Typeable kd => FromCBOR (VKey kd) | |||||
Typeable kd => ToCBOR (VKey kd) | |||||
Typeable kd => DecCBOR (VKey kd) | |||||
Typeable kd => EncCBOR (VKey kd) | |||||
NFData (VKey kd) | |||||
Defined in Cardano.Ledger.Keys.Internal | |||||
Eq (VKey kd) | |||||
NoThunks (VKey kd) | |||||
type Rep (VKey kd) | |||||
Defined in Cardano.Ledger.Keys.Internal type Rep (VKey kd) = D1 ('MetaData "VKey" "Cardano.Ledger.Keys.Internal" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'True) (C1 ('MetaCons "VKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unVKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VerKeyDSIGN DSIGN)))) |
Protocol parameters
Constructors
PParams (PParamsHKD Identity era) |
Instances
FromJSON (PParamsHKD Identity era) => FromJSON (PParams era) | |||||
Defined in Cardano.Ledger.Core.PParams Methods parseJSON :: Value -> Parser (PParams era) parseJSONList :: Value -> Parser [PParams era] omittedField :: Maybe (PParams era) | |||||
ToJSON (PParamsHKD Identity era) => ToJSON (PParams era) | |||||
Defined in Cardano.Ledger.Core.PParams Methods toJSON :: PParams era -> Value toEncoding :: PParams era -> Encoding toJSONList :: [PParams era] -> Value toEncodingList :: [PParams era] -> Encoding | |||||
Generic (PParams era) | |||||
Defined in Cardano.Ledger.Core.PParams Associated Types
| |||||
Show (PParamsHKD Identity era) => Show (PParams era) | |||||
(Typeable era, FromCBOR (PParamsHKD Identity era)) => FromCBOR (PParams era) | |||||
(Typeable era, ToCBOR (PParamsHKD Identity era)) => ToCBOR (PParams era) | |||||
(Typeable era, DecCBOR (PParamsHKD Identity era)) => DecCBOR (PParams era) | |||||
(Typeable era, EncCBOR (PParamsHKD Identity era)) => EncCBOR (PParams era) | |||||
EraPParams era => Default (PParams era) | |||||
Defined in Cardano.Ledger.Core.PParams | |||||
NFData (PParamsHKD Identity era) => NFData (PParams era) | |||||
Defined in Cardano.Ledger.Core.PParams | |||||
Eq (PParamsHKD Identity era) => Eq (PParams era) | |||||
Ord (PParamsHKD Identity era) => Ord (PParams era) | |||||
Defined in Cardano.Ledger.Core.PParams Methods compare :: PParams era -> PParams era -> Ordering Source # (<) :: PParams era -> PParams era -> Bool Source # (<=) :: PParams era -> PParams era -> Bool Source # (>) :: PParams era -> PParams era -> Bool Source # (>=) :: PParams era -> PParams era -> Bool Source # | |||||
NoThunks (PParamsHKD Identity era) => NoThunks (PParams era) | |||||
type TranslationError AllegraEra PParams | |||||
Defined in Cardano.Ledger.Allegra.Translation | |||||
type TranslationError AlonzoEra PParams | |||||
Defined in Cardano.Ledger.Alonzo.Translation | |||||
type TranslationError BabbageEra PParams | |||||
Defined in Cardano.Ledger.Babbage.Translation | |||||
type TranslationError ConwayEra PParams | |||||
Defined in Cardano.Ledger.Conway.Translation | |||||
type TranslationError MaryEra PParams | |||||
Defined in Cardano.Ledger.Mary.Translation | |||||
type Rep (PParams era) | |||||
Defined in Cardano.Ledger.Core.PParams type Rep (PParams era) = D1 ('MetaData "PParams" "Cardano.Ledger.Core.PParams" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'True) (C1 ('MetaCons "PParams" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PParamsHKD Identity era)))) |
Instances
FromJSON ProtVer | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
ToJSON ProtVer | |||||
Defined in Cardano.Ledger.BaseTypes Methods toEncoding :: ProtVer -> Encoding toJSONList :: [ProtVer] -> Value toEncodingList :: [ProtVer] -> Encoding | |||||
Generic ProtVer | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
| |||||
Show ProtVer | |||||
FromCBOR ProtVer | |||||
ToCBOR ProtVer | |||||
DecCBOR ProtVer | |||||
EncCBOR ProtVer | |||||
DecCBORGroup ProtVer | |||||
Defined in Cardano.Ledger.BaseTypes Methods decCBORGroup :: Decoder s ProtVer Source # | |||||
EncCBORGroup ProtVer | |||||
ToPlutusData ProtVer | |||||
Defined in Cardano.Ledger.Plutus.ToPlutusData | |||||
NFData ProtVer | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
Eq ProtVer | |||||
Ord ProtVer | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
NoThunks ProtVer | |||||
type Rep ProtVer | |||||
Defined in Cardano.Ledger.BaseTypes type Rep ProtVer = D1 ('MetaData "ProtVer" "Cardano.Ledger.BaseTypes" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'False) (C1 ('MetaCons "ProtVer" 'PrefixI 'True) (S1 ('MetaSel ('Just "pvMajor") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Version) :*: S1 ('MetaSel ('Just "pvMinor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Natural))) |
Instances
ToJSON Vote | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods toEncoding :: Vote -> Encoding toJSONList :: [Vote] -> Value toEncodingList :: [Vote] -> Encoding | |||||
Bounded Vote | |||||
Enum Vote | |||||
Generic Vote | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
| |||||
Show Vote | |||||
DecCBOR Vote | |||||
EncCBOR Vote | |||||
NFData Vote | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
Eq Vote | |||||
Ord Vote | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
NoThunks Vote | |||||
type Rep Vote | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures type Rep Vote = D1 ('MetaData "Vote" "Cardano.Ledger.Conway.Governance.Procedures" "cardano-ledger-conway-1.19.0.0-4c27ba0e7c20c908d1dfe5f4038fdf7297360e4c38f5293876b47703f80d0e2c" 'False) (C1 ('MetaCons "VoteNo" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "VoteYes" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Abstain" 'PrefixI 'False) (U1 :: Type -> Type))) |
class (EraTxBody era, EraTxWits era, EraTxAuxData era, EraPParams era, NoThunks (Tx era), DecCBOR (Annotator (Tx era)), EncCBOR (Tx era), ToCBOR (Tx era), Show (Tx era), Eq (Tx era), EqRaw (Tx era)) => EraTx era where Source #
A transaction.
Minimal complete definition
mkBasicTx, bodyTxL, witsTxL, auxDataTxL, sizeTxF, wireSizeTxF, validateNativeScript, getMinFeeTx, upgradeTx
type family Tx era = (r :: Type) | r -> era Source #
Instances
type Tx AllegraEra | |
Defined in Cardano.Ledger.Allegra.Tx | |
type Tx AlonzoEra | |
Defined in Cardano.Ledger.Alonzo.Tx | |
type Tx BabbageEra | |
Defined in Cardano.Ledger.Babbage.Tx | |
type Tx ConwayEra | |
Defined in Cardano.Ledger.Conway.Tx | |
type Tx MaryEra | |
Defined in Cardano.Ledger.Mary.Tx | |
type Tx ShelleyEra | |
Defined in Cardano.Ledger.Shelley.Tx.Internal |
The input of a UTxO.
Instances
ToJSON TxIn | |||||
Defined in Cardano.Ledger.TxIn Methods toEncoding :: TxIn -> Encoding toJSONList :: [TxIn] -> Value toEncodingList :: [TxIn] -> Encoding | |||||
ToJSONKey TxIn | |||||
Defined in Cardano.Ledger.TxIn | |||||
Generic TxIn | |||||
Defined in Cardano.Ledger.TxIn Associated Types
| |||||
Show TxIn | |||||
DecCBOR TxIn | |||||
DecShareCBOR TxIn | |||||
EncCBOR TxIn | |||||
NFData TxIn | |||||
Defined in Cardano.Ledger.TxIn | |||||
Eq TxIn | |||||
Ord TxIn | |||||
Defined in Cardano.Ledger.TxIn | |||||
HeapWords TxIn | |||||
Defined in Cardano.Ledger.TxIn | |||||
MemPack TxIn | |||||
Defined in Cardano.Ledger.TxIn | |||||
NoThunks TxIn | |||||
type Rep TxIn | |||||
Defined in Cardano.Ledger.TxIn type Rep TxIn = D1 ('MetaData "TxIn" "Cardano.Ledger.TxIn" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'False) (C1 ('MetaCons "TxIn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec0 TxIx))) | |||||
type Share TxIn | |||||
A unique ID of a transaction, which is computable from the transaction.
Constructors
TxId | |
Fields |
Instances
FromJSON TxId | |||||
Defined in Cardano.Ledger.TxIn | |||||
ToJSON TxId | |||||
Defined in Cardano.Ledger.TxIn Methods toEncoding :: TxId -> Encoding toJSONList :: [TxId] -> Value toEncodingList :: [TxId] -> Encoding | |||||
Generic TxId | |||||
Defined in Cardano.Ledger.TxIn Associated Types
| |||||
Show TxId | |||||
DecCBOR TxId | |||||
EncCBOR TxId | |||||
NFData TxId | |||||
Defined in Cardano.Ledger.TxIn | |||||
Eq TxId | |||||
Ord TxId | |||||
Defined in Cardano.Ledger.TxIn | |||||
HeapWords TxId | |||||
Defined in Cardano.Ledger.TxIn | |||||
MemPack TxId | |||||
Defined in Cardano.Ledger.TxIn | |||||
NoThunks TxId | |||||
type Rep TxId | |||||
Defined in Cardano.Ledger.TxIn type Rep TxId = D1 ('MetaData "TxId" "Cardano.Ledger.TxIn" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'True) (C1 ('MetaCons "TxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SafeHash EraIndependentTxBody)))) |
serialize' :: EncCBOR a => Version -> a -> ByteString Source #
Serialize a Haskell value to an external binary representation.
The output is represented as a strict ByteString
.
slice :: ByteString -> ByteSpan -> ByteString Source #
Extract a substring of a given ByteString corresponding to the offsets.
Arguments
:: HashAlgorithm h | |
=> ByteString | It must have an exact length, as given by |
-> Maybe (Hash h a) |
Make a hash from it bytes representation.
hashToBytes :: Hash h a -> ByteString Source #
The representation of the hash as bytes.
hashWithSerialiser :: HashAlgorithm h => (a -> Encoding) -> a -> Hash h a Source #
A variation on hashWith
, but specially for CBOR encodings.
hashVerKeyVRF :: forall c (r :: KeyRoleVRF). Crypto c => VerKeyVRF (VRF c) -> VRFVerKeyHash r Source #
data StrictMaybe a Source #
Instances
MonadFail StrictMaybe | |||||
Defined in Data.Maybe.Strict Methods fail :: String -> StrictMaybe a Source # | |||||
Foldable StrictMaybe | |||||
Defined in Data.Maybe.Strict Methods fold :: Monoid m => StrictMaybe m -> m Source # foldMap :: Monoid m => (a -> m) -> StrictMaybe a -> m Source # foldMap' :: Monoid m => (a -> m) -> StrictMaybe a -> m Source # foldr :: (a -> b -> b) -> b -> StrictMaybe a -> b Source # foldr' :: (a -> b -> b) -> b -> StrictMaybe a -> b Source # foldl :: (b -> a -> b) -> b -> StrictMaybe a -> b Source # foldl' :: (b -> a -> b) -> b -> StrictMaybe a -> b Source # foldr1 :: (a -> a -> a) -> StrictMaybe a -> a Source # foldl1 :: (a -> a -> a) -> StrictMaybe a -> a Source # toList :: StrictMaybe a -> [a] Source # null :: StrictMaybe a -> Bool Source # length :: StrictMaybe a -> Int Source # elem :: Eq a => a -> StrictMaybe a -> Bool Source # maximum :: Ord a => StrictMaybe a -> a Source # minimum :: Ord a => StrictMaybe a -> a Source # sum :: Num a => StrictMaybe a -> a Source # product :: Num a => StrictMaybe a -> a Source # | |||||
Traversable StrictMaybe | |||||
Defined in Data.Maybe.Strict Methods traverse :: Applicative f => (a -> f b) -> StrictMaybe a -> f (StrictMaybe b) Source # sequenceA :: Applicative f => StrictMaybe (f a) -> f (StrictMaybe a) Source # mapM :: Monad m => (a -> m b) -> StrictMaybe a -> m (StrictMaybe b) Source # sequence :: Monad m => StrictMaybe (m a) -> m (StrictMaybe a) Source # | |||||
Alternative StrictMaybe | |||||
Defined in Data.Maybe.Strict Methods empty :: StrictMaybe a Source # (<|>) :: StrictMaybe a -> StrictMaybe a -> StrictMaybe a Source # some :: StrictMaybe a -> StrictMaybe [a] Source # many :: StrictMaybe a -> StrictMaybe [a] Source # | |||||
Applicative StrictMaybe | |||||
Defined in Data.Maybe.Strict Methods pure :: a -> StrictMaybe a Source # (<*>) :: StrictMaybe (a -> b) -> StrictMaybe a -> StrictMaybe b Source # liftA2 :: (a -> b -> c) -> StrictMaybe a -> StrictMaybe b -> StrictMaybe c Source # (*>) :: StrictMaybe a -> StrictMaybe b -> StrictMaybe b Source # (<*) :: StrictMaybe a -> StrictMaybe b -> StrictMaybe a Source # | |||||
Functor StrictMaybe | |||||
Defined in Data.Maybe.Strict Methods fmap :: (a -> b) -> StrictMaybe a -> StrictMaybe b Source # (<$) :: a -> StrictMaybe b -> StrictMaybe a Source # | |||||
Monad StrictMaybe | |||||
Defined in Data.Maybe.Strict Methods (>>=) :: StrictMaybe a -> (a -> StrictMaybe b) -> StrictMaybe b Source # (>>) :: StrictMaybe a -> StrictMaybe b -> StrictMaybe b Source # return :: a -> StrictMaybe a Source # | |||||
HKDApplicative StrictMaybe | |||||
Defined in Cardano.Ledger.HKD Methods hkdPure :: a -> HKD StrictMaybe a Source # hkdLiftA2 :: (a -> b -> c) -> HKD StrictMaybe a -> HKD StrictMaybe b -> HKD StrictMaybe c Source # | |||||
HKDFunctor StrictMaybe | |||||
Defined in Cardano.Ledger.HKD Methods hkdMap :: proxy StrictMaybe -> (a -> b) -> HKD StrictMaybe a -> HKD StrictMaybe b Source # toNoUpdate :: HKD StrictMaybe a -> HKDNoUpdate StrictMaybe a Source # fromNoUpdate :: HKDNoUpdate StrictMaybe a -> HKD StrictMaybe a Source # | |||||
FromJSON a => FromJSON (StrictMaybe a) | |||||
Defined in Data.Maybe.Strict Methods parseJSON :: Value -> Parser (StrictMaybe a) parseJSONList :: Value -> Parser [StrictMaybe a] omittedField :: Maybe (StrictMaybe a) | |||||
ToJSON a => ToJSON (StrictMaybe a) | |||||
Defined in Data.Maybe.Strict Methods toJSON :: StrictMaybe a -> Value toEncoding :: StrictMaybe a -> Encoding toJSONList :: [StrictMaybe a] -> Value toEncodingList :: [StrictMaybe a] -> Encoding omitField :: StrictMaybe a -> Bool | |||||
Semigroup a => Monoid (StrictMaybe a) | |||||
Defined in Data.Maybe.Strict Methods mempty :: StrictMaybe a Source # mappend :: StrictMaybe a -> StrictMaybe a -> StrictMaybe a Source # mconcat :: [StrictMaybe a] -> StrictMaybe a Source # | |||||
Semigroup a => Semigroup (StrictMaybe a) | |||||
Defined in Data.Maybe.Strict Methods (<>) :: StrictMaybe a -> StrictMaybe a -> StrictMaybe a Source # sconcat :: NonEmpty (StrictMaybe a) -> StrictMaybe a Source # stimes :: Integral b => b -> StrictMaybe a -> StrictMaybe a Source # | |||||
Generic (StrictMaybe a) | |||||
Defined in Data.Maybe.Strict Associated Types
Methods from :: StrictMaybe a -> Rep (StrictMaybe a) x Source # to :: Rep (StrictMaybe a) x -> StrictMaybe a Source # | |||||
Show (UpgradeConwayPParams StrictMaybe) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods showsPrec :: Int -> UpgradeConwayPParams StrictMaybe -> ShowS Source # show :: UpgradeConwayPParams StrictMaybe -> String Source # showList :: [UpgradeConwayPParams StrictMaybe] -> ShowS Source # | |||||
Show a => Show (StrictMaybe a) | |||||
Defined in Data.Maybe.Strict | |||||
FromCBOR a => FromCBOR (StrictMaybe a) | |||||
Defined in Data.Maybe.Strict | |||||
ToCBOR a => ToCBOR (StrictMaybe a) | |||||
Defined in Data.Maybe.Strict Methods toCBOR :: StrictMaybe a -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (StrictMaybe a) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [StrictMaybe a] -> Size Source # | |||||
DecCBOR a => DecCBOR (StrictMaybe a) | |||||
Defined in Cardano.Ledger.Binary.Decoding.DecCBOR | |||||
EncCBOR a => EncCBOR (StrictMaybe a) | |||||
Defined in Cardano.Ledger.Binary.Encoding.EncCBOR Methods encCBOR :: StrictMaybe a -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (StrictMaybe a) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [StrictMaybe a] -> Size Source # | |||||
Default (UpgradeAlonzoPParams StrictMaybe) | |||||
Defined in Cardano.Ledger.Alonzo.PParams Methods | |||||
Default (UpgradeConwayPParams StrictMaybe) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods | |||||
Default (StrictMaybe t) | |||||
Defined in Data.Maybe.Strict Methods def :: StrictMaybe t # | |||||
NFData (UpgradeConwayPParams StrictMaybe) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods rnf :: UpgradeConwayPParams StrictMaybe -> () Source # | |||||
NFData a => NFData (StrictMaybe a) | |||||
Defined in Data.Maybe.Strict Methods rnf :: StrictMaybe a -> () Source # | |||||
Eq (UpgradeConwayPParams StrictMaybe) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods (==) :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> Bool Source # (/=) :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> Bool Source # | |||||
Eq a => Eq (StrictMaybe a) | |||||
Defined in Data.Maybe.Strict Methods (==) :: StrictMaybe a -> StrictMaybe a -> Bool Source # (/=) :: StrictMaybe a -> StrictMaybe a -> Bool Source # | |||||
Ord (UpgradeConwayPParams StrictMaybe) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods compare :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> Ordering Source # (<) :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> Bool Source # (<=) :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> Bool Source # (>) :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> Bool Source # (>=) :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> Bool Source # max :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe Source # min :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe Source # | |||||
Ord a => Ord (StrictMaybe a) | |||||
Defined in Data.Maybe.Strict Methods compare :: StrictMaybe a -> StrictMaybe a -> Ordering Source # (<) :: StrictMaybe a -> StrictMaybe a -> Bool Source # (<=) :: StrictMaybe a -> StrictMaybe a -> Bool Source # (>) :: StrictMaybe a -> StrictMaybe a -> Bool Source # (>=) :: StrictMaybe a -> StrictMaybe a -> Bool Source # max :: StrictMaybe a -> StrictMaybe a -> StrictMaybe a Source # min :: StrictMaybe a -> StrictMaybe a -> StrictMaybe a Source # | |||||
NoThunks (UpgradeConwayPParams StrictMaybe) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods noThunks :: Context -> UpgradeConwayPParams StrictMaybe -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> UpgradeConwayPParams StrictMaybe -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (UpgradeConwayPParams StrictMaybe) -> String # | |||||
NoThunks a => NoThunks (StrictMaybe a) | |||||
Defined in Data.Maybe.Strict Methods noThunks :: Context -> StrictMaybe a -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> StrictMaybe a -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (StrictMaybe a) -> String # | |||||
ToJSON (AlonzoPParams StrictMaybe AlonzoEra) | |||||
Defined in Cardano.Ledger.Alonzo.PParams Methods toJSON :: AlonzoPParams StrictMaybe AlonzoEra -> Value toEncoding :: AlonzoPParams StrictMaybe AlonzoEra -> Encoding toJSONList :: [AlonzoPParams StrictMaybe AlonzoEra] -> Value toEncodingList :: [AlonzoPParams StrictMaybe AlonzoEra] -> Encoding | |||||
(PParamsHKD StrictMaybe era ~ BabbagePParams StrictMaybe era, BabbageEraPParams era, ProtVerAtMost era 8) => ToJSON (BabbagePParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Babbage.PParams Methods toJSON :: BabbagePParams StrictMaybe era -> Value toEncoding :: BabbagePParams StrictMaybe era -> Encoding toJSONList :: [BabbagePParams StrictMaybe era] -> Value toEncodingList :: [BabbagePParams StrictMaybe era] -> Encoding omitField :: BabbagePParams StrictMaybe era -> Bool | |||||
(ConwayEraPParams era, PParamsHKD StrictMaybe era ~ ConwayPParams StrictMaybe era) => ToJSON (ConwayPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods toJSON :: ConwayPParams StrictMaybe era -> Value toEncoding :: ConwayPParams StrictMaybe era -> Encoding toJSONList :: [ConwayPParams StrictMaybe era] -> Value toEncodingList :: [ConwayPParams StrictMaybe era] -> Encoding omitField :: ConwayPParams StrictMaybe era -> Bool | |||||
(EraPParams era, PParamsHKD StrictMaybe era ~ ShelleyPParams StrictMaybe era, ProtVerAtMost era 4, ProtVerAtMost era 6, ProtVerAtMost era 8) => ToJSON (ShelleyPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Shelley.PParams Methods toJSON :: ShelleyPParams StrictMaybe era -> Value toEncoding :: ShelleyPParams StrictMaybe era -> Encoding toJSONList :: [ShelleyPParams StrictMaybe era] -> Value toEncodingList :: [ShelleyPParams StrictMaybe era] -> Encoding omitField :: ShelleyPParams StrictMaybe era -> Bool | |||||
Semigroup (AlonzoPParams StrictMaybe era) Source # | |||||
Defined in Cardano.Api.Internal.Orphans Methods (<>) :: AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era Source # sconcat :: NonEmpty (AlonzoPParams StrictMaybe era) -> AlonzoPParams StrictMaybe era Source # stimes :: Integral b => b -> AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era Source # | |||||
Semigroup (BabbagePParams StrictMaybe era) Source # | |||||
Defined in Cardano.Api.Internal.Orphans Methods (<>) :: BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era Source # sconcat :: NonEmpty (BabbagePParams StrictMaybe era) -> BabbagePParams StrictMaybe era Source # stimes :: Integral b => b -> BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era Source # | |||||
Semigroup (ConwayPParams StrictMaybe era) Source # | |||||
Defined in Cardano.Api.Internal.Orphans Methods (<>) :: ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era Source # sconcat :: NonEmpty (ConwayPParams StrictMaybe era) -> ConwayPParams StrictMaybe era Source # stimes :: Integral b => b -> ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era Source # | |||||
Semigroup (ShelleyPParams StrictMaybe era) Source # | |||||
Defined in Cardano.Api.Internal.Orphans Methods (<>) :: ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era Source # sconcat :: NonEmpty (ShelleyPParams StrictMaybe era) -> ShelleyPParams StrictMaybe era Source # stimes :: Integral b => b -> ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era Source # | |||||
Show (AlonzoPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Alonzo.PParams Methods showsPrec :: Int -> AlonzoPParams StrictMaybe era -> ShowS Source # show :: AlonzoPParams StrictMaybe era -> String Source # showList :: [AlonzoPParams StrictMaybe era] -> ShowS Source # | |||||
Show (BabbagePParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Babbage.PParams Methods showsPrec :: Int -> BabbagePParams StrictMaybe era -> ShowS Source # show :: BabbagePParams StrictMaybe era -> String Source # showList :: [BabbagePParams StrictMaybe era] -> ShowS Source # | |||||
Show (ConwayPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods showsPrec :: Int -> ConwayPParams StrictMaybe era -> ShowS Source # show :: ConwayPParams StrictMaybe era -> String Source # showList :: [ConwayPParams StrictMaybe era] -> ShowS Source # | |||||
Show (ShelleyPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Shelley.PParams Methods showsPrec :: Int -> ShelleyPParams StrictMaybe era -> ShowS Source # show :: ShelleyPParams StrictMaybe era -> String Source # showList :: [ShelleyPParams StrictMaybe era] -> ShowS Source # | |||||
Era era => FromCBOR (AlonzoPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Alonzo.PParams Methods fromCBOR :: Decoder s (AlonzoPParams StrictMaybe era) Source # label :: Proxy (AlonzoPParams StrictMaybe era) -> Text Source # | |||||
Era era => FromCBOR (BabbagePParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Babbage.PParams Methods fromCBOR :: Decoder s (BabbagePParams StrictMaybe era) Source # label :: Proxy (BabbagePParams StrictMaybe era) -> Text Source # | |||||
Era era => FromCBOR (ConwayPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods fromCBOR :: Decoder s (ConwayPParams StrictMaybe era) Source # label :: Proxy (ConwayPParams StrictMaybe era) -> Text Source # | |||||
Era era => FromCBOR (ShelleyPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Shelley.PParams Methods fromCBOR :: Decoder s (ShelleyPParams StrictMaybe era) Source # label :: Proxy (ShelleyPParams StrictMaybe era) -> Text Source # | |||||
Era era => ToCBOR (AlonzoPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Alonzo.PParams Methods toCBOR :: AlonzoPParams StrictMaybe era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (AlonzoPParams StrictMaybe era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [AlonzoPParams StrictMaybe era] -> Size Source # | |||||
Era era => ToCBOR (BabbagePParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Babbage.PParams Methods toCBOR :: BabbagePParams StrictMaybe era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (BabbagePParams StrictMaybe era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [BabbagePParams StrictMaybe era] -> Size Source # | |||||
Era era => ToCBOR (ConwayPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods toCBOR :: ConwayPParams StrictMaybe era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ConwayPParams StrictMaybe era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ConwayPParams StrictMaybe era] -> Size Source # | |||||
Era era => ToCBOR (ShelleyPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Shelley.PParams Methods toCBOR :: ShelleyPParams StrictMaybe era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyPParams StrictMaybe era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ShelleyPParams StrictMaybe era] -> Size Source # | |||||
Era era => DecCBOR (AlonzoPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Alonzo.PParams Methods decCBOR :: Decoder s (AlonzoPParams StrictMaybe era) Source # dropCBOR :: Proxy (AlonzoPParams StrictMaybe era) -> Decoder s () Source # label :: Proxy (AlonzoPParams StrictMaybe era) -> Text Source # | |||||
Era era => DecCBOR (BabbagePParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Babbage.PParams Methods decCBOR :: Decoder s (BabbagePParams StrictMaybe era) Source # dropCBOR :: Proxy (BabbagePParams StrictMaybe era) -> Decoder s () Source # label :: Proxy (BabbagePParams StrictMaybe era) -> Text Source # | |||||
Era era => DecCBOR (ConwayPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods decCBOR :: Decoder s (ConwayPParams StrictMaybe era) Source # dropCBOR :: Proxy (ConwayPParams StrictMaybe era) -> Decoder s () Source # label :: Proxy (ConwayPParams StrictMaybe era) -> Text Source # | |||||
Era era => DecCBOR (ShelleyPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Shelley.PParams Methods decCBOR :: Decoder s (ShelleyPParams StrictMaybe era) Source # dropCBOR :: Proxy (ShelleyPParams StrictMaybe era) -> Decoder s () Source # label :: Proxy (ShelleyPParams StrictMaybe era) -> Text Source # | |||||
Era era => EncCBOR (AlonzoPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Alonzo.PParams Methods encCBOR :: AlonzoPParams StrictMaybe era -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (AlonzoPParams StrictMaybe era) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [AlonzoPParams StrictMaybe era] -> Size Source # | |||||
Era era => EncCBOR (BabbagePParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Babbage.PParams Methods encCBOR :: BabbagePParams StrictMaybe era -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (BabbagePParams StrictMaybe era) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [BabbagePParams StrictMaybe era] -> Size Source # | |||||
Era era => EncCBOR (ConwayPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods encCBOR :: ConwayPParams StrictMaybe era -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (ConwayPParams StrictMaybe era) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ConwayPParams StrictMaybe era] -> Size Source # | |||||
Era era => EncCBOR (ShelleyPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Shelley.PParams Methods encCBOR :: ShelleyPParams StrictMaybe era -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (ShelleyPParams StrictMaybe era) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ShelleyPParams StrictMaybe era] -> Size Source # | |||||
NFData (AlonzoPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Alonzo.PParams Methods rnf :: AlonzoPParams StrictMaybe era -> () Source # | |||||
NFData (BabbagePParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Babbage.PParams Methods rnf :: BabbagePParams StrictMaybe era -> () Source # | |||||
NFData (ConwayPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods rnf :: ConwayPParams StrictMaybe era -> () Source # | |||||
NFData (ShelleyPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Shelley.PParams Methods rnf :: ShelleyPParams StrictMaybe era -> () Source # | |||||
Eq (AlonzoPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Alonzo.PParams Methods (==) :: AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era -> Bool Source # (/=) :: AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era -> Bool Source # | |||||
Eq (BabbagePParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Babbage.PParams Methods (==) :: BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era -> Bool Source # (/=) :: BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era -> Bool Source # | |||||
Eq (ConwayPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods (==) :: ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era -> Bool Source # (/=) :: ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era -> Bool Source # | |||||
Eq (ShelleyPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Shelley.PParams Methods (==) :: ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era -> Bool Source # (/=) :: ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era -> Bool Source # | |||||
Ord (AlonzoPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Alonzo.PParams Methods compare :: AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era -> Ordering Source # (<) :: AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era -> Bool Source # (<=) :: AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era -> Bool Source # (>) :: AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era -> Bool Source # (>=) :: AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era -> Bool Source # max :: AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era Source # min :: AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era Source # | |||||
Ord (BabbagePParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Babbage.PParams Methods compare :: BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era -> Ordering Source # (<) :: BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era -> Bool Source # (<=) :: BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era -> Bool Source # (>) :: BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era -> Bool Source # (>=) :: BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era -> Bool Source # max :: BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era Source # min :: BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era Source # | |||||
Ord (ConwayPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods compare :: ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era -> Ordering Source # (<) :: ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era -> Bool Source # (<=) :: ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era -> Bool Source # (>) :: ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era -> Bool Source # (>=) :: ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era -> Bool Source # max :: ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era Source # min :: ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era Source # | |||||
Ord (ShelleyPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Shelley.PParams Methods compare :: ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era -> Ordering Source # (<) :: ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era -> Bool Source # (<=) :: ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era -> Bool Source # (>) :: ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era -> Bool Source # (>=) :: ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era -> Bool Source # max :: ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era Source # min :: ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era Source # | |||||
NoThunks (AlonzoPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Alonzo.PParams Methods noThunks :: Context -> AlonzoPParams StrictMaybe era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> AlonzoPParams StrictMaybe era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (AlonzoPParams StrictMaybe era) -> String # | |||||
NoThunks (BabbagePParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Babbage.PParams Methods noThunks :: Context -> BabbagePParams StrictMaybe era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> BabbagePParams StrictMaybe era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (BabbagePParams StrictMaybe era) -> String # | |||||
NoThunks (ConwayPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods noThunks :: Context -> ConwayPParams StrictMaybe era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> ConwayPParams StrictMaybe era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (ConwayPParams StrictMaybe era) -> String # | |||||
NoThunks (ShelleyPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Shelley.PParams Methods noThunks :: Context -> ShelleyPParams StrictMaybe era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> ShelleyPParams StrictMaybe era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (ShelleyPParams StrictMaybe era) -> String # | |||||
(Typeable t, FromJSON a) => FromJSON (THKD t StrictMaybe a) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods parseJSON :: Value -> Parser (THKD t StrictMaybe a) parseJSONList :: Value -> Parser [THKD t StrictMaybe a] omittedField :: Maybe (THKD t StrictMaybe a) | |||||
(Typeable t, ToJSON a) => ToJSON (THKD t StrictMaybe a) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods toJSON :: THKD t StrictMaybe a -> Value toEncoding :: THKD t StrictMaybe a -> Encoding toJSONList :: [THKD t StrictMaybe a] -> Value toEncodingList :: [THKD t StrictMaybe a] -> Encoding omitField :: THKD t StrictMaybe a -> Bool | |||||
(Typeable t, DecCBOR a) => DecCBOR (THKD t StrictMaybe a) | |||||
(Typeable t, EncCBOR a) => EncCBOR (THKD t StrictMaybe a) | |||||
Defined in Cardano.Ledger.Conway.PParams | |||||
Updatable (K1 t x a) (K1 t (StrictMaybe x) u) | |||||
Defined in Cardano.Ledger.Core.PParams Methods applyUpdate :: K1 t x a -> K1 t (StrictMaybe x) u -> K1 t x a | |||||
type Rep (StrictMaybe a) | |||||
Defined in Data.Maybe.Strict type Rep (StrictMaybe a) = D1 ('MetaData "StrictMaybe" "Data.Maybe.Strict" "cardano-strict-containers-0.1.4.0-67294b19697ab3670f6f49836e20edc2687e8b3a67ebb79cfee434c04d46b529" 'False) (C1 ('MetaCons "SNothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SJust" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a))) |
showTimelock :: AllegraEraScript era => NativeScript era -> String Source #
fromEraCBOR :: (Era era, DecCBOR t) => Decoder s t Source #
Convert a type that implements DecCBOR
to plain Decoder
using the lowest
protocol version for the supplied era
This action should not be used for decoders that require access to original bytes, use
toPlainDecoder
instead.
ppMinFeeAL :: EraPParams era => Lens' (PParams era) Coin Source #
The linear factor for the minimum fee calculation
ppMinUTxOValueL :: (EraPParams era, ProtVerAtMost era 4) => Lens' (PParams era) Coin Source #
Minimum UTxO value
pattern RegPoolTxCert :: EraTxCert era => PoolParams -> TxCert era Source #
castSafeHash :: SafeHash i -> SafeHash j Source #
To change the index parameter of SafeHash (which is a phantom type) use castSafeHash
fromVRFVerKeyHash :: forall (r :: KeyRoleVRF) v. VRFVerKeyHash r -> Hash HASH (VerKeyVRF v) Source #
toVRFVerKeyHash :: forall v (r :: KeyRoleVRF). Hash HASH (VerKeyVRF v) -> VRFVerKeyHash r Source #
pattern DelegStakeTxCert :: ShelleyEraTxCert era => StakeCredential -> KeyHash 'StakePool -> TxCert era Source #
pattern GenesisDelegTxCert :: (ShelleyEraTxCert era, ProtVerAtMost era 8) => KeyHash 'Genesis -> KeyHash 'GenesisDelegate -> VRFVerKeyHash 'GenDelegVRF -> TxCert era Source #
pattern MirTxCert :: (ShelleyEraTxCert era, ProtVerAtMost era 8) => MIRCert -> TxCert era Source #
pattern RegTxCert :: ShelleyEraTxCert era => StakeCredential -> TxCert era Source #
pattern UnRegTxCert :: ShelleyEraTxCert era => StakeCredential -> TxCert era Source #
type family Script era = (r :: Type) | r -> era Source #
Scripts which may lock transaction outputs in this era
Instances
type Script AllegraEra | |
Defined in Cardano.Ledger.Allegra.Scripts | |
type Script AlonzoEra | |
Defined in Cardano.Ledger.Alonzo.Scripts | |
type Script BabbageEra | |
Defined in Cardano.Ledger.Babbage.Scripts | |
type Script ConwayEra | |
Defined in Cardano.Ledger.Conway.Scripts | |
type Script MaryEra | |
Defined in Cardano.Ledger.Mary.Scripts | |
type Script ShelleyEra | |
Defined in Cardano.Ledger.Shelley.Scripts |
getNativeScript :: EraScript era => Script era -> Maybe (NativeScript era) Source #
type family Script era = (r :: Type) | r -> era Source #
Scripts which may lock transaction outputs in this era
Instances
type Script AllegraEra | |
Defined in Cardano.Ledger.Allegra.Scripts | |
type Script AlonzoEra | |
Defined in Cardano.Ledger.Alonzo.Scripts | |
type Script BabbageEra | |
Defined in Cardano.Ledger.Babbage.Scripts | |
type Script ConwayEra | |
Defined in Cardano.Ledger.Conway.Scripts | |
type Script MaryEra | |
Defined in Cardano.Ledger.Mary.Scripts | |
type Script ShelleyEra | |
Defined in Cardano.Ledger.Shelley.Scripts |
class (Val (Value era), ToJSON (TxOut era), DecCBOR (Value era), DecCBOR (CompactForm (Value era)), MemPack (CompactForm (Value era)), EncCBOR (Value era), ToCBOR (TxOut era), EncCBOR (TxOut era), DecCBOR (TxOut era), DecShareCBOR (TxOut era), Share (TxOut era) ~ Interns (Credential 'Staking), NoThunks (TxOut era), NFData (TxOut era), Show (TxOut era), Eq (TxOut era), MemPack (TxOut era), EraPParams era) => EraTxOut era Source #
Abstract interface into specific fields of a TxOut
Minimal complete definition
mkBasicTxOut, upgradeTxOut, valueEitherTxOutL, addrEitherTxOutL, (getMinCoinSizedTxOut | getMinCoinTxOut)
class (EraScript era, Eq (TxWits era), EqRaw (TxWits era), Show (TxWits era), Monoid (TxWits era), NoThunks (TxWits era), ToCBOR (TxWits era), EncCBOR (TxWits era), DecCBOR (Annotator (TxWits era))) => EraTxWits era where Source #
A collection of witnesses in a Tx
Minimal complete definition
Methods
mkBasicTxWits :: TxWits era Source #
addrTxWitsL :: Lens' (TxWits era) (Set (WitVKey 'Witness)) Source #
bootAddrTxWitsL :: Lens' (TxWits era) (Set BootstrapWitness) Source #
scriptTxWitsL :: Lens' (TxWits era) (Map ScriptHash (Script era)) Source #
upgradeTxWits :: TxWits (PreviousEra era) -> TxWits era Source #
type family TxWits era = (r :: Type) | r -> era Source #
Instances
type TxWits AllegraEra | |
Defined in Cardano.Ledger.Allegra.TxWits | |
type TxWits AlonzoEra | |
Defined in Cardano.Ledger.Alonzo.TxWits | |
type TxWits BabbageEra | |
Defined in Cardano.Ledger.Babbage.TxWits | |
type TxWits ConwayEra | |
Defined in Cardano.Ledger.Conway.TxWits | |
type TxWits MaryEra | |
Defined in Cardano.Ledger.Mary.TxWits | |
type TxWits ShelleyEra | |
Defined in Cardano.Ledger.Shelley.TxWits |
type family Value era Source #
A value is something which quantifies a transaction output.
Instances
type Value AllegraEra | |
Defined in Cardano.Ledger.Allegra.Era | |
type Value AlonzoEra | |
Defined in Cardano.Ledger.Alonzo.Era | |
type Value BabbageEra | |
Defined in Cardano.Ledger.Babbage.Era | |
type Value ConwayEra | |
Defined in Cardano.Ledger.Conway.Era | |
type Value MaryEra | |
Defined in Cardano.Ledger.Mary.Era | |
type Value ShelleyEra | |
Defined in Cardano.Ledger.Shelley.Era |
class (Typeable era, KnownNat (ProtVerLow era), KnownNat (ProtVerHigh era), ProtVerLow era <= ProtVerHigh era, MinVersion <= ProtVerLow era, MinVersion <= ProtVerHigh era, CmpNat (ProtVerLow era) MaxVersion ~ 'LT, CmpNat (ProtVerHigh era) MaxVersion ~ 'LT, ProtVerLow era <= MaxVersion, ProtVerHigh era <= MaxVersion) => Era era where Source #
Associated Types
type PreviousEra era = (r :: Type) | r -> era Source #
Map an era to its predecessor.
For example:
type instance PreviousEra (AllegraEra c) = ShelleyEra c
type ProtVerLow era :: Nat Source #
Lowest major protocol version for this era
type ProtVerHigh era :: Nat Source #
Highest major protocol version for this era. By default se to ProtVerLow
type ProtVerHigh era = ProtVerLow era
Methods
Textual name of the current era.
Designed to be used with TypeApplications
:
>>>
eraName @ByronEra
Byron
Instances
Era AllegraEra | |||||||||||||
Defined in Cardano.Ledger.Allegra.Era Associated Types
| |||||||||||||
Era AlonzoEra | |||||||||||||
Defined in Cardano.Ledger.Alonzo.Era Associated Types
| |||||||||||||
Era BabbageEra | |||||||||||||
Defined in Cardano.Ledger.Babbage.Era Associated Types
| |||||||||||||
Era ConwayEra | |||||||||||||
Defined in Cardano.Ledger.Conway.Era Associated Types
| |||||||||||||
Era ByronEra | |||||||||||||
Defined in Cardano.Ledger.Core.Era Associated Types
| |||||||||||||
Era MaryEra | |||||||||||||
Defined in Cardano.Ledger.Mary.Era Associated Types
| |||||||||||||
Era ShelleyEra | |||||||||||||
Defined in Cardano.Ledger.Shelley.Era Associated Types
|
type family PreviousEra era = (r :: Type) | r -> era Source #
Map an era to its predecessor.
For example:
type instance PreviousEra (AllegraEra c) = ShelleyEra c
Instances
type PreviousEra AllegraEra | |
Defined in Cardano.Ledger.Allegra.Era | |
type PreviousEra AlonzoEra | |
Defined in Cardano.Ledger.Alonzo.Era | |
type PreviousEra BabbageEra | |
Defined in Cardano.Ledger.Babbage.Era | |
type PreviousEra ConwayEra | |
Defined in Cardano.Ledger.Conway.Era | |
type PreviousEra ByronEra | |
Defined in Cardano.Ledger.Core.Era | |
type PreviousEra MaryEra | |
Defined in Cardano.Ledger.Mary.Era | |
type PreviousEra ShelleyEra | |
Defined in Cardano.Ledger.Shelley.Era |
type family ProtVerHigh era :: Nat Source #
Highest major protocol version for this era. By default se to ProtVerLow
Instances
type ProtVerHigh AllegraEra | |
Defined in Cardano.Ledger.Allegra.Era | |
type ProtVerHigh AlonzoEra | |
Defined in Cardano.Ledger.Alonzo.Era | |
type ProtVerHigh BabbageEra | |
Defined in Cardano.Ledger.Babbage.Era | |
type ProtVerHigh ConwayEra | |
Defined in Cardano.Ledger.Conway.Era | |
type ProtVerHigh ByronEra | |
Defined in Cardano.Ledger.Core.Era | |
type ProtVerHigh MaryEra | |
Defined in Cardano.Ledger.Mary.Era | |
type ProtVerHigh ShelleyEra | |
Defined in Cardano.Ledger.Shelley.Era |
type family ProtVerLow era :: Nat Source #
Lowest major protocol version for this era
Instances
type ProtVerLow AllegraEra | |
Defined in Cardano.Ledger.Allegra.Era | |
type ProtVerLow AlonzoEra | |
Defined in Cardano.Ledger.Alonzo.Era | |
type ProtVerLow BabbageEra | |
Defined in Cardano.Ledger.Babbage.Era | |
type ProtVerLow ConwayEra | |
Defined in Cardano.Ledger.Conway.Era | |
type ProtVerLow ByronEra | |
Defined in Cardano.Ledger.Core.Era | |
type ProtVerLow MaryEra | |
Defined in Cardano.Ledger.Mary.Era | |
type ProtVerLow ShelleyEra | |
Defined in Cardano.Ledger.Shelley.Era |
class (Era era, Eq (PParamsHKD Identity era), Ord (PParamsHKD Identity era), Show (PParamsHKD Identity era), NFData (PParamsHKD Identity era), EncCBOR (PParamsHKD Identity era), DecCBOR (PParamsHKD Identity era), ToCBOR (PParamsHKD Identity era), FromCBOR (PParamsHKD Identity era), NoThunks (PParamsHKD Identity era), ToJSON (PParamsHKD Identity era), FromJSON (PParamsHKD Identity era), Eq (PParamsHKD StrictMaybe era), Ord (PParamsHKD StrictMaybe era), Show (PParamsHKD StrictMaybe era), NFData (PParamsHKD StrictMaybe era), EncCBOR (PParamsHKD StrictMaybe era), DecCBOR (PParamsHKD StrictMaybe era), ToCBOR (PParamsHKD StrictMaybe era), FromCBOR (PParamsHKD StrictMaybe era), NoThunks (PParamsHKD StrictMaybe era), ToJSON (PParamsHKD StrictMaybe era)) => EraPParams era where Source #
Minimal complete definition
emptyPParamsIdentity, emptyPParamsStrictMaybe, upgradePParamsHKD, downgradePParamsHKD, hkdMinFeeAL, hkdMinFeeBL, hkdMaxBBSizeL, hkdMaxTxSizeL, hkdMaxBHSizeL, hkdKeyDepositL, hkdPoolDepositL, hkdEMaxL, hkdNOptL, hkdA0L, hkdRhoL, hkdTauL, hkdDL, hkdExtraEntropyL, hkdProtocolVersionL, hkdMinUTxOValueL, hkdMinPoolCostL
Associated Types
type PParamsHKD (f :: Type -> Type) era = (r :: Type) | r -> era Source #
Protocol parameters where the fields are represented with a HKD
type UpgradePParams (f :: Type -> Type) era Source #
type DowngradePParams (f :: Type -> Type) era Source #
Methods
applyPPUpdates :: PParams era -> PParamsUpdate era -> PParams era Source #
Applies a protocol parameters update
default applyPPUpdates :: (Generic (PParamsHKD Identity era), Generic (PParamsHKD StrictMaybe era), Updatable (Rep (PParamsHKD Identity era) a) (Rep (PParamsHKD StrictMaybe era) u)) => PParams era -> PParamsUpdate era -> PParams era Source #
emptyPParamsIdentity :: PParamsHKD Identity era Source #
emptyPParamsStrictMaybe :: PParamsHKD StrictMaybe era Source #
upgradePParamsHKD :: forall (f :: Type -> Type). (HKDApplicative f, EraPParams (PreviousEra era)) => UpgradePParams f era -> PParamsHKD f (PreviousEra era) -> PParamsHKD f era Source #
Upgrade PParams from previous era to the current one
downgradePParamsHKD :: forall (f :: Type -> Type). (HKDFunctor f, EraPParams (PreviousEra era)) => DowngradePParams f era -> PParamsHKD f era -> PParamsHKD f (PreviousEra era) Source #
Downgrade PParams from the current era to the previous one
hkdMinFeeAL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f Coin) Source #
The linear factor for the minimum fee calculation
hkdMinFeeBL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f Coin) Source #
The constant factor for the minimum fee calculation
hkdMaxBBSizeL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f Word32) Source #
Maximal block body size
hkdMaxTxSizeL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f Word32) Source #
Maximal transaction size
hkdMaxBHSizeL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f Word16) Source #
Maximal block header size
hkdKeyDepositL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f Coin) Source #
The amount of a key registration deposit
hkdPoolDepositL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f Coin) Source #
The amount of a pool registration deposit
hkdEMaxL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f EpochInterval) Source #
epoch bound on pool retirement
hkdNOptL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f Word16) Source #
Desired number of pools
hkdA0L :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f NonNegativeInterval) Source #
Pool influence
hkdRhoL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f UnitInterval) Source #
Monetary expansion
hkdTauL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f UnitInterval) Source #
Treasury expansion
hkdDL :: forall (f :: Type -> Type). (HKDFunctor f, ProtVerAtMost era 6) => Lens' (PParamsHKD f era) (HKD f UnitInterval) Source #
Decentralization parameter
ppDG :: SimpleGetter (PParams era) UnitInterval Source #
Decentralization parameter getter
default ppDG :: ProtVerAtMost era 6 => SimpleGetter (PParams era) UnitInterval Source #
hkdExtraEntropyL :: forall (f :: Type -> Type). (HKDFunctor f, ProtVerAtMost era 6) => Lens' (PParamsHKD f era) (HKD f Nonce) Source #
Extra entropy
hkdProtocolVersionL :: forall (f :: Type -> Type). (HKDFunctor f, ProtVerAtMost era 8) => Lens' (PParamsHKD f era) (HKD f ProtVer) Source #
Protocol version
ppProtocolVersionL :: Lens' (PParams era) ProtVer Source #
default ppProtocolVersionL :: ProtVerAtMost era 8 => Lens' (PParams era) ProtVer Source #
ppuProtocolVersionL :: Lens' (PParamsUpdate era) (StrictMaybe ProtVer) Source #
PParamsUpdate Protocol version
hkdMinUTxOValueL :: forall (f :: Type -> Type). (HKDFunctor f, ProtVerAtMost era 4) => Lens' (PParamsHKD f era) (HKD f Coin) Source #
Minimum UTxO value
hkdMinPoolCostL :: forall (f :: Type -> Type). HKDFunctor f => Lens' (PParamsHKD f era) (HKD f Coin) Source #
Minimum Stake Pool Cost
type family DowngradePParams (f :: Type -> Type) era Source #
Instances
type DowngradePParams f AllegraEra | |
Defined in Cardano.Ledger.Allegra.PParams | |
type DowngradePParams f AlonzoEra | |
Defined in Cardano.Ledger.Alonzo.PParams | |
type DowngradePParams f BabbageEra | |
Defined in Cardano.Ledger.Babbage.PParams | |
type DowngradePParams f ConwayEra | |
Defined in Cardano.Ledger.Conway.PParams | |
type DowngradePParams f MaryEra | |
Defined in Cardano.Ledger.Mary.PParams | |
type DowngradePParams f ShelleyEra | |
Defined in Cardano.Ledger.Shelley.PParams |
type family PParamsHKD (f :: Type -> Type) era = (r :: Type) | r -> era Source #
Protocol parameters where the fields are represented with a HKD
Instances
type PParamsHKD f AllegraEra | |
Defined in Cardano.Ledger.Allegra.PParams | |
type PParamsHKD f AlonzoEra | |
Defined in Cardano.Ledger.Alonzo.PParams | |
type PParamsHKD f BabbageEra | |
Defined in Cardano.Ledger.Babbage.PParams | |
type PParamsHKD f ConwayEra | |
Defined in Cardano.Ledger.Conway.PParams | |
type PParamsHKD f MaryEra | |
Defined in Cardano.Ledger.Mary.PParams | |
type PParamsHKD f ShelleyEra | |
Defined in Cardano.Ledger.Shelley.PParams |
type family UpgradePParams (f :: Type -> Type) era Source #
Instances
type UpgradePParams f AllegraEra | |
Defined in Cardano.Ledger.Allegra.PParams | |
type UpgradePParams f AlonzoEra | |
Defined in Cardano.Ledger.Alonzo.PParams | |
type UpgradePParams f BabbageEra | |
Defined in Cardano.Ledger.Babbage.PParams | |
type UpgradePParams f ConwayEra | |
Defined in Cardano.Ledger.Conway.PParams | |
type UpgradePParams f MaryEra | |
Defined in Cardano.Ledger.Mary.PParams | |
type UpgradePParams f ShelleyEra | |
Defined in Cardano.Ledger.Shelley.PParams |
data PParamsUpdate era Source #
The type of updates to Protocol parameters
Instances
FromJSON (PParamsHKD StrictMaybe era) => FromJSON (PParamsUpdate era) | |||||
Defined in Cardano.Ledger.Core.PParams Methods parseJSON :: Value -> Parser (PParamsUpdate era) parseJSONList :: Value -> Parser [PParamsUpdate era] omittedField :: Maybe (PParamsUpdate era) | |||||
ToJSON (PParamsHKD StrictMaybe era) => ToJSON (PParamsUpdate era) | |||||
Defined in Cardano.Ledger.Core.PParams Methods toJSON :: PParamsUpdate era -> Value toEncoding :: PParamsUpdate era -> Encoding toJSONList :: [PParamsUpdate era] -> Value toEncodingList :: [PParamsUpdate era] -> Encoding omitField :: PParamsUpdate era -> Bool | |||||
Generic (PParamsUpdate era) | |||||
Defined in Cardano.Ledger.Core.PParams Associated Types
Methods from :: PParamsUpdate era -> Rep (PParamsUpdate era) x Source # to :: Rep (PParamsUpdate era) x -> PParamsUpdate era Source # | |||||
Show (PParamsHKD StrictMaybe era) => Show (PParamsUpdate era) | |||||
Defined in Cardano.Ledger.Core.PParams | |||||
(Typeable era, FromCBOR (PParamsHKD StrictMaybe era)) => FromCBOR (PParamsUpdate era) | |||||
Defined in Cardano.Ledger.Core.PParams | |||||
(Typeable era, ToCBOR (PParamsHKD StrictMaybe era)) => ToCBOR (PParamsUpdate era) | |||||
Defined in Cardano.Ledger.Core.PParams Methods toCBOR :: PParamsUpdate era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (PParamsUpdate era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [PParamsUpdate era] -> Size Source # | |||||
(Typeable era, DecCBOR (PParamsHKD StrictMaybe era)) => DecCBOR (PParamsUpdate era) | |||||
Defined in Cardano.Ledger.Core.PParams | |||||
(Typeable era, EncCBOR (PParamsHKD StrictMaybe era)) => EncCBOR (PParamsUpdate era) | |||||
Defined in Cardano.Ledger.Core.PParams Methods encCBOR :: PParamsUpdate era -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (PParamsUpdate era) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [PParamsUpdate era] -> Size Source # | |||||
EraPParams era => Default (PParamsUpdate era) | |||||
Defined in Cardano.Ledger.Core.PParams Methods def :: PParamsUpdate era # | |||||
NFData (PParamsHKD StrictMaybe era) => NFData (PParamsUpdate era) | |||||
Defined in Cardano.Ledger.Core.PParams Methods rnf :: PParamsUpdate era -> () Source # | |||||
Eq (PParamsHKD StrictMaybe era) => Eq (PParamsUpdate era) | |||||
Defined in Cardano.Ledger.Core.PParams Methods (==) :: PParamsUpdate era -> PParamsUpdate era -> Bool Source # (/=) :: PParamsUpdate era -> PParamsUpdate era -> Bool Source # | |||||
Ord (PParamsHKD StrictMaybe era) => Ord (PParamsUpdate era) | |||||
Defined in Cardano.Ledger.Core.PParams Methods compare :: PParamsUpdate era -> PParamsUpdate era -> Ordering Source # (<) :: PParamsUpdate era -> PParamsUpdate era -> Bool Source # (<=) :: PParamsUpdate era -> PParamsUpdate era -> Bool Source # (>) :: PParamsUpdate era -> PParamsUpdate era -> Bool Source # (>=) :: PParamsUpdate era -> PParamsUpdate era -> Bool Source # max :: PParamsUpdate era -> PParamsUpdate era -> PParamsUpdate era Source # min :: PParamsUpdate era -> PParamsUpdate era -> PParamsUpdate era Source # | |||||
NoThunks (PParamsHKD StrictMaybe era) => NoThunks (PParamsUpdate era) | |||||
Defined in Cardano.Ledger.Core.PParams Methods noThunks :: Context -> PParamsUpdate era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> PParamsUpdate era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (PParamsUpdate era) -> String # | |||||
type TranslationError AllegraEra PParamsUpdate | |||||
Defined in Cardano.Ledger.Allegra.Translation | |||||
type TranslationError MaryEra PParamsUpdate | |||||
Defined in Cardano.Ledger.Mary.Translation | |||||
type Rep (PParamsUpdate era) | |||||
Defined in Cardano.Ledger.Core.PParams type Rep (PParamsUpdate era) = D1 ('MetaData "PParamsUpdate" "Cardano.Ledger.Core.PParams" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'True) (C1 ('MetaCons "PParamsUpdate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PParamsHKD StrictMaybe era)))) |
class (Era era, ToJSON (TxCert era), DecCBOR (TxCert era), EncCBOR (TxCert era), ToCBOR (TxCert era), FromCBOR (TxCert era), NoThunks (TxCert era), NFData (TxCert era), Show (TxCert era), Ord (TxCert era), Eq (TxCert era)) => EraTxCert era where Source #
Associated Types
type TxCert era = (r :: Type) | r -> era Source #
type TxCertUpgradeError era Source #
type TxCertUpgradeError era = Void
Methods
upgradeTxCert :: TxCert (PreviousEra era) -> Either (TxCertUpgradeError era) (TxCert era) Source #
Every era, except Shelley, must be able to upgrade a TxCert
from a previous
era. However, not all certificates can be upgraded, because some eras lose some of
the certificates, thus return type is an Either
. Eg. from Babbage to Conway: MIR
and Genesis certificates were removed.
getVKeyWitnessTxCert :: TxCert era -> Maybe (KeyHash 'Witness) Source #
Return a witness key whenever a certificate requires one
getScriptWitnessTxCert :: TxCert era -> Maybe ScriptHash Source #
Return a ScriptHash for certificate types that require a witness
mkRegPoolTxCert :: PoolParams -> TxCert era Source #
getRegPoolTxCert :: TxCert era -> Maybe PoolParams Source #
mkRetirePoolTxCert :: KeyHash 'StakePool -> EpochNo -> TxCert era Source #
getRetirePoolTxCert :: TxCert era -> Maybe (KeyHash 'StakePool, EpochNo) Source #
lookupRegStakeTxCert :: TxCert era -> Maybe (Credential 'Staking) Source #
Extract staking credential from any certificate that can register such credential
lookupUnRegStakeTxCert :: TxCert era -> Maybe (Credential 'Staking) Source #
Extract staking credential from any certificate that can unregister such credential
getTotalDepositsTxCerts Source #
Arguments
:: Foldable f | |
=> PParams era | |
-> (KeyHash 'StakePool -> Bool) | Check whether stake pool is registered or not |
-> f (TxCert era) | |
-> Coin |
Compute the total deposits from a list of certificates.
getTotalRefundsTxCerts Source #
Arguments
:: Foldable f | |
=> PParams era | |
-> (Credential 'Staking -> Maybe Coin) | Lookup current deposit for Staking credential if one is registered |
-> (Credential 'DRepRole -> Maybe Coin) | Lookup current deposit for DRep credential if one is registered |
-> f (TxCert era) | |
-> Coin |
Compute the total refunds from a list of certificates.
type family TxCert era = (r :: Type) | r -> era Source #
Instances
type TxCert AllegraEra | |
Defined in Cardano.Ledger.Allegra.TxCert | |
type TxCert AlonzoEra | |
Defined in Cardano.Ledger.Alonzo.TxCert | |
type TxCert BabbageEra | |
Defined in Cardano.Ledger.Babbage.TxCert | |
type TxCert ConwayEra | |
Defined in Cardano.Ledger.Conway.TxCert | |
type TxCert MaryEra | |
Defined in Cardano.Ledger.Mary.TxCert | |
type TxCert ShelleyEra | |
Defined in Cardano.Ledger.Shelley.TxCert |
type family TxCertUpgradeError era Source #
Instances
type TxCertUpgradeError AllegraEra | |
Defined in Cardano.Ledger.Allegra.TxCert | |
type TxCertUpgradeError AlonzoEra | |
Defined in Cardano.Ledger.Alonzo.TxCert | |
type TxCertUpgradeError BabbageEra | |
Defined in Cardano.Ledger.Babbage.TxCert | |
type TxCertUpgradeError ConwayEra | |
Defined in Cardano.Ledger.Conway.TxCert | |
type TxCertUpgradeError MaryEra | |
Defined in Cardano.Ledger.Mary.TxCert | |
type TxCertUpgradeError ShelleyEra | |
Defined in Cardano.Ledger.Shelley.TxCert |
Constructors
RegPool !PoolParams | A stake pool registration certificate. |
RetirePool !(KeyHash 'StakePool) !EpochNo | A stake pool retirement certificate. |
Instances
ToJSON PoolCert | |||||
Defined in Cardano.Ledger.Core.TxCert Methods toEncoding :: PoolCert -> Encoding toJSONList :: [PoolCert] -> Value toEncodingList :: [PoolCert] -> Encoding | |||||
Generic PoolCert | |||||
Defined in Cardano.Ledger.Core.TxCert Associated Types
| |||||
Show PoolCert | |||||
EncCBOR PoolCert | |||||
NFData PoolCert | |||||
Defined in Cardano.Ledger.Core.TxCert | |||||
Eq PoolCert | |||||
Ord PoolCert | |||||
Defined in Cardano.Ledger.Core.TxCert | |||||
NoThunks PoolCert | |||||
type Rep PoolCert | |||||
Defined in Cardano.Ledger.Core.TxCert type Rep PoolCert = D1 ('MetaData "PoolCert" "Cardano.Ledger.Core.TxCert" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'False) (C1 ('MetaCons "RegPool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PoolParams)) :+: C1 ('MetaCons "RetirePool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 EpochNo))) |
type ADDRHASH = Blake2b_224 Source #
Hashing algorithm used for hashing cryptographic keys and scripts. As the type synonym name alludes, this is the hashing algorithm used for addresses.
newtype KeyHash (r :: KeyRole) Source #
Discriminated hash of public Key
Instances
HasKeyRole KeyHash | |
Defined in Cardano.Ledger.Hashes | |
FromJSON (KeyHash r) | |
Defined in Cardano.Ledger.Hashes Methods parseJSON :: Value -> Parser (KeyHash r) parseJSONList :: Value -> Parser [KeyHash r] omittedField :: Maybe (KeyHash r) | |
FromJSONKey (KeyHash r) | |
Defined in Cardano.Ledger.Hashes Methods fromJSONKey :: FromJSONKeyFunction (KeyHash r) fromJSONKeyList :: FromJSONKeyFunction [KeyHash r] | |
ToJSON (KeyHash r) | |
Defined in Cardano.Ledger.Hashes Methods toEncoding :: KeyHash r -> Encoding toJSONList :: [KeyHash r] -> Value toEncodingList :: [KeyHash r] -> Encoding | |
ToJSONKey (KeyHash r) | |
Defined in Cardano.Ledger.Hashes | |
Generic (KeyHash r) | |
Show (KeyHash r) | |
Typeable r => FromCBOR (KeyHash r) | |
Typeable r => ToCBOR (KeyHash r) | |
Typeable r => DecCBOR (KeyHash r) | |
Typeable r => EncCBOR (KeyHash r) | |
MakeStakeReference (KeyHash 'Staking) | |
Defined in Test.Cardano.Ledger.Core.KeyPair Methods mkStakeRef :: KeyHash 'Staking -> StakeReference | |
MakeStakeReference (Maybe (KeyHash 'Staking)) | |
Defined in Test.Cardano.Ledger.Core.KeyPair Methods mkStakeRef :: Maybe (KeyHash 'Staking) -> StakeReference | |
Default (KeyHash r) | |
Defined in Cardano.Ledger.Hashes | |
NFData (KeyHash r) | |
Defined in Cardano.Ledger.Hashes | |
Eq (KeyHash r) | |
Ord (KeyHash r) | |
Defined in Cardano.Ledger.Hashes | |
MemPack (KeyHash r) | |
Defined in Cardano.Ledger.Hashes | |
NoThunks (KeyHash r) | |
MakeCredential (KeyHash r) r | |
Defined in Test.Cardano.Ledger.Core.KeyPair Methods mkCredential :: KeyHash r -> Credential r | |
type Rep (KeyHash r) | |
Defined in Cardano.Ledger.Hashes |
A SafeHash
is a hash of something that is safe to hash. Such types store their own
serialisation bytes. The prime example is (
, but other examples are
things that consist of only ByteStrings (i.e. they are their own serialization) or for
some other reason store their original bytes.MemoBytes
t)
We do NOT export the constructor SafeHash
, but instead export other functions such as
hashAnnotated
and extractHash
which have constraints that limit their application
to types which preserve their original serialization bytes.
Instances
FromJSON (SafeHash i) | |
Defined in Cardano.Ledger.Hashes Methods parseJSON :: Value -> Parser (SafeHash i) parseJSONList :: Value -> Parser [SafeHash i] omittedField :: Maybe (SafeHash i) | |
ToJSON (SafeHash i) | |
Defined in Cardano.Ledger.Hashes Methods toEncoding :: SafeHash i -> Encoding toJSONList :: [SafeHash i] -> Value toEncodingList :: [SafeHash i] -> Encoding | |
Show (SafeHash i) | |
Typeable i => FromCBOR (SafeHash i) | |
Typeable i => ToCBOR (SafeHash i) | |
Typeable i => DecCBOR (SafeHash i) | |
Typeable i => EncCBOR (SafeHash i) | |
SafeToHash (SafeHash i) | |
Defined in Cardano.Ledger.Hashes Methods originalBytes :: SafeHash i -> ByteString Source # originalBytesSize :: SafeHash i -> Int Source # makeHashWithExplicitProxys :: Proxy i0 -> SafeHash i -> SafeHash i0 Source # | |
Default (SafeHash i) | |
Defined in Cardano.Ledger.Hashes | |
NFData (SafeHash i) | |
Defined in Cardano.Ledger.Hashes | |
Eq (SafeHash i) | |
Ord (SafeHash i) | |
Defined in Cardano.Ledger.Hashes Methods compare :: SafeHash i -> SafeHash i -> Ordering Source # (<) :: SafeHash i -> SafeHash i -> Bool Source # (<=) :: SafeHash i -> SafeHash i -> Bool Source # (>) :: SafeHash i -> SafeHash i -> Bool Source # (>=) :: SafeHash i -> SafeHash i -> Bool Source # | |
HeapWords (SafeHash i) | |
Defined in Cardano.Ledger.Hashes | |
MemPack (SafeHash i) | |
Defined in Cardano.Ledger.Hashes | |
NoThunks (SafeHash i) | |
The role of a key.
All key roles are fixed and unique, except for the Witness
role. In particular,
keys can be cast to a Witness
role with the help of asWitness
, because same witness
can be valid for many roles.
In fact, it is perfectly allowable for a key to be used in many roles by the end user; there is nothing prohibiting somebody using the same underlying key or a script as their payment and staking credential, as well as the key for their stake pool. However, in the ledger code mixing up keys with different roles could be catastrophic, that is why we have this separation.
class (EraPParams era, Eq (GovState era), Show (GovState era), NoThunks (GovState era), NFData (GovState era), EncCBOR (GovState era), DecCBOR (GovState era), DecShareCBOR (GovState era), Share (GovState era) ~ (Interns (Credential 'Staking), Interns (KeyHash 'StakePool), Interns (Credential 'DRepRole), Interns (Credential 'HotCommitteeRole)), ToCBOR (GovState era), FromCBOR (GovState era), Default (GovState era), ToJSON (GovState era)) => EraGov era Source #
Minimal complete definition
curPParamsGovStateL, prevPParamsGovStateL, futurePParamsGovStateL, obligationGovState
type family GovState era = (r :: Type) | r -> era Source #
Instances
type GovState AllegraEra | |
Defined in Cardano.Ledger.Allegra.PParams | |
type GovState AlonzoEra | |
Defined in Cardano.Ledger.Alonzo.PParams | |
type GovState BabbageEra | |
Defined in Cardano.Ledger.Babbage.PParams | |
type GovState ConwayEra | |
Defined in Cardano.Ledger.Conway.Governance | |
type GovState MaryEra | |
Defined in Cardano.Ledger.Mary.PParams | |
type GovState ShelleyEra | |
Defined in Cardano.Ledger.Shelley.Governance |
Move instantaneous rewards certificate
Constructors
MIRCert | |
Fields
|
Instances
ToJSON MIRCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods toEncoding :: MIRCert -> Encoding toJSONList :: [MIRCert] -> Value toEncodingList :: [MIRCert] -> Encoding | |||||
Generic MIRCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert Associated Types
| |||||
Show MIRCert | |||||
DecCBOR MIRCert | |||||
EncCBOR MIRCert | |||||
NFData MIRCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert | |||||
Eq MIRCert | |||||
Ord MIRCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert | |||||
NoThunks MIRCert | |||||
type Rep MIRCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert type Rep MIRCert = D1 ('MetaData "MIRCert" "Cardano.Ledger.Shelley.TxCert" "cardano-ledger-shelley-1.16.0.0-66390a9322bb0fb64b3f0442ebc385a2f8e5928f157dc0d1b8e0fcc9dabbabc0" 'False) (C1 ('MetaCons "MIRCert" 'PrefixI 'True) (S1 ('MetaSel ('Just "mirPot") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MIRPot) :*: S1 ('MetaSel ('Just "mirRewards") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MIRTarget))) |
Constructors
ReservesMIR | |
TreasuryMIR |
Instances
ToJSON MIRPot | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods toEncoding :: MIRPot -> Encoding toJSONList :: [MIRPot] -> Value toEncodingList :: [MIRPot] -> Encoding | |||||
Bounded MIRPot | |||||
Enum MIRPot | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods succ :: MIRPot -> MIRPot Source # pred :: MIRPot -> MIRPot Source # toEnum :: Int -> MIRPot Source # fromEnum :: MIRPot -> Int Source # enumFrom :: MIRPot -> [MIRPot] Source # enumFromThen :: MIRPot -> MIRPot -> [MIRPot] Source # enumFromTo :: MIRPot -> MIRPot -> [MIRPot] Source # enumFromThenTo :: MIRPot -> MIRPot -> MIRPot -> [MIRPot] Source # | |||||
Generic MIRPot | |||||
Defined in Cardano.Ledger.Shelley.TxCert Associated Types
| |||||
Show MIRPot | |||||
DecCBOR MIRPot | |||||
EncCBOR MIRPot | |||||
NFData MIRPot | |||||
Defined in Cardano.Ledger.Shelley.TxCert | |||||
Eq MIRPot | |||||
Ord MIRPot | |||||
Defined in Cardano.Ledger.Shelley.TxCert | |||||
NoThunks MIRPot | |||||
type Rep MIRPot | |||||
Defined in Cardano.Ledger.Shelley.TxCert type Rep MIRPot = D1 ('MetaData "MIRPot" "Cardano.Ledger.Shelley.TxCert" "cardano-ledger-shelley-1.16.0.0-66390a9322bb0fb64b3f0442ebc385a2f8e5928f157dc0d1b8e0fcc9dabbabc0" 'False) (C1 ('MetaCons "ReservesMIR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TreasuryMIR" 'PrefixI 'False) (U1 :: Type -> Type)) |
MIRTarget specifies if funds from either the reserves or the treasury are to be handed out to a collection of reward accounts or instead transfered to the opposite pot.
Constructors
StakeAddressesMIR !(Map (Credential 'Staking) DeltaCoin) | |
SendToOppositePotMIR !Coin |
Instances
ToJSON MIRTarget | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods toEncoding :: MIRTarget -> Encoding toJSONList :: [MIRTarget] -> Value toEncodingList :: [MIRTarget] -> Encoding | |||||
Generic MIRTarget | |||||
Defined in Cardano.Ledger.Shelley.TxCert Associated Types
| |||||
Show MIRTarget | |||||
DecCBOR MIRTarget | |||||
EncCBOR MIRTarget | |||||
NFData MIRTarget | |||||
Defined in Cardano.Ledger.Shelley.TxCert | |||||
Eq MIRTarget | |||||
Ord MIRTarget | |||||
Defined in Cardano.Ledger.Shelley.TxCert | |||||
NoThunks MIRTarget | |||||
type Rep MIRTarget | |||||
Defined in Cardano.Ledger.Shelley.TxCert type Rep MIRTarget = D1 ('MetaData "MIRTarget" "Cardano.Ledger.Shelley.TxCert" "cardano-ledger-shelley-1.16.0.0-66390a9322bb0fb64b3f0442ebc385a2f8e5928f157dc0d1b8e0fcc9dabbabc0" 'False) (C1 ('MetaCons "StakeAddressesMIR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (Credential 'Staking) DeltaCoin))) :+: C1 ('MetaCons "SendToOppositePotMIR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin))) |
class EraTxCert era => ShelleyEraTxCert era where Source #
Methods
mkRegTxCert :: StakeCredential -> TxCert era Source #
getRegTxCert :: TxCert era -> Maybe StakeCredential Source #
mkUnRegTxCert :: StakeCredential -> TxCert era Source #
getUnRegTxCert :: TxCert era -> Maybe StakeCredential Source #
mkDelegStakeTxCert :: StakeCredential -> KeyHash 'StakePool -> TxCert era Source #
getDelegStakeTxCert :: TxCert era -> Maybe (StakeCredential, KeyHash 'StakePool) Source #
mkGenesisDelegTxCert :: GenesisDelegCert -> TxCert era Source #
getGenesisDelegTxCert :: TxCert era -> Maybe GenesisDelegCert Source #
mkMirTxCert :: MIRCert -> TxCert era Source #
Instances
ShelleyEraTxCert ShelleyEra | |
Defined in Cardano.Ledger.Shelley.TxCert Methods mkRegTxCert :: StakeCredential -> TxCert ShelleyEra Source # getRegTxCert :: TxCert ShelleyEra -> Maybe StakeCredential Source # mkUnRegTxCert :: StakeCredential -> TxCert ShelleyEra Source # getUnRegTxCert :: TxCert ShelleyEra -> Maybe StakeCredential Source # mkDelegStakeTxCert :: StakeCredential -> KeyHash 'StakePool -> TxCert ShelleyEra Source # getDelegStakeTxCert :: TxCert ShelleyEra -> Maybe (StakeCredential, KeyHash 'StakePool) Source # mkGenesisDelegTxCert :: GenesisDelegCert -> TxCert ShelleyEra Source # getGenesisDelegTxCert :: TxCert ShelleyEra -> Maybe GenesisDelegCert Source # mkMirTxCert :: MIRCert -> TxCert ShelleyEra Source # getMirTxCert :: TxCert ShelleyEra -> Maybe MIRCert Source # |
data AccountState Source #
Constructors
AccountState | |
Fields
|
Instances
ToJSON AccountState | |||||
Defined in Cardano.Ledger.State.AccountState Methods toJSON :: AccountState -> Value toEncoding :: AccountState -> Encoding toJSONList :: [AccountState] -> Value toEncodingList :: [AccountState] -> Encoding omitField :: AccountState -> Bool | |||||
Generic AccountState | |||||
Defined in Cardano.Ledger.State.AccountState Associated Types
Methods from :: AccountState -> Rep AccountState x Source # to :: Rep AccountState x -> AccountState Source # | |||||
Show AccountState | |||||
Defined in Cardano.Ledger.State.AccountState | |||||
DecCBOR AccountState | |||||
Defined in Cardano.Ledger.State.AccountState | |||||
EncCBOR AccountState | |||||
Defined in Cardano.Ledger.State.AccountState Methods encCBOR :: AccountState -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy AccountState -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [AccountState] -> Size Source # | |||||
Default AccountState | |||||
Defined in Cardano.Ledger.State.AccountState Methods def :: AccountState # | |||||
NFData AccountState | |||||
Defined in Cardano.Ledger.State.AccountState Methods rnf :: AccountState -> () Source # | |||||
Eq AccountState | |||||
Defined in Cardano.Ledger.State.AccountState Methods (==) :: AccountState -> AccountState -> Bool Source # (/=) :: AccountState -> AccountState -> Bool Source # | |||||
NoThunks AccountState | |||||
Defined in Cardano.Ledger.State.AccountState Methods noThunks :: Context -> AccountState -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> AccountState -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy AccountState -> String # | |||||
type Rep AccountState | |||||
Defined in Cardano.Ledger.State.AccountState type Rep AccountState = D1 ('MetaData "AccountState" "Cardano.Ledger.State.AccountState" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'False) (C1 ('MetaCons "AccountState" 'PrefixI 'True) (S1 ('MetaSel ('Just "asTreasury") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin) :*: S1 ('MetaSel ('Just "asReserves") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin))) |
newtype CoinPerWord Source #
Constructors
CoinPerWord | |
Fields |
Instances
FromJSON CoinPerWord | |
Defined in Cardano.Ledger.Alonzo.PParams | |
ToJSON CoinPerWord | |
Defined in Cardano.Ledger.Alonzo.PParams Methods toJSON :: CoinPerWord -> Value toEncoding :: CoinPerWord -> Encoding toJSONList :: [CoinPerWord] -> Value toEncodingList :: [CoinPerWord] -> Encoding omitField :: CoinPerWord -> Bool | |
Show CoinPerWord | |
Defined in Cardano.Ledger.Alonzo.PParams | |
DecCBOR CoinPerWord | |
Defined in Cardano.Ledger.Alonzo.PParams | |
EncCBOR CoinPerWord | |
Defined in Cardano.Ledger.Alonzo.PParams Methods encCBOR :: CoinPerWord -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy CoinPerWord -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [CoinPerWord] -> Size Source # | |
NFData CoinPerWord | |
Defined in Cardano.Ledger.Alonzo.PParams Methods rnf :: CoinPerWord -> () Source # | |
Eq CoinPerWord | |
Defined in Cardano.Ledger.Alonzo.PParams Methods (==) :: CoinPerWord -> CoinPerWord -> Bool Source # (/=) :: CoinPerWord -> CoinPerWord -> Bool Source # | |
Ord CoinPerWord | |
Defined in Cardano.Ledger.Alonzo.PParams Methods compare :: CoinPerWord -> CoinPerWord -> Ordering Source # (<) :: CoinPerWord -> CoinPerWord -> Bool Source # (<=) :: CoinPerWord -> CoinPerWord -> Bool Source # (>) :: CoinPerWord -> CoinPerWord -> Bool Source # (>=) :: CoinPerWord -> CoinPerWord -> Bool Source # max :: CoinPerWord -> CoinPerWord -> CoinPerWord Source # min :: CoinPerWord -> CoinPerWord -> CoinPerWord Source # | |
NoThunks CoinPerWord | |
Defined in Cardano.Ledger.Alonzo.PParams Methods noThunks :: Context -> CoinPerWord -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> CoinPerWord -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy CoinPerWord -> String # |
plutusScriptLanguage :: AlonzoEraScript era => PlutusScript era -> Language Source #
Get value level plutus language of the plutus script
class (EraScript era, Eq (PlutusScript era), Ord (PlutusScript era), Show (PlutusScript era), NoThunks (PlutusScript era), NFData (PlutusScript era), SafeToHash (PlutusScript era), Eq (PlutusPurpose AsItem era), Show (PlutusPurpose AsItem era), EncCBOR (PlutusPurpose AsItem era), DecCBOR (PlutusPurpose AsItem era), NoThunks (PlutusPurpose AsItem era), NFData (PlutusPurpose AsItem era), Eq (PlutusPurpose AsIx era), Ord (PlutusPurpose AsIx era), Show (PlutusPurpose AsIx era), EncCBOR (PlutusPurpose AsIx era), DecCBOR (PlutusPurpose AsIx era), EncCBORGroup (PlutusPurpose AsIx era), DecCBORGroup (PlutusPurpose AsIx era), NoThunks (PlutusPurpose AsIx era), NFData (PlutusPurpose AsIx era), Eq (PlutusPurpose AsIxItem era), Show (PlutusPurpose AsIxItem era), NoThunks (PlutusPurpose AsIxItem era), NFData (PlutusPurpose AsIxItem era), AllegraEraScript era) => AlonzoEraScript era where Source #
Minimal complete definition
eraMaxLanguage, mkPlutusScript, withPlutusScript, hoistPlutusPurpose, mkSpendingPurpose, toSpendingPurpose, mkMintingPurpose, toMintingPurpose, mkCertifyingPurpose, toCertifyingPurpose, mkRewardingPurpose, toRewardingPurpose, upgradePlutusPurposeAsIx
Associated Types
data PlutusScript era Source #
type PlutusPurpose (f :: Type -> Type -> Type) era = (r :: Type) | r -> era Source #
Methods
eraMaxLanguage :: Language Source #
Highest supported Plutus language version for this era.
toPlutusScript :: Script era -> Maybe (PlutusScript era) Source #
Attempt to extract a PlutusScript
from a wrapper type family Script
. Whenevr
Script
is a native script Nothing
will be returned
default toPlutusScript :: Script era ~ AlonzoScript era => Script era -> Maybe (PlutusScript era) Source #
fromPlutusScript :: PlutusScript era -> Script era Source #
Convert a PlutusScript
to a wrapper type family Script
default fromPlutusScript :: Script era ~ AlonzoScript era => PlutusScript era -> Script era Source #
mkPlutusScript :: forall (l :: Language). PlutusLanguage l => Plutus l -> Maybe (PlutusScript era) Source #
Returns Nothing, whenver plutus language is not supported for this era.
withPlutusScript :: PlutusScript era -> (forall (l :: Language). PlutusLanguage l => Plutus l -> a) -> a Source #
Give a PlutusScript
apply a function that can handle Plutus
scripts of all
known versions.
hoistPlutusPurpose :: (forall ix it. g ix it -> f ix it) -> PlutusPurpose g era -> PlutusPurpose f era Source #
mkSpendingPurpose :: f Word32 TxIn -> PlutusPurpose f era Source #
toSpendingPurpose :: PlutusPurpose f era -> Maybe (f Word32 TxIn) Source #
mkMintingPurpose :: f Word32 PolicyID -> PlutusPurpose f era Source #
toMintingPurpose :: PlutusPurpose f era -> Maybe (f Word32 PolicyID) Source #
mkCertifyingPurpose :: f Word32 (TxCert era) -> PlutusPurpose f era Source #
toCertifyingPurpose :: PlutusPurpose f era -> Maybe (f Word32 (TxCert era)) Source #
mkRewardingPurpose :: f Word32 RewardAccount -> PlutusPurpose f era Source #
toRewardingPurpose :: PlutusPurpose f era -> Maybe (f Word32 RewardAccount) Source #
upgradePlutusPurposeAsIx :: PlutusPurpose AsIx (PreviousEra era) -> PlutusPurpose AsIx era Source #
Instances
AlonzoEraScript AlonzoEra | |||||||||
Defined in Cardano.Ledger.Alonzo.Scripts Associated Types
Methods eraMaxLanguage :: Language Source # toPlutusScript :: Script AlonzoEra -> Maybe (PlutusScript AlonzoEra) Source # fromPlutusScript :: PlutusScript AlonzoEra -> Script AlonzoEra Source # mkPlutusScript :: forall (l :: Language). PlutusLanguage l => Plutus l -> Maybe (PlutusScript AlonzoEra) Source # withPlutusScript :: PlutusScript AlonzoEra -> (forall (l :: Language). PlutusLanguage l => Plutus l -> a) -> a Source # hoistPlutusPurpose :: (forall ix it. g ix it -> f ix it) -> PlutusPurpose g AlonzoEra -> PlutusPurpose f AlonzoEra Source # mkSpendingPurpose :: f Word32 TxIn -> PlutusPurpose f AlonzoEra Source # toSpendingPurpose :: PlutusPurpose f AlonzoEra -> Maybe (f Word32 TxIn) Source # mkMintingPurpose :: f Word32 PolicyID -> PlutusPurpose f AlonzoEra Source # toMintingPurpose :: PlutusPurpose f AlonzoEra -> Maybe (f Word32 PolicyID) Source # mkCertifyingPurpose :: f Word32 (TxCert AlonzoEra) -> PlutusPurpose f AlonzoEra Source # toCertifyingPurpose :: PlutusPurpose f AlonzoEra -> Maybe (f Word32 (TxCert AlonzoEra)) Source # mkRewardingPurpose :: f Word32 RewardAccount -> PlutusPurpose f AlonzoEra Source # toRewardingPurpose :: PlutusPurpose f AlonzoEra -> Maybe (f Word32 RewardAccount) Source # upgradePlutusPurposeAsIx :: PlutusPurpose AsIx (PreviousEra AlonzoEra) -> PlutusPurpose AsIx AlonzoEra Source # |
type family PlutusPurpose (f :: Type -> Type -> Type) era = (r :: Type) | r -> era Source #
Instances
type PlutusPurpose f AlonzoEra | |
Defined in Cardano.Ledger.Alonzo.Scripts | |
type PlutusPurpose f BabbageEra | |
Defined in Cardano.Ledger.Babbage.Scripts | |
type PlutusPurpose f ConwayEra | |
Defined in Cardano.Ledger.Conway.Scripts |
data family PlutusScript era Source #
Instances
Generic (PlutusScript AlonzoEra) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Associated Types
Methods from :: PlutusScript AlonzoEra -> Rep (PlutusScript AlonzoEra) x Source # to :: Rep (PlutusScript AlonzoEra) x -> PlutusScript AlonzoEra Source # | |||||
Show (PlutusScript AlonzoEra) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts | |||||
SafeToHash (PlutusScript AlonzoEra) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Methods originalBytes :: PlutusScript AlonzoEra -> ByteString Source # originalBytesSize :: PlutusScript AlonzoEra -> Int Source # makeHashWithExplicitProxys :: Proxy i -> PlutusScript AlonzoEra -> SafeHash i Source # | |||||
NFData (PlutusScript AlonzoEra) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Methods rnf :: PlutusScript AlonzoEra -> () Source # | |||||
Eq (PlutusScript AlonzoEra) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Methods (==) :: PlutusScript AlonzoEra -> PlutusScript AlonzoEra -> Bool Source # (/=) :: PlutusScript AlonzoEra -> PlutusScript AlonzoEra -> Bool Source # | |||||
Ord (PlutusScript AlonzoEra) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Methods compare :: PlutusScript AlonzoEra -> PlutusScript AlonzoEra -> Ordering Source # (<) :: PlutusScript AlonzoEra -> PlutusScript AlonzoEra -> Bool Source # (<=) :: PlutusScript AlonzoEra -> PlutusScript AlonzoEra -> Bool Source # (>) :: PlutusScript AlonzoEra -> PlutusScript AlonzoEra -> Bool Source # (>=) :: PlutusScript AlonzoEra -> PlutusScript AlonzoEra -> Bool Source # max :: PlutusScript AlonzoEra -> PlutusScript AlonzoEra -> PlutusScript AlonzoEra Source # min :: PlutusScript AlonzoEra -> PlutusScript AlonzoEra -> PlutusScript AlonzoEra Source # | |||||
MemPack (PlutusScript AlonzoEra) | It might seem that this instance unnecessarily utilizes a zero Tag, but it is needed for forward compatibility with plutus scripts from future eras. That being said, currently this instance is not used at all, since reference scripts where
introduced in Babbage era and | ||||
Defined in Cardano.Ledger.Alonzo.Scripts Methods packedByteCount :: PlutusScript AlonzoEra -> Int packM :: PlutusScript AlonzoEra -> Pack s () unpackM :: Buffer b => Unpack b (PlutusScript AlonzoEra) | |||||
NoThunks (PlutusScript AlonzoEra) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Methods noThunks :: Context -> PlutusScript AlonzoEra -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> PlutusScript AlonzoEra -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (PlutusScript AlonzoEra) -> String # | |||||
newtype PlutusScript AlonzoEra | |||||
Defined in Cardano.Ledger.Alonzo.Scripts | |||||
data PlutusScript BabbageEra | |||||
Defined in Cardano.Ledger.Babbage.Scripts data PlutusScript BabbageEra
| |||||
data PlutusScript ConwayEra | |||||
Defined in Cardano.Ledger.Conway.Scripts data PlutusScript ConwayEra
| |||||
type Rep (PlutusScript AlonzoEra) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts | |||||
type Rep (PlutusScript BabbageEra) | |||||
Defined in Cardano.Ledger.Babbage.Scripts type Rep (PlutusScript BabbageEra) = D1 ('MetaData "PlutusScript" "Cardano.Ledger.Babbage.Scripts" "cardano-ledger-babbage-1.11.0.0-18938ff90b8b1b2ee4a8593d22f265f620b9a01405a1e90489c0bced8db2d2d2" 'False) (C1 ('MetaCons "BabbagePlutusV1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 (Plutus 'PlutusV1))) :+: C1 ('MetaCons "BabbagePlutusV2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 (Plutus 'PlutusV2)))) | |||||
type Rep (PlutusScript ConwayEra) | |||||
Defined in Cardano.Ledger.Conway.Scripts type Rep (PlutusScript ConwayEra) = D1 ('MetaData "PlutusScript" "Cardano.Ledger.Conway.Scripts" "cardano-ledger-conway-1.19.0.0-4c27ba0e7c20c908d1dfe5f4038fdf7297360e4c38f5293876b47703f80d0e2c" 'False) (C1 ('MetaCons "ConwayPlutusV1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 (Plutus 'PlutusV1))) :+: (C1 ('MetaCons "ConwayPlutusV2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 (Plutus 'PlutusV2))) :+: C1 ('MetaCons "ConwayPlutusV3" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 (Plutus 'PlutusV3))))) |
data AlonzoPlutusPurpose (f :: Type -> Type -> Type) era Source #
Constructors
AlonzoSpending !(f Word32 TxIn) | |
AlonzoMinting !(f Word32 PolicyID) | |
AlonzoCertifying !(f Word32 (TxCert era)) | |
AlonzoRewarding !(f Word32 RewardAccount) |
Instances
(forall a b. (ToJSON a, ToJSON b) => ToJSON (f a b), ToJSON (TxCert era), Era era) => ToJSON (AlonzoPlutusPurpose f era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Methods toJSON :: AlonzoPlutusPurpose f era -> Value toEncoding :: AlonzoPlutusPurpose f era -> Encoding toJSONList :: [AlonzoPlutusPurpose f era] -> Value toEncodingList :: [AlonzoPlutusPurpose f era] -> Encoding omitField :: AlonzoPlutusPurpose f era -> Bool | |||||
Generic (AlonzoPlutusPurpose f era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Associated Types
Methods from :: AlonzoPlutusPurpose f era -> Rep (AlonzoPlutusPurpose f era) x Source # to :: Rep (AlonzoPlutusPurpose f era) x -> AlonzoPlutusPurpose f era Source # | |||||
Show (TxCert era) => Show (AlonzoPlutusPurpose AsItem era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts | |||||
Show (AlonzoPlutusPurpose AsIx era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts | |||||
Show (TxCert era) => Show (AlonzoPlutusPurpose AsIxItem era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts | |||||
(Era era, DecCBOR (TxCert era)) => DecCBOR (AlonzoPlutusPurpose AsItem era) | See note on the | ||||
Era era => DecCBOR (AlonzoPlutusPurpose AsIx era) | Incorrect CBOR implementation. Missing length encoding. Must keep it for backwards compatibility | ||||
(Era era, EncCBOR (TxCert era)) => EncCBOR (AlonzoPlutusPurpose AsItem era) | Note - serialization of
| ||||
Defined in Cardano.Ledger.Alonzo.Scripts Methods encCBOR :: AlonzoPlutusPurpose AsItem era -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (AlonzoPlutusPurpose AsItem era) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [AlonzoPlutusPurpose AsItem era] -> Size Source # | |||||
Era era => EncCBOR (AlonzoPlutusPurpose AsIx era) | Incorrect CBOR implementation. Missing length encoding. Must keep it for backwards compatibility | ||||
Defined in Cardano.Ledger.Alonzo.Scripts Methods encCBOR :: AlonzoPlutusPurpose AsIx era -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (AlonzoPlutusPurpose AsIx era) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [AlonzoPlutusPurpose AsIx era] -> Size Source # | |||||
Era era => DecCBORGroup (AlonzoPlutusPurpose AsIx era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Methods decCBORGroup :: Decoder s (AlonzoPlutusPurpose AsIx era) Source # | |||||
Era era => EncCBORGroup (AlonzoPlutusPurpose AsIx era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Methods encCBORGroup :: AlonzoPlutusPurpose AsIx era -> Encoding Source # encodedGroupSizeExpr :: (forall x. EncCBOR x => Proxy x -> Size) -> Proxy (AlonzoPlutusPurpose AsIx era) -> Size Source # listLen :: AlonzoPlutusPurpose AsIx era -> Word Source # listLenBound :: Proxy (AlonzoPlutusPurpose AsIx era) -> Word Source # | |||||
(forall a b. (NFData a, NFData b) => NFData (f a b), NFData (TxCert era), Era era) => NFData (AlonzoPlutusPurpose f era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Methods rnf :: AlonzoPlutusPurpose f era -> () Source # | |||||
Eq (TxCert era) => Eq (AlonzoPlutusPurpose AsItem era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Methods (==) :: AlonzoPlutusPurpose AsItem era -> AlonzoPlutusPurpose AsItem era -> Bool Source # (/=) :: AlonzoPlutusPurpose AsItem era -> AlonzoPlutusPurpose AsItem era -> Bool Source # | |||||
Eq (AlonzoPlutusPurpose AsIx era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Methods (==) :: AlonzoPlutusPurpose AsIx era -> AlonzoPlutusPurpose AsIx era -> Bool Source # (/=) :: AlonzoPlutusPurpose AsIx era -> AlonzoPlutusPurpose AsIx era -> Bool Source # | |||||
Eq (TxCert era) => Eq (AlonzoPlutusPurpose AsIxItem era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Methods (==) :: AlonzoPlutusPurpose AsIxItem era -> AlonzoPlutusPurpose AsIxItem era -> Bool Source # (/=) :: AlonzoPlutusPurpose AsIxItem era -> AlonzoPlutusPurpose AsIxItem era -> Bool Source # | |||||
Ord (AlonzoPlutusPurpose AsIx era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Methods compare :: AlonzoPlutusPurpose AsIx era -> AlonzoPlutusPurpose AsIx era -> Ordering Source # (<) :: AlonzoPlutusPurpose AsIx era -> AlonzoPlutusPurpose AsIx era -> Bool Source # (<=) :: AlonzoPlutusPurpose AsIx era -> AlonzoPlutusPurpose AsIx era -> Bool Source # (>) :: AlonzoPlutusPurpose AsIx era -> AlonzoPlutusPurpose AsIx era -> Bool Source # (>=) :: AlonzoPlutusPurpose AsIx era -> AlonzoPlutusPurpose AsIx era -> Bool Source # max :: AlonzoPlutusPurpose AsIx era -> AlonzoPlutusPurpose AsIx era -> AlonzoPlutusPurpose AsIx era Source # min :: AlonzoPlutusPurpose AsIx era -> AlonzoPlutusPurpose AsIx era -> AlonzoPlutusPurpose AsIx era Source # | |||||
NoThunks (TxCert era) => NoThunks (AlonzoPlutusPurpose AsItem era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Methods noThunks :: Context -> AlonzoPlutusPurpose AsItem era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> AlonzoPlutusPurpose AsItem era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (AlonzoPlutusPurpose AsItem era) -> String # | |||||
NoThunks (AlonzoPlutusPurpose AsIx era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Methods noThunks :: Context -> AlonzoPlutusPurpose AsIx era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> AlonzoPlutusPurpose AsIx era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (AlonzoPlutusPurpose AsIx era) -> String # | |||||
NoThunks (TxCert era) => NoThunks (AlonzoPlutusPurpose AsIxItem era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Methods noThunks :: Context -> AlonzoPlutusPurpose AsIxItem era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> AlonzoPlutusPurpose AsIxItem era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (AlonzoPlutusPurpose AsIxItem era) -> String # | |||||
type Rep (AlonzoPlutusPurpose f era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts type Rep (AlonzoPlutusPurpose f era) = D1 ('MetaData "AlonzoPlutusPurpose" "Cardano.Ledger.Alonzo.Scripts" "cardano-ledger-alonzo-1.13.0.0-035057ec4286c2bfa3f31fa34d470f3b39ae570662a593c8fca25947ad923ae2" 'False) ((C1 ('MetaCons "AlonzoSpending" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f Word32 TxIn))) :+: C1 ('MetaCons "AlonzoMinting" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f Word32 PolicyID)))) :+: (C1 ('MetaCons "AlonzoCertifying" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f Word32 (TxCert era)))) :+: C1 ('MetaCons "AlonzoRewarding" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f Word32 RewardAccount))))) |
Instances
ToJSON ix => ToJSON (AsIx ix it) | |
Defined in Cardano.Ledger.Alonzo.Scripts Methods toEncoding :: AsIx ix it -> Encoding toJSONList :: [AsIx ix it] -> Value toEncodingList :: [AsIx ix it] -> Encoding | |
Generic ix => Generic (AsIx ix it) | |
Show (AlonzoPlutusPurpose AsIx era) | |
Defined in Cardano.Ledger.Alonzo.Scripts | |
Show ix => Show (AsIx ix it) | |
Show (ConwayPlutusPurpose AsIx era) | |
Defined in Cardano.Ledger.Conway.Scripts | |
Era era => DecCBOR (AlonzoPlutusPurpose AsIx era) | Incorrect CBOR implementation. Missing length encoding. Must keep it for backwards compatibility |
(Typeable it, DecCBOR ix) => DecCBOR (AsIx ix it) | |
Era era => EncCBOR (AlonzoPlutusPurpose AsIx era) | Incorrect CBOR implementation. Missing length encoding. Must keep it for backwards compatibility |
Defined in Cardano.Ledger.Alonzo.Scripts Methods encCBOR :: AlonzoPlutusPurpose AsIx era -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (AlonzoPlutusPurpose AsIx era) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [AlonzoPlutusPurpose AsIx era] -> Size Source # | |
(Typeable it, EncCBOR ix) => EncCBOR (AsIx ix it) | |
Era era => DecCBORGroup (AlonzoPlutusPurpose AsIx era) | |
Defined in Cardano.Ledger.Alonzo.Scripts Methods decCBORGroup :: Decoder s (AlonzoPlutusPurpose AsIx era) Source # | |
Era era => EncCBORGroup (AlonzoPlutusPurpose AsIx era) | |
Defined in Cardano.Ledger.Alonzo.Scripts Methods encCBORGroup :: AlonzoPlutusPurpose AsIx era -> Encoding Source # encodedGroupSizeExpr :: (forall x. EncCBOR x => Proxy x -> Size) -> Proxy (AlonzoPlutusPurpose AsIx era) -> Size Source # listLen :: AlonzoPlutusPurpose AsIx era -> Word Source # listLenBound :: Proxy (AlonzoPlutusPurpose AsIx era) -> Word Source # | |
NFData ix => NFData (AsIx ix it) | |
Defined in Cardano.Ledger.Alonzo.Scripts | |
Eq (AlonzoPlutusPurpose AsIx era) | |
Defined in Cardano.Ledger.Alonzo.Scripts Methods (==) :: AlonzoPlutusPurpose AsIx era -> AlonzoPlutusPurpose AsIx era -> Bool Source # (/=) :: AlonzoPlutusPurpose AsIx era -> AlonzoPlutusPurpose AsIx era -> Bool Source # | |
Eq ix => Eq (AsIx ix it) | |
Eq (ConwayPlutusPurpose AsIx era) | |
Defined in Cardano.Ledger.Conway.Scripts Methods (==) :: ConwayPlutusPurpose AsIx era -> ConwayPlutusPurpose AsIx era -> Bool Source # (/=) :: ConwayPlutusPurpose AsIx era -> ConwayPlutusPurpose AsIx era -> Bool Source # | |
Ord (AlonzoPlutusPurpose AsIx era) | |
Defined in Cardano.Ledger.Alonzo.Scripts Methods compare :: AlonzoPlutusPurpose AsIx era -> AlonzoPlutusPurpose AsIx era -> Ordering Source # (<) :: AlonzoPlutusPurpose AsIx era -> AlonzoPlutusPurpose AsIx era -> Bool Source # (<=) :: AlonzoPlutusPurpose AsIx era -> AlonzoPlutusPurpose AsIx era -> Bool Source # (>) :: AlonzoPlutusPurpose AsIx era -> AlonzoPlutusPurpose AsIx era -> Bool Source # (>=) :: AlonzoPlutusPurpose AsIx era -> AlonzoPlutusPurpose AsIx era -> Bool Source # max :: AlonzoPlutusPurpose AsIx era -> AlonzoPlutusPurpose AsIx era -> AlonzoPlutusPurpose AsIx era Source # min :: AlonzoPlutusPurpose AsIx era -> AlonzoPlutusPurpose AsIx era -> AlonzoPlutusPurpose AsIx era Source # | |
Ord ix => Ord (AsIx ix it) | |
Defined in Cardano.Ledger.Alonzo.Scripts Methods compare :: AsIx ix it -> AsIx ix it -> Ordering Source # (<) :: AsIx ix it -> AsIx ix it -> Bool Source # (<=) :: AsIx ix it -> AsIx ix it -> Bool Source # (>) :: AsIx ix it -> AsIx ix it -> Bool Source # (>=) :: AsIx ix it -> AsIx ix it -> Bool Source # | |
Ord (ConwayPlutusPurpose AsIx era) | |
Defined in Cardano.Ledger.Conway.Scripts Methods compare :: ConwayPlutusPurpose AsIx era -> ConwayPlutusPurpose AsIx era -> Ordering Source # (<) :: ConwayPlutusPurpose AsIx era -> ConwayPlutusPurpose AsIx era -> Bool Source # (<=) :: ConwayPlutusPurpose AsIx era -> ConwayPlutusPurpose AsIx era -> Bool Source # (>) :: ConwayPlutusPurpose AsIx era -> ConwayPlutusPurpose AsIx era -> Bool Source # (>=) :: ConwayPlutusPurpose AsIx era -> ConwayPlutusPurpose AsIx era -> Bool Source # max :: ConwayPlutusPurpose AsIx era -> ConwayPlutusPurpose AsIx era -> ConwayPlutusPurpose AsIx era Source # min :: ConwayPlutusPurpose AsIx era -> ConwayPlutusPurpose AsIx era -> ConwayPlutusPurpose AsIx era Source # | |
NoThunks (AlonzoPlutusPurpose AsIx era) | |
Defined in Cardano.Ledger.Alonzo.Scripts Methods noThunks :: Context -> AlonzoPlutusPurpose AsIx era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> AlonzoPlutusPurpose AsIx era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (AlonzoPlutusPurpose AsIx era) -> String # | |
NoThunks ix => NoThunks (AsIx ix it) | |
NoThunks (ConwayPlutusPurpose AsIx era) | |
Defined in Cardano.Ledger.Conway.Scripts Methods noThunks :: Context -> ConwayPlutusPurpose AsIx era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> ConwayPlutusPurpose AsIx era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (ConwayPlutusPurpose AsIx era) -> String # | |
type Rep (AsIx ix it) | |
Defined in Cardano.Ledger.Alonzo.Scripts |
Constructors
AsIxItem !ix !it |
Instances
(ToJSON ix, ToJSON it) => ToJSON (AsIxItem ix it) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Methods toJSON :: AsIxItem ix it -> Value toEncoding :: AsIxItem ix it -> Encoding toJSONList :: [AsIxItem ix it] -> Value toEncodingList :: [AsIxItem ix it] -> Encoding | |||||
Generic (AsIxItem ix it) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Associated Types
| |||||
Show (TxCert era) => Show (AlonzoPlutusPurpose AsIxItem era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts | |||||
(Show ix, Show it) => Show (AsIxItem ix it) | |||||
(Show (TxCert era), EraPParams era) => Show (ConwayPlutusPurpose AsIxItem era) | |||||
Defined in Cardano.Ledger.Conway.Scripts | |||||
(NFData ix, NFData it) => NFData (AsIxItem ix it) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts | |||||
Eq (TxCert era) => Eq (AlonzoPlutusPurpose AsIxItem era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Methods (==) :: AlonzoPlutusPurpose AsIxItem era -> AlonzoPlutusPurpose AsIxItem era -> Bool Source # (/=) :: AlonzoPlutusPurpose AsIxItem era -> AlonzoPlutusPurpose AsIxItem era -> Bool Source # | |||||
(Eq ix, Eq it) => Eq (AsIxItem ix it) | |||||
(Eq (TxCert era), EraPParams era) => Eq (ConwayPlutusPurpose AsIxItem era) | |||||
Defined in Cardano.Ledger.Conway.Scripts Methods (==) :: ConwayPlutusPurpose AsIxItem era -> ConwayPlutusPurpose AsIxItem era -> Bool Source # (/=) :: ConwayPlutusPurpose AsIxItem era -> ConwayPlutusPurpose AsIxItem era -> Bool Source # | |||||
(Ord ix, Ord it) => Ord (AsIxItem ix it) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Methods compare :: AsIxItem ix it -> AsIxItem ix it -> Ordering Source # (<) :: AsIxItem ix it -> AsIxItem ix it -> Bool Source # (<=) :: AsIxItem ix it -> AsIxItem ix it -> Bool Source # (>) :: AsIxItem ix it -> AsIxItem ix it -> Bool Source # (>=) :: AsIxItem ix it -> AsIxItem ix it -> Bool Source # max :: AsIxItem ix it -> AsIxItem ix it -> AsIxItem ix it Source # min :: AsIxItem ix it -> AsIxItem ix it -> AsIxItem ix it Source # | |||||
NoThunks (TxCert era) => NoThunks (AlonzoPlutusPurpose AsIxItem era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts Methods noThunks :: Context -> AlonzoPlutusPurpose AsIxItem era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> AlonzoPlutusPurpose AsIxItem era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (AlonzoPlutusPurpose AsIxItem era) -> String # | |||||
(NoThunks ix, NoThunks it) => NoThunks (AsIxItem ix it) | |||||
(NoThunks (TxCert era), EraPParams era) => NoThunks (ConwayPlutusPurpose AsIxItem era) | |||||
Defined in Cardano.Ledger.Conway.Scripts Methods noThunks :: Context -> ConwayPlutusPurpose AsIxItem era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> ConwayPlutusPurpose AsIxItem era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (ConwayPlutusPurpose AsIxItem era) -> String # | |||||
type Rep (AsIxItem ix it) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts type Rep (AsIxItem ix it) = D1 ('MetaData "AsIxItem" "Cardano.Ledger.Alonzo.Scripts" "cardano-ledger-alonzo-1.13.0.0-035057ec4286c2bfa3f31fa34d470f3b39ae570662a593c8fca25947ad923ae2" 'False) (C1 ('MetaCons "AsIxItem" 'PrefixI 'True) (S1 ('MetaSel ('Just "asIndex") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ix) :*: S1 ('MetaSel ('Just "asItem") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 it))) |
data AlonzoGenesis Source #
All configuration that is necessary to bootstrap AlonzoEra from ShelleyGenesis
Instances
FromJSON AlonzoGenesis | |||||
Defined in Cardano.Ledger.Alonzo.Genesis | |||||
ToJSON AlonzoGenesis | |||||
Defined in Cardano.Ledger.Alonzo.Genesis Methods toJSON :: AlonzoGenesis -> Value toEncoding :: AlonzoGenesis -> Encoding toJSONList :: [AlonzoGenesis] -> Value toEncodingList :: [AlonzoGenesis] -> Encoding omitField :: AlonzoGenesis -> Bool | |||||
Generic AlonzoGenesis | |||||
Defined in Cardano.Ledger.Alonzo.Genesis Associated Types
Methods from :: AlonzoGenesis -> Rep AlonzoGenesis x Source # to :: Rep AlonzoGenesis x -> AlonzoGenesis Source # | |||||
Show AlonzoGenesis | |||||
Defined in Cardano.Ledger.Alonzo.Genesis | |||||
FromCBOR AlonzoGenesis | |||||
Defined in Cardano.Ledger.Alonzo.Genesis | |||||
ToCBOR AlonzoGenesis | |||||
Defined in Cardano.Ledger.Alonzo.Genesis Methods toCBOR :: AlonzoGenesis -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy AlonzoGenesis -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [AlonzoGenesis] -> Size Source # | |||||
DecCBOR AlonzoGenesis | Genesis types are always encoded with the version of era they are defined in. | ||||
Defined in Cardano.Ledger.Alonzo.Genesis | |||||
EncCBOR AlonzoGenesis | |||||
Defined in Cardano.Ledger.Alonzo.Genesis Methods encCBOR :: AlonzoGenesis -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy AlonzoGenesis -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [AlonzoGenesis] -> Size Source # | |||||
Eq AlonzoGenesis | |||||
Defined in Cardano.Ledger.Alonzo.Genesis Methods (==) :: AlonzoGenesis -> AlonzoGenesis -> Bool Source # (/=) :: AlonzoGenesis -> AlonzoGenesis -> Bool Source # | |||||
NoThunks AlonzoGenesis | |||||
Defined in Cardano.Ledger.Alonzo.Genesis Methods noThunks :: Context -> AlonzoGenesis -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> AlonzoGenesis -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy AlonzoGenesis -> String # | |||||
type Rep AlonzoGenesis | |||||
Defined in Cardano.Ledger.Alonzo.Genesis type Rep AlonzoGenesis = D1 ('MetaData "AlonzoGenesis" "Cardano.Ledger.Alonzo.Genesis" "cardano-ledger-alonzo-1.13.0.0-035057ec4286c2bfa3f31fa34d470f3b39ae570662a593c8fca25947ad923ae2" 'True) (C1 ('MetaCons "AlonzoGenesisWrapper" 'PrefixI 'True) (S1 ('MetaSel ('Just "unAlonzoGenesisWrapper") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (UpgradeAlonzoPParams Identity)))) |
class (MaryEraTxBody era, AlonzoEraTxOut era) => AlonzoEraTxBody era where Source #
Methods
collateralInputsTxBodyL :: Lens' (TxBody era) (Set TxIn) Source #
reqSignerHashesTxBodyL :: Lens' (TxBody era) (Set (KeyHash 'Witness)) Source #
scriptIntegrityHashTxBodyL :: Lens' (TxBody era) (StrictMaybe ScriptIntegrityHash) Source #
networkIdTxBodyL :: Lens' (TxBody era) (StrictMaybe Network) Source #
redeemerPointer :: TxBody era -> PlutusPurpose AsItem era -> StrictMaybe (PlutusPurpose AsIx era) Source #
This function is called rdptr
in the spec. Given a TxBody
and a plutus
purpose with an item, we should be able to find the plutus purpose as in index
redeemerPointerInverse :: TxBody era -> PlutusPurpose AsIx era -> StrictMaybe (PlutusPurpose AsIxItem era) Source #
This is an inverse of redeemerPointer
. Given purpose as an index return it as an item.
Instances
AlonzoEraTxBody AlonzoEra | |
Defined in Cardano.Ledger.Alonzo.TxBody.Internal Methods collateralInputsTxBodyL :: Lens' (TxBody AlonzoEra) (Set TxIn) Source # reqSignerHashesTxBodyL :: Lens' (TxBody AlonzoEra) (Set (KeyHash 'Witness)) Source # scriptIntegrityHashTxBodyL :: Lens' (TxBody AlonzoEra) (StrictMaybe ScriptIntegrityHash) Source # networkIdTxBodyL :: Lens' (TxBody AlonzoEra) (StrictMaybe Network) Source # redeemerPointer :: TxBody AlonzoEra -> PlutusPurpose AsItem AlonzoEra -> StrictMaybe (PlutusPurpose AsIx AlonzoEra) Source # redeemerPointerInverse :: TxBody AlonzoEra -> PlutusPurpose AsIx AlonzoEra -> StrictMaybe (PlutusPurpose AsIxItem AlonzoEra) Source # |
unRedeemers :: Redeemers era -> Map (PlutusPurpose AsIx era) (Data era, ExUnits) Source #
class (EraTxWits era, AlonzoEraScript era) => AlonzoEraTxWits era where Source #
Methods
datsTxWitsL :: Lens' (TxWits era) (TxDats era) Source #
rdmrsTxWitsL :: Lens' (TxWits era) (Redeemers era) Source #
Instances
EraScript AlonzoEra => AlonzoEraTxWits AlonzoEra | |
Defined in Cardano.Ledger.Alonzo.TxWits |
data TxDats era where Source #
Note that TxDats
are based on MemoBytes
since we must preserve
the original bytes for the ScriptIntegrity
.
Since the TxDats
exist outside of the transaction body,
this is how we ensure that they are not manipulated.
Bundled Patterns
pattern TxDats :: Era era => Map DataHash (Data era) -> TxDats era | |
pattern TxDats' :: Map DataHash (Data era) -> TxDats era |
Instances
Era era => Monoid (TxDats era) | |||||
Era era => Semigroup (TxDats era) | |||||
Generic (TxDats era) | |||||
Defined in Cardano.Ledger.Alonzo.TxWits Associated Types
| |||||
Show (TxDats era) | |||||
Typeable era => ToCBOR (TxDats era) | |||||
Era era => DecCBOR (TxDats era) | |||||
Era era => DecCBOR (Annotator (TxDats era)) | |||||
Era era => EncCBOR (TxDats era) | Encodes memoized bytes created upon construction. | ||||
SafeToHash (TxDats era) | |||||
Defined in Cardano.Ledger.Alonzo.TxWits Methods originalBytes :: TxDats era -> ByteString Source # originalBytesSize :: TxDats era -> Int Source # makeHashWithExplicitProxys :: Proxy i -> TxDats era -> SafeHash i Source # | |||||
Memoized (TxDats era) | |||||
Defined in Cardano.Ledger.Alonzo.TxWits Associated Types
Methods getMemoBytes :: TxDats era -> MemoBytes (RawType (TxDats era)) wrapMemoBytes :: MemoBytes (RawType (TxDats era)) -> TxDats era | |||||
NFData (TxDats era) | |||||
Defined in Cardano.Ledger.Alonzo.TxWits | |||||
Eq (TxDats era) | |||||
Typeable era => NoThunks (TxDats era) | |||||
type Rep (TxDats era) | |||||
Defined in Cardano.Ledger.Alonzo.TxWits type Rep (TxDats era) = D1 ('MetaData "TxDats" "Cardano.Ledger.Alonzo.TxWits" "cardano-ledger-alonzo-1.13.0.0-035057ec4286c2bfa3f31fa34d470f3b39ae570662a593c8fca25947ad923ae2" 'True) (C1 ('MetaCons "TxDatsConstr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MemoBytes (TxDatsRaw era))))) | |||||
type RawType (TxDats era) | |||||
Defined in Cardano.Ledger.Alonzo.TxWits |
This newtype wrapper of ExUnits' is used to hide an implementation detail inside the ExUnits pattern.
Constructors
WrapExUnits | |
Fields |
Bundled Patterns
pattern ExUnits :: Natural -> Natural -> ExUnits | Arbitrary execution unit in which we measure the cost of scripts in terms of space in memory and execution time. This pattern hides the fact that ExUnits' is parametric in the underlying type.
The ledger itself uses We would have preferred to use a type alias for |
Instances
FromJSON ExUnits | |||||
Defined in Cardano.Ledger.Plutus.ExUnits | |||||
ToJSON ExUnits | |||||
Defined in Cardano.Ledger.Plutus.ExUnits Methods toEncoding :: ExUnits -> Encoding toJSONList :: [ExUnits] -> Value toEncodingList :: [ExUnits] -> Encoding | |||||
Monoid ExUnits | |||||
Semigroup ExUnits | |||||
Generic ExUnits | |||||
Defined in Cardano.Ledger.Plutus.ExUnits Associated Types
| |||||
Show ExUnits | |||||
DecCBOR ExUnits | |||||
EncCBOR ExUnits | |||||
ToPlutusData ExUnits | |||||
Defined in Cardano.Ledger.Plutus.ToPlutusData | |||||
NFData ExUnits | |||||
Defined in Cardano.Ledger.Plutus.ExUnits | |||||
Eq ExUnits | |||||
NoThunks ExUnits | |||||
type Rep ExUnits | |||||
Defined in Cardano.Ledger.Plutus.ExUnits type Rep ExUnits = D1 ('MetaData "ExUnits" "Cardano.Ledger.Plutus.ExUnits" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'True) (C1 ('MetaCons "WrapExUnits" 'PrefixI 'True) (S1 ('MetaSel ('Just "unWrapExUnits") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ExUnits' Natural)))) |
data Plutus (l :: Language) Source #
Serialized representation of a Plutus script that distinguishes the language version at the type level. When encoded in CBOR language version is also encoded.
Instances
Generic (Plutus l) | |||||
Defined in Cardano.Ledger.Plutus.Language Associated Types
| |||||
Show (Plutus l) | |||||
PlutusLanguage l => DecCBOR (Plutus l) | |||||
PlutusLanguage l => EncCBOR (Plutus l) | |||||
SafeToHash (Plutus l) | |||||
Defined in Cardano.Ledger.Plutus.Language Methods originalBytes :: Plutus l -> ByteString Source # originalBytesSize :: Plutus l -> Int Source # makeHashWithExplicitProxys :: Proxy i -> Plutus l -> SafeHash i Source # | |||||
NFData (Plutus l) | |||||
Defined in Cardano.Ledger.Plutus.Language | |||||
Eq (Plutus l) | |||||
Ord (Plutus l) | |||||
Defined in Cardano.Ledger.Plutus.Language | |||||
MemPack (Plutus l) | |||||
Defined in Cardano.Ledger.Plutus.Language | |||||
NoThunks (Plutus l) | |||||
type Rep (Plutus l) | |||||
Defined in Cardano.Ledger.Plutus.Language type Rep (Plutus l) = D1 ('MetaData "Plutus" "Cardano.Ledger.Plutus.Language" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'True) (C1 ('MetaCons "Plutus" 'PrefixI 'True) (S1 ('MetaSel ('Just "plutusBinary") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PlutusBinary))) |
data CostModels Source #
For a known version of Plutus, attempting to construct a cost model with
too few parameters (depending on the version) will result in an error.
CostModelApplyError
exists to collect these errors in the CostModels
type.
The CostModels
type itself needs to be flexible enough to accept any map
of Word8
to '[Int64]', so that cost models can be placed in the protocol parameters
ahead of changes to the Plutus evaluation context. In this way, serializing a cost model,
updating software, and deserializing can result in errors going away.
Additionally, CostModels
needs to be able to store cost models for future version
of Plutus, which we cannot yet even validate. These are stored in
costModelsUnknown
.
Instances
FromJSON CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels | |||||
ToJSON CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels Methods toJSON :: CostModels -> Value toEncoding :: CostModels -> Encoding toJSONList :: [CostModels] -> Value toEncodingList :: [CostModels] -> Encoding omitField :: CostModels -> Bool | |||||
Monoid CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels Methods mempty :: CostModels Source # mappend :: CostModels -> CostModels -> CostModels Source # mconcat :: [CostModels] -> CostModels Source # | |||||
Semigroup CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels Methods (<>) :: CostModels -> CostModels -> CostModels Source # sconcat :: NonEmpty CostModels -> CostModels Source # stimes :: Integral b => b -> CostModels -> CostModels Source # | |||||
Generic CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels Associated Types
| |||||
Show CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels | |||||
DecCBOR CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels | |||||
EncCBOR CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels Methods encCBOR :: CostModels -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy CostModels -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [CostModels] -> Size Source # | |||||
ToPlutusData CostModels | |||||
Defined in Cardano.Ledger.Plutus.ToPlutusData Methods toPlutusData :: CostModels -> Data Source # fromPlutusData :: Data -> Maybe CostModels Source # | |||||
NFData CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels Methods rnf :: CostModels -> () Source # | |||||
Eq CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels Methods (==) :: CostModels -> CostModels -> Bool Source # (/=) :: CostModels -> CostModels -> Bool Source # | |||||
Ord CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels Methods compare :: CostModels -> CostModels -> Ordering Source # (<) :: CostModels -> CostModels -> Bool Source # (<=) :: CostModels -> CostModels -> Bool Source # (>) :: CostModels -> CostModels -> Bool Source # (>=) :: CostModels -> CostModels -> Bool Source # max :: CostModels -> CostModels -> CostModels Source # min :: CostModels -> CostModels -> CostModels Source # | |||||
NoThunks CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels Methods noThunks :: Context -> CostModels -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> CostModels -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy CostModels -> String # | |||||
type Rep CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels type Rep CostModels = D1 ('MetaData "CostModels" "Cardano.Ledger.Plutus.CostModels" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'False) (C1 ('MetaCons "CostModels" 'PrefixI 'True) (S1 ('MetaSel ('Just "_costModelsValid") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map Language CostModel)) :*: S1 ('MetaSel ('Just "_costModelsUnknown") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map Word8 [Int64])))) |
Prices per execution unit
Constructors
Prices | |
Fields |
Instances
FromJSON Prices | |||||
Defined in Cardano.Ledger.Plutus.ExUnits | |||||
ToJSON Prices | |||||
Defined in Cardano.Ledger.Plutus.ExUnits Methods toEncoding :: Prices -> Encoding toJSONList :: [Prices] -> Value toEncodingList :: [Prices] -> Encoding | |||||
Generic Prices | |||||
Defined in Cardano.Ledger.Plutus.ExUnits Associated Types
| |||||
Show Prices | |||||
DecCBOR Prices | |||||
EncCBOR Prices | |||||
ToPlutusData Prices | |||||
Defined in Cardano.Ledger.Plutus.ToPlutusData | |||||
NFData Prices | |||||
Defined in Cardano.Ledger.Plutus.ExUnits | |||||
Eq Prices | |||||
Ord Prices | |||||
Defined in Cardano.Ledger.Plutus.ExUnits | |||||
NoThunks Prices | |||||
type Rep Prices | |||||
Defined in Cardano.Ledger.Plutus.ExUnits type Rep Prices = D1 ('MetaData "Prices" "Cardano.Ledger.Plutus.ExUnits" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'False) (C1 ('MetaCons "Prices" 'PrefixI 'True) (S1 ('MetaSel ('Just "prMem") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NonNegativeInterval) :*: S1 ('MetaSel ('Just "prSteps") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NonNegativeInterval))) |
newtype CoinPerByte Source #
Constructors
CoinPerByte | |
Fields |
Instances
FromJSON CoinPerByte | |
Defined in Cardano.Ledger.Babbage.PParams | |
ToJSON CoinPerByte | |
Defined in Cardano.Ledger.Babbage.PParams Methods toJSON :: CoinPerByte -> Value toEncoding :: CoinPerByte -> Encoding toJSONList :: [CoinPerByte] -> Value toEncodingList :: [CoinPerByte] -> Encoding omitField :: CoinPerByte -> Bool | |
Show CoinPerByte | |
Defined in Cardano.Ledger.Babbage.PParams | |
DecCBOR CoinPerByte | |
Defined in Cardano.Ledger.Babbage.PParams | |
EncCBOR CoinPerByte | |
Defined in Cardano.Ledger.Babbage.PParams Methods encCBOR :: CoinPerByte -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy CoinPerByte -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [CoinPerByte] -> Size Source # | |
NFData CoinPerByte | |
Defined in Cardano.Ledger.Babbage.PParams Methods rnf :: CoinPerByte -> () Source # | |
Eq CoinPerByte | |
Defined in Cardano.Ledger.Babbage.PParams Methods (==) :: CoinPerByte -> CoinPerByte -> Bool Source # (/=) :: CoinPerByte -> CoinPerByte -> Bool Source # | |
Ord CoinPerByte | |
Defined in Cardano.Ledger.Babbage.PParams Methods compare :: CoinPerByte -> CoinPerByte -> Ordering Source # (<) :: CoinPerByte -> CoinPerByte -> Bool Source # (<=) :: CoinPerByte -> CoinPerByte -> Bool Source # (>) :: CoinPerByte -> CoinPerByte -> Bool Source # (>=) :: CoinPerByte -> CoinPerByte -> Bool Source # max :: CoinPerByte -> CoinPerByte -> CoinPerByte Source # min :: CoinPerByte -> CoinPerByte -> CoinPerByte Source # | |
NoThunks CoinPerByte | |
Defined in Cardano.Ledger.Babbage.PParams Methods noThunks :: Context -> CoinPerByte -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> CoinPerByte -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy CoinPerByte -> String # |
Constructors
Anchor | |
Fields
|
Instances
FromJSON Anchor | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
ToJSON Anchor | |||||
Defined in Cardano.Ledger.BaseTypes Methods toEncoding :: Anchor -> Encoding toJSONList :: [Anchor] -> Value toEncodingList :: [Anchor] -> Encoding | |||||
Generic Anchor | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
| |||||
Show Anchor | |||||
DecCBOR Anchor | |||||
EncCBOR Anchor | |||||
Default Anchor | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
NFData Anchor | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
Eq Anchor | |||||
Ord Anchor | |||||
NoThunks Anchor | |||||
type Rep Anchor | |||||
Defined in Cardano.Ledger.BaseTypes type Rep Anchor = D1 ('MetaData "Anchor" "Cardano.Ledger.BaseTypes" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'False) (C1 ('MetaCons "Anchor" 'PrefixI 'True) (S1 ('MetaSel ('Just "anchorUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Url) :*: S1 ('MetaSel ('Just "anchorDataHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SafeHash AnchorData)))) |
newtype AnchorData Source #
Constructors
AnchorData ByteString |
Instances
SafeToHash AnchorData | |
Defined in Cardano.Ledger.BaseTypes Methods originalBytes :: AnchorData -> ByteString Source # originalBytesSize :: AnchorData -> Int Source # makeHashWithExplicitProxys :: Proxy i -> AnchorData -> SafeHash i Source # | |
Eq AnchorData | |
Defined in Cardano.Ledger.BaseTypes Methods (==) :: AnchorData -> AnchorData -> Bool Source # (/=) :: AnchorData -> AnchorData -> Bool Source # | |
HashAnnotated AnchorData AnchorData | |
Defined in Cardano.Ledger.BaseTypes Methods |
data Constitution era Source #
Constructors
Constitution | |
Fields |
Instances
Era era => FromJSON (Constitution era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods parseJSON :: Value -> Parser (Constitution era) parseJSONList :: Value -> Parser [Constitution era] omittedField :: Maybe (Constitution era) | |||||
Era era => ToJSON (Constitution era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods toJSON :: Constitution era -> Value toEncoding :: Constitution era -> Encoding toJSONList :: [Constitution era] -> Value toEncodingList :: [Constitution era] -> Encoding omitField :: Constitution era -> Bool | |||||
Generic (Constitution era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
Methods from :: Constitution era -> Rep (Constitution era) x Source # to :: Rep (Constitution era) x -> Constitution era Source # | |||||
Show (Constitution era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
Era era => FromCBOR (Constitution era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
Era era => ToCBOR (Constitution era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods toCBOR :: Constitution era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Constitution era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Constitution era] -> Size Source # | |||||
Era era => DecCBOR (Constitution era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
Era era => EncCBOR (Constitution era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods encCBOR :: Constitution era -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (Constitution era) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Constitution era] -> Size Source # | |||||
Era era => Default (Constitution era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods def :: Constitution era # | |||||
Era era => NFData (Constitution era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods rnf :: Constitution era -> () Source # | |||||
Eq (Constitution era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods (==) :: Constitution era -> Constitution era -> Bool Source # (/=) :: Constitution era -> Constitution era -> Bool Source # | |||||
Ord (Constitution era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods compare :: Constitution era -> Constitution era -> Ordering Source # (<) :: Constitution era -> Constitution era -> Bool Source # (<=) :: Constitution era -> Constitution era -> Bool Source # (>) :: Constitution era -> Constitution era -> Bool Source # (>=) :: Constitution era -> Constitution era -> Bool Source # max :: Constitution era -> Constitution era -> Constitution era Source # min :: Constitution era -> Constitution era -> Constitution era Source # | |||||
Era era => NoThunks (Constitution era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods noThunks :: Context -> Constitution era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> Constitution era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (Constitution era) -> String # | |||||
type Rep (Constitution era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures type Rep (Constitution era) = D1 ('MetaData "Constitution" "Cardano.Ledger.Conway.Governance.Procedures" "cardano-ledger-conway-1.19.0.0-4c27ba0e7c20c908d1dfe5f4038fdf7297360e4c38f5293876b47703f80d0e2c" 'False) (C1 ('MetaCons "Constitution" 'PrefixI 'True) (S1 ('MetaSel ('Just "constitutionAnchor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Anchor) :*: S1 ('MetaSel ('Just "constitutionScript") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe ScriptHash)))) |
Note that the previous governance action id is only optional for the very first governance action of the same purpose.
Constructors
ParameterChange | |
Fields
| |
HardForkInitiation | |
Fields
| |
TreasuryWithdrawals | |
Fields
| |
NoConfidence | |
Fields
| |
UpdateCommittee | |
Fields
| |
NewConstitution | |
Fields
| |
InfoAction |
Instances
EraPParams era => ToJSON (GovAction era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods toJSON :: GovAction era -> Value toEncoding :: GovAction era -> Encoding toJSONList :: [GovAction era] -> Value toEncodingList :: [GovAction era] -> Encoding | |||||
Generic (GovAction era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
| |||||
EraPParams era => Show (GovAction era) | |||||
EraPParams era => DecCBOR (GovAction era) | |||||
EraPParams era => EncCBOR (GovAction era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
EraPParams era => NFData (GovAction era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
EraPParams era => Eq (GovAction era) | |||||
EraPParams era => Ord (GovAction era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods compare :: GovAction era -> GovAction era -> Ordering Source # (<) :: GovAction era -> GovAction era -> Bool Source # (<=) :: GovAction era -> GovAction era -> Bool Source # (>) :: GovAction era -> GovAction era -> Bool Source # (>=) :: GovAction era -> GovAction era -> Bool Source # max :: GovAction era -> GovAction era -> GovAction era Source # min :: GovAction era -> GovAction era -> GovAction era Source # | |||||
EraPParams era => NoThunks (GovAction era) | |||||
type Rep (GovAction era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures type Rep (GovAction era) = D1 ('MetaData "GovAction" "Cardano.Ledger.Conway.Governance.Procedures" "cardano-ledger-conway-1.19.0.0-4c27ba0e7c20c908d1dfe5f4038fdf7297360e4c38f5293876b47703f80d0e2c" 'False) ((C1 ('MetaCons "ParameterChange" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe (GovPurposeId 'PParamUpdatePurpose era))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PParamsUpdate era)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe ScriptHash)))) :+: (C1 ('MetaCons "HardForkInitiation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe (GovPurposeId 'HardForkPurpose era))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ProtVer)) :+: C1 ('MetaCons "TreasuryWithdrawals" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map RewardAccount Coin)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe ScriptHash))))) :+: ((C1 ('MetaCons "NoConfidence" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe (GovPurposeId 'CommitteePurpose era)))) :+: C1 ('MetaCons "UpdateCommittee" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe (GovPurposeId 'CommitteePurpose era))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set (Credential 'ColdCommitteeRole)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (Credential 'ColdCommitteeRole) EpochNo)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitInterval)))) :+: (C1 ('MetaCons "NewConstitution" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe (GovPurposeId 'ConstitutionPurpose era))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Constitution era))) :+: C1 ('MetaCons "InfoAction" 'PrefixI 'False) (U1 :: Type -> Type)))) |
data GovActionId Source #
Constructors
GovActionId | |
Fields
|
Instances
ToJSON GovActionId | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods toJSON :: GovActionId -> Value toEncoding :: GovActionId -> Encoding toJSONList :: [GovActionId] -> Value toEncodingList :: [GovActionId] -> Encoding omitField :: GovActionId -> Bool | |||||
ToJSONKey GovActionId | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
Generic GovActionId | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
Methods from :: GovActionId -> Rep GovActionId x Source # to :: Rep GovActionId x -> GovActionId Source # | |||||
Show GovActionId | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
DecCBOR GovActionId | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
EncCBOR GovActionId | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods encCBOR :: GovActionId -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy GovActionId -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [GovActionId] -> Size Source # | |||||
NFData GovActionId | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods rnf :: GovActionId -> () Source # | |||||
Eq GovActionId | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods (==) :: GovActionId -> GovActionId -> Bool Source # (/=) :: GovActionId -> GovActionId -> Bool Source # | |||||
Ord GovActionId | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods compare :: GovActionId -> GovActionId -> Ordering Source # (<) :: GovActionId -> GovActionId -> Bool Source # (<=) :: GovActionId -> GovActionId -> Bool Source # (>) :: GovActionId -> GovActionId -> Bool Source # (>=) :: GovActionId -> GovActionId -> Bool Source # max :: GovActionId -> GovActionId -> GovActionId Source # min :: GovActionId -> GovActionId -> GovActionId Source # | |||||
NoThunks GovActionId | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods noThunks :: Context -> GovActionId -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> GovActionId -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy GovActionId -> String # | |||||
HasOKey GovActionId (GovActionState era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods okeyL :: Lens' (GovActionState era) GovActionId Source # | |||||
type Rep GovActionId | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures type Rep GovActionId = D1 ('MetaData "GovActionId" "Cardano.Ledger.Conway.Governance.Procedures" "cardano-ledger-conway-1.19.0.0-4c27ba0e7c20c908d1dfe5f4038fdf7297360e4c38f5293876b47703f80d0e2c" 'False) (C1 ('MetaCons "GovActionId" 'PrefixI 'True) (S1 ('MetaSel ('Just "gaidTxId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxId) :*: S1 ('MetaSel ('Just "gaidGovActionIx") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 GovActionIx))) |
newtype GovActionIx Source #
Constructors
GovActionIx | |
Fields |
Instances
ToJSON GovActionIx | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods toJSON :: GovActionIx -> Value toEncoding :: GovActionIx -> Encoding toJSONList :: [GovActionIx] -> Value toEncodingList :: [GovActionIx] -> Encoding omitField :: GovActionIx -> Bool | |||||
Generic GovActionIx | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
Methods from :: GovActionIx -> Rep GovActionIx x Source # to :: Rep GovActionIx x -> GovActionIx Source # | |||||
Show GovActionIx | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
DecCBOR GovActionIx | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
EncCBOR GovActionIx | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods encCBOR :: GovActionIx -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy GovActionIx -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [GovActionIx] -> Size Source # | |||||
NFData GovActionIx | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods rnf :: GovActionIx -> () Source # | |||||
Eq GovActionIx | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods (==) :: GovActionIx -> GovActionIx -> Bool Source # (/=) :: GovActionIx -> GovActionIx -> Bool Source # | |||||
Ord GovActionIx | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods compare :: GovActionIx -> GovActionIx -> Ordering Source # (<) :: GovActionIx -> GovActionIx -> Bool Source # (<=) :: GovActionIx -> GovActionIx -> Bool Source # (>) :: GovActionIx -> GovActionIx -> Bool Source # (>=) :: GovActionIx -> GovActionIx -> Bool Source # max :: GovActionIx -> GovActionIx -> GovActionIx Source # min :: GovActionIx -> GovActionIx -> GovActionIx Source # | |||||
NoThunks GovActionIx | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods noThunks :: Context -> GovActionIx -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> GovActionIx -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy GovActionIx -> String # | |||||
type Rep GovActionIx | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures type Rep GovActionIx = D1 ('MetaData "GovActionIx" "Cardano.Ledger.Conway.Governance.Procedures" "cardano-ledger-conway-1.19.0.0-4c27ba0e7c20c908d1dfe5f4038fdf7297360e4c38f5293876b47703f80d0e2c" 'True) (C1 ('MetaCons "GovActionIx" 'PrefixI 'True) (S1 ('MetaSel ('Just "unGovActionIx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16))) |
data GovActionState era Source #
Constructors
GovActionState | |
Fields
|
Instances
HasOKey GovActionId (GovActionState era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods okeyL :: Lens' (GovActionState era) GovActionId Source # | |||||
EraPParams era => ToJSON (GovActionState era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods toJSON :: GovActionState era -> Value toEncoding :: GovActionState era -> Encoding toJSONList :: [GovActionState era] -> Value toEncodingList :: [GovActionState era] -> Encoding omitField :: GovActionState era -> Bool | |||||
Generic (GovActionState era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
Methods from :: GovActionState era -> Rep (GovActionState era) x Source # to :: Rep (GovActionState era) x -> GovActionState era Source # | |||||
EraPParams era => Show (GovActionState era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
EraPParams era => DecCBOR (GovActionState era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
EraPParams era => DecShareCBOR (GovActionState era) | |||||
EraPParams era => EncCBOR (GovActionState era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods encCBOR :: GovActionState era -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (GovActionState era) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [GovActionState era] -> Size Source # | |||||
EraPParams era => NFData (GovActionState era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods rnf :: GovActionState era -> () Source # | |||||
EraPParams era => Eq (GovActionState era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods (==) :: GovActionState era -> GovActionState era -> Bool Source # (/=) :: GovActionState era -> GovActionState era -> Bool Source # | |||||
EraPParams era => Ord (GovActionState era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods compare :: GovActionState era -> GovActionState era -> Ordering Source # (<) :: GovActionState era -> GovActionState era -> Bool Source # (<=) :: GovActionState era -> GovActionState era -> Bool Source # (>) :: GovActionState era -> GovActionState era -> Bool Source # (>=) :: GovActionState era -> GovActionState era -> Bool Source # max :: GovActionState era -> GovActionState era -> GovActionState era Source # min :: GovActionState era -> GovActionState era -> GovActionState era Source # | |||||
EraPParams era => NoThunks (GovActionState era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods noThunks :: Context -> GovActionState era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> GovActionState era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (GovActionState era) -> String # | |||||
type Rep (GovActionState era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures type Rep (GovActionState era) = D1 ('MetaData "GovActionState" "Cardano.Ledger.Conway.Governance.Procedures" "cardano-ledger-conway-1.19.0.0-4c27ba0e7c20c908d1dfe5f4038fdf7297360e4c38f5293876b47703f80d0e2c" 'False) (C1 ('MetaCons "GovActionState" 'PrefixI 'True) ((S1 ('MetaSel ('Just "gasId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 GovActionId) :*: (S1 ('MetaSel ('Just "gasCommitteeVotes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (Credential 'HotCommitteeRole) Vote)) :*: S1 ('MetaSel ('Just "gasDRepVotes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (Credential 'DRepRole) Vote)))) :*: ((S1 ('MetaSel ('Just "gasStakePoolVotes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (KeyHash 'StakePool) Vote)) :*: S1 ('MetaSel ('Just "gasProposalProcedure") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ProposalProcedure era))) :*: (S1 ('MetaSel ('Just "gasProposedIn") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 EpochNo) :*: S1 ('MetaSel ('Just "gasExpiresAfter") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 EpochNo))))) | |||||
type Share (GovActionState era) | |||||
data ProposalProcedure era Source #
Constructors
ProposalProcedure | |
Fields
|
Instances
EraPParams era => ToJSON (ProposalProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods toJSON :: ProposalProcedure era -> Value toEncoding :: ProposalProcedure era -> Encoding toJSONList :: [ProposalProcedure era] -> Value toEncodingList :: [ProposalProcedure era] -> Encoding omitField :: ProposalProcedure era -> Bool | |||||
Generic (ProposalProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
Methods from :: ProposalProcedure era -> Rep (ProposalProcedure era) x Source # to :: Rep (ProposalProcedure era) x -> ProposalProcedure era Source # | |||||
EraPParams era => Show (ProposalProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
EraPParams era => DecCBOR (ProposalProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
EraPParams era => EncCBOR (ProposalProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods encCBOR :: ProposalProcedure era -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (ProposalProcedure era) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ProposalProcedure era] -> Size Source # | |||||
EraPParams era => NFData (ProposalProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods rnf :: ProposalProcedure era -> () Source # | |||||
EraPParams era => Eq (ProposalProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods (==) :: ProposalProcedure era -> ProposalProcedure era -> Bool Source # (/=) :: ProposalProcedure era -> ProposalProcedure era -> Bool Source # | |||||
EraPParams era => Ord (ProposalProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods compare :: ProposalProcedure era -> ProposalProcedure era -> Ordering Source # (<) :: ProposalProcedure era -> ProposalProcedure era -> Bool Source # (<=) :: ProposalProcedure era -> ProposalProcedure era -> Bool Source # (>) :: ProposalProcedure era -> ProposalProcedure era -> Bool Source # (>=) :: ProposalProcedure era -> ProposalProcedure era -> Bool Source # max :: ProposalProcedure era -> ProposalProcedure era -> ProposalProcedure era Source # min :: ProposalProcedure era -> ProposalProcedure era -> ProposalProcedure era Source # | |||||
EraPParams era => NoThunks (ProposalProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods noThunks :: Context -> ProposalProcedure era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> ProposalProcedure era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (ProposalProcedure era) -> String # | |||||
type Rep (ProposalProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures type Rep (ProposalProcedure era) = D1 ('MetaData "ProposalProcedure" "Cardano.Ledger.Conway.Governance.Procedures" "cardano-ledger-conway-1.19.0.0-4c27ba0e7c20c908d1dfe5f4038fdf7297360e4c38f5293876b47703f80d0e2c" 'False) (C1 ('MetaCons "ProposalProcedure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "pProcDeposit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin) :*: S1 ('MetaSel ('Just "pProcReturnAddr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RewardAccount)) :*: (S1 ('MetaSel ('Just "pProcGovAction") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GovAction era)) :*: S1 ('MetaSel ('Just "pProcAnchor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Anchor)))) |
Constructors
CommitteeVoter !(Credential 'HotCommitteeRole) | |
DRepVoter !(Credential 'DRepRole) | |
StakePoolVoter !(KeyHash 'StakePool) |
Instances
ToJSON Voter | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods toEncoding :: Voter -> Encoding toJSONList :: [Voter] -> Value toEncodingList :: [Voter] -> Encoding | |||||
ToJSONKey Voter | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
Generic Voter | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
| |||||
Show Voter | |||||
DecCBOR Voter | |||||
EncCBOR Voter | |||||
NFData Voter | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
Eq Voter | |||||
Ord Voter | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
NoThunks Voter | |||||
Indexable Voter (VotingProcedures era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
type Rep Voter | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures type Rep Voter = D1 ('MetaData "Voter" "Cardano.Ledger.Conway.Governance.Procedures" "cardano-ledger-conway-1.19.0.0-4c27ba0e7c20c908d1dfe5f4038fdf7297360e4c38f5293876b47703f80d0e2c" 'False) (C1 ('MetaCons "CommitteeVoter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Credential 'HotCommitteeRole))) :+: (C1 ('MetaCons "DRepVoter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Credential 'DRepRole))) :+: C1 ('MetaCons "StakePoolVoter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool))))) |
data VotingProcedure era Source #
Constructors
VotingProcedure | |
Fields
|
Instances
EraPParams era => ToJSON (VotingProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods toJSON :: VotingProcedure era -> Value toEncoding :: VotingProcedure era -> Encoding toJSONList :: [VotingProcedure era] -> Value toEncodingList :: [VotingProcedure era] -> Encoding omitField :: VotingProcedure era -> Bool | |||||
Generic (VotingProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
Methods from :: VotingProcedure era -> Rep (VotingProcedure era) x Source # to :: Rep (VotingProcedure era) x -> VotingProcedure era Source # | |||||
Show (VotingProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
Era era => DecCBOR (VotingProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
Era era => EncCBOR (VotingProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods encCBOR :: VotingProcedure era -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (VotingProcedure era) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [VotingProcedure era] -> Size Source # | |||||
NFData (VotingProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods rnf :: VotingProcedure era -> () Source # | |||||
Eq (VotingProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods (==) :: VotingProcedure era -> VotingProcedure era -> Bool Source # (/=) :: VotingProcedure era -> VotingProcedure era -> Bool Source # | |||||
NoThunks (VotingProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods noThunks :: Context -> VotingProcedure era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> VotingProcedure era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (VotingProcedure era) -> String # | |||||
type Rep (VotingProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures type Rep (VotingProcedure era) = D1 ('MetaData "VotingProcedure" "Cardano.Ledger.Conway.Governance.Procedures" "cardano-ledger-conway-1.19.0.0-4c27ba0e7c20c908d1dfe5f4038fdf7297360e4c38f5293876b47703f80d0e2c" 'False) (C1 ('MetaCons "VotingProcedure" 'PrefixI 'True) (S1 ('MetaSel ('Just "vProcVote") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Vote) :*: S1 ('MetaSel ('Just "vProcAnchor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe Anchor)))) |
newtype VotingProcedures era Source #
Constructors
VotingProcedures | |
Fields
|
Instances
Indexable Voter (VotingProcedures era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
EraPParams era => ToJSON (VotingProcedures era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods toJSON :: VotingProcedures era -> Value toEncoding :: VotingProcedures era -> Encoding toJSONList :: [VotingProcedures era] -> Value toEncodingList :: [VotingProcedures era] -> Encoding omitField :: VotingProcedures era -> Bool | |||||
Generic (VotingProcedures era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
Methods from :: VotingProcedures era -> Rep (VotingProcedures era) x Source # to :: Rep (VotingProcedures era) x -> VotingProcedures era Source # | |||||
Show (VotingProcedures era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
Era era => DecCBOR (VotingProcedures era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
Era era => EncCBOR (VotingProcedures era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods encCBOR :: VotingProcedures era -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (VotingProcedures era) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [VotingProcedures era] -> Size Source # | |||||
Era era => NFData (VotingProcedures era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods rnf :: VotingProcedures era -> () Source # | |||||
Eq (VotingProcedures era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods (==) :: VotingProcedures era -> VotingProcedures era -> Bool Source # (/=) :: VotingProcedures era -> VotingProcedures era -> Bool Source # | |||||
NoThunks (VotingProcedures era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods noThunks :: Context -> VotingProcedures era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> VotingProcedures era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (VotingProcedures era) -> String # | |||||
type Rep (VotingProcedures era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures type Rep (VotingProcedures era) = D1 ('MetaData "VotingProcedures" "Cardano.Ledger.Conway.Governance.Procedures" "cardano-ledger-conway-1.19.0.0-4c27ba0e7c20c908d1dfe5f4038fdf7297360e4c38f5293876b47703f80d0e2c" 'True) (C1 ('MetaCons "VotingProcedures" 'PrefixI 'True) (S1 ('MetaSel ('Just "unVotingProcedures") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map Voter (Map GovActionId (VotingProcedure era)))))) |
pattern AuthCommitteeHotKeyTxCert :: ConwayEraTxCert era => Credential 'ColdCommitteeRole -> Credential 'HotCommitteeRole -> TxCert era Source #
pattern DelegTxCert :: ConwayEraTxCert era => StakeCredential -> Delegatee -> TxCert era Source #
pattern RegDRepTxCert :: ConwayEraTxCert era => Credential 'DRepRole -> Coin -> StrictMaybe Anchor -> TxCert era Source #
pattern RegDepositDelegTxCert :: ConwayEraTxCert era => StakeCredential -> Delegatee -> Coin -> TxCert era Source #
pattern RegDepositTxCert :: ConwayEraTxCert era => StakeCredential -> Coin -> TxCert era Source #
pattern ResignCommitteeColdTxCert :: ConwayEraTxCert era => Credential 'ColdCommitteeRole -> StrictMaybe Anchor -> TxCert era Source #
pattern UnRegDRepTxCert :: ConwayEraTxCert era => Credential 'DRepRole -> Coin -> TxCert era Source #
pattern UnRegDepositTxCert :: ConwayEraTxCert era => StakeCredential -> Coin -> TxCert era Source #
class ShelleyEraTxCert era => ConwayEraTxCert era where Source #
Methods
mkRegDepositTxCert :: StakeCredential -> Coin -> TxCert era Source #
getRegDepositTxCert :: TxCert era -> Maybe (StakeCredential, Coin) Source #
mkUnRegDepositTxCert :: StakeCredential -> Coin -> TxCert era Source #
getUnRegDepositTxCert :: TxCert era -> Maybe (StakeCredential, Coin) Source #
mkDelegTxCert :: StakeCredential -> Delegatee -> TxCert era Source #
getDelegTxCert :: TxCert era -> Maybe (StakeCredential, Delegatee) Source #
mkRegDepositDelegTxCert :: StakeCredential -> Delegatee -> Coin -> TxCert era Source #
getRegDepositDelegTxCert :: TxCert era -> Maybe (StakeCredential, Delegatee, Coin) Source #
mkAuthCommitteeHotKeyTxCert :: Credential 'ColdCommitteeRole -> Credential 'HotCommitteeRole -> TxCert era Source #
getAuthCommitteeHotKeyTxCert :: TxCert era -> Maybe (Credential 'ColdCommitteeRole, Credential 'HotCommitteeRole) Source #
mkResignCommitteeColdTxCert :: Credential 'ColdCommitteeRole -> StrictMaybe Anchor -> TxCert era Source #
getResignCommitteeColdTxCert :: TxCert era -> Maybe (Credential 'ColdCommitteeRole, StrictMaybe Anchor) Source #
mkRegDRepTxCert :: Credential 'DRepRole -> Coin -> StrictMaybe Anchor -> TxCert era Source #
getRegDRepTxCert :: TxCert era -> Maybe (Credential 'DRepRole, Coin, StrictMaybe Anchor) Source #
mkUnRegDRepTxCert :: Credential 'DRepRole -> Coin -> TxCert era Source #
getUnRegDRepTxCert :: TxCert era -> Maybe (Credential 'DRepRole, Coin) Source #
mkUpdateDRepTxCert :: Credential 'DRepRole -> StrictMaybe Anchor -> TxCert era Source #
getUpdateDRepTxCert :: TxCert era -> Maybe (Credential 'DRepRole, StrictMaybe Anchor) Source #
Instances
ConwayEraTxCert ConwayEra | |
Defined in Cardano.Ledger.Conway.TxCert Methods mkRegDepositTxCert :: StakeCredential -> Coin -> TxCert ConwayEra Source # getRegDepositTxCert :: TxCert ConwayEra -> Maybe (StakeCredential, Coin) Source # mkUnRegDepositTxCert :: StakeCredential -> Coin -> TxCert ConwayEra Source # getUnRegDepositTxCert :: TxCert ConwayEra -> Maybe (StakeCredential, Coin) Source # mkDelegTxCert :: StakeCredential -> Delegatee -> TxCert ConwayEra Source # getDelegTxCert :: TxCert ConwayEra -> Maybe (StakeCredential, Delegatee) Source # mkRegDepositDelegTxCert :: StakeCredential -> Delegatee -> Coin -> TxCert ConwayEra Source # getRegDepositDelegTxCert :: TxCert ConwayEra -> Maybe (StakeCredential, Delegatee, Coin) Source # mkAuthCommitteeHotKeyTxCert :: Credential 'ColdCommitteeRole -> Credential 'HotCommitteeRole -> TxCert ConwayEra Source # getAuthCommitteeHotKeyTxCert :: TxCert ConwayEra -> Maybe (Credential 'ColdCommitteeRole, Credential 'HotCommitteeRole) Source # mkResignCommitteeColdTxCert :: Credential 'ColdCommitteeRole -> StrictMaybe Anchor -> TxCert ConwayEra Source # getResignCommitteeColdTxCert :: TxCert ConwayEra -> Maybe (Credential 'ColdCommitteeRole, StrictMaybe Anchor) Source # mkRegDRepTxCert :: Credential 'DRepRole -> Coin -> StrictMaybe Anchor -> TxCert ConwayEra Source # getRegDRepTxCert :: TxCert ConwayEra -> Maybe (Credential 'DRepRole, Coin, StrictMaybe Anchor) Source # mkUnRegDRepTxCert :: Credential 'DRepRole -> Coin -> TxCert ConwayEra Source # getUnRegDRepTxCert :: TxCert ConwayEra -> Maybe (Credential 'DRepRole, Coin) Source # mkUpdateDRepTxCert :: Credential 'DRepRole -> StrictMaybe Anchor -> TxCert ConwayEra Source # getUpdateDRepTxCert :: TxCert ConwayEra -> Maybe (Credential 'DRepRole, StrictMaybe Anchor) Source # |
First type argument is the deposit
Constructors
DelegStake !(KeyHash 'StakePool) | |
DelegVote !DRep | |
DelegStakeVote !(KeyHash 'StakePool) !DRep |
Instances
FromJSON Delegatee | |||||
Defined in Cardano.Ledger.Conway.TxCert | |||||
ToJSON Delegatee | |||||
Defined in Cardano.Ledger.Conway.TxCert Methods toEncoding :: Delegatee -> Encoding toJSONList :: [Delegatee] -> Value toEncodingList :: [Delegatee] -> Encoding | |||||
Generic Delegatee | |||||
Defined in Cardano.Ledger.Conway.TxCert Associated Types
| |||||
Show Delegatee | |||||
DecCBOR Delegatee | |||||
EncCBOR Delegatee | |||||
NFData Delegatee | |||||
Defined in Cardano.Ledger.Conway.TxCert | |||||
Eq Delegatee | |||||
Ord Delegatee | |||||
Defined in Cardano.Ledger.Conway.TxCert | |||||
NoThunks Delegatee | |||||
type Rep Delegatee | |||||
Defined in Cardano.Ledger.Conway.TxCert type Rep Delegatee = D1 ('MetaData "Delegatee" "Cardano.Ledger.Conway.TxCert" "cardano-ledger-conway-1.19.0.0-4c27ba0e7c20c908d1dfe5f4038fdf7297360e4c38f5293876b47703f80d0e2c" 'False) (C1 ('MetaCons "DelegStake" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool))) :+: (C1 ('MetaCons "DelegVote" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DRep)) :+: C1 ('MetaCons "DelegStakeVote" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DRep)))) |
data ConwayPlutusPurpose (f :: Type -> Type -> Type) era Source #
Constructors
ConwaySpending !(f Word32 TxIn) | |
ConwayMinting !(f Word32 PolicyID) | |
ConwayCertifying !(f Word32 (TxCert era)) | |
ConwayRewarding !(f Word32 RewardAccount) | |
ConwayVoting !(f Word32 Voter) | |
ConwayProposing !(f Word32 (ProposalProcedure era)) |
Instances
(forall a b. (ToJSON a, ToJSON b) => ToJSON (f a b), ToJSON (TxCert era), EraPParams era) => ToJSON (ConwayPlutusPurpose f era) | |||||
Defined in Cardano.Ledger.Conway.Scripts Methods toJSON :: ConwayPlutusPurpose f era -> Value toEncoding :: ConwayPlutusPurpose f era -> Encoding toJSONList :: [ConwayPlutusPurpose f era] -> Value toEncodingList :: [ConwayPlutusPurpose f era] -> Encoding omitField :: ConwayPlutusPurpose f era -> Bool | |||||
Generic (ConwayPlutusPurpose f era) | |||||
Defined in Cardano.Ledger.Conway.Scripts Associated Types
Methods from :: ConwayPlutusPurpose f era -> Rep (ConwayPlutusPurpose f era) x Source # to :: Rep (ConwayPlutusPurpose f era) x -> ConwayPlutusPurpose f era Source # | |||||
(Show (TxCert era), EraPParams era) => Show (ConwayPlutusPurpose AsItem era) | |||||
Defined in Cardano.Ledger.Conway.Scripts | |||||
Show (ConwayPlutusPurpose AsIx era) | |||||
Defined in Cardano.Ledger.Conway.Scripts | |||||
(Show (TxCert era), EraPParams era) => Show (ConwayPlutusPurpose AsIxItem era) | |||||
Defined in Cardano.Ledger.Conway.Scripts | |||||
(forall a b. (EncCBOR a, EncCBOR b) => EncCBOR (f a b), forall a b. (DecCBOR a, DecCBOR b) => DecCBOR (f a b), EraPParams era, Typeable f, EncCBOR (TxCert era), DecCBOR (TxCert era)) => DecCBOR (ConwayPlutusPurpose f era) | |||||
Defined in Cardano.Ledger.Conway.Scripts | |||||
(forall a b. (EncCBOR a, EncCBOR b) => EncCBOR (f a b), EraPParams era, Typeable f, EncCBOR (TxCert era)) => EncCBOR (ConwayPlutusPurpose f era) | |||||
Defined in Cardano.Ledger.Conway.Scripts Methods encCBOR :: ConwayPlutusPurpose f era -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (ConwayPlutusPurpose f era) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ConwayPlutusPurpose f era] -> Size Source # | |||||
(forall a b. (DecCBOR a, DecCBOR b) => DecCBOR (f a b), EraPParams era, Typeable f, DecCBOR (TxCert era)) => DecCBORGroup (ConwayPlutusPurpose f era) | |||||
Defined in Cardano.Ledger.Conway.Scripts Methods decCBORGroup :: Decoder s (ConwayPlutusPurpose f era) Source # | |||||
(forall a b. (EncCBOR a, EncCBOR b) => EncCBOR (f a b), EraPParams era, Typeable f, EncCBOR (TxCert era)) => EncCBORGroup (ConwayPlutusPurpose f era) | |||||
Defined in Cardano.Ledger.Conway.Scripts Methods encCBORGroup :: ConwayPlutusPurpose f era -> Encoding Source # encodedGroupSizeExpr :: (forall x. EncCBOR x => Proxy x -> Size) -> Proxy (ConwayPlutusPurpose f era) -> Size Source # listLen :: ConwayPlutusPurpose f era -> Word Source # listLenBound :: Proxy (ConwayPlutusPurpose f era) -> Word Source # | |||||
(forall a b. (NFData a, NFData b) => NFData (f a b), NFData (TxCert era), EraPParams era) => NFData (ConwayPlutusPurpose f era) | |||||
Defined in Cardano.Ledger.Conway.Scripts Methods rnf :: ConwayPlutusPurpose f era -> () Source # | |||||
(Eq (TxCert era), EraPParams era) => Eq (ConwayPlutusPurpose AsItem era) | |||||
Defined in Cardano.Ledger.Conway.Scripts Methods (==) :: ConwayPlutusPurpose AsItem era -> ConwayPlutusPurpose AsItem era -> Bool Source # (/=) :: ConwayPlutusPurpose AsItem era -> ConwayPlutusPurpose AsItem era -> Bool Source # | |||||
Eq (ConwayPlutusPurpose AsIx era) | |||||
Defined in Cardano.Ledger.Conway.Scripts Methods (==) :: ConwayPlutusPurpose AsIx era -> ConwayPlutusPurpose AsIx era -> Bool Source # (/=) :: ConwayPlutusPurpose AsIx era -> ConwayPlutusPurpose AsIx era -> Bool Source # | |||||
(Eq (TxCert era), EraPParams era) => Eq (ConwayPlutusPurpose AsIxItem era) | |||||
Defined in Cardano.Ledger.Conway.Scripts Methods (==) :: ConwayPlutusPurpose AsIxItem era -> ConwayPlutusPurpose AsIxItem era -> Bool Source # (/=) :: ConwayPlutusPurpose AsIxItem era -> ConwayPlutusPurpose AsIxItem era -> Bool Source # | |||||
Ord (ConwayPlutusPurpose AsIx era) | |||||
Defined in Cardano.Ledger.Conway.Scripts Methods compare :: ConwayPlutusPurpose AsIx era -> ConwayPlutusPurpose AsIx era -> Ordering Source # (<) :: ConwayPlutusPurpose AsIx era -> ConwayPlutusPurpose AsIx era -> Bool Source # (<=) :: ConwayPlutusPurpose AsIx era -> ConwayPlutusPurpose AsIx era -> Bool Source # (>) :: ConwayPlutusPurpose AsIx era -> ConwayPlutusPurpose AsIx era -> Bool Source # (>=) :: ConwayPlutusPurpose AsIx era -> ConwayPlutusPurpose AsIx era -> Bool Source # max :: ConwayPlutusPurpose AsIx era -> ConwayPlutusPurpose AsIx era -> ConwayPlutusPurpose AsIx era Source # min :: ConwayPlutusPurpose AsIx era -> ConwayPlutusPurpose AsIx era -> ConwayPlutusPurpose AsIx era Source # | |||||
(NoThunks (TxCert era), EraPParams era) => NoThunks (ConwayPlutusPurpose AsItem era) | |||||
Defined in Cardano.Ledger.Conway.Scripts Methods noThunks :: Context -> ConwayPlutusPurpose AsItem era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> ConwayPlutusPurpose AsItem era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (ConwayPlutusPurpose AsItem era) -> String # | |||||
NoThunks (ConwayPlutusPurpose AsIx era) | |||||
Defined in Cardano.Ledger.Conway.Scripts Methods noThunks :: Context -> ConwayPlutusPurpose AsIx era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> ConwayPlutusPurpose AsIx era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (ConwayPlutusPurpose AsIx era) -> String # | |||||
(NoThunks (TxCert era), EraPParams era) => NoThunks (ConwayPlutusPurpose AsIxItem era) | |||||
Defined in Cardano.Ledger.Conway.Scripts Methods noThunks :: Context -> ConwayPlutusPurpose AsIxItem era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> ConwayPlutusPurpose AsIxItem era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (ConwayPlutusPurpose AsIxItem era) -> String # | |||||
type Rep (ConwayPlutusPurpose f era) | |||||
Defined in Cardano.Ledger.Conway.Scripts type Rep (ConwayPlutusPurpose f era) = D1 ('MetaData "ConwayPlutusPurpose" "Cardano.Ledger.Conway.Scripts" "cardano-ledger-conway-1.19.0.0-4c27ba0e7c20c908d1dfe5f4038fdf7297360e4c38f5293876b47703f80d0e2c" 'False) ((C1 ('MetaCons "ConwaySpending" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f Word32 TxIn))) :+: (C1 ('MetaCons "ConwayMinting" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f Word32 PolicyID))) :+: C1 ('MetaCons "ConwayCertifying" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f Word32 (TxCert era)))))) :+: (C1 ('MetaCons "ConwayRewarding" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f Word32 RewardAccount))) :+: (C1 ('MetaCons "ConwayVoting" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f Word32 Voter))) :+: C1 ('MetaCons "ConwayProposing" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f Word32 (ProposalProcedure era))))))) |
data ConwayGenesis Source #
Constructors
ConwayGenesis | |
Fields |
Instances
FromJSON ConwayGenesis | |||||
Defined in Cardano.Ledger.Conway.Genesis | |||||
ToJSON ConwayGenesis | |||||
Defined in Cardano.Ledger.Conway.Genesis Methods toJSON :: ConwayGenesis -> Value toEncoding :: ConwayGenesis -> Encoding toJSONList :: [ConwayGenesis] -> Value toEncodingList :: [ConwayGenesis] -> Encoding omitField :: ConwayGenesis -> Bool | |||||
Generic ConwayGenesis | |||||
Defined in Cardano.Ledger.Conway.Genesis Associated Types
Methods from :: ConwayGenesis -> Rep ConwayGenesis x Source # to :: Rep ConwayGenesis x -> ConwayGenesis Source # | |||||
Show ConwayGenesis | |||||
Defined in Cardano.Ledger.Conway.Genesis | |||||
FromCBOR ConwayGenesis | Genesis are always encoded with the version of era they are defined in. | ||||
Defined in Cardano.Ledger.Conway.Genesis | |||||
ToCBOR ConwayGenesis | |||||
Defined in Cardano.Ledger.Conway.Genesis Methods toCBOR :: ConwayGenesis -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy ConwayGenesis -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ConwayGenesis] -> Size Source # | |||||
DecCBOR ConwayGenesis | |||||
Defined in Cardano.Ledger.Conway.Genesis | |||||
EncCBOR ConwayGenesis | |||||
Defined in Cardano.Ledger.Conway.Genesis Methods encCBOR :: ConwayGenesis -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy ConwayGenesis -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ConwayGenesis] -> Size Source # | |||||
Eq ConwayGenesis | |||||
Defined in Cardano.Ledger.Conway.Genesis Methods (==) :: ConwayGenesis -> ConwayGenesis -> Bool Source # (/=) :: ConwayGenesis -> ConwayGenesis -> Bool Source # | |||||
NoThunks ConwayGenesis | |||||
Defined in Cardano.Ledger.Conway.Genesis Methods noThunks :: Context -> ConwayGenesis -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> ConwayGenesis -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy ConwayGenesis -> String # | |||||
type Rep ConwayGenesis | |||||
Defined in Cardano.Ledger.Conway.Genesis type Rep ConwayGenesis = D1 ('MetaData "ConwayGenesis" "Cardano.Ledger.Conway.Genesis" "cardano-ledger-conway-1.19.0.0-4c27ba0e7c20c908d1dfe5f4038fdf7297360e4c38f5293876b47703f80d0e2c" 'False) (C1 ('MetaCons "ConwayGenesis" 'PrefixI 'True) ((S1 ('MetaSel ('Just "cgUpgradePParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (UpgradeConwayPParams Identity)) :*: S1 ('MetaSel ('Just "cgConstitution") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Constitution ConwayEra))) :*: (S1 ('MetaSel ('Just "cgCommittee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Committee ConwayEra)) :*: (S1 ('MetaSel ('Just "cgDelegs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListMap (Credential 'Staking) Delegatee)) :*: S1 ('MetaSel ('Just "cgInitialDReps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListMap (Credential 'DRepRole) DRepState)))))) |
data WitVKey (kr :: KeyRole) where Source #
Proof/Witness that a transaction is authorized by the given key holder.
Bundled Patterns
pattern WitVKey :: Typeable kr => VKey kr -> SignedDSIGN DSIGN (Hash HASH EraIndependentTxBody) -> WitVKey kr |
Instances
Generic (WitVKey kr) | |||||
Defined in Cardano.Ledger.Keys.WitVKey Associated Types
| |||||
Show (WitVKey kr) | |||||
Typeable kr => ToCBOR (WitVKey kr) | |||||
Typeable kr => DecCBOR (Annotator (WitVKey kr)) | |||||
Typeable kr => DecCBOR (WitVKey kr) | |||||
Typeable kr => EncCBOR (WitVKey kr) | Encodes memoized bytes created upon construction. | ||||
Typeable kr => EqRaw (WitVKey kr) | |||||
NFData (WitVKey kr) | |||||
Defined in Cardano.Ledger.Keys.WitVKey | |||||
Eq (WitVKey kr) | |||||
Typeable kr => Ord (WitVKey kr) | |||||
Defined in Cardano.Ledger.Keys.WitVKey Methods compare :: WitVKey kr -> WitVKey kr -> Ordering Source # (<) :: WitVKey kr -> WitVKey kr -> Bool Source # (<=) :: WitVKey kr -> WitVKey kr -> Bool Source # (>) :: WitVKey kr -> WitVKey kr -> Bool Source # (>=) :: WitVKey kr -> WitVKey kr -> Bool Source # | |||||
Typeable kr => NoThunks (WitVKey kr) | |||||
type Rep (WitVKey kr) | |||||
Defined in Cardano.Ledger.Keys.WitVKey type Rep (WitVKey kr) = D1 ('MetaData "WitVKey" "Cardano.Ledger.Keys.WitVKey" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'False) (C1 ('MetaCons "WitVKeyInternal" 'PrefixI 'True) ((S1 ('MetaSel ('Just "wvkKey") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 (VKey kr)) :*: S1 ('MetaSel ('Just "wvkSig") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 (SignedDSIGN DSIGN (Hash HASH EraIndependentTxBody)))) :*: (S1 ('MetaSel ('Just "wvkKeyHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (KeyHash 'Witness)) :*: S1 ('MetaSel ('Just "wvkBytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))) |
hashAnchorData :: AnchorData -> SafeHash AnchorData Source #
Hash AnchorData
data RewardAccount Source #
An account based address for rewards
Constructors
RewardAccount | |
Fields
|
Instances
FromJSON RewardAccount | |||||
Defined in Cardano.Ledger.Address | |||||
FromJSONKey RewardAccount | |||||
Defined in Cardano.Ledger.Address Methods fromJSONKey :: FromJSONKeyFunction RewardAccount fromJSONKeyList :: FromJSONKeyFunction [RewardAccount] | |||||
ToJSON RewardAccount | |||||
Defined in Cardano.Ledger.Address Methods toJSON :: RewardAccount -> Value toEncoding :: RewardAccount -> Encoding toJSONList :: [RewardAccount] -> Value toEncodingList :: [RewardAccount] -> Encoding omitField :: RewardAccount -> Bool | |||||
ToJSONKey RewardAccount | |||||
Defined in Cardano.Ledger.Address Methods toJSONKey :: ToJSONKeyFunction RewardAccount toJSONKeyList :: ToJSONKeyFunction [RewardAccount] | |||||
Generic RewardAccount | |||||
Defined in Cardano.Ledger.Address Associated Types
Methods from :: RewardAccount -> Rep RewardAccount x Source # to :: Rep RewardAccount x -> RewardAccount Source # | |||||
Show RewardAccount | |||||
Defined in Cardano.Ledger.Address | |||||
DecCBOR RewardAccount | |||||
Defined in Cardano.Ledger.Address | |||||
EncCBOR RewardAccount | |||||
Defined in Cardano.Ledger.Address Methods encCBOR :: RewardAccount -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy RewardAccount -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [RewardAccount] -> Size Source # | |||||
Default RewardAccount | |||||
Defined in Cardano.Ledger.Address Methods def :: RewardAccount # | |||||
NFData RewardAccount | |||||
Defined in Cardano.Ledger.Address Methods rnf :: RewardAccount -> () Source # | |||||
Eq RewardAccount | |||||
Defined in Cardano.Ledger.Address Methods (==) :: RewardAccount -> RewardAccount -> Bool Source # (/=) :: RewardAccount -> RewardAccount -> Bool Source # | |||||
Ord RewardAccount | |||||
Defined in Cardano.Ledger.Address Methods compare :: RewardAccount -> RewardAccount -> Ordering Source # (<) :: RewardAccount -> RewardAccount -> Bool Source # (<=) :: RewardAccount -> RewardAccount -> Bool Source # (>) :: RewardAccount -> RewardAccount -> Bool Source # (>=) :: RewardAccount -> RewardAccount -> Bool Source # max :: RewardAccount -> RewardAccount -> RewardAccount Source # min :: RewardAccount -> RewardAccount -> RewardAccount Source # | |||||
NoThunks RewardAccount | |||||
Defined in Cardano.Ledger.Address Methods noThunks :: Context -> RewardAccount -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> RewardAccount -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy RewardAccount -> String # | |||||
type Rep RewardAccount | |||||
Defined in Cardano.Ledger.Address type Rep RewardAccount = D1 ('MetaData "RewardAccount" "Cardano.Ledger.Address" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'False) (C1 ('MetaCons "RewardAccount" 'PrefixI 'True) (S1 ('MetaSel ('Just "raNetwork") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Network) :*: S1 ('MetaSel ('Just "raCredential") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Credential 'Staking)))) |
data NewEpochState era Source #
New Epoch state and environment
Constructors
NewEpochState | |
Fields
|
Instances
CanGetInstantStake NewEpochState | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types Methods instantStakeG :: SimpleGetter (NewEpochState era) (InstantStake era) Source # | |||||
CanSetInstantStake NewEpochState | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types Methods instantStakeL :: Lens' (NewEpochState era) (InstantStake era) Source # | |||||
CanGetUTxO NewEpochState | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types Methods utxoG :: SimpleGetter (NewEpochState era) (UTxO era) Source # | |||||
CanSetUTxO NewEpochState | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types Methods utxoL :: Lens' (NewEpochState era) (UTxO era) Source # | |||||
Generic (NewEpochState era) | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types Associated Types
Methods from :: NewEpochState era -> Rep (NewEpochState era) x Source # to :: Rep (NewEpochState era) x -> NewEpochState era Source # | |||||
(EraTxOut era, Show (StashedAVVMAddresses era), Show (GovState era), Show (CertState era), Show (InstantStake era)) => Show (NewEpochState era) | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types | |||||
(EraTxOut era, EraGov era, EraStake era, EraCertState era, DecCBOR (StashedAVVMAddresses era)) => FromCBOR (NewEpochState era) | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types | |||||
(EraTxOut era, EraGov era, EraStake era, EraCertState era, EncCBOR (StashedAVVMAddresses era)) => ToCBOR (NewEpochState era) | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types Methods toCBOR :: NewEpochState era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (NewEpochState era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [NewEpochState era] -> Size Source # | |||||
(EraTxOut era, EraGov era, EraStake era, DecCBOR (StashedAVVMAddresses era), EraCertState era) => DecCBOR (NewEpochState era) | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types | |||||
(EraTxOut era, EraStake era, EncCBOR (StashedAVVMAddresses era), EncCBOR (GovState era), EncCBOR (CertState era)) => EncCBOR (NewEpochState era) | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types Methods encCBOR :: NewEpochState era -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (NewEpochState era) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [NewEpochState era] -> Size Source # | |||||
(EraTxOut era, NFData (StashedAVVMAddresses era), NFData (GovState era), NFData (CertState era), NFData (InstantStake era)) => NFData (NewEpochState era) | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types Methods rnf :: NewEpochState era -> () Source # | |||||
(EraTxOut era, Eq (StashedAVVMAddresses era), Eq (GovState era), Eq (CertState era), Eq (InstantStake era)) => Eq (NewEpochState era) | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types Methods (==) :: NewEpochState era -> NewEpochState era -> Bool Source # (/=) :: NewEpochState era -> NewEpochState era -> Bool Source # | |||||
(Era era, NoThunks (EpochState era), NoThunks (StashedAVVMAddresses era)) => NoThunks (NewEpochState era) | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types Methods noThunks :: Context -> NewEpochState era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> NewEpochState era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (NewEpochState era) -> String # | |||||
type TranslationError AllegraEra NewEpochState | |||||
Defined in Cardano.Ledger.Allegra.Translation | |||||
type TranslationError AlonzoEra NewEpochState | |||||
Defined in Cardano.Ledger.Alonzo.Translation | |||||
type TranslationError BabbageEra NewEpochState | |||||
Defined in Cardano.Ledger.Babbage.Translation | |||||
type TranslationError ConwayEra NewEpochState | |||||
Defined in Cardano.Ledger.Conway.Translation | |||||
type TranslationError MaryEra NewEpochState | |||||
Defined in Cardano.Ledger.Mary.Translation | |||||
type Rep (NewEpochState era) | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types type Rep (NewEpochState era) = D1 ('MetaData "NewEpochState" "Cardano.Ledger.Shelley.LedgerState.Types" "cardano-ledger-shelley-1.16.0.0-66390a9322bb0fb64b3f0442ebc385a2f8e5928f157dc0d1b8e0fcc9dabbabc0" 'False) (C1 ('MetaCons "NewEpochState" 'PrefixI 'True) ((S1 ('MetaSel ('Just "nesEL") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 EpochNo) :*: (S1 ('MetaSel ('Just "nesBprev") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlocksMade) :*: S1 ('MetaSel ('Just "nesBcur") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlocksMade))) :*: ((S1 ('MetaSel ('Just "nesEs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (EpochState era)) :*: S1 ('MetaSel ('Just "nesRu") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe PulsingRewUpdate))) :*: (S1 ('MetaSel ('Just "nesPd") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PoolDistr) :*: S1 ('MetaSel ('Just "stashedAVVMAddresses") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StashedAVVMAddresses era)))))) |
The amount of value held by a transaction output.
Instances
FromJSON Coin | |||||
Defined in Cardano.Ledger.Coin | |||||
ToJSON Coin | |||||
Defined in Cardano.Ledger.Coin Methods toEncoding :: Coin -> Encoding toJSONList :: [Coin] -> Value toEncodingList :: [Coin] -> Encoding | |||||
Monoid Coin | |||||
Semigroup Coin | |||||
Enum Coin | |||||
Generic Coin | |||||
Defined in Cardano.Ledger.Coin Associated Types
| |||||
Num Coin Source # | |||||
Integral Coin Source # | |||||
Defined in Cardano.Api.Internal.Orphans | |||||
Real Coin Source # | These instances originally existed on the Lovelace type. As the Lovelace type is deleted and we use L.Coin instead, these instances are added to L.Coin. The instances are purely for the convenience of writing expressions involving L.Coin but be aware that not all uses of these typeclasses are valid. | ||||
Defined in Cardano.Api.Internal.Orphans Methods toRational :: Coin -> Rational Source # | |||||
Show Coin | |||||
FromCBOR Coin | |||||
ToCBOR Coin | |||||
DecCBOR Coin | |||||
EncCBOR Coin | |||||
HasZero Coin | |||||
Compactible Coin | |||||
Defined in Cardano.Ledger.Coin Associated Types
Methods toCompact :: Coin -> Maybe (CompactForm Coin) Source # fromCompact :: CompactForm Coin -> Coin Source # | |||||
ToPlutusData Coin | |||||
Defined in Cardano.Ledger.Plutus.ToPlutusData | |||||
Val Coin | |||||
Defined in Cardano.Ledger.Val Methods (<+>) :: Coin -> Coin -> Coin Source # (<×>) :: Integral i => i -> Coin -> Coin Source # (<->) :: Coin -> Coin -> Coin Source # isZero :: Coin -> Bool Source # modifyCoin :: (Coin -> Coin) -> Coin -> Coin Source # size :: Coin -> Integer Source # pointwise :: (Integer -> Integer -> Bool) -> Coin -> Coin -> Bool Source # isAdaOnly :: Coin -> Bool Source # isAdaOnlyCompact :: CompactForm Coin -> Bool Source # coinCompact :: CompactForm Coin -> CompactForm Coin Source # injectCompact :: CompactForm Coin -> CompactForm Coin Source # modifyCompactCoin :: (CompactForm Coin -> CompactForm Coin) -> CompactForm Coin -> CompactForm Coin Source # | |||||
NFData Coin | |||||
Defined in Cardano.Ledger.Coin | |||||
Eq Coin | |||||
Ord Coin | |||||
Defined in Cardano.Ledger.Coin | |||||
Abelian Coin | |||||
Defined in Cardano.Ledger.Coin | |||||
Group Coin | |||||
HeapWords Coin | |||||
Defined in Cardano.Ledger.Coin | |||||
NoThunks Coin | |||||
PartialOrd Coin | |||||
Pretty Coin Source # | |||||
Defined in Cardano.Api.Internal.Orphans | |||||
Uniform Coin | |||||
Defined in Cardano.Ledger.Coin | |||||
UniformRange Coin | |||||
Defined in Cardano.Ledger.Coin | |||||
Inject Coin DeltaCoin | |||||
Inject Coin MaryValue | |||||
FromJSON (CompactForm Coin) | |||||
Defined in Cardano.Ledger.Coin Methods parseJSON :: Value -> Parser (CompactForm Coin) parseJSONList :: Value -> Parser [CompactForm Coin] omittedField :: Maybe (CompactForm Coin) | |||||
ToJSON (CompactForm Coin) | |||||
Defined in Cardano.Ledger.Coin Methods toJSON :: CompactForm Coin -> Value toEncoding :: CompactForm Coin -> Encoding toJSONList :: [CompactForm Coin] -> Value toEncodingList :: [CompactForm Coin] -> Encoding omitField :: CompactForm Coin -> Bool | |||||
Monoid (CompactForm Coin) | |||||
Defined in Cardano.Ledger.Coin Methods mempty :: CompactForm Coin Source # mappend :: CompactForm Coin -> CompactForm Coin -> CompactForm Coin Source # mconcat :: [CompactForm Coin] -> CompactForm Coin Source # | |||||
Semigroup (CompactForm Coin) | |||||
Defined in Cardano.Ledger.Coin Methods (<>) :: CompactForm Coin -> CompactForm Coin -> CompactForm Coin Source # sconcat :: NonEmpty (CompactForm Coin) -> CompactForm Coin Source # stimes :: Integral b => b -> CompactForm Coin -> CompactForm Coin Source # | |||||
Show (CompactForm Coin) | |||||
Defined in Cardano.Ledger.Coin | |||||
ToCBOR (CompactForm Coin) | |||||
Defined in Cardano.Ledger.Coin | |||||
DecCBOR (CompactForm Coin) | |||||
EncCBOR (CompactForm Coin) | |||||
Defined in Cardano.Ledger.Coin | |||||
NFData (CompactForm Coin) | |||||
Defined in Cardano.Ledger.Coin Methods rnf :: CompactForm Coin -> () Source # | |||||
Eq (CompactForm Coin) | |||||
Defined in Cardano.Ledger.Coin Methods (==) :: CompactForm Coin -> CompactForm Coin -> Bool Source # (/=) :: CompactForm Coin -> CompactForm Coin -> Bool Source # | |||||
Ord (CompactForm Coin) | |||||
Defined in Cardano.Ledger.Coin Methods compare :: CompactForm Coin -> CompactForm Coin -> Ordering Source # (<) :: CompactForm Coin -> CompactForm Coin -> Bool Source # (<=) :: CompactForm Coin -> CompactForm Coin -> Bool Source # (>) :: CompactForm Coin -> CompactForm Coin -> Bool Source # (>=) :: CompactForm Coin -> CompactForm Coin -> Bool Source # max :: CompactForm Coin -> CompactForm Coin -> CompactForm Coin Source # min :: CompactForm Coin -> CompactForm Coin -> CompactForm Coin Source # | |||||
Abelian (CompactForm Coin) | |||||
Defined in Cardano.Ledger.Coin | |||||
Group (CompactForm Coin) | |||||
Defined in Cardano.Ledger.Coin Methods invert :: CompactForm Coin -> CompactForm Coin (~~) :: CompactForm Coin -> CompactForm Coin -> CompactForm Coin pow :: Integral x => CompactForm Coin -> x -> CompactForm Coin | |||||
HeapWords (CompactForm Coin) | |||||
Defined in Cardano.Ledger.Coin Methods heapWords :: CompactForm Coin -> Int | |||||
MemPack (CompactForm Coin) | This instance prefixes with a 0 Tag for binary compatibility with compact form of multiassets. | ||||
Defined in Cardano.Ledger.Coin Methods packedByteCount :: CompactForm Coin -> Int packM :: CompactForm Coin -> Pack s () unpackM :: Buffer b => Unpack b (CompactForm Coin) | |||||
NoThunks (CompactForm Coin) | |||||
Defined in Cardano.Ledger.Coin Methods noThunks :: Context -> CompactForm Coin -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> CompactForm Coin -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (CompactForm Coin) -> String # | |||||
Prim (CompactForm Coin) | |||||
Defined in Cardano.Ledger.Coin Methods sizeOfType# :: Proxy (CompactForm Coin) -> Int# sizeOf# :: CompactForm Coin -> Int# alignmentOfType# :: Proxy (CompactForm Coin) -> Int# alignment# :: CompactForm Coin -> Int# indexByteArray# :: ByteArray# -> Int# -> CompactForm Coin readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CompactForm Coin #) writeByteArray# :: MutableByteArray# s -> Int# -> CompactForm Coin -> State# s -> State# s setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CompactForm Coin -> State# s -> State# s indexOffAddr# :: Addr# -> Int# -> CompactForm Coin readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CompactForm Coin #) writeOffAddr# :: Addr# -> Int# -> CompactForm Coin -> State# s -> State# s setOffAddr# :: Addr# -> Int# -> Int# -> CompactForm Coin -> State# s -> State# s | |||||
Uniform (CompactForm Coin) | |||||
Defined in Cardano.Ledger.Coin Methods uniformM :: StatefulGen g m => g -> m (CompactForm Coin) | |||||
UniformRange (CompactForm Coin) | |||||
Defined in Cardano.Ledger.Coin Methods uniformRM :: StatefulGen g m => (CompactForm Coin, CompactForm Coin) -> g -> m (CompactForm Coin) | |||||
type Rep Coin | |||||
Defined in Cardano.Ledger.Coin type Rep Coin = D1 ('MetaData "Coin" "Cardano.Ledger.Coin" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'True) (C1 ('MetaCons "Coin" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCoin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer))) | |||||
newtype CompactForm Coin | |||||
Defined in Cardano.Ledger.Coin |
serializeAsHexText :: ToCBOR a => a -> Text Source #
Encode a type as CBOR and encode it as base16
mkVersion :: (Integral i, MonadFail m) => i -> m Version Source #
Construct a Version
and fail if the supplied value is not a supported version number.
Arguments
:: Maybe ByteString | Some decoders require the original bytes to be supplied as well. Such decoders will
fail whenever |
-> Version | |
-> Decoder s a | |
-> Decoder s a |
Extract the underlying Decoder
by optionally supplying the original bytes and
specifying the concrete version to be used.
Constructors
Annotated | |
Fields
|
Instances
Bifunctor Annotated | |||||
Functor (Annotated b) | |||||
FromJSON b => FromJSON (Annotated b ()) | |||||
Defined in Cardano.Ledger.Binary.Decoding.Annotated Methods parseJSON :: Value -> Parser (Annotated b ()) parseJSONList :: Value -> Parser [Annotated b ()] omittedField :: Maybe (Annotated b ()) | |||||
ToJSON b => ToJSON (Annotated b a) | |||||
Defined in Cardano.Ledger.Binary.Decoding.Annotated Methods toJSON :: Annotated b a -> Value toEncoding :: Annotated b a -> Encoding toJSONList :: [Annotated b a] -> Value toEncodingList :: [Annotated b a] -> Encoding | |||||
Generic (Annotated b a) | |||||
Defined in Cardano.Ledger.Binary.Decoding.Annotated Associated Types
| |||||
(Show b, Show a) => Show (Annotated b a) | |||||
Decoded (Annotated b ByteString) | |||||
Defined in Cardano.Ledger.Binary.Decoding.Annotated Associated Types
Methods recoverBytes :: Annotated b ByteString -> ByteString Source # | |||||
DecCBOR a => DecCBOR (Annotated a ByteString) | |||||
(NFData b, NFData a) => NFData (Annotated b a) | |||||
Defined in Cardano.Ledger.Binary.Decoding.Annotated | |||||
(Eq b, Eq a) => Eq (Annotated b a) | |||||
(Eq a, Ord b) => Ord (Annotated b a) | |||||
Defined in Cardano.Ledger.Binary.Decoding.Annotated Methods compare :: Annotated b a -> Annotated b a -> Ordering Source # (<) :: Annotated b a -> Annotated b a -> Bool Source # (<=) :: Annotated b a -> Annotated b a -> Bool Source # (>) :: Annotated b a -> Annotated b a -> Bool Source # (>=) :: Annotated b a -> Annotated b a -> Bool Source # max :: Annotated b a -> Annotated b a -> Annotated b a Source # min :: Annotated b a -> Annotated b a -> Annotated b a Source # | |||||
(NoThunks b, NoThunks a) => NoThunks (Annotated b a) | |||||
HasSignTag (Annotated ToSign ByteString) | |||||
Defined in Ouroboros.Consensus.Byron.Crypto.DSIGN Methods signTag :: VerKeyDSIGN ByronDSIGN -> proxy (Annotated ToSign ByteString) -> SignTag Source # | |||||
type Rep (Annotated b a) | |||||
Defined in Cardano.Ledger.Binary.Decoding.Annotated type Rep (Annotated b a) = D1 ('MetaData "Annotated" "Cardano.Ledger.Binary.Decoding.Annotated" "cardano-ledger-binary-1.6.0.0-6bbb0a2902fd9319920d178667f54ff9f221f2d87b67cfcbbc2019c86d31adb0" 'False) (C1 ('MetaCons "Annotated" 'PrefixI 'True) (S1 ('MetaSel ('Just "unAnnotated") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "annotation") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a))) | |||||
type BaseType (Annotated b ByteString) | |||||
Defined in Cardano.Ledger.Binary.Decoding.Annotated |
A pair of offsets delimiting the beginning and end of a substring of a ByteString
Constructors
ByteSpan !ByteOffset !ByteOffset |
Instances
ToJSON ByteSpan | |||||
Defined in Cardano.Ledger.Binary.Decoding.Annotated Methods toEncoding :: ByteSpan -> Encoding toJSONList :: [ByteSpan] -> Value toEncodingList :: [ByteSpan] -> Encoding | |||||
Generic ByteSpan | |||||
Defined in Cardano.Ledger.Binary.Decoding.Annotated Associated Types
| |||||
Show ByteSpan | |||||
FromCBOR (ABody ByteSpan) | |||||
FromCBOR (ABlockSignature ByteSpan) | |||||
Defined in Cardano.Chain.Block.Header | |||||
FromCBOR (ACertificate ByteSpan) | |||||
Defined in Cardano.Chain.Delegation.Certificate | |||||
FromCBOR (APayload ByteSpan) | |||||
FromCBOR (AMempoolPayload ByteSpan) | |||||
Defined in Cardano.Chain.MempoolPayload | |||||
FromCBOR (ATxAux ByteSpan) | |||||
FromCBOR (ATxPayload ByteSpan) | |||||
Defined in Cardano.Chain.UTxO.TxPayload | |||||
FromCBOR (APayload ByteSpan) | |||||
FromCBOR (AProposal ByteSpan) | |||||
FromCBOR (AVote ByteSpan) | |||||
DecCBOR (ABody ByteSpan) | |||||
DecCBOR (ABlockSignature ByteSpan) | |||||
DecCBOR (ACertificate ByteSpan) | |||||
DecCBOR (APayload ByteSpan) | |||||
DecCBOR (AMempoolPayload ByteSpan) | |||||
DecCBOR (ATxAux ByteSpan) | |||||
DecCBOR (ATxPayload ByteSpan) | |||||
DecCBOR (APayload ByteSpan) | |||||
DecCBOR (AProposal ByteSpan) | |||||
DecCBOR (AVote ByteSpan) | |||||
type Rep ByteSpan | |||||
Defined in Cardano.Ledger.Binary.Decoding.Annotated type Rep ByteSpan = D1 ('MetaData "ByteSpan" "Cardano.Ledger.Binary.Decoding.Annotated" "cardano-ledger-binary-1.6.0.0-6bbb0a2902fd9319920d178667f54ff9f221f2d87b67cfcbbc2019c86d31adb0" 'False) (C1 ('MetaCons "ByteSpan" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ByteOffset) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 ByteOffset))) |
class (UnsoundPureKESAlgorithm (KES c), VRFAlgorithm (VRF c), ContextKES (KES c) ~ (), ContextVRF (VRF c) ~ (), Typeable c) => Crypto c Source #
Instances
Crypto StandardCrypto | |||||||||
Defined in Cardano.Ledger.Crypto.Internal Associated Types
|
Constructors
Committee | |
Fields
|
Instances
Era era => FromJSON (Committee era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods parseJSON :: Value -> Parser (Committee era) parseJSONList :: Value -> Parser [Committee era] omittedField :: Maybe (Committee era) | |||||
EraPParams era => ToJSON (Committee era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods toJSON :: Committee era -> Value toEncoding :: Committee era -> Encoding toJSONList :: [Committee era] -> Value toEncodingList :: [Committee era] -> Encoding | |||||
Generic (Committee era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures Associated Types
| |||||
Show (Committee era) | |||||
Era era => DecCBOR (Committee era) | |||||
Era era => EncCBOR (Committee era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
Default (Committee era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
Era era => NFData (Committee era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
Eq (Committee era) | |||||
Era era => NoThunks (Committee era) | |||||
type Rep (Committee era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures type Rep (Committee era) = D1 ('MetaData "Committee" "Cardano.Ledger.Conway.Governance.Procedures" "cardano-ledger-conway-1.19.0.0-4c27ba0e7c20c908d1dfe5f4038fdf7297360e4c38f5293876b47703f80d0e2c" 'False) (C1 ('MetaCons "Committee" 'PrefixI 'True) (S1 ('MetaSel ('Just "committeeMembers") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (Credential 'ColdCommitteeRole) EpochNo)) :*: S1 ('MetaSel ('Just "committeeThreshold") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitInterval))) |
data DRepVotingThresholds Source #
Constructors
DRepVotingThresholds | |
Fields
|
Instances
FromJSON DRepVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams Methods parseJSON :: Value -> Parser DRepVotingThresholds parseJSONList :: Value -> Parser [DRepVotingThresholds] | |||||
ToJSON DRepVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams Methods toJSON :: DRepVotingThresholds -> Value toEncoding :: DRepVotingThresholds -> Encoding toJSONList :: [DRepVotingThresholds] -> Value toEncodingList :: [DRepVotingThresholds] -> Encoding | |||||
Generic DRepVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams Associated Types
Methods from :: DRepVotingThresholds -> Rep DRepVotingThresholds x Source # to :: Rep DRepVotingThresholds x -> DRepVotingThresholds Source # | |||||
Show DRepVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams | |||||
DecCBOR DRepVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams | |||||
EncCBOR DRepVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams Methods encCBOR :: DRepVotingThresholds -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy DRepVotingThresholds -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [DRepVotingThresholds] -> Size Source # | |||||
Default DRepVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams Methods | |||||
NFData DRepVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams Methods rnf :: DRepVotingThresholds -> () Source # | |||||
Eq DRepVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams Methods (==) :: DRepVotingThresholds -> DRepVotingThresholds -> Bool Source # (/=) :: DRepVotingThresholds -> DRepVotingThresholds -> Bool Source # | |||||
Ord DRepVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams Methods compare :: DRepVotingThresholds -> DRepVotingThresholds -> Ordering Source # (<) :: DRepVotingThresholds -> DRepVotingThresholds -> Bool Source # (<=) :: DRepVotingThresholds -> DRepVotingThresholds -> Bool Source # (>) :: DRepVotingThresholds -> DRepVotingThresholds -> Bool Source # (>=) :: DRepVotingThresholds -> DRepVotingThresholds -> Bool Source # max :: DRepVotingThresholds -> DRepVotingThresholds -> DRepVotingThresholds Source # min :: DRepVotingThresholds -> DRepVotingThresholds -> DRepVotingThresholds Source # | |||||
NoThunks DRepVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams Methods noThunks :: Context -> DRepVotingThresholds -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> DRepVotingThresholds -> IO (Maybe ThunkInfo) # | |||||
type Rep DRepVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams type Rep DRepVotingThresholds = D1 ('MetaData "DRepVotingThresholds" "Cardano.Ledger.Conway.PParams" "cardano-ledger-conway-1.19.0.0-4c27ba0e7c20c908d1dfe5f4038fdf7297360e4c38f5293876b47703f80d0e2c" 'False) (C1 ('MetaCons "DRepVotingThresholds" 'PrefixI 'True) (((S1 ('MetaSel ('Just "dvtMotionNoConfidence") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitInterval) :*: S1 ('MetaSel ('Just "dvtCommitteeNormal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitInterval)) :*: (S1 ('MetaSel ('Just "dvtCommitteeNoConfidence") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitInterval) :*: (S1 ('MetaSel ('Just "dvtUpdateToConstitution") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitInterval) :*: S1 ('MetaSel ('Just "dvtHardForkInitiation") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitInterval)))) :*: ((S1 ('MetaSel ('Just "dvtPPNetworkGroup") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitInterval) :*: S1 ('MetaSel ('Just "dvtPPEconomicGroup") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitInterval)) :*: (S1 ('MetaSel ('Just "dvtPPTechnicalGroup") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitInterval) :*: (S1 ('MetaSel ('Just "dvtPPGovGroup") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitInterval) :*: S1 ('MetaSel ('Just "dvtTreasuryWithdrawal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitInterval)))))) |
data PoolVotingThresholds Source #
Constructors
PoolVotingThresholds | |
Instances
FromJSON PoolVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams Methods parseJSON :: Value -> Parser PoolVotingThresholds parseJSONList :: Value -> Parser [PoolVotingThresholds] | |||||
ToJSON PoolVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams Methods toJSON :: PoolVotingThresholds -> Value toEncoding :: PoolVotingThresholds -> Encoding toJSONList :: [PoolVotingThresholds] -> Value toEncodingList :: [PoolVotingThresholds] -> Encoding | |||||
Generic PoolVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams Associated Types
Methods from :: PoolVotingThresholds -> Rep PoolVotingThresholds x Source # to :: Rep PoolVotingThresholds x -> PoolVotingThresholds Source # | |||||
Show PoolVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams | |||||
DecCBOR PoolVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams | |||||
EncCBOR PoolVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams Methods encCBOR :: PoolVotingThresholds -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy PoolVotingThresholds -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [PoolVotingThresholds] -> Size Source # | |||||
Default PoolVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams Methods | |||||
NFData PoolVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams Methods rnf :: PoolVotingThresholds -> () Source # | |||||
Eq PoolVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams Methods (==) :: PoolVotingThresholds -> PoolVotingThresholds -> Bool Source # (/=) :: PoolVotingThresholds -> PoolVotingThresholds -> Bool Source # | |||||
Ord PoolVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams Methods compare :: PoolVotingThresholds -> PoolVotingThresholds -> Ordering Source # (<) :: PoolVotingThresholds -> PoolVotingThresholds -> Bool Source # (<=) :: PoolVotingThresholds -> PoolVotingThresholds -> Bool Source # (>) :: PoolVotingThresholds -> PoolVotingThresholds -> Bool Source # (>=) :: PoolVotingThresholds -> PoolVotingThresholds -> Bool Source # max :: PoolVotingThresholds -> PoolVotingThresholds -> PoolVotingThresholds Source # min :: PoolVotingThresholds -> PoolVotingThresholds -> PoolVotingThresholds Source # | |||||
NoThunks PoolVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams Methods noThunks :: Context -> PoolVotingThresholds -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> PoolVotingThresholds -> IO (Maybe ThunkInfo) # | |||||
type Rep PoolVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams type Rep PoolVotingThresholds = D1 ('MetaData "PoolVotingThresholds" "Cardano.Ledger.Conway.PParams" "cardano-ledger-conway-1.19.0.0-4c27ba0e7c20c908d1dfe5f4038fdf7297360e4c38f5293876b47703f80d0e2c" 'False) (C1 ('MetaCons "PoolVotingThresholds" 'PrefixI 'True) ((S1 ('MetaSel ('Just "pvtMotionNoConfidence") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitInterval) :*: S1 ('MetaSel ('Just "pvtCommitteeNormal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitInterval)) :*: (S1 ('MetaSel ('Just "pvtCommitteeNoConfidence") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitInterval) :*: (S1 ('MetaSel ('Just "pvtHardForkInitiation") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitInterval) :*: S1 ('MetaSel ('Just "pvtPPSecurityGroup") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitInterval))))) |
data UpgradeConwayPParams (f :: Type -> Type) Source #
Constructors
UpgradeConwayPParams | |
Fields
|
Instances
FromJSON (UpgradeConwayPParams Identity) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods parseJSON :: Value -> Parser (UpgradeConwayPParams Identity) parseJSONList :: Value -> Parser [UpgradeConwayPParams Identity] | |||||
ToJSON (UpgradeConwayPParams Identity) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods toJSON :: UpgradeConwayPParams Identity -> Value toEncoding :: UpgradeConwayPParams Identity -> Encoding toJSONList :: [UpgradeConwayPParams Identity] -> Value toEncodingList :: [UpgradeConwayPParams Identity] -> Encoding | |||||
Generic (UpgradeConwayPParams f) | |||||
Defined in Cardano.Ledger.Conway.PParams Associated Types
Methods from :: UpgradeConwayPParams f -> Rep (UpgradeConwayPParams f) x Source # to :: Rep (UpgradeConwayPParams f) x -> UpgradeConwayPParams f Source # | |||||
Show (UpgradeConwayPParams Identity) | |||||
Defined in Cardano.Ledger.Conway.PParams | |||||
Show (UpgradeConwayPParams StrictMaybe) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods showsPrec :: Int -> UpgradeConwayPParams StrictMaybe -> ShowS Source # show :: UpgradeConwayPParams StrictMaybe -> String Source # showList :: [UpgradeConwayPParams StrictMaybe] -> ShowS Source # | |||||
DecCBOR (UpgradeConwayPParams Identity) | |||||
EncCBOR (UpgradeConwayPParams Identity) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods encCBOR :: UpgradeConwayPParams Identity -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (UpgradeConwayPParams Identity) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [UpgradeConwayPParams Identity] -> Size Source # | |||||
Default (UpgradeConwayPParams StrictMaybe) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods | |||||
NFData (UpgradeConwayPParams Identity) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods rnf :: UpgradeConwayPParams Identity -> () Source # | |||||
NFData (UpgradeConwayPParams StrictMaybe) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods rnf :: UpgradeConwayPParams StrictMaybe -> () Source # | |||||
Eq (UpgradeConwayPParams Identity) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods (==) :: UpgradeConwayPParams Identity -> UpgradeConwayPParams Identity -> Bool Source # (/=) :: UpgradeConwayPParams Identity -> UpgradeConwayPParams Identity -> Bool Source # | |||||
Eq (UpgradeConwayPParams StrictMaybe) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods (==) :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> Bool Source # (/=) :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> Bool Source # | |||||
Ord (UpgradeConwayPParams Identity) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods compare :: UpgradeConwayPParams Identity -> UpgradeConwayPParams Identity -> Ordering Source # (<) :: UpgradeConwayPParams Identity -> UpgradeConwayPParams Identity -> Bool Source # (<=) :: UpgradeConwayPParams Identity -> UpgradeConwayPParams Identity -> Bool Source # (>) :: UpgradeConwayPParams Identity -> UpgradeConwayPParams Identity -> Bool Source # (>=) :: UpgradeConwayPParams Identity -> UpgradeConwayPParams Identity -> Bool Source # max :: UpgradeConwayPParams Identity -> UpgradeConwayPParams Identity -> UpgradeConwayPParams Identity Source # min :: UpgradeConwayPParams Identity -> UpgradeConwayPParams Identity -> UpgradeConwayPParams Identity Source # | |||||
Ord (UpgradeConwayPParams StrictMaybe) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods compare :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> Ordering Source # (<) :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> Bool Source # (<=) :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> Bool Source # (>) :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> Bool Source # (>=) :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> Bool Source # max :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe Source # min :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe Source # | |||||
NoThunks (UpgradeConwayPParams Identity) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods noThunks :: Context -> UpgradeConwayPParams Identity -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> UpgradeConwayPParams Identity -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (UpgradeConwayPParams Identity) -> String # | |||||
NoThunks (UpgradeConwayPParams StrictMaybe) | |||||
Defined in Cardano.Ledger.Conway.PParams Methods noThunks :: Context -> UpgradeConwayPParams StrictMaybe -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> UpgradeConwayPParams StrictMaybe -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (UpgradeConwayPParams StrictMaybe) -> String # | |||||
type Rep (UpgradeConwayPParams f) | |||||
Defined in Cardano.Ledger.Conway.PParams type Rep (UpgradeConwayPParams f) = D1 ('MetaData "UpgradeConwayPParams" "Cardano.Ledger.Conway.PParams" "cardano-ledger-conway-1.19.0.0-4c27ba0e7c20c908d1dfe5f4038fdf7297360e4c38f5293876b47703f80d0e2c" 'False) (C1 ('MetaCons "UpgradeConwayPParams" 'PrefixI 'True) (((S1 ('MetaSel ('Just "ucppPoolVotingThresholds") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HKD f PoolVotingThresholds)) :*: S1 ('MetaSel ('Just "ucppDRepVotingThresholds") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HKD f DRepVotingThresholds))) :*: (S1 ('MetaSel ('Just "ucppCommitteeMinSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HKD f Word16)) :*: (S1 ('MetaSel ('Just "ucppCommitteeMaxTermLength") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HKD f EpochInterval)) :*: S1 ('MetaSel ('Just "ucppGovActionLifetime") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HKD f EpochInterval))))) :*: ((S1 ('MetaSel ('Just "ucppGovActionDeposit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HKD f Coin)) :*: S1 ('MetaSel ('Just "ucppDRepDeposit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HKD f Coin))) :*: (S1 ('MetaSel ('Just "ucppDRepActivity") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HKD f EpochInterval)) :*: (S1 ('MetaSel ('Just "ucppMinFeeRefScriptCostPerByte") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HKD f NonNegativeInterval)) :*: S1 ('MetaSel ('Just "ucppPlutusV3CostModel") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HKD f CostModel))))))) |
pattern UpdateDRepTxCert :: ConwayEraTxCert era => Credential 'DRepRole -> StrictMaybe Anchor -> TxCert era Source #
data ConwayDelegCert Source #
Certificates for registration and delegation of stake to Pools and DReps. Comparing to previous eras, there is now ability to:
- Register and delegate with a single certificate:
ConwayRegDelegCert
- Ability to delegate to DReps with
DelegVote
andDelegStakeVote
- Ability to specify the deposit amount. Deposits during registration and
unregistration in Conway are optional, which will change in the future era. They are
optional only for the smooth transition from Babbage to Conway. Validity of deposits
is checked by the
CERT
rule.
Constructors
ConwayRegCert !StakeCredential !(StrictMaybe Coin) | Register staking credential. Deposit, when present, must match the expected deposit
amount specified by |
ConwayUnRegCert !StakeCredential !(StrictMaybe Coin) | De-Register the staking credential. Deposit, if present, must match the amount that was left as a deposit upon stake credential registration. |
ConwayDelegCert !StakeCredential !Delegatee | Delegate staking credentials to a delegatee. Staking credential must already be registered. |
ConwayRegDelegCert !StakeCredential !Delegatee !Coin | This is a new type of certificate, which allows to register staking credential
and delegate within a single certificate. Deposit is required and must match the
expected deposit amount specified by |
Instances
ToJSON ConwayDelegCert | |||||
Defined in Cardano.Ledger.Conway.TxCert Methods toJSON :: ConwayDelegCert -> Value toEncoding :: ConwayDelegCert -> Encoding toJSONList :: [ConwayDelegCert] -> Value toEncodingList :: [ConwayDelegCert] -> Encoding omitField :: ConwayDelegCert -> Bool | |||||
Generic ConwayDelegCert | |||||
Defined in Cardano.Ledger.Conway.TxCert Associated Types
Methods from :: ConwayDelegCert -> Rep ConwayDelegCert x Source # to :: Rep ConwayDelegCert x -> ConwayDelegCert Source # | |||||
Show ConwayDelegCert | |||||
Defined in Cardano.Ledger.Conway.TxCert | |||||
EncCBOR ConwayDelegCert | |||||
Defined in Cardano.Ledger.Conway.TxCert Methods encCBOR :: ConwayDelegCert -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy ConwayDelegCert -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ConwayDelegCert] -> Size Source # | |||||
NFData ConwayDelegCert | |||||
Defined in Cardano.Ledger.Conway.TxCert Methods rnf :: ConwayDelegCert -> () Source # | |||||
Eq ConwayDelegCert | |||||
Defined in Cardano.Ledger.Conway.TxCert Methods (==) :: ConwayDelegCert -> ConwayDelegCert -> Bool Source # (/=) :: ConwayDelegCert -> ConwayDelegCert -> Bool Source # | |||||
Ord ConwayDelegCert | |||||
Defined in Cardano.Ledger.Conway.TxCert Methods compare :: ConwayDelegCert -> ConwayDelegCert -> Ordering Source # (<) :: ConwayDelegCert -> ConwayDelegCert -> Bool Source # (<=) :: ConwayDelegCert -> ConwayDelegCert -> Bool Source # (>) :: ConwayDelegCert -> ConwayDelegCert -> Bool Source # (>=) :: ConwayDelegCert -> ConwayDelegCert -> Bool Source # max :: ConwayDelegCert -> ConwayDelegCert -> ConwayDelegCert Source # min :: ConwayDelegCert -> ConwayDelegCert -> ConwayDelegCert Source # | |||||
NoThunks ConwayDelegCert | |||||
Defined in Cardano.Ledger.Conway.TxCert Methods noThunks :: Context -> ConwayDelegCert -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> ConwayDelegCert -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy ConwayDelegCert -> String # | |||||
type Rep ConwayDelegCert | |||||
Defined in Cardano.Ledger.Conway.TxCert type Rep ConwayDelegCert = D1 ('MetaData "ConwayDelegCert" "Cardano.Ledger.Conway.TxCert" "cardano-ledger-conway-1.19.0.0-4c27ba0e7c20c908d1dfe5f4038fdf7297360e4c38f5293876b47703f80d0e2c" 'False) ((C1 ('MetaCons "ConwayRegCert" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StakeCredential) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe Coin))) :+: C1 ('MetaCons "ConwayUnRegCert" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StakeCredential) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe Coin)))) :+: (C1 ('MetaCons "ConwayDelegCert" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StakeCredential) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Delegatee)) :+: C1 ('MetaCons "ConwayRegDelegCert" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StakeCredential) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Delegatee) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin))))) |
data ConwayGovCert Source #
Constructors
ConwayRegDRep !(Credential 'DRepRole) !Coin !(StrictMaybe Anchor) | |
ConwayUnRegDRep !(Credential 'DRepRole) !Coin | |
ConwayUpdateDRep !(Credential 'DRepRole) !(StrictMaybe Anchor) | |
ConwayAuthCommitteeHotKey !(Credential 'ColdCommitteeRole) !(Credential 'HotCommitteeRole) | |
ConwayResignCommitteeColdKey !(Credential 'ColdCommitteeRole) !(StrictMaybe Anchor) |
Instances
ToJSON ConwayGovCert | |||||
Defined in Cardano.Ledger.Conway.TxCert Methods toJSON :: ConwayGovCert -> Value toEncoding :: ConwayGovCert -> Encoding toJSONList :: [ConwayGovCert] -> Value toEncodingList :: [ConwayGovCert] -> Encoding omitField :: ConwayGovCert -> Bool | |||||
Generic ConwayGovCert | |||||
Defined in Cardano.Ledger.Conway.TxCert Associated Types
Methods from :: ConwayGovCert -> Rep ConwayGovCert x Source # to :: Rep ConwayGovCert x -> ConwayGovCert Source # | |||||
Show ConwayGovCert | |||||
Defined in Cardano.Ledger.Conway.TxCert | |||||
EncCBOR ConwayGovCert | |||||
Defined in Cardano.Ledger.Conway.TxCert Methods encCBOR :: ConwayGovCert -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy ConwayGovCert -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ConwayGovCert] -> Size Source # | |||||
NFData ConwayGovCert | |||||
Defined in Cardano.Ledger.Conway.TxCert Methods rnf :: ConwayGovCert -> () Source # | |||||
Eq ConwayGovCert | |||||
Defined in Cardano.Ledger.Conway.TxCert Methods (==) :: ConwayGovCert -> ConwayGovCert -> Bool Source # (/=) :: ConwayGovCert -> ConwayGovCert -> Bool Source # | |||||
Ord ConwayGovCert | |||||
Defined in Cardano.Ledger.Conway.TxCert Methods compare :: ConwayGovCert -> ConwayGovCert -> Ordering Source # (<) :: ConwayGovCert -> ConwayGovCert -> Bool Source # (<=) :: ConwayGovCert -> ConwayGovCert -> Bool Source # (>) :: ConwayGovCert -> ConwayGovCert -> Bool Source # (>=) :: ConwayGovCert -> ConwayGovCert -> Bool Source # max :: ConwayGovCert -> ConwayGovCert -> ConwayGovCert Source # min :: ConwayGovCert -> ConwayGovCert -> ConwayGovCert Source # | |||||
NoThunks ConwayGovCert | |||||
Defined in Cardano.Ledger.Conway.TxCert Methods noThunks :: Context -> ConwayGovCert -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> ConwayGovCert -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy ConwayGovCert -> String # | |||||
type Rep ConwayGovCert | |||||
Defined in Cardano.Ledger.Conway.TxCert type Rep ConwayGovCert = D1 ('MetaData "ConwayGovCert" "Cardano.Ledger.Conway.TxCert" "cardano-ledger-conway-1.19.0.0-4c27ba0e7c20c908d1dfe5f4038fdf7297360e4c38f5293876b47703f80d0e2c" 'False) ((C1 ('MetaCons "ConwayRegDRep" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Credential 'DRepRole)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe Anchor)))) :+: C1 ('MetaCons "ConwayUnRegDRep" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Credential 'DRepRole)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin))) :+: (C1 ('MetaCons "ConwayUpdateDRep" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Credential 'DRepRole)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe Anchor))) :+: (C1 ('MetaCons "ConwayAuthCommitteeHotKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Credential 'ColdCommitteeRole)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Credential 'HotCommitteeRole))) :+: C1 ('MetaCons "ConwayResignCommitteeColdKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Credential 'ColdCommitteeRole)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe Anchor)))))) |
data ConwayTxCert era Source #
Constructors
ConwayTxCertDeleg !ConwayDelegCert | |
ConwayTxCertPool !PoolCert | |
ConwayTxCertGov !ConwayGovCert |
Instances
Era era => ToJSON (ConwayTxCert era) | |||||
Defined in Cardano.Ledger.Conway.TxCert Methods toJSON :: ConwayTxCert era -> Value toEncoding :: ConwayTxCert era -> Encoding toJSONList :: [ConwayTxCert era] -> Value toEncodingList :: [ConwayTxCert era] -> Encoding omitField :: ConwayTxCert era -> Bool | |||||
Generic (ConwayTxCert era) | |||||
Defined in Cardano.Ledger.Conway.TxCert Associated Types
Methods from :: ConwayTxCert era -> Rep (ConwayTxCert era) x Source # to :: Rep (ConwayTxCert era) x -> ConwayTxCert era Source # | |||||
Show (ConwayTxCert era) | |||||
Defined in Cardano.Ledger.Conway.TxCert | |||||
(ShelleyEraTxCert era, TxCert era ~ ConwayTxCert era) => FromCBOR (ConwayTxCert era) | |||||
Defined in Cardano.Ledger.Conway.TxCert | |||||
(Era era, Val (Value era)) => ToCBOR (ConwayTxCert era) | |||||
Defined in Cardano.Ledger.Conway.TxCert Methods toCBOR :: ConwayTxCert era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ConwayTxCert era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ConwayTxCert era] -> Size Source # | |||||
(ConwayEraTxCert era, TxCert era ~ ConwayTxCert era) => DecCBOR (ConwayTxCert era) | |||||
Defined in Cardano.Ledger.Conway.TxCert | |||||
(Era era, Val (Value era)) => EncCBOR (ConwayTxCert era) | |||||
Defined in Cardano.Ledger.Conway.TxCert Methods encCBOR :: ConwayTxCert era -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (ConwayTxCert era) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ConwayTxCert era] -> Size Source # | |||||
NFData (ConwayTxCert era) | |||||
Defined in Cardano.Ledger.Conway.TxCert Methods rnf :: ConwayTxCert era -> () Source # | |||||
Eq (ConwayTxCert era) | |||||
Defined in Cardano.Ledger.Conway.TxCert Methods (==) :: ConwayTxCert era -> ConwayTxCert era -> Bool Source # (/=) :: ConwayTxCert era -> ConwayTxCert era -> Bool Source # | |||||
Ord (ConwayTxCert era) | |||||
Defined in Cardano.Ledger.Conway.TxCert Methods compare :: ConwayTxCert era -> ConwayTxCert era -> Ordering Source # (<) :: ConwayTxCert era -> ConwayTxCert era -> Bool Source # (<=) :: ConwayTxCert era -> ConwayTxCert era -> Bool Source # (>) :: ConwayTxCert era -> ConwayTxCert era -> Bool Source # (>=) :: ConwayTxCert era -> ConwayTxCert era -> Bool Source # max :: ConwayTxCert era -> ConwayTxCert era -> ConwayTxCert era Source # min :: ConwayTxCert era -> ConwayTxCert era -> ConwayTxCert era Source # | |||||
NoThunks (ConwayTxCert era) | |||||
Defined in Cardano.Ledger.Conway.TxCert Methods noThunks :: Context -> ConwayTxCert era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> ConwayTxCert era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (ConwayTxCert era) -> String # | |||||
type Rep (ConwayTxCert era) | |||||
Defined in Cardano.Ledger.Conway.TxCert type Rep (ConwayTxCert era) = D1 ('MetaData "ConwayTxCert" "Cardano.Ledger.Conway.TxCert" "cardano-ledger-conway-1.19.0.0-4c27ba0e7c20c908d1dfe5f4038fdf7297360e4c38f5293876b47703f80d0e2c" 'False) (C1 ('MetaCons "ConwayTxCertDeleg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ConwayDelegCert)) :+: (C1 ('MetaCons "ConwayTxCertPool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PoolCert)) :+: C1 ('MetaCons "ConwayTxCertGov" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ConwayGovCert)))) |
newtype EpochInterval Source #
Constructors
EpochInterval | |
Fields |
Instances
FromJSON EpochInterval | |||||
Defined in Cardano.Slotting.Slot | |||||
ToJSON EpochInterval | |||||
Defined in Cardano.Slotting.Slot Methods toJSON :: EpochInterval -> Value toEncoding :: EpochInterval -> Encoding toJSONList :: [EpochInterval] -> Value toEncodingList :: [EpochInterval] -> Encoding omitField :: EpochInterval -> Bool | |||||
Generic EpochInterval | |||||
Defined in Cardano.Slotting.Slot Associated Types
Methods from :: EpochInterval -> Rep EpochInterval x Source # to :: Rep EpochInterval x -> EpochInterval Source # | |||||
Show EpochInterval | |||||
Defined in Cardano.Slotting.Slot | |||||
FromCBOR EpochInterval | |||||
Defined in Cardano.Slotting.Slot | |||||
ToCBOR EpochInterval | |||||
Defined in Cardano.Slotting.Slot Methods toCBOR :: EpochInterval -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy EpochInterval -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [EpochInterval] -> Size Source # | |||||
DecCBOR EpochInterval | |||||
Defined in Cardano.Ledger.Binary.Decoding.DecCBOR | |||||
EncCBOR EpochInterval | |||||
Defined in Cardano.Ledger.Binary.Encoding.EncCBOR Methods encCBOR :: EpochInterval -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy EpochInterval -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [EpochInterval] -> Size Source # | |||||
ToPlutusData EpochInterval | |||||
Defined in Cardano.Ledger.Plutus.ToPlutusData Methods toPlutusData :: EpochInterval -> Data Source # fromPlutusData :: Data -> Maybe EpochInterval Source # | |||||
NFData EpochInterval | |||||
Defined in Cardano.Slotting.Slot Methods rnf :: EpochInterval -> () Source # | |||||
Eq EpochInterval | |||||
Defined in Cardano.Slotting.Slot Methods (==) :: EpochInterval -> EpochInterval -> Bool Source # (/=) :: EpochInterval -> EpochInterval -> Bool Source # | |||||
Ord EpochInterval | |||||
Defined in Cardano.Slotting.Slot Methods compare :: EpochInterval -> EpochInterval -> Ordering Source # (<) :: EpochInterval -> EpochInterval -> Bool Source # (<=) :: EpochInterval -> EpochInterval -> Bool Source # (>) :: EpochInterval -> EpochInterval -> Bool Source # (>=) :: EpochInterval -> EpochInterval -> Bool Source # max :: EpochInterval -> EpochInterval -> EpochInterval Source # min :: EpochInterval -> EpochInterval -> EpochInterval Source # | |||||
NoThunks EpochInterval | |||||
Defined in Cardano.Slotting.Slot Methods noThunks :: Context -> EpochInterval -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> EpochInterval -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy EpochInterval -> String # | |||||
type Rep EpochInterval | |||||
Defined in Cardano.Slotting.Slot type Rep EpochInterval = D1 ('MetaData "EpochInterval" "Cardano.Slotting.Slot" "cardano-slotting-0.2.0.0-82c22cdb2514559023eda0f88c682c31e6479fd72e460ca987a3a9a5cfc0842b" 'True) (C1 ('MetaCons "EpochInterval" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEpochInterval") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32))) |
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-82c22cdb2514559023eda0f88c682c31e6479fd72e460ca987a3a9a5cfc0842b" 'True) (C1 ('MetaCons "EpochNo" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEpochNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64))) |
class HasKeyRole (a :: KeyRole -> Type) Source #
Instances
HasKeyRole Credential | |
Defined in Cardano.Ledger.Credential Methods coerceKeyRole :: forall (r :: KeyRole) (r' :: KeyRole). Credential r -> Credential r' Source # | |
HasKeyRole KeyHash | |
Defined in Cardano.Ledger.Hashes | |
HasKeyRole VKey | |
Defined in Cardano.Ledger.Keys.Internal | |
HasKeyRole KeyPair | |
Defined in Test.Cardano.Ledger.Core.KeyPair Methods coerceKeyRole :: forall (r :: KeyRole) (r' :: KeyRole). KeyPair r -> KeyPair r' Source # |
unsafeMakeSafeHash :: Hash HASH i -> SafeHash i Source #
Don't use this except in Testing to make Arbitrary instances, etc. or in cases when it can be guaranteed that original bytes were used for computing the hash.
data GenDelegPair Source #
Constructors
GenDelegPair | |
Fields
|
Instances
FromJSON GenDelegPair | |||||
Defined in Cardano.Ledger.Hashes | |||||
ToJSON GenDelegPair | |||||
Defined in Cardano.Ledger.Hashes Methods toJSON :: GenDelegPair -> Value toEncoding :: GenDelegPair -> Encoding toJSONList :: [GenDelegPair] -> Value toEncodingList :: [GenDelegPair] -> Encoding omitField :: GenDelegPair -> Bool | |||||
Generic GenDelegPair | |||||
Defined in Cardano.Ledger.Hashes Associated Types
Methods from :: GenDelegPair -> Rep GenDelegPair x Source # to :: Rep GenDelegPair x -> GenDelegPair Source # | |||||
Show GenDelegPair | |||||
Defined in Cardano.Ledger.Hashes | |||||
DecCBOR GenDelegPair | |||||
Defined in Cardano.Ledger.Hashes | |||||
EncCBOR GenDelegPair | |||||
Defined in Cardano.Ledger.Hashes Methods encCBOR :: GenDelegPair -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy GenDelegPair -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [GenDelegPair] -> Size Source # | |||||
NFData GenDelegPair | |||||
Defined in Cardano.Ledger.Hashes Methods rnf :: GenDelegPair -> () Source # | |||||
Eq GenDelegPair | |||||
Defined in Cardano.Ledger.Hashes Methods (==) :: GenDelegPair -> GenDelegPair -> Bool Source # (/=) :: GenDelegPair -> GenDelegPair -> Bool Source # | |||||
Ord GenDelegPair | |||||
Defined in Cardano.Ledger.Hashes Methods compare :: GenDelegPair -> GenDelegPair -> Ordering Source # (<) :: GenDelegPair -> GenDelegPair -> Bool Source # (<=) :: GenDelegPair -> GenDelegPair -> Bool Source # (>) :: GenDelegPair -> GenDelegPair -> Bool Source # (>=) :: GenDelegPair -> GenDelegPair -> Bool Source # max :: GenDelegPair -> GenDelegPair -> GenDelegPair Source # min :: GenDelegPair -> GenDelegPair -> GenDelegPair Source # | |||||
NoThunks GenDelegPair | |||||
Defined in Cardano.Ledger.Hashes Methods noThunks :: Context -> GenDelegPair -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> GenDelegPair -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy GenDelegPair -> String # | |||||
type Rep GenDelegPair | |||||
Defined in Cardano.Ledger.Hashes type Rep GenDelegPair = D1 ('MetaData "GenDelegPair" "Cardano.Ledger.Hashes" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'False) (C1 ('MetaCons "GenDelegPair" 'PrefixI 'True) (S1 ('MetaSel ('Just "genDelegKeyHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'GenesisDelegate)) :*: S1 ('MetaSel ('Just "genDelegVrfHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (VRFVerKeyHash 'GenDelegVRF)))) |
data StandardCrypto Source #
The same crypto used on the net
Instances
Crypto StandardCrypto | |||||||||
Defined in Cardano.Ledger.Crypto.Internal Associated Types
| |||||||||
PraosCrypto StandardCrypto | |||||||||
Defined in Cardano.Protocol.TPraos.API | |||||||||
PraosCrypto StandardCrypto | |||||||||
Defined in Ouroboros.Consensus.Protocol.Praos | |||||||||
(CardanoHardForkConstraints StandardCrypto, IOLike m) => Protocol m (CardanoBlock StandardCrypto) Source # | |||||||||
Defined in Cardano.Api.Internal.Protocol Associated Types
Methods protocolInfo :: ProtocolInfoArgs (CardanoBlock StandardCrypto) -> (ProtocolInfo (CardanoBlock StandardCrypto), m [BlockForging m (CardanoBlock StandardCrypto)]) Source # | |||||||||
(IOLike m, LedgerSupportsProtocol (ShelleyBlock (TPraos StandardCrypto) ShelleyEra)) => Protocol m (ShelleyBlockHFC (TPraos StandardCrypto) ShelleyEra) Source # | |||||||||
Defined in Cardano.Api.Internal.Protocol Associated Types
Methods protocolInfo :: ProtocolInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) ShelleyEra) -> (ProtocolInfo (ShelleyBlockHFC (TPraos StandardCrypto) ShelleyEra), m [BlockForging m (ShelleyBlockHFC (TPraos StandardCrypto) ShelleyEra)]) Source # | |||||||||
type KES StandardCrypto | |||||||||
Defined in Cardano.Ledger.Crypto.Internal | |||||||||
type VRF StandardCrypto | |||||||||
Defined in Cardano.Ledger.Crypto.Internal | |||||||||
data ProtocolInfoArgs (CardanoBlock StandardCrypto) Source # | |||||||||
data ProtocolInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) ShelleyEra) Source # | |||||||||
textToDns :: MonadFail m => Int -> Text -> m DnsName Source #
Turn a Text into a DnsName, fail if the Text has more than n
Bytes
textToUrl :: MonadFail m => Int -> Text -> m Url Source #
Turn a Text into a Url, fail if the Text has more than n
Bytes
boundRational :: BoundedRational r => Rational -> Maybe r Source #
Returns Nothing
when supplied value is not within bounds or when precision is
too high to be represented by the underlying type
Example
>>>
:set -XTypeApplications
>>>
import Data.Ratio
>>>
boundRational @UnitInterval $ 2 % 3
Just (2 % 3)>>>
boundRational @UnitInterval (-0.5)
Nothing>>>
boundRational @UnitInterval (1.5)
Nothing>>>
boundRational @UnitInterval 0
Just (0 % 1)>>>
boundRational @PositiveUnitInterval 0
Nothing
unboundRational :: BoundedRational r => r -> Rational Source #
Promote bounded rational type into the unbounded Rational
.
Instances
FromJSON DnsName | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
ToJSON DnsName | |||||
Defined in Cardano.Ledger.BaseTypes Methods toEncoding :: DnsName -> Encoding toJSONList :: [DnsName] -> Value toEncodingList :: [DnsName] -> Encoding | |||||
Generic DnsName | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
| |||||
Show DnsName | |||||
DecCBOR DnsName | |||||
EncCBOR DnsName | |||||
NFData DnsName | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
Eq DnsName | |||||
Ord DnsName | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
NoThunks DnsName | |||||
type Rep DnsName | |||||
Defined in Cardano.Ledger.BaseTypes type Rep DnsName = D1 ('MetaData "DnsName" "Cardano.Ledger.BaseTypes" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'True) (C1 ('MetaCons "DnsName" 'PrefixI 'True) (S1 ('MetaSel ('Just "dnsToText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
Instances
FromJSON Network | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
ToJSON Network | |||||
Defined in Cardano.Ledger.BaseTypes Methods toEncoding :: Network -> Encoding toJSONList :: [Network] -> Value toEncodingList :: [Network] -> Encoding | |||||
Bounded Network | |||||
Enum Network | |||||
Defined in Cardano.Ledger.BaseTypes Methods succ :: Network -> Network Source # pred :: Network -> Network Source # toEnum :: Int -> Network Source # fromEnum :: Network -> Int Source # enumFrom :: Network -> [Network] Source # enumFromThen :: Network -> Network -> [Network] Source # enumFromTo :: Network -> Network -> [Network] Source # enumFromThenTo :: Network -> Network -> Network -> [Network] Source # | |||||
Generic Network | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
| |||||
Show Network | |||||
FromCBOR Network | |||||
ToCBOR Network | |||||
DecCBOR Network | |||||
EncCBOR Network | |||||
Default Network | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
NFData Network | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
Eq Network | |||||
Ord Network | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
NoThunks Network | |||||
type Rep Network | |||||
Defined in Cardano.Ledger.BaseTypes type Rep Network = D1 ('MetaData "Network" "Cardano.Ledger.BaseTypes" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'False) (C1 ('MetaCons "Testnet" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mainnet" 'PrefixI 'False) (U1 :: Type -> Type)) |
data NonNegativeInterval Source #
Type to represent a value in the interval [0; +∞)
Instances
FromJSON NonNegativeInterval | |||||
Defined in Cardano.Ledger.BaseTypes Methods parseJSON :: Value -> Parser NonNegativeInterval parseJSONList :: Value -> Parser [NonNegativeInterval] | |||||
ToJSON NonNegativeInterval | |||||
Defined in Cardano.Ledger.BaseTypes Methods toJSON :: NonNegativeInterval -> Value toEncoding :: NonNegativeInterval -> Encoding toJSONList :: [NonNegativeInterval] -> Value toEncodingList :: [NonNegativeInterval] -> Encoding omitField :: NonNegativeInterval -> Bool | |||||
Bounded NonNegativeInterval | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
Generic NonNegativeInterval | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
Methods from :: NonNegativeInterval -> Rep NonNegativeInterval x Source # to :: Rep NonNegativeInterval x -> NonNegativeInterval Source # | |||||
Show NonNegativeInterval | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
DecCBOR NonNegativeInterval | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
EncCBOR NonNegativeInterval | |||||
Defined in Cardano.Ledger.BaseTypes Methods encCBOR :: NonNegativeInterval -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy NonNegativeInterval -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [NonNegativeInterval] -> Size Source # | |||||
BoundedRational NonNegativeInterval | |||||
Defined in Cardano.Ledger.BaseTypes Methods boundRational :: Rational -> Maybe NonNegativeInterval Source # | |||||
ToPlutusData NonNegativeInterval | |||||
Defined in Cardano.Ledger.Plutus.ToPlutusData Methods toPlutusData :: NonNegativeInterval -> Data Source # fromPlutusData :: Data -> Maybe NonNegativeInterval Source # | |||||
IsRatio NonNegativeInterval | |||||
Defined in Test.Cardano.Ledger.Core.Rational Methods (%!) :: Integer -> Integer -> NonNegativeInterval | |||||
NFData NonNegativeInterval | |||||
Defined in Cardano.Ledger.BaseTypes Methods rnf :: NonNegativeInterval -> () Source # | |||||
Eq NonNegativeInterval | |||||
Defined in Cardano.Ledger.BaseTypes Methods (==) :: NonNegativeInterval -> NonNegativeInterval -> Bool Source # (/=) :: NonNegativeInterval -> NonNegativeInterval -> Bool Source # | |||||
Ord NonNegativeInterval | |||||
Defined in Cardano.Ledger.BaseTypes Methods compare :: NonNegativeInterval -> NonNegativeInterval -> Ordering Source # (<) :: NonNegativeInterval -> NonNegativeInterval -> Bool Source # (<=) :: NonNegativeInterval -> NonNegativeInterval -> Bool Source # (>) :: NonNegativeInterval -> NonNegativeInterval -> Bool Source # (>=) :: NonNegativeInterval -> NonNegativeInterval -> Bool Source # max :: NonNegativeInterval -> NonNegativeInterval -> NonNegativeInterval Source # min :: NonNegativeInterval -> NonNegativeInterval -> NonNegativeInterval Source # | |||||
NoThunks NonNegativeInterval | |||||
Defined in Cardano.Ledger.BaseTypes Methods noThunks :: Context -> NonNegativeInterval -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> NonNegativeInterval -> IO (Maybe ThunkInfo) # | |||||
Bounded (BoundedRatio NonNegativeInterval Word64) | |||||
Defined in Cardano.Ledger.BaseTypes Methods minBound :: BoundedRatio NonNegativeInterval Word64 Source # maxBound :: BoundedRatio NonNegativeInterval Word64 Source # | |||||
type Rep NonNegativeInterval | |||||
Defined in Cardano.Ledger.BaseTypes type Rep NonNegativeInterval = D1 ('MetaData "NonNegativeInterval" "Cardano.Ledger.BaseTypes" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'True) (C1 ('MetaCons "NonNegativeInterval" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (BoundedRatio NonNegativeInterval Word64)))) |
portToWord16 :: Port -> Word16 Source #
data UnitInterval Source #
Type to represent a value in the unit interval [0; 1]
Instances
FromJSON UnitInterval | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
ToJSON UnitInterval | |||||
Defined in Cardano.Ledger.BaseTypes Methods toJSON :: UnitInterval -> Value toEncoding :: UnitInterval -> Encoding toJSONList :: [UnitInterval] -> Value toEncodingList :: [UnitInterval] -> Encoding omitField :: UnitInterval -> Bool | |||||
Bounded UnitInterval | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
Generic UnitInterval | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
Methods from :: UnitInterval -> Rep UnitInterval x Source # to :: Rep UnitInterval x -> UnitInterval Source # | |||||
Show UnitInterval | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
DecCBOR UnitInterval | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
EncCBOR UnitInterval | |||||
Defined in Cardano.Ledger.BaseTypes Methods encCBOR :: UnitInterval -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy UnitInterval -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [UnitInterval] -> Size Source # | |||||
BoundedRational UnitInterval | |||||
Defined in Cardano.Ledger.BaseTypes Methods | |||||
ToPlutusData UnitInterval | |||||
Defined in Cardano.Ledger.Plutus.ToPlutusData Methods toPlutusData :: UnitInterval -> Data Source # fromPlutusData :: Data -> Maybe UnitInterval Source # | |||||
IsRatio UnitInterval | |||||
Defined in Test.Cardano.Ledger.Core.Rational Methods (%!) :: Integer -> Integer -> UnitInterval | |||||
Default UnitInterval | |||||
Defined in Cardano.Ledger.BaseTypes Methods def :: UnitInterval # | |||||
NFData UnitInterval | |||||
Defined in Cardano.Ledger.BaseTypes Methods rnf :: UnitInterval -> () Source # | |||||
Eq UnitInterval | |||||
Defined in Cardano.Ledger.BaseTypes Methods (==) :: UnitInterval -> UnitInterval -> Bool Source # (/=) :: UnitInterval -> UnitInterval -> Bool Source # | |||||
Ord UnitInterval | |||||
Defined in Cardano.Ledger.BaseTypes Methods compare :: UnitInterval -> UnitInterval -> Ordering Source # (<) :: UnitInterval -> UnitInterval -> Bool Source # (<=) :: UnitInterval -> UnitInterval -> Bool Source # (>) :: UnitInterval -> UnitInterval -> Bool Source # (>=) :: UnitInterval -> UnitInterval -> Bool Source # max :: UnitInterval -> UnitInterval -> UnitInterval Source # min :: UnitInterval -> UnitInterval -> UnitInterval Source # | |||||
NoThunks UnitInterval | |||||
Defined in Cardano.Ledger.BaseTypes Methods noThunks :: Context -> UnitInterval -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> UnitInterval -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy UnitInterval -> String # | |||||
Integral a => Bounded (BoundedRatio UnitInterval a) | |||||
Defined in Cardano.Ledger.BaseTypes Methods minBound :: BoundedRatio UnitInterval a Source # maxBound :: BoundedRatio UnitInterval a Source # | |||||
type Rep UnitInterval | |||||
Defined in Cardano.Ledger.BaseTypes type Rep UnitInterval = D1 ('MetaData "UnitInterval" "Cardano.Ledger.BaseTypes" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'True) (C1 ('MetaCons "UnitInterval" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (BoundedRatio UnitInterval Word64)))) |
Instances
FromJSON Url | |||||
Defined in Cardano.Ledger.BaseTypes Methods parseJSON :: Value -> Parser Url parseJSONList :: Value -> Parser [Url] omittedField :: Maybe Url | |||||
ToJSON Url | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
Generic Url | |||||
Defined in Cardano.Ledger.BaseTypes Associated Types
| |||||
Show Url | |||||
DecCBOR Url | |||||
EncCBOR Url | |||||
NFData Url | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
Eq Url | |||||
Ord Url | |||||
NoThunks Url | |||||
type Rep Url | |||||
Defined in Cardano.Ledger.BaseTypes type Rep Url = D1 ('MetaData "Url" "Cardano.Ledger.BaseTypes" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'True) (C1 ('MetaCons "Url" 'PrefixI 'True) (S1 ('MetaSel ('Just "urlToText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
credToText :: forall (kr :: KeyRole). Credential kr -> Text Source #
data Credential (kr :: KeyRole) Source #
Script hash or key hash for a payment or a staking object.
Note that credentials (unlike raw key hashes) do appear to vary from era to era, since they reference the hash of a script, which can change. This parameter is a phantom, however, so in actuality the instances will remain the same.
Constructors
ScriptHashObj !ScriptHash | |
KeyHashObj !(KeyHash kr) |
Instances
HasKeyRole Credential | |||||
Defined in Cardano.Ledger.Credential Methods coerceKeyRole :: forall (r :: KeyRole) (r' :: KeyRole). Credential r -> Credential r' Source # | |||||
FromJSON (Credential kr) | |||||
Defined in Cardano.Ledger.Credential Methods parseJSON :: Value -> Parser (Credential kr) parseJSONList :: Value -> Parser [Credential kr] omittedField :: Maybe (Credential kr) | |||||
FromJSONKey (Credential kr) | |||||
Defined in Cardano.Ledger.Credential Methods fromJSONKey :: FromJSONKeyFunction (Credential kr) fromJSONKeyList :: FromJSONKeyFunction [Credential kr] | |||||
ToJSON (Credential kr) | |||||
Defined in Cardano.Ledger.Credential Methods toJSON :: Credential kr -> Value toEncoding :: Credential kr -> Encoding toJSONList :: [Credential kr] -> Value toEncodingList :: [Credential kr] -> Encoding omitField :: Credential kr -> Bool | |||||
ToJSONKey (Credential kr) | |||||
Defined in Cardano.Ledger.Credential Methods toJSONKey :: ToJSONKeyFunction (Credential kr) toJSONKeyList :: ToJSONKeyFunction [Credential kr] | |||||
Generic (Credential kr) | |||||
Defined in Cardano.Ledger.Credential Associated Types
Methods from :: Credential kr -> Rep (Credential kr) x Source # to :: Rep (Credential kr) x -> Credential kr Source # | |||||
Show (Credential kr) | |||||
Defined in Cardano.Ledger.Credential | |||||
Typeable kr => FromCBOR (Credential kr) | |||||
Defined in Cardano.Ledger.Credential | |||||
Typeable kr => ToCBOR (Credential kr) | |||||
Defined in Cardano.Ledger.Credential Methods toCBOR :: Credential kr -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Credential kr) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Credential kr] -> Size Source # | |||||
Typeable kr => DecCBOR (Credential kr) | |||||
Defined in Cardano.Ledger.Credential | |||||
Typeable kr => EncCBOR (Credential kr) | |||||
Defined in Cardano.Ledger.Credential Methods encCBOR :: Credential kr -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (Credential kr) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Credential kr] -> Size Source # | |||||
MakeStakeReference (Credential 'Staking) | |||||
Defined in Test.Cardano.Ledger.Core.KeyPair Methods | |||||
MakeStakeReference (Maybe (Credential 'Staking)) | |||||
Defined in Test.Cardano.Ledger.Core.KeyPair Methods mkStakeRef :: Maybe (Credential 'Staking) -> StakeReference | |||||
Default (Credential r) | |||||
Defined in Cardano.Ledger.Credential Methods def :: Credential r # | |||||
NFData (Credential r) | |||||
Defined in Cardano.Ledger.Credential Methods rnf :: Credential r -> () Source # | |||||
Eq (Credential kr) | |||||
Defined in Cardano.Ledger.Credential Methods (==) :: Credential kr -> Credential kr -> Bool Source # (/=) :: Credential kr -> Credential kr -> Bool Source # | |||||
Ord (Credential kr) | |||||
Defined in Cardano.Ledger.Credential Methods compare :: Credential kr -> Credential kr -> Ordering Source # (<) :: Credential kr -> Credential kr -> Bool Source # (<=) :: Credential kr -> Credential kr -> Bool Source # (>) :: Credential kr -> Credential kr -> Bool Source # (>=) :: Credential kr -> Credential kr -> Bool Source # max :: Credential kr -> Credential kr -> Credential kr Source # min :: Credential kr -> Credential kr -> Credential kr Source # | |||||
Typeable kr => MemPack (Credential kr) | |||||
Defined in Cardano.Ledger.Credential Methods packedByteCount :: Credential kr -> Int packM :: Credential kr -> Pack s () unpackM :: Buffer b => Unpack b (Credential kr) | |||||
NoThunks (Credential kr) | |||||
Defined in Cardano.Ledger.Credential Methods noThunks :: Context -> Credential kr -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> Credential kr -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (Credential kr) -> String # | |||||
MakeCredential (Credential r) r | |||||
Defined in Test.Cardano.Ledger.Core.KeyPair Methods mkCredential :: Credential r -> Credential r | |||||
type Rep (Credential kr) | |||||
Defined in Cardano.Ledger.Credential type Rep (Credential kr) = D1 ('MetaData "Credential" "Cardano.Ledger.Credential" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'False) (C1 ('MetaCons "ScriptHashObj" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ScriptHash)) :+: C1 ('MetaCons "KeyHashObj" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash kr)))) |
data StakeReference Source #
Constructors
StakeRefBase !StakeCredential | |
StakeRefPtr !Ptr | |
StakeRefNull |
Instances
ToJSON StakeReference | |||||
Defined in Cardano.Ledger.Credential Methods toJSON :: StakeReference -> Value toEncoding :: StakeReference -> Encoding toJSONList :: [StakeReference] -> Value toEncodingList :: [StakeReference] -> Encoding omitField :: StakeReference -> Bool | |||||
Generic StakeReference | |||||
Defined in Cardano.Ledger.Credential Associated Types
Methods from :: StakeReference -> Rep StakeReference x Source # to :: Rep StakeReference x -> StakeReference Source # | |||||
Show StakeReference | |||||
Defined in Cardano.Ledger.Credential | |||||
MakeStakeReference StakeReference | |||||
Defined in Test.Cardano.Ledger.Core.KeyPair Methods | |||||
NFData StakeReference | |||||
Defined in Cardano.Ledger.Credential Methods rnf :: StakeReference -> () Source # | |||||
Eq StakeReference | |||||
Defined in Cardano.Ledger.Credential Methods (==) :: StakeReference -> StakeReference -> Bool Source # (/=) :: StakeReference -> StakeReference -> Bool Source # | |||||
Ord StakeReference | |||||
Defined in Cardano.Ledger.Credential Methods compare :: StakeReference -> StakeReference -> Ordering Source # (<) :: StakeReference -> StakeReference -> Bool Source # (<=) :: StakeReference -> StakeReference -> Bool Source # (>) :: StakeReference -> StakeReference -> Bool Source # (>=) :: StakeReference -> StakeReference -> Bool Source # max :: StakeReference -> StakeReference -> StakeReference Source # min :: StakeReference -> StakeReference -> StakeReference Source # | |||||
NoThunks StakeReference | |||||
Defined in Cardano.Ledger.Credential Methods noThunks :: Context -> StakeReference -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> StakeReference -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy StakeReference -> String # | |||||
MakeStakeReference (Maybe StakeReference) | |||||
Defined in Test.Cardano.Ledger.Core.KeyPair Methods | |||||
type Rep StakeReference | |||||
Defined in Cardano.Ledger.Credential type Rep StakeReference = D1 ('MetaData "StakeReference" "Cardano.Ledger.Credential" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'False) (C1 ('MetaCons "StakeRefBase" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StakeCredential)) :+: (C1 ('MetaCons "StakeRefPtr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Ptr)) :+: C1 ('MetaCons "StakeRefNull" 'PrefixI 'False) (U1 :: Type -> Type))) |
toDeltaCoin :: Coin -> DeltaCoin Source #
drepAnchorL :: Lens' DRepState (StrictMaybe Anchor) Source #
drepDepositL :: Lens' DRepState Coin Source #
drepExpiryL :: Lens' DRepState EpochNo Source #
Constructors
DRepKeyHash !(KeyHash 'DRepRole) | |
DRepScriptHash !ScriptHash | |
DRepAlwaysAbstain | |
DRepAlwaysNoConfidence |
Bundled Patterns
pattern DRepCredential :: Credential 'DRepRole -> DRep |
Instances
FromJSON DRep | |||||
Defined in Cardano.Ledger.DRep | |||||
FromJSONKey DRep | |||||
Defined in Cardano.Ledger.DRep | |||||
ToJSON DRep | |||||
Defined in Cardano.Ledger.DRep Methods toEncoding :: DRep -> Encoding toJSONList :: [DRep] -> Value toEncodingList :: [DRep] -> Encoding | |||||
ToJSONKey DRep | |||||
Defined in Cardano.Ledger.DRep | |||||
Generic DRep | |||||
Defined in Cardano.Ledger.DRep Associated Types
| |||||
Show DRep | |||||
DecCBOR DRep | |||||
DecShareCBOR DRep | |||||
EncCBOR DRep | |||||
NFData DRep | |||||
Defined in Cardano.Ledger.DRep | |||||
Eq DRep | |||||
Ord DRep | |||||
Defined in Cardano.Ledger.DRep | |||||
NoThunks DRep | |||||
type Rep DRep | |||||
Defined in Cardano.Ledger.DRep type Rep DRep = D1 ('MetaData "DRep" "Cardano.Ledger.DRep" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'False) ((C1 ('MetaCons "DRepKeyHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'DRepRole))) :+: C1 ('MetaCons "DRepScriptHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ScriptHash))) :+: (C1 ('MetaCons "DRepAlwaysAbstain" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DRepAlwaysNoConfidence" 'PrefixI 'False) (U1 :: Type -> Type))) | |||||
type Share DRep | |||||
Constructors
DRepState | |
Fields
|
Instances
FromJSON DRepState | |||||
Defined in Cardano.Ledger.DRep | |||||
ToJSON DRepState | |||||
Defined in Cardano.Ledger.DRep Methods toEncoding :: DRepState -> Encoding toJSONList :: [DRepState] -> Value toEncodingList :: [DRepState] -> Encoding | |||||
Generic DRepState | |||||
Defined in Cardano.Ledger.DRep Associated Types
| |||||
Show DRepState | |||||
DecCBOR DRepState | |||||
DecShareCBOR DRepState | |||||
EncCBOR DRepState | |||||
NFData DRepState | |||||
Defined in Cardano.Ledger.DRep | |||||
Eq DRepState | |||||
Ord DRepState | |||||
Defined in Cardano.Ledger.DRep | |||||
NoThunks DRepState | |||||
type Rep DRepState | |||||
Defined in Cardano.Ledger.DRep type Rep DRepState = D1 ('MetaData "DRepState" "Cardano.Ledger.DRep" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'False) (C1 ('MetaCons "DRepState" 'PrefixI 'True) ((S1 ('MetaSel ('Just "drepExpiry") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 EpochNo) :*: S1 ('MetaSel ('Just "drepAnchor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe Anchor))) :*: (S1 ('MetaSel ('Just "drepDeposit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin) :*: S1 ('MetaSel ('Just "drepDelegs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set (Credential 'Staking)))))) | |||||
type Share DRepState | |||||
languageToText :: Language -> Text Source #
Non-Native Plutus Script language. This is expected to be an open type. We will add new Constuctors to this type as additional Plutus language versions as are added. We use an enumerated type for two reasons.
- We can write total functions by case analysis over the constructors
- We use DataKinds to make some datatypes indexed by Language.
Note that the the serialization of Language
depends on the ordering.
Instances
FromJSON Language | |||||
Defined in Cardano.Ledger.Plutus.Language | |||||
FromJSONKey Language | |||||
Defined in Cardano.Ledger.Plutus.Language | |||||
ToJSON Language | |||||
Defined in Cardano.Ledger.Plutus.Language Methods toEncoding :: Language -> Encoding toJSONList :: [Language] -> Value toEncodingList :: [Language] -> Encoding | |||||
ToJSONKey Language | |||||
Defined in Cardano.Ledger.Plutus.Language | |||||
Bounded Language | |||||
Enum Language | |||||
Defined in Cardano.Ledger.Plutus.Language Methods succ :: Language -> Language Source # pred :: Language -> Language Source # toEnum :: Int -> Language Source # fromEnum :: Language -> Int Source # enumFrom :: Language -> [Language] Source # enumFromThen :: Language -> Language -> [Language] Source # enumFromTo :: Language -> Language -> [Language] Source # enumFromThenTo :: Language -> Language -> Language -> [Language] Source # | |||||
Generic Language | |||||
Defined in Cardano.Ledger.Plutus.Language Associated Types
| |||||
Ix Language | |||||
Defined in Cardano.Ledger.Plutus.Language | |||||
Read Language | |||||
Show Language | |||||
FromCBOR Language | |||||
ToCBOR Language | |||||
DecCBOR Language | |||||
EncCBOR Language | |||||
NFData Language | |||||
Defined in Cardano.Ledger.Plutus.Language | |||||
Eq Language | |||||
Ord Language | |||||
Defined in Cardano.Ledger.Plutus.Language | |||||
NoThunks Language | |||||
Random Language | |||||
Uniform Language | |||||
Defined in Cardano.Ledger.Plutus.Language | |||||
UniformRange Language | |||||
Defined in Cardano.Ledger.Plutus.Language | |||||
type Rep Language | |||||
Defined in Cardano.Ledger.Plutus.Language type Rep Language = D1 ('MetaData "Language" "Cardano.Ledger.Plutus.Language" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'False) (C1 ('MetaCons "PlutusV1" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PlutusV2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PlutusV3" 'PrefixI 'False) (U1 :: Type -> Type))) |
data PoolMetadata Source #
Constructors
PoolMetadata | |
Fields
|
Instances
FromJSON PoolMetadata | |||||
Defined in Cardano.Ledger.PoolParams | |||||
ToJSON PoolMetadata | |||||
Defined in Cardano.Ledger.PoolParams Methods toJSON :: PoolMetadata -> Value toEncoding :: PoolMetadata -> Encoding toJSONList :: [PoolMetadata] -> Value toEncodingList :: [PoolMetadata] -> Encoding omitField :: PoolMetadata -> Bool | |||||
Generic PoolMetadata | |||||
Defined in Cardano.Ledger.PoolParams Associated Types
Methods from :: PoolMetadata -> Rep PoolMetadata x Source # to :: Rep PoolMetadata x -> PoolMetadata Source # | |||||
Show PoolMetadata | |||||
Defined in Cardano.Ledger.PoolParams | |||||
DecCBOR PoolMetadata | |||||
Defined in Cardano.Ledger.PoolParams | |||||
EncCBOR PoolMetadata | |||||
Defined in Cardano.Ledger.PoolParams Methods encCBOR :: PoolMetadata -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy PoolMetadata -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [PoolMetadata] -> Size Source # | |||||
NFData PoolMetadata | |||||
Defined in Cardano.Ledger.PoolParams Methods rnf :: PoolMetadata -> () Source # | |||||
Eq PoolMetadata | |||||
Defined in Cardano.Ledger.PoolParams Methods (==) :: PoolMetadata -> PoolMetadata -> Bool Source # (/=) :: PoolMetadata -> PoolMetadata -> Bool Source # | |||||
Ord PoolMetadata | |||||
Defined in Cardano.Ledger.PoolParams Methods compare :: PoolMetadata -> PoolMetadata -> Ordering Source # (<) :: PoolMetadata -> PoolMetadata -> Bool Source # (<=) :: PoolMetadata -> PoolMetadata -> Bool Source # (>) :: PoolMetadata -> PoolMetadata -> Bool Source # (>=) :: PoolMetadata -> PoolMetadata -> Bool Source # max :: PoolMetadata -> PoolMetadata -> PoolMetadata Source # min :: PoolMetadata -> PoolMetadata -> PoolMetadata Source # | |||||
NoThunks PoolMetadata | |||||
Defined in Cardano.Ledger.PoolParams Methods noThunks :: Context -> PoolMetadata -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> PoolMetadata -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy PoolMetadata -> String # | |||||
type Rep PoolMetadata | |||||
Defined in Cardano.Ledger.PoolParams type Rep PoolMetadata = D1 ('MetaData "PoolMetadata" "Cardano.Ledger.PoolParams" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'False) (C1 ('MetaCons "PoolMetadata" 'PrefixI 'True) (S1 ('MetaSel ('Just "pmUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Url) :*: S1 ('MetaSel ('Just "pmHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString))) |
data PoolParams Source #
A stake pool.
Constructors
PoolParams | |
Fields
|
Instances
FromJSON PoolParams | |||||
Defined in Cardano.Ledger.PoolParams | |||||
ToJSON PoolParams | |||||
Defined in Cardano.Ledger.PoolParams Methods toJSON :: PoolParams -> Value toEncoding :: PoolParams -> Encoding toJSONList :: [PoolParams] -> Value toEncodingList :: [PoolParams] -> Encoding omitField :: PoolParams -> Bool | |||||
Generic PoolParams | |||||
Defined in Cardano.Ledger.PoolParams Associated Types
| |||||
Show PoolParams | |||||
Defined in Cardano.Ledger.PoolParams | |||||
DecCBOR PoolParams | |||||
Defined in Cardano.Ledger.PoolParams | |||||
EncCBOR PoolParams | |||||
Defined in Cardano.Ledger.PoolParams Methods encCBOR :: PoolParams -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy PoolParams -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [PoolParams] -> Size Source # | |||||
DecCBORGroup PoolParams | |||||
Defined in Cardano.Ledger.PoolParams Methods decCBORGroup :: Decoder s PoolParams Source # | |||||
EncCBORGroup PoolParams | |||||
Defined in Cardano.Ledger.PoolParams Methods encCBORGroup :: PoolParams -> Encoding Source # encodedGroupSizeExpr :: (forall x. EncCBOR x => Proxy x -> Size) -> Proxy PoolParams -> Size Source # listLen :: PoolParams -> Word Source # listLenBound :: Proxy PoolParams -> Word Source # | |||||
Default PoolParams | |||||
Defined in Cardano.Ledger.PoolParams Methods def :: PoolParams # | |||||
NFData PoolParams | |||||
Defined in Cardano.Ledger.PoolParams Methods rnf :: PoolParams -> () Source # | |||||
Eq PoolParams | |||||
Defined in Cardano.Ledger.PoolParams Methods (==) :: PoolParams -> PoolParams -> Bool Source # (/=) :: PoolParams -> PoolParams -> Bool Source # | |||||
Ord PoolParams | |||||
Defined in Cardano.Ledger.PoolParams Methods compare :: PoolParams -> PoolParams -> Ordering Source # (<) :: PoolParams -> PoolParams -> Bool Source # (<=) :: PoolParams -> PoolParams -> Bool Source # (>) :: PoolParams -> PoolParams -> Bool Source # (>=) :: PoolParams -> PoolParams -> Bool Source # max :: PoolParams -> PoolParams -> PoolParams Source # min :: PoolParams -> PoolParams -> PoolParams Source # | |||||
NoThunks PoolParams | |||||
Defined in Cardano.Ledger.PoolParams Methods noThunks :: Context -> PoolParams -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> PoolParams -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy PoolParams -> String # | |||||
type Rep PoolParams | |||||
Defined in Cardano.Ledger.PoolParams type Rep PoolParams = D1 ('MetaData "PoolParams" "Cardano.Ledger.PoolParams" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'False) (C1 ('MetaCons "PoolParams" 'PrefixI 'True) (((S1 ('MetaSel ('Just "ppId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool)) :*: S1 ('MetaSel ('Just "ppVrf") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (VRFVerKeyHash 'StakePoolVRF))) :*: (S1 ('MetaSel ('Just "ppPledge") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin) :*: S1 ('MetaSel ('Just "ppCost") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin))) :*: ((S1 ('MetaSel ('Just "ppMargin") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitInterval) :*: S1 ('MetaSel ('Just "ppRewardAccount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RewardAccount)) :*: (S1 ('MetaSel ('Just "ppOwners") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set (KeyHash 'Staking))) :*: (S1 ('MetaSel ('Just "ppRelays") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictSeq StakePoolRelay)) :*: S1 ('MetaSel ('Just "ppMetadata") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe PoolMetadata))))))) |
data StakePoolRelay Source #
Constructors
SingleHostAddr !(StrictMaybe Port) !(StrictMaybe IPv4) !(StrictMaybe IPv6) | One or both of IPv4 & IPv6 |
SingleHostName !(StrictMaybe Port) !DnsName | An |
MultiHostName !DnsName | A |
Instances
FromJSON StakePoolRelay | |||||
Defined in Cardano.Ledger.PoolParams | |||||
ToJSON StakePoolRelay | |||||
Defined in Cardano.Ledger.PoolParams Methods toJSON :: StakePoolRelay -> Value toEncoding :: StakePoolRelay -> Encoding toJSONList :: [StakePoolRelay] -> Value toEncodingList :: [StakePoolRelay] -> Encoding omitField :: StakePoolRelay -> Bool | |||||
Generic StakePoolRelay | |||||
Defined in Cardano.Ledger.PoolParams Associated Types
Methods from :: StakePoolRelay -> Rep StakePoolRelay x Source # to :: Rep StakePoolRelay x -> StakePoolRelay Source # | |||||
Show StakePoolRelay | |||||
Defined in Cardano.Ledger.PoolParams | |||||
DecCBOR StakePoolRelay | |||||
Defined in Cardano.Ledger.PoolParams | |||||
EncCBOR StakePoolRelay | |||||
Defined in Cardano.Ledger.PoolParams Methods encCBOR :: StakePoolRelay -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy StakePoolRelay -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [StakePoolRelay] -> Size Source # | |||||
NFData StakePoolRelay | |||||
Defined in Cardano.Ledger.PoolParams Methods rnf :: StakePoolRelay -> () Source # | |||||
Eq StakePoolRelay | |||||
Defined in Cardano.Ledger.PoolParams Methods (==) :: StakePoolRelay -> StakePoolRelay -> Bool Source # (/=) :: StakePoolRelay -> StakePoolRelay -> Bool Source # | |||||
Ord StakePoolRelay | |||||
Defined in Cardano.Ledger.PoolParams Methods compare :: StakePoolRelay -> StakePoolRelay -> Ordering Source # (<) :: StakePoolRelay -> StakePoolRelay -> Bool Source # (<=) :: StakePoolRelay -> StakePoolRelay -> Bool Source # (>) :: StakePoolRelay -> StakePoolRelay -> Bool Source # (>=) :: StakePoolRelay -> StakePoolRelay -> Bool Source # max :: StakePoolRelay -> StakePoolRelay -> StakePoolRelay Source # min :: StakePoolRelay -> StakePoolRelay -> StakePoolRelay Source # | |||||
NoThunks StakePoolRelay | |||||
Defined in Cardano.Ledger.PoolParams Methods noThunks :: Context -> StakePoolRelay -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> StakePoolRelay -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy StakePoolRelay -> String # | |||||
type Rep StakePoolRelay | |||||
Defined in Cardano.Ledger.PoolParams type Rep StakePoolRelay = D1 ('MetaData "StakePoolRelay" "Cardano.Ledger.PoolParams" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'False) (C1 ('MetaCons "SingleHostAddr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe Port)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe IPv4)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe IPv6)))) :+: (C1 ('MetaCons "SingleHostName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe Port)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DnsName)) :+: C1 ('MetaCons "MultiHostName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 DnsName)))) |
csCommitteeCredsL :: forall era f. Functor f => (Map (Credential 'ColdCommitteeRole) CommitteeAuthorization -> f (Map (Credential 'ColdCommitteeRole) CommitteeAuthorization)) -> CommitteeState era -> f (CommitteeState era) Source #
The state used by the POOL rule, which tracks stake pool information.
Constructors
PState | |
Fields
|
Instances
ToJSON (PState era) | |||||
Defined in Cardano.Ledger.CertState Methods toEncoding :: PState era -> Encoding toJSONList :: [PState era] -> Value toEncodingList :: [PState era] -> Encoding | |||||
Generic (PState era) | |||||
Defined in Cardano.Ledger.CertState Associated Types
| |||||
Show (PState era) | |||||
(Era era, DecShareCBOR (PState era)) => DecCBOR (PState era) | |||||
DecShareCBOR (PState era) | |||||
Era era => EncCBOR (PState era) | |||||
Default (PState era) | |||||
Defined in Cardano.Ledger.CertState | |||||
NFData (PState era) | |||||
Defined in Cardano.Ledger.CertState | |||||
Eq (PState era) | |||||
NoThunks (PState era) | |||||
type TranslationError AllegraEra PState | |||||
Defined in Cardano.Ledger.Allegra.Translation | |||||
type TranslationError AlonzoEra PState | |||||
Defined in Cardano.Ledger.Alonzo.Translation | |||||
type TranslationError BabbageEra PState | |||||
Defined in Cardano.Ledger.Babbage.Translation | |||||
type TranslationError ConwayEra PState | |||||
Defined in Cardano.Ledger.Conway.Translation | |||||
type TranslationError MaryEra PState | |||||
Defined in Cardano.Ledger.Mary.Translation | |||||
type Rep (PState era) | |||||
Defined in Cardano.Ledger.CertState type Rep (PState era) = D1 ('MetaData "PState" "Cardano.Ledger.CertState" "cardano-ledger-core-1.17.0.0-dd7a8a3d38bd779adfa04191c70602269e23fd57c17ad2e1d5bda5828f7703f5" 'False) (C1 ('MetaCons "PState" 'PrefixI 'True) ((S1 ('MetaSel ('Just "psStakePoolParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (KeyHash 'StakePool) PoolParams)) :*: S1 ('MetaSel ('Just "psFutureStakePoolParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (KeyHash 'StakePool) PoolParams))) :*: (S1 ('MetaSel ('Just "psRetiring") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (KeyHash 'StakePool) EpochNo)) :*: S1 ('MetaSel ('Just "psDeposits") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (KeyHash 'StakePool) Coin))))) | |||||
type Share (PState era) | |||||
maybeToStrictMaybe :: Maybe a -> StrictMaybe a Source #
strictMaybeToMaybe :: StrictMaybe a -> Maybe a Source #
newtype MultiAsset Source #
The MultiAssets map
Instances
ToJSON MultiAsset | |||||
Defined in Cardano.Ledger.Mary.Value Methods toJSON :: MultiAsset -> Value toEncoding :: MultiAsset -> Encoding toJSONList :: [MultiAsset] -> Value toEncodingList :: [MultiAsset] -> Encoding omitField :: MultiAsset -> Bool | |||||
Monoid MultiAsset | |||||
Defined in Cardano.Ledger.Mary.Value Methods mempty :: MultiAsset Source # mappend :: MultiAsset -> MultiAsset -> MultiAsset Source # mconcat :: [MultiAsset] -> MultiAsset Source # | |||||
Semigroup MultiAsset | |||||
Defined in Cardano.Ledger.Mary.Value Methods (<>) :: MultiAsset -> MultiAsset -> MultiAsset Source # sconcat :: NonEmpty MultiAsset -> MultiAsset Source # stimes :: Integral b => b -> MultiAsset -> MultiAsset Source # | |||||
Generic MultiAsset | |||||
Defined in Cardano.Ledger.Mary.Value Associated Types
| |||||
Show MultiAsset | |||||
Defined in Cardano.Ledger.Mary.Value | |||||
DecCBOR MultiAsset | |||||
Defined in Cardano.Ledger.Mary.Value | |||||
EncCBOR MultiAsset | |||||
Defined in Cardano.Ledger.Mary.Value Methods encCBOR :: MultiAsset -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy MultiAsset -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [MultiAsset] -> Size Source # | |||||
NFData MultiAsset | |||||
Defined in Cardano.Ledger.Mary.Value Methods rnf :: MultiAsset -> () Source # | |||||
Eq MultiAsset | |||||
Defined in Cardano.Ledger.Mary.Value Methods (==) :: MultiAsset -> MultiAsset -> Bool Source # (/=) :: MultiAsset -> MultiAsset -> Bool Source # | |||||
Group MultiAsset | |||||
Defined in Cardano.Ledger.Mary.Value Methods invert :: MultiAsset -> MultiAsset (~~) :: MultiAsset -> MultiAsset -> MultiAsset pow :: Integral x => MultiAsset -> x -> MultiAsset | |||||
NoThunks MultiAsset | |||||
Defined in Cardano.Ledger.Mary.Value Methods noThunks :: Context -> MultiAsset -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> MultiAsset -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy MultiAsset -> String # | |||||
type Rep MultiAsset | |||||
Defined in Cardano.Ledger.Mary.Value type Rep MultiAsset = D1 ('MetaData "MultiAsset" "Cardano.Ledger.Mary.Value" "cardano-ledger-mary-1.8.0.0-fffce5657aebdcd5e62e356f8f8f5e13ce4d144e90ec88b5d1f207e99893ae76" 'True) (C1 ('MetaCons "MultiAsset" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map PolicyID (Map AssetName Integer))))) |
data ShelleyGenesisStaking Source #
Genesis Shelley staking configuration.
This allows us to configure some initial stake pools and delegation to them, in order to test Praos in a static configuration, without requiring on-chain registration and delegation.
For simplicity, pools defined in the genesis staking do not pay deposits for their registration.
Constructors
ShelleyGenesisStaking | |
Fields
|
Instances
FromJSON ShelleyGenesisStaking | |||||
Defined in Cardano.Ledger.Shelley.Genesis Methods parseJSON :: Value -> Parser ShelleyGenesisStaking parseJSONList :: Value -> Parser [ShelleyGenesisStaking] | |||||
ToJSON ShelleyGenesisStaking | |||||
Defined in Cardano.Ledger.Shelley.Genesis Methods toJSON :: ShelleyGenesisStaking -> Value toEncoding :: ShelleyGenesisStaking -> Encoding toJSONList :: [ShelleyGenesisStaking] -> Value toEncodingList :: [ShelleyGenesisStaking] -> Encoding | |||||
Monoid ShelleyGenesisStaking | |||||
Defined in Cardano.Ledger.Shelley.Genesis | |||||
Semigroup ShelleyGenesisStaking | |||||
Defined in Cardano.Ledger.Shelley.Genesis Methods (<>) :: ShelleyGenesisStaking -> ShelleyGenesisStaking -> ShelleyGenesisStaking Source # sconcat :: NonEmpty ShelleyGenesisStaking -> ShelleyGenesisStaking Source # stimes :: Integral b => b -> ShelleyGenesisStaking -> ShelleyGenesisStaking Source # | |||||
Generic ShelleyGenesisStaking | |||||
Defined in Cardano.Ledger.Shelley.Genesis Associated Types
Methods from :: ShelleyGenesisStaking -> Rep ShelleyGenesisStaking x Source # to :: Rep ShelleyGenesisStaking x -> ShelleyGenesisStaking Source # | |||||
Show ShelleyGenesisStaking | |||||
Defined in Cardano.Ledger.Shelley.Genesis | |||||
DecCBOR ShelleyGenesisStaking | |||||
Defined in Cardano.Ledger.Shelley.Genesis | |||||
EncCBOR ShelleyGenesisStaking | |||||
Defined in Cardano.Ledger.Shelley.Genesis Methods encCBOR :: ShelleyGenesisStaking -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy ShelleyGenesisStaking -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ShelleyGenesisStaking] -> Size Source # | |||||
Eq ShelleyGenesisStaking | |||||
Defined in Cardano.Ledger.Shelley.Genesis Methods (==) :: ShelleyGenesisStaking -> ShelleyGenesisStaking -> Bool Source # (/=) :: ShelleyGenesisStaking -> ShelleyGenesisStaking -> Bool Source # | |||||
NoThunks ShelleyGenesisStaking | |||||
Defined in Cardano.Ledger.Shelley.Genesis Methods noThunks :: Context -> ShelleyGenesisStaking -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> ShelleyGenesisStaking -> IO (Maybe ThunkInfo) # | |||||
type Rep ShelleyGenesisStaking | |||||
Defined in Cardano.Ledger.Shelley.Genesis type Rep ShelleyGenesisStaking = D1 ('MetaData "ShelleyGenesisStaking" "Cardano.Ledger.Shelley.Genesis" "cardano-ledger-shelley-1.16.0.0-66390a9322bb0fb64b3f0442ebc385a2f8e5928f157dc0d1b8e0fcc9dabbabc0" 'False) (C1 ('MetaCons "ShelleyGenesisStaking" 'PrefixI 'True) (S1 ('MetaSel ('Just "sgsPools") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListMap (KeyHash 'StakePool) PoolParams)) :*: S1 ('MetaSel ('Just "sgsStake") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListMap (KeyHash 'Staking) (KeyHash 'StakePool))))) |
data GenesisDelegCert Source #
Genesis key delegation certificate
Constructors
GenesisDelegCert !(KeyHash 'Genesis) !(KeyHash 'GenesisDelegate) !(VRFVerKeyHash 'GenDelegVRF) |
Instances
ToJSON GenesisDelegCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods toJSON :: GenesisDelegCert -> Value toEncoding :: GenesisDelegCert -> Encoding toJSONList :: [GenesisDelegCert] -> Value toEncodingList :: [GenesisDelegCert] -> Encoding omitField :: GenesisDelegCert -> Bool | |||||
Generic GenesisDelegCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert Associated Types
Methods from :: GenesisDelegCert -> Rep GenesisDelegCert x Source # to :: Rep GenesisDelegCert x -> GenesisDelegCert Source # | |||||
Show GenesisDelegCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert | |||||
NFData GenesisDelegCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods rnf :: GenesisDelegCert -> () Source # | |||||
Eq GenesisDelegCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods (==) :: GenesisDelegCert -> GenesisDelegCert -> Bool Source # (/=) :: GenesisDelegCert -> GenesisDelegCert -> Bool Source # | |||||
Ord GenesisDelegCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods compare :: GenesisDelegCert -> GenesisDelegCert -> Ordering Source # (<) :: GenesisDelegCert -> GenesisDelegCert -> Bool Source # (<=) :: GenesisDelegCert -> GenesisDelegCert -> Bool Source # (>) :: GenesisDelegCert -> GenesisDelegCert -> Bool Source # (>=) :: GenesisDelegCert -> GenesisDelegCert -> Bool Source # max :: GenesisDelegCert -> GenesisDelegCert -> GenesisDelegCert Source # min :: GenesisDelegCert -> GenesisDelegCert -> GenesisDelegCert Source # | |||||
NoThunks GenesisDelegCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods noThunks :: Context -> GenesisDelegCert -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> GenesisDelegCert -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy GenesisDelegCert -> String # | |||||
type Rep GenesisDelegCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert type Rep GenesisDelegCert = D1 ('MetaData "GenesisDelegCert" "Cardano.Ledger.Shelley.TxCert" "cardano-ledger-shelley-1.16.0.0-66390a9322bb0fb64b3f0442ebc385a2f8e5928f157dc0d1b8e0fcc9dabbabc0" 'False) (C1 ('MetaCons "GenesisDelegCert" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'Genesis)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'GenesisDelegate)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (VRFVerKeyHash 'GenDelegVRF))))) |
data ShelleyDelegCert Source #
Constructors
ShelleyRegCert !StakeCredential | A stake credential registration certificate. |
ShelleyUnRegCert !StakeCredential | A stake credential deregistration certificate. |
ShelleyDelegCert !StakeCredential !(KeyHash 'StakePool) | A stake delegation certificate. |
Instances
ToJSON ShelleyDelegCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods toJSON :: ShelleyDelegCert -> Value toEncoding :: ShelleyDelegCert -> Encoding toJSONList :: [ShelleyDelegCert] -> Value toEncodingList :: [ShelleyDelegCert] -> Encoding omitField :: ShelleyDelegCert -> Bool | |||||
Generic ShelleyDelegCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert Associated Types
Methods from :: ShelleyDelegCert -> Rep ShelleyDelegCert x Source # to :: Rep ShelleyDelegCert x -> ShelleyDelegCert Source # | |||||
Show ShelleyDelegCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert | |||||
NFData ShelleyDelegCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods rnf :: ShelleyDelegCert -> () Source # | |||||
Eq ShelleyDelegCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods (==) :: ShelleyDelegCert -> ShelleyDelegCert -> Bool Source # (/=) :: ShelleyDelegCert -> ShelleyDelegCert -> Bool Source # | |||||
Ord ShelleyDelegCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods compare :: ShelleyDelegCert -> ShelleyDelegCert -> Ordering Source # (<) :: ShelleyDelegCert -> ShelleyDelegCert -> Bool Source # (<=) :: ShelleyDelegCert -> ShelleyDelegCert -> Bool Source # (>) :: ShelleyDelegCert -> ShelleyDelegCert -> Bool Source # (>=) :: ShelleyDelegCert -> ShelleyDelegCert -> Bool Source # max :: ShelleyDelegCert -> ShelleyDelegCert -> ShelleyDelegCert Source # min :: ShelleyDelegCert -> ShelleyDelegCert -> ShelleyDelegCert Source # | |||||
NoThunks ShelleyDelegCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods noThunks :: Context -> ShelleyDelegCert -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> ShelleyDelegCert -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy ShelleyDelegCert -> String # | |||||
type Rep ShelleyDelegCert | |||||
Defined in Cardano.Ledger.Shelley.TxCert type Rep ShelleyDelegCert = D1 ('MetaData "ShelleyDelegCert" "Cardano.Ledger.Shelley.TxCert" "cardano-ledger-shelley-1.16.0.0-66390a9322bb0fb64b3f0442ebc385a2f8e5928f157dc0d1b8e0fcc9dabbabc0" 'False) (C1 ('MetaCons "ShelleyRegCert" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StakeCredential)) :+: (C1 ('MetaCons "ShelleyUnRegCert" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StakeCredential)) :+: C1 ('MetaCons "ShelleyDelegCert" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StakeCredential) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool))))) |
data ShelleyTxCert era Source #
A heavyweight certificate.
Constructors
ShelleyTxCertDelegCert !ShelleyDelegCert | |
ShelleyTxCertPool !PoolCert | |
ShelleyTxCertGenesisDeleg !GenesisDelegCert | |
ShelleyTxCertMir !MIRCert |
Instances
Era era => ToJSON (ShelleyTxCert era) | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods toJSON :: ShelleyTxCert era -> Value toEncoding :: ShelleyTxCert era -> Encoding toJSONList :: [ShelleyTxCert era] -> Value toEncodingList :: [ShelleyTxCert era] -> Encoding omitField :: ShelleyTxCert era -> Bool | |||||
Generic (ShelleyTxCert era) | |||||
Defined in Cardano.Ledger.Shelley.TxCert Associated Types
Methods from :: ShelleyTxCert era -> Rep (ShelleyTxCert era) x Source # to :: Rep (ShelleyTxCert era) x -> ShelleyTxCert era Source # | |||||
Show (ShelleyTxCert era) | |||||
Defined in Cardano.Ledger.Shelley.TxCert | |||||
(ShelleyEraTxCert era, TxCert era ~ ShelleyTxCert era) => FromCBOR (ShelleyTxCert era) | |||||
Defined in Cardano.Ledger.Shelley.TxCert | |||||
Era era => ToCBOR (ShelleyTxCert era) | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods toCBOR :: ShelleyTxCert era -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyTxCert era) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ShelleyTxCert era] -> Size Source # | |||||
(ShelleyEraTxCert era, TxCert era ~ ShelleyTxCert era) => DecCBOR (ShelleyTxCert era) | |||||
Defined in Cardano.Ledger.Shelley.TxCert | |||||
Era era => EncCBOR (ShelleyTxCert era) | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods encCBOR :: ShelleyTxCert era -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (ShelleyTxCert era) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ShelleyTxCert era] -> Size Source # | |||||
NFData (ShelleyTxCert era) | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods rnf :: ShelleyTxCert era -> () Source # | |||||
Eq (ShelleyTxCert era) | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods (==) :: ShelleyTxCert era -> ShelleyTxCert era -> Bool Source # (/=) :: ShelleyTxCert era -> ShelleyTxCert era -> Bool Source # | |||||
Ord (ShelleyTxCert era) | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods compare :: ShelleyTxCert era -> ShelleyTxCert era -> Ordering Source # (<) :: ShelleyTxCert era -> ShelleyTxCert era -> Bool Source # (<=) :: ShelleyTxCert era -> ShelleyTxCert era -> Bool Source # (>) :: ShelleyTxCert era -> ShelleyTxCert era -> Bool Source # (>=) :: ShelleyTxCert era -> ShelleyTxCert era -> Bool Source # max :: ShelleyTxCert era -> ShelleyTxCert era -> ShelleyTxCert era Source # min :: ShelleyTxCert era -> ShelleyTxCert era -> ShelleyTxCert era Source # | |||||
NoThunks (ShelleyTxCert era) | |||||
Defined in Cardano.Ledger.Shelley.TxCert Methods noThunks :: Context -> ShelleyTxCert era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> ShelleyTxCert era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (ShelleyTxCert era) -> String # | |||||
type Rep (ShelleyTxCert era) | |||||
Defined in Cardano.Ledger.Shelley.TxCert type Rep (ShelleyTxCert era) = D1 ('MetaData "ShelleyTxCert" "Cardano.Ledger.Shelley.TxCert" "cardano-ledger-shelley-1.16.0.0-66390a9322bb0fb64b3f0442ebc385a2f8e5928f157dc0d1b8e0fcc9dabbabc0" 'False) ((C1 ('MetaCons "ShelleyTxCertDelegCert" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShelleyDelegCert)) :+: C1 ('MetaCons "ShelleyTxCertPool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PoolCert))) :+: (C1 ('MetaCons "ShelleyTxCertGenesisDeleg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 GenesisDelegCert)) :+: C1 ('MetaCons "ShelleyTxCertMir" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MIRCert)))) |