Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Data era where
- data Decoder s a
- newtype VKey (kd :: KeyRole) c = VKey {
- unVKey :: VerKeyDSIGN (DSIGN c)
- 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 c = TxIn !(TxId c) !TxIx
- newtype TxId c = 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 :: (VRFAlgorithm v, HashAlgorithm h) => VerKeyVRF v -> Hash h (VerKeyVRF v)
- 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 (EraCrypto era) -> TxCert era
- pattern RetirePoolTxCert :: EraTxCert era => KeyHash 'StakePool (EraCrypto era) -> EpochNo -> TxCert era
- pattern DelegStakeTxCert :: ShelleyEraTxCert era => StakeCredential (EraCrypto era) -> KeyHash 'StakePool (EraCrypto era) -> TxCert era
- pattern GenesisDelegTxCert :: (ShelleyEraTxCert era, ProtVerAtMost era 8) => KeyHash 'Genesis (EraCrypto era) -> KeyHash 'GenesisDelegate (EraCrypto era) -> Hash (EraCrypto era) (VerKeyVRF (EraCrypto era)) -> TxCert era
- pattern MirTxCert :: (ShelleyEraTxCert era, ProtVerAtMost era 8) => MIRCert (EraCrypto era) -> TxCert era
- pattern RegTxCert :: ShelleyEraTxCert era => StakeCredential (EraCrypto era) -> TxCert era
- pattern UnRegTxCert :: ShelleyEraTxCert era => StakeCredential (EraCrypto era) -> 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)), EncCBOR (Value era), ToCBOR (TxOut era), FromCBOR (TxOut era), EncCBOR (TxOut era), DecCBOR (TxOut era), DecShareCBOR (TxOut era), Share (TxOut era) ~ Interns (Credential 'Staking (EraCrypto era)), NoThunks (TxOut era), NFData (TxOut era), Show (TxOut era), Eq (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 (EraCrypto era)))
- bootAddrTxWitsL :: Lens' (TxWits era) (Set (BootstrapWitness (EraCrypto era)))
- scriptTxWitsL :: Lens' (TxWits era) (Map (ScriptHash (EraCrypto era)) (Script era))
- upgradeTxWits :: TxWits (PreviousEra era) -> TxWits era
- type family TxWits era = (r :: Type) | r -> era
- type family Value era
- class (Crypto (EraCrypto era), 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 EraCrypto era
- type PreviousEra era = (r :: Type) | r -> era
- type ProtVerLow era :: Nat
- type ProtVerHigh era :: Nat
- eraName :: String
- type family EraCrypto era
- 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 Natural)
- 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 (EraCrypto era))
- getScriptWitnessTxCert :: TxCert era -> Maybe (ScriptHash (EraCrypto era))
- mkRegPoolTxCert :: PoolParams (EraCrypto era) -> TxCert era
- getRegPoolTxCert :: TxCert era -> Maybe (PoolParams (EraCrypto era))
- mkRetirePoolTxCert :: KeyHash 'StakePool (EraCrypto era) -> EpochNo -> TxCert era
- getRetirePoolTxCert :: TxCert era -> Maybe (KeyHash 'StakePool (EraCrypto era), EpochNo)
- lookupRegStakeTxCert :: TxCert era -> Maybe (Credential 'Staking (EraCrypto era))
- lookupUnRegStakeTxCert :: TxCert era -> Maybe (Credential 'Staking (EraCrypto era))
- getTotalDepositsTxCerts :: Foldable f => PParams era -> (KeyHash 'StakePool (EraCrypto era) -> Bool) -> f (TxCert era) -> Coin
- getTotalRefundsTxCerts :: Foldable f => PParams era -> (Credential 'Staking (EraCrypto era) -> Maybe Coin) -> (Credential 'DRepRole (EraCrypto era) -> Maybe Coin) -> f (TxCert era) -> Coin
- type family TxCert era = (r :: Type) | r -> era
- type family TxCertUpgradeError era
- data PoolCert c
- = RegPool !(PoolParams c)
- | RetirePool !(KeyHash 'StakePool c) !EpochNo
- class (EraPParams era, Eq (GovState era), Show (GovState era), NoThunks (GovState era), NFData (GovState era), EncCBOR (GovState era), DecCBOR (GovState era), DecShareCBOR (GovState era), 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 c = MIRCert {
- mirPot :: !MIRPot
- mirRewards :: !(MIRTarget c)
- data MIRPot
- data MIRTarget c
- = StakeAddressesMIR !(Map (Credential 'Staking c) DeltaCoin)
- | SendToOppositePotMIR !Coin
- class EraTxCert era => ShelleyEraTxCert era where
- mkRegTxCert :: StakeCredential (EraCrypto era) -> TxCert era
- getRegTxCert :: TxCert era -> Maybe (StakeCredential (EraCrypto era))
- mkUnRegTxCert :: StakeCredential (EraCrypto era) -> TxCert era
- getUnRegTxCert :: TxCert era -> Maybe (StakeCredential (EraCrypto era))
- mkDelegStakeTxCert :: StakeCredential (EraCrypto era) -> KeyHash 'StakePool (EraCrypto era) -> TxCert era
- getDelegStakeTxCert :: TxCert era -> Maybe (StakeCredential (EraCrypto era), KeyHash 'StakePool (EraCrypto era))
- mkGenesisDelegTxCert :: GenesisDelegCert (EraCrypto era) -> TxCert era
- getGenesisDelegTxCert :: TxCert era -> Maybe (GenesisDelegCert (EraCrypto era))
- mkMirTxCert :: MIRCert (EraCrypto era) -> TxCert era
- getMirTxCert :: TxCert era -> Maybe (MIRCert (EraCrypto era))
- 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 (EraCrypto era)) -> PlutusPurpose f era
- toSpendingPurpose :: PlutusPurpose f era -> Maybe (f Word32 (TxIn (EraCrypto era)))
- mkMintingPurpose :: f Word32 (PolicyID (EraCrypto era)) -> PlutusPurpose f era
- toMintingPurpose :: PlutusPurpose f era -> Maybe (f Word32 (PolicyID (EraCrypto era)))
- mkCertifyingPurpose :: f Word32 (TxCert era) -> PlutusPurpose f era
- toCertifyingPurpose :: PlutusPurpose f era -> Maybe (f Word32 (TxCert era))
- mkRewardingPurpose :: f Word32 (RewardAccount (EraCrypto era)) -> PlutusPurpose f era
- toRewardingPurpose :: PlutusPurpose f era -> Maybe (f Word32 (RewardAccount (EraCrypto era)))
- 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 (EraCrypto era)))
- | AlonzoMinting !(f Word32 (PolicyID (EraCrypto era)))
- | AlonzoCertifying !(f Word32 (TxCert era))
- | AlonzoRewarding !(f Word32 (RewardAccount (EraCrypto era)))
- 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 (EraCrypto era)))
- reqSignerHashesTxBodyL :: Lens' (TxBody era) (Set (KeyHash 'Witness (EraCrypto era)))
- scriptIntegrityHashTxBodyL :: Lens' (TxBody era) (StrictMaybe (ScriptIntegrityHash (EraCrypto era)))
- 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
- languageToText :: Language -> Text
- data Language
- data Plutus (l :: Language)
- newtype ExUnits where
- WrapExUnits { }
- pattern ExUnits :: Natural -> Natural -> ExUnits
- unData :: Data era -> Data
- data CostModels
- data Prices = Prices {}
- newtype CoinPerByte = CoinPerByte {}
- data Anchor c = Anchor {
- anchorUrl :: !Url
- anchorDataHash :: !(SafeHash c AnchorData)
- newtype AnchorData = AnchorData ByteString
- data Constitution era = Constitution {
- constitutionAnchor :: !(Anchor (EraCrypto era))
- constitutionScript :: !(StrictMaybe (ScriptHash (EraCrypto era)))
- data GovAction era
- = ParameterChange !(StrictMaybe (GovPurposeId 'PParamUpdatePurpose era)) !(PParamsUpdate era) !(StrictMaybe (ScriptHash (EraCrypto era)))
- | HardForkInitiation !(StrictMaybe (GovPurposeId 'HardForkPurpose era)) !ProtVer
- | TreasuryWithdrawals !(Map (RewardAccount (EraCrypto era)) Coin) !(StrictMaybe (ScriptHash (EraCrypto era)))
- | NoConfidence !(StrictMaybe (GovPurposeId 'CommitteePurpose era))
- | UpdateCommittee !(StrictMaybe (GovPurposeId 'CommitteePurpose era)) !(Set (Credential 'ColdCommitteeRole (EraCrypto era))) !(Map (Credential 'ColdCommitteeRole (EraCrypto era)) EpochNo) !UnitInterval
- | NewConstitution !(StrictMaybe (GovPurposeId 'ConstitutionPurpose era)) !(Constitution era)
- | InfoAction
- data GovActionId c = GovActionId {
- gaidTxId :: !(TxId c)
- gaidGovActionIx :: !GovActionIx
- newtype GovActionIx = GovActionIx {}
- data ProposalProcedure era = ProposalProcedure {
- pProcDeposit :: !Coin
- pProcReturnAddr :: !(RewardAccount (EraCrypto era))
- pProcGovAction :: !(GovAction era)
- pProcAnchor :: !(Anchor (EraCrypto era))
- data Voter c
- = CommitteeVoter !(Credential 'HotCommitteeRole c)
- | DRepVoter !(Credential 'DRepRole c)
- | StakePoolVoter !(KeyHash 'StakePool c)
- data VotingProcedure era = VotingProcedure {
- vProcVote :: !Vote
- vProcAnchor :: !(StrictMaybe (Anchor (EraCrypto era)))
- newtype VotingProcedures era = VotingProcedures {
- unVotingProcedures :: Map (Voter (EraCrypto era)) (Map (GovActionId (EraCrypto era)) (VotingProcedure era))
- pattern AuthCommitteeHotKeyTxCert :: ConwayEraTxCert era => Credential 'ColdCommitteeRole (EraCrypto era) -> Credential 'HotCommitteeRole (EraCrypto era) -> TxCert era
- pattern DelegTxCert :: ConwayEraTxCert era => StakeCredential (EraCrypto era) -> Delegatee (EraCrypto era) -> TxCert era
- pattern RegDRepTxCert :: ConwayEraTxCert era => Credential 'DRepRole (EraCrypto era) -> Coin -> StrictMaybe (Anchor (EraCrypto era)) -> TxCert era
- pattern RegDepositDelegTxCert :: ConwayEraTxCert era => StakeCredential (EraCrypto era) -> Delegatee (EraCrypto era) -> Coin -> TxCert era
- pattern RegDepositTxCert :: ConwayEraTxCert era => StakeCredential (EraCrypto era) -> Coin -> TxCert era
- pattern ResignCommitteeColdTxCert :: ConwayEraTxCert era => Credential 'ColdCommitteeRole (EraCrypto era) -> StrictMaybe (Anchor (EraCrypto era)) -> TxCert era
- pattern UnRegDRepTxCert :: ConwayEraTxCert era => Credential 'DRepRole (EraCrypto era) -> Coin -> TxCert era
- pattern UnRegDepositTxCert :: ConwayEraTxCert era => StakeCredential (EraCrypto era) -> Coin -> TxCert era
- class ShelleyEraTxCert era => ConwayEraTxCert era where
- mkRegDepositTxCert :: StakeCredential (EraCrypto era) -> Coin -> TxCert era
- getRegDepositTxCert :: TxCert era -> Maybe (StakeCredential (EraCrypto era), Coin)
- mkUnRegDepositTxCert :: StakeCredential (EraCrypto era) -> Coin -> TxCert era
- getUnRegDepositTxCert :: TxCert era -> Maybe (StakeCredential (EraCrypto era), Coin)
- mkDelegTxCert :: StakeCredential (EraCrypto era) -> Delegatee (EraCrypto era) -> TxCert era
- getDelegTxCert :: TxCert era -> Maybe (StakeCredential (EraCrypto era), Delegatee (EraCrypto era))
- mkRegDepositDelegTxCert :: StakeCredential (EraCrypto era) -> Delegatee (EraCrypto era) -> Coin -> TxCert era
- getRegDepositDelegTxCert :: TxCert era -> Maybe (StakeCredential (EraCrypto era), Delegatee (EraCrypto era), Coin)
- mkAuthCommitteeHotKeyTxCert :: Credential 'ColdCommitteeRole (EraCrypto era) -> Credential 'HotCommitteeRole (EraCrypto era) -> TxCert era
- getAuthCommitteeHotKeyTxCert :: TxCert era -> Maybe (Credential 'ColdCommitteeRole (EraCrypto era), Credential 'HotCommitteeRole (EraCrypto era))
- mkResignCommitteeColdTxCert :: Credential 'ColdCommitteeRole (EraCrypto era) -> StrictMaybe (Anchor (EraCrypto era)) -> TxCert era
- getResignCommitteeColdTxCert :: TxCert era -> Maybe (Credential 'ColdCommitteeRole (EraCrypto era), StrictMaybe (Anchor (EraCrypto era)))
- mkRegDRepTxCert :: Credential 'DRepRole (EraCrypto era) -> Coin -> StrictMaybe (Anchor (EraCrypto era)) -> TxCert era
- getRegDRepTxCert :: TxCert era -> Maybe (Credential 'DRepRole (EraCrypto era), Coin, StrictMaybe (Anchor (EraCrypto era)))
- mkUnRegDRepTxCert :: Credential 'DRepRole (EraCrypto era) -> Coin -> TxCert era
- getUnRegDRepTxCert :: TxCert era -> Maybe (Credential 'DRepRole (EraCrypto era), Coin)
- mkUpdateDRepTxCert :: Credential 'DRepRole (EraCrypto era) -> StrictMaybe (Anchor (EraCrypto era)) -> TxCert era
- getUpdateDRepTxCert :: TxCert era -> Maybe (Credential 'DRepRole (EraCrypto era), StrictMaybe (Anchor (EraCrypto era)))
- data Delegatee c
- = DelegStake !(KeyHash 'StakePool c)
- | DelegVote !(DRep c)
- | DelegStakeVote !(KeyHash 'StakePool c) !(DRep c)
- data ConwayPlutusPurpose (f :: Type -> Type -> Type) era
- = ConwaySpending !(f Word32 (TxIn (EraCrypto era)))
- | ConwayMinting !(f Word32 (PolicyID (EraCrypto era)))
- | ConwayCertifying !(f Word32 (TxCert era))
- | ConwayRewarding !(f Word32 (RewardAccount (EraCrypto era)))
- | ConwayVoting !(f Word32 (Voter (EraCrypto era)))
- | ConwayProposing !(f Word32 (ProposalProcedure era))
- data ConwayGenesis c = ConwayGenesis {
- cgUpgradePParams :: !(UpgradeConwayPParams Identity)
- cgConstitution :: !(Constitution (ConwayEra c))
- cgCommittee :: !(Committee (ConwayEra c))
- cgDelegs :: ListMap (Credential 'Staking c) (Delegatee c)
- cgInitialDReps :: ListMap (Credential 'DRepRole c) (DRepState c)
- class (HashAlgorithm (HASH c), HashAlgorithm (ADDRHASH c), DSIGNAlgorithm (DSIGN c), KESAlgorithm (KES c), VRFAlgorithm (VRF c), ContextDSIGN (DSIGN c) ~ (), ContextKES (KES c) ~ (), ContextVRF (VRF c) ~ (), Typeable c) => Crypto c where
- type ADDRHASH c
- type family ADDRHASH c
- data StandardCrypto
- data KeyRole
- data WitVKey (kr :: KeyRole) c where
- pattern WitVKey :: (Typeable kr, Crypto c) => VKey kr c -> SignedDSIGN c (Hash c EraIndependentTxBody) -> WitVKey kr c
- hashAnchorData :: Crypto c => AnchorData -> SafeHash c AnchorData
- txIxToInt :: TxIx -> Int
- data NewEpochState era = NewEpochState {
- nesEL :: !EpochNo
- nesBprev :: !(BlocksMade (EraCrypto era))
- nesBcur :: !(BlocksMade (EraCrypto era))
- nesEs :: !(EpochState era)
- nesRu :: !(StrictMaybe (PulsingRewUpdate (EraCrypto era)))
- nesPd :: !(PoolDistr (EraCrypto era))
- stashedAVVMAddresses :: !(StashedAVVMAddresses era)
- newtype Coin = Coin {}
- serializeAsHexText :: ToCBOR a => a -> Text
- byronProtVer :: Version
- mkVersion :: (Integral i, MonadFail m) => i -> m Version
- toPlainDecoder :: Version -> Decoder s a -> Decoder s a
- data Annotated b a = Annotated {
- unAnnotated :: !b
- annotation :: !a
- data ByteSpan = ByteSpan !ByteOffset !ByteOffset
- newtype KeyHash (discriminator :: KeyRole) c = KeyHash {
- unKeyHash :: Hash (ADDRHASH c) (VerKeyDSIGN (DSIGN c))
- hashKey :: forall c (kd :: KeyRole). Crypto c => VKey kd c -> KeyHash kd c
- data Committee era = Committee {
- committeeMembers :: !(Map (Credential 'ColdCommitteeRole (EraCrypto era)) EpochNo)
- committeeThreshold :: !UnitInterval
- 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 (EraCrypto era) -> StrictMaybe (Anchor (EraCrypto era)) -> TxCert era
- data ConwayDelegCert c
- = ConwayRegCert !(StakeCredential c) !(StrictMaybe Coin)
- | ConwayUnRegCert !(StakeCredential c) !(StrictMaybe Coin)
- | ConwayDelegCert !(StakeCredential c) !(Delegatee c)
- | ConwayRegDelegCert !(StakeCredential c) !(Delegatee c) !Coin
- data ConwayGovCert c
- = ConwayRegDRep !(Credential 'DRepRole c) !Coin !(StrictMaybe (Anchor c))
- | ConwayUnRegDRep !(Credential 'DRepRole c) !Coin
- | ConwayUpdateDRep !(Credential 'DRepRole c) !(StrictMaybe (Anchor c))
- | ConwayAuthCommitteeHotKey !(Credential 'ColdCommitteeRole c) !(Credential 'HotCommitteeRole c)
- | ConwayResignCommitteeColdKey !(Credential 'ColdCommitteeRole c) !(StrictMaybe (Anchor c))
- data ConwayTxCert era
- = ConwayTxCertDeleg !(ConwayDelegCert (EraCrypto era))
- | ConwayTxCertPool !(PoolCert (EraCrypto era))
- | ConwayTxCertGov !(ConwayGovCert (EraCrypto era))
- newtype EpochInterval = EpochInterval {}
- newtype EpochNo = EpochNo {}
- data GenDelegPair c = GenDelegPair {
- genDelegKeyHash :: !(KeyHash 'GenesisDelegate c)
- genDelegVrfHash :: !(Hash c (VerKeyVRF c))
- class HasKeyRole (a :: KeyRole -> Type -> Type)
- castSafeHash :: forall i j c. SafeHash c i -> SafeHash c j
- extractHash :: SafeHash c i -> Hash (HASH c) i
- unsafeMakeSafeHash :: Hash (HASH c) index -> SafeHash c index
- data SafeHash c index
- 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) c. Credential kr c -> Text
- data Credential (kr :: KeyRole) c
- = ScriptHashObj !(ScriptHash c)
- | KeyHashObj !(KeyHash kr c)
- data StakeReference c
- = StakeRefBase !(StakeCredential c)
- | StakeRefPtr !Ptr
- | StakeRefNull
- addDeltaCoin :: Coin -> DeltaCoin -> Coin
- toDeltaCoin :: Coin -> DeltaCoin
- drepAnchorL :: forall c f. Functor f => (StrictMaybe (Anchor c) -> f (StrictMaybe (Anchor c))) -> DRepState c -> f (DRepState c)
- drepDepositL :: forall c f. Functor f => (Coin -> f Coin) -> DRepState c -> f (DRepState c)
- drepExpiryL :: forall c f. Functor f => (EpochNo -> f EpochNo) -> DRepState c -> f (DRepState c)
- data DRep c where
- DRepKeyHash !(KeyHash 'DRepRole c)
- DRepScriptHash !(ScriptHash c)
- DRepAlwaysAbstain
- DRepAlwaysNoConfidence
- pattern DRepCredential :: Credential 'DRepRole c -> DRep c
- data DRepState c = DRepState {
- drepExpiry :: !EpochNo
- drepAnchor :: !(StrictMaybe (Anchor c))
- drepDeposit :: !Coin
- drepDelegs :: !(Set (Credential 'Staking c))
- data PoolMetadata = PoolMetadata {
- pmUrl :: !Url
- pmHash :: !ByteString
- data PoolParams c = PoolParams {
- ppId :: !(KeyHash 'StakePool c)
- ppVrf :: !(Hash c (VerKeyVRF c))
- ppPledge :: !Coin
- ppCost :: !Coin
- ppMargin :: !UnitInterval
- ppRewardAccount :: !(RewardAccount c)
- ppOwners :: !(Set (KeyHash 'Staking c))
- ppRelays :: !(StrictSeq StakePoolRelay)
- ppMetadata :: !(StrictMaybe PoolMetadata)
- data StakePoolRelay
- = SingleHostAddr !(StrictMaybe Port) !(StrictMaybe IPv4) !(StrictMaybe IPv6)
- | SingleHostName !(StrictMaybe Port) !DnsName
- | MultiHostName !DnsName
- csCommitteeCredsL :: forall era f. Functor f => (Map (Credential 'ColdCommitteeRole (EraCrypto era)) (CommitteeAuthorization (EraCrypto era)) -> f (Map (Credential 'ColdCommitteeRole (EraCrypto era)) (CommitteeAuthorization (EraCrypto era)))) -> CommitteeState era -> f (CommitteeState era)
- data PState era = PState {
- psStakePoolParams :: !(Map (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era)))
- psFutureStakePoolParams :: !(Map (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era)))
- psRetiring :: !(Map (KeyHash 'StakePool (EraCrypto era)) EpochNo)
- psDeposits :: !(Map (KeyHash 'StakePool (EraCrypto era)) Coin)
- maybeToStrictMaybe :: Maybe a -> StrictMaybe a
- strictMaybeToMaybe :: StrictMaybe a -> Maybe a
- secondsToNominalDiffTimeMicro :: Micro -> NominalDiffTimeMicro
- data ShelleyGenesisStaking c = ShelleyGenesisStaking {}
- data GenesisDelegCert c = GenesisDelegCert !(KeyHash 'Genesis c) !(KeyHash 'GenesisDelegate c) !(Hash c (VerKeyVRF c))
- data ShelleyDelegCert c where
- ShelleyRegCert !(StakeCredential c)
- ShelleyUnRegCert !(StakeCredential c)
- ShelleyDelegCert !(StakeCredential c) !(KeyHash 'StakePool c)
- pattern DeRegKey :: StakeCredential c -> ShelleyDelegCert c
- pattern Delegate :: Delegation c -> ShelleyDelegCert c
- pattern RegKey :: StakeCredential c -> ShelleyDelegCert c
- data ShelleyTxCert era
- = ShelleyTxCertDelegCert !(ShelleyDelegCert (EraCrypto era))
- | ShelleyTxCertPool !(PoolCert (EraCrypto era))
- | ShelleyTxCertGenesisDeleg !(GenesisDelegCert (EraCrypto era))
- | ShelleyTxCertMir !(MIRCert (EraCrypto era))
- data AccountState = AccountState {
- asTreasury :: !Coin
- asReserves :: !Coin
Documentation
Instances
Instances
MonadFail (Decoder s) | |
Applicative (Decoder s) | |
Defined in Codec.CBOR.Decoding | |
Functor (Decoder s) | |
Monad (Decoder s) | |
newtype VKey (kd :: KeyRole) c Source #
Discriminated verification key
We wrap the basic VerKeyDSIGN
in order to add the key role.
VKey | |
|
Instances
HasKeyRole VKey | |||||
Defined in Cardano.Ledger.Keys.Internal | |||||
Generic (VKey kd c) | |||||
Defined in Cardano.Ledger.Keys.Internal
| |||||
Crypto c => Show (VKey kd c) | |||||
(Crypto c, Typeable kd) => FromCBOR (VKey kd c) | |||||
(Crypto c, Typeable kd) => ToCBOR (VKey kd c) | |||||
(Crypto c, Typeable kd) => DecCBOR (VKey kd c) | |||||
(Crypto c, Typeable kd) => EncCBOR (VKey kd c) | |||||
(Crypto c, NFData (VerKeyDSIGN (DSIGN c))) => NFData (VKey kd c) | |||||
Defined in Cardano.Ledger.Keys.Internal | |||||
Crypto c => Eq (VKey kd c) | |||||
Crypto c => NoThunks (VKey kd c) | |||||
type Rep (VKey kd c) | |||||
Defined in Cardano.Ledger.Keys.Internal type Rep (VKey kd c) = D1 ('MetaData "VKey" "Cardano.Ledger.Keys.Internal" "cardano-ledger-core-1.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" 'True) (C1 ('MetaCons "VKey" 'PrefixI 'True) (S1 ('MetaSel ('Just "unVKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VerKeyDSIGN (DSIGN c))))) |
Protocol parameters
PParams (PParamsHKD Identity era) |
Instances
FromJSON (PParamsHKD Identity era) => FromJSON (PParams era) | |||||
Defined in Cardano.Ledger.Core.PParams 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 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
| |||||
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 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 Rep (PParams era) | |||||
Defined in Cardano.Ledger.Core.PParams type Rep (PParams era) = D1 ('MetaData "PParams" "Cardano.Ledger.Core.PParams" "cardano-ledger-core-1.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" 'True) (C1 ('MetaCons "PParams" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PParamsHKD Identity era)))) | |||||
type TranslationError (AllegraEra c) PParams | |||||
Defined in Cardano.Ledger.Allegra.Translation | |||||
type TranslationError (AlonzoEra c) PParams | |||||
Defined in Cardano.Ledger.Alonzo.Translation | |||||
type TranslationError (BabbageEra c) PParams | |||||
Defined in Cardano.Ledger.Babbage.Translation | |||||
type TranslationError (ConwayEra c) PParams | |||||
Defined in Cardano.Ledger.Conway.Translation | |||||
type TranslationError (MaryEra c) PParams | |||||
Defined in Cardano.Ledger.Mary.Translation |
Instances
FromJSON ProtVer | |||||
Defined in Cardano.Ledger.BaseTypes parseJSON :: Value -> Parser ProtVer parseJSONList :: Value -> Parser [ProtVer] | |||||
ToJSON ProtVer | |||||
Defined in Cardano.Ledger.BaseTypes toEncoding :: ProtVer -> Encoding toJSONList :: [ProtVer] -> Value toEncodingList :: [ProtVer] -> Encoding | |||||
Generic ProtVer | |||||
Defined in Cardano.Ledger.BaseTypes
| |||||
Show ProtVer | |||||
FromCBOR ProtVer | |||||
ToCBOR ProtVer | |||||
DecCBOR ProtVer | |||||
EncCBOR ProtVer | |||||
DecCBORGroup ProtVer | |||||
Defined in Cardano.Ledger.BaseTypes decCBORGroup :: Decoder s ProtVer Source # | |||||
EncCBORGroup ProtVer | |||||
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.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" '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 | |||||
Bounded Vote | |||||
Enum Vote | |||||
Generic Vote | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures
| |||||
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.17.0.0-ed41115f30aea12826c7e98271388af39c652244463f16622d3682aa6c1354c0" '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.
type family Tx era = (r :: Type) | r -> era Source #
Instances
type Tx (AllegraEra c) | |
Defined in Cardano.Ledger.Allegra.Tx | |
type Tx (AlonzoEra c) | |
Defined in Cardano.Ledger.Alonzo.Tx | |
type Tx (BabbageEra c) | |
Defined in Cardano.Ledger.Babbage.Tx | |
type Tx (ConwayEra c) | |
Defined in Cardano.Ledger.Conway.Tx | |
type Tx (MaryEra c) | |
Defined in Cardano.Ledger.Mary.Tx | |
type Tx (ShelleyEra c) | |
Defined in Cardano.Ledger.Shelley.Tx.Internal |
The input of a UTxO.
Instances
Crypto c => ToJSON (TxIn c) | |||||
Defined in Cardano.Ledger.TxIn toEncoding :: TxIn c -> Encoding toJSONList :: [TxIn c] -> Value toEncodingList :: [TxIn c] -> Encoding | |||||
Crypto c => ToJSONKey (TxIn c) | |||||
Defined in Cardano.Ledger.TxIn toJSONKey :: ToJSONKeyFunction (TxIn c) toJSONKeyList :: ToJSONKeyFunction [TxIn c] | |||||
Generic (TxIn c) | |||||
Defined in Cardano.Ledger.TxIn
| |||||
Show (TxIn c) | |||||
Crypto c => DecCBOR (TxIn c) | |||||
Crypto c => EncCBOR (TxIn c) | |||||
Crypto c => NFData (TxIn c) | |||||
Defined in Cardano.Ledger.TxIn | |||||
Eq (TxIn c) | |||||
Ord (TxIn c) | |||||
Defined in Cardano.Ledger.TxIn | |||||
Crypto c => HeapWords (TxIn c) | |||||
Defined in Cardano.Ledger.TxIn | |||||
NoThunks (TxIn c) | |||||
type Rep (TxIn c) | |||||
Defined in Cardano.Ledger.TxIn type Rep (TxIn c) = D1 ('MetaData "TxIn" "Cardano.Ledger.TxIn" "cardano-ledger-core-1.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" 'False) (C1 ('MetaCons "TxIn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TxId c)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedUnpack) (Rec0 TxIx))) |
A unique ID of a transaction, which is computable from the transaction.
Instances
Crypto c => FromJSON (TxId c) | |||||
Defined in Cardano.Ledger.TxIn parseJSON :: Value -> Parser (TxId c) parseJSONList :: Value -> Parser [TxId c] omittedField :: Maybe (TxId c) | |||||
Crypto c => ToJSON (TxId c) | |||||
Defined in Cardano.Ledger.TxIn toEncoding :: TxId c -> Encoding toJSONList :: [TxId c] -> Value toEncodingList :: [TxId c] -> Encoding | |||||
Generic (TxId c) | |||||
Defined in Cardano.Ledger.TxIn
| |||||
Show (TxId c) | |||||
Crypto c => DecCBOR (TxId c) | |||||
Crypto c => EncCBOR (TxId c) | |||||
Crypto c => NFData (TxId c) | |||||
Defined in Cardano.Ledger.TxIn | |||||
Eq (TxId c) | |||||
Ord (TxId c) | |||||
Defined in Cardano.Ledger.TxIn | |||||
Crypto c => HeapWords (TxId c) | |||||
Defined in Cardano.Ledger.TxIn | |||||
NoThunks (TxId c) | |||||
type Rep (TxId c) | |||||
Defined in Cardano.Ledger.TxIn type Rep (TxId c) = D1 ('MetaData "TxId" "Cardano.Ledger.TxIn" "cardano-ledger-core-1.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" 'True) (C1 ('MetaCons "TxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SafeHash c 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.
:: 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 :: (VRFAlgorithm v, HashAlgorithm h) => VerKeyVRF v -> Hash h (VerKeyVRF v) Source #
data StrictMaybe a Source #
Instances
MonadFail StrictMaybe | |||||
Defined in Data.Maybe.Strict fail :: String -> StrictMaybe a Source # | |||||
Foldable StrictMaybe | |||||
Defined in Data.Maybe.Strict 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 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 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 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 fmap :: (a -> b) -> StrictMaybe a -> StrictMaybe b Source # (<$) :: a -> StrictMaybe b -> StrictMaybe a Source # | |||||
Monad StrictMaybe | |||||
Defined in Data.Maybe.Strict (>>=) :: 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 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 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 parseJSON :: Value -> Parser (StrictMaybe a) parseJSONList :: Value -> Parser [StrictMaybe a] omittedField :: Maybe (StrictMaybe a) | |||||
ToJSON a => ToJSON (StrictMaybe a) | |||||
Defined in Data.Maybe.Strict 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 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 (<>) :: 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
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 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 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 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 | |||||
Default (UpgradeConwayPParams StrictMaybe) | |||||
Defined in Cardano.Ledger.Conway.PParams | |||||
Default (StrictMaybe t) | |||||
Defined in Data.Maybe.Strict def :: StrictMaybe t # | |||||
NFData (UpgradeConwayPParams StrictMaybe) | |||||
Defined in Cardano.Ledger.Conway.PParams rnf :: UpgradeConwayPParams StrictMaybe -> () Source # | |||||
NFData a => NFData (StrictMaybe a) | |||||
Defined in Data.Maybe.Strict rnf :: StrictMaybe a -> () Source # | |||||
Eq (UpgradeConwayPParams StrictMaybe) | |||||
Eq a => Eq (StrictMaybe a) | |||||
Defined in Data.Maybe.Strict (==) :: StrictMaybe a -> StrictMaybe a -> Bool Source # (/=) :: StrictMaybe a -> StrictMaybe a -> Bool Source # | |||||
Ord (UpgradeConwayPParams StrictMaybe) | |||||
Defined in Cardano.Ledger.Conway.PParams 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 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 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 noThunks :: Context -> StrictMaybe a -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> StrictMaybe a -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (StrictMaybe a) -> String # | |||||
Crypto c => ToJSON (AlonzoPParams StrictMaybe (AlonzoEra c)) | |||||
Defined in Cardano.Ledger.Alonzo.PParams toJSON :: AlonzoPParams StrictMaybe (AlonzoEra c) -> Value toEncoding :: AlonzoPParams StrictMaybe (AlonzoEra c) -> Encoding toJSONList :: [AlonzoPParams StrictMaybe (AlonzoEra c)] -> Value toEncodingList :: [AlonzoPParams StrictMaybe (AlonzoEra c)] -> Encoding omitField :: AlonzoPParams StrictMaybe (AlonzoEra c) -> Bool | |||||
(PParamsHKD StrictMaybe era ~ BabbagePParams StrictMaybe era, BabbageEraPParams era, ProtVerAtMost era 8) => ToJSON (BabbagePParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Babbage.PParams 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 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 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 | |||||
Show (AlonzoPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Alonzo.PParams 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 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 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 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 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 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 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 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 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 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 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 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 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 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 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 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 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 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 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 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 rnf :: AlonzoPParams StrictMaybe era -> () Source # | |||||
NFData (BabbagePParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Babbage.PParams rnf :: BabbagePParams StrictMaybe era -> () Source # | |||||
NFData (ConwayPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Conway.PParams rnf :: ConwayPParams StrictMaybe era -> () Source # | |||||
NFData (ShelleyPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Shelley.PParams rnf :: ShelleyPParams StrictMaybe era -> () Source # | |||||
Eq (AlonzoPParams StrictMaybe era) | |||||
Defined in Cardano.Ledger.Alonzo.PParams (==) :: 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 (==) :: 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 (==) :: 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 (==) :: 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 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 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 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 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 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 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 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 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 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 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 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.3.0-0a3f9168281c6ab7fea9d29726617b85d9cafa4cf443fc9b32faaad15c31f49b" '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 #
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 (EraCrypto era) -> TxCert era Source #
pattern RetirePoolTxCert :: EraTxCert era => KeyHash 'StakePool (EraCrypto era) -> EpochNo -> TxCert era Source #
pattern DelegStakeTxCert :: ShelleyEraTxCert era => StakeCredential (EraCrypto era) -> KeyHash 'StakePool (EraCrypto era) -> TxCert era Source #
pattern GenesisDelegTxCert :: (ShelleyEraTxCert era, ProtVerAtMost era 8) => KeyHash 'Genesis (EraCrypto era) -> KeyHash 'GenesisDelegate (EraCrypto era) -> Hash (EraCrypto era) (VerKeyVRF (EraCrypto era)) -> TxCert era Source #
pattern MirTxCert :: (ShelleyEraTxCert era, ProtVerAtMost era 8) => MIRCert (EraCrypto era) -> TxCert era Source #
pattern RegTxCert :: ShelleyEraTxCert era => StakeCredential (EraCrypto era) -> TxCert era Source #
pattern UnRegTxCert :: ShelleyEraTxCert era => StakeCredential (EraCrypto era) -> 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 c) | |
Defined in Cardano.Ledger.Allegra.Scripts | |
type Script (AlonzoEra c) | |
Defined in Cardano.Ledger.Alonzo.Scripts | |
type Script (BabbageEra c) | |
Defined in Cardano.Ledger.Babbage.Scripts | |
type Script (ConwayEra c) | |
Defined in Cardano.Ledger.Conway.Scripts | |
type Script (MaryEra c) | |
Defined in Cardano.Ledger.Mary.Scripts | |
type Script (ShelleyEra c) | |
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 c) | |
Defined in Cardano.Ledger.Allegra.Scripts | |
type Script (AlonzoEra c) | |
Defined in Cardano.Ledger.Alonzo.Scripts | |
type Script (BabbageEra c) | |
Defined in Cardano.Ledger.Babbage.Scripts | |
type Script (ConwayEra c) | |
Defined in Cardano.Ledger.Conway.Scripts | |
type Script (MaryEra c) | |
Defined in Cardano.Ledger.Mary.Scripts | |
type Script (ShelleyEra c) | |
Defined in Cardano.Ledger.Shelley.Scripts |
class (Val (Value era), ToJSON (TxOut era), DecCBOR (Value era), DecCBOR (CompactForm (Value era)), EncCBOR (Value era), ToCBOR (TxOut era), FromCBOR (TxOut era), EncCBOR (TxOut era), DecCBOR (TxOut era), DecShareCBOR (TxOut era), Share (TxOut era) ~ Interns (Credential 'Staking (EraCrypto era)), NoThunks (TxOut era), NFData (TxOut era), Show (TxOut era), Eq (TxOut era), EraPParams era) => EraTxOut era Source #
Abstract interface into specific fields of a TxOut
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
mkBasicTxWits :: TxWits era Source #
addrTxWitsL :: Lens' (TxWits era) (Set (WitVKey 'Witness (EraCrypto era))) Source #
bootAddrTxWitsL :: Lens' (TxWits era) (Set (BootstrapWitness (EraCrypto era))) Source #
scriptTxWitsL :: Lens' (TxWits era) (Map (ScriptHash (EraCrypto era)) (Script era)) Source #
upgradeTxWits :: TxWits (PreviousEra era) -> TxWits era Source #
type family TxWits era = (r :: Type) | r -> era Source #
Instances
type TxWits (AllegraEra c) | |
Defined in Cardano.Ledger.Allegra.TxWits | |
type TxWits (AlonzoEra c) | |
Defined in Cardano.Ledger.Alonzo.TxWits | |
type TxWits (BabbageEra c) | |
Defined in Cardano.Ledger.Babbage.TxWits | |
type TxWits (ConwayEra c) | |
Defined in Cardano.Ledger.Conway.TxWits | |
type TxWits (MaryEra c) | |
Defined in Cardano.Ledger.Mary.TxWits | |
type TxWits (ShelleyEra c) | |
Defined in Cardano.Ledger.Shelley.TxWits |
type family Value era Source #
A value is something which quantifies a transaction output.
Instances
type Value (ConwayEra c) | |
Defined in Cardano.Ledger.Conway.Era | |
type Value (ShelleyEra _c) | |
Defined in Cardano.Ledger.Shelley.Era |
class (Crypto (EraCrypto era), 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 #
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
Textual name of the current era.
Designed to be used with TypeApplications
:
>>>
eraName @(ByronEra StandardCrypto)
Byron
Instances
Crypto c => Era (ConwayEra c) | |||||||||||||||||
Defined in Cardano.Ledger.Conway.Era
| |||||||||||||||||
Crypto c => Era (ByronEra c) | |||||||||||||||||
Defined in Cardano.Ledger.Core.Era
| |||||||||||||||||
Crypto c => Era (ShelleyEra c) | |||||||||||||||||
Defined in Cardano.Ledger.Shelley.Era
|
type family EraCrypto era Source #
Instances
type EraCrypto (ConwayEra c) | |
Defined in Cardano.Ledger.Conway.Era | |
type EraCrypto (ByronEra c) | |
Defined in Cardano.Ledger.Core.Era | |
type EraCrypto (ShelleyEra c) | |
Defined in Cardano.Ledger.Shelley.Era |
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 (ConwayEra c) | |
Defined in Cardano.Ledger.Conway.Era | |
type PreviousEra (ByronEra c) | |
Defined in Cardano.Ledger.Core.Era | |
type PreviousEra (ShelleyEra c) | |
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 (ConwayEra c) | |
Defined in Cardano.Ledger.Conway.Era | |
type ProtVerHigh (ByronEra c) | |
Defined in Cardano.Ledger.Core.Era | |
type ProtVerHigh (ShelleyEra c) | |
Defined in Cardano.Ledger.Shelley.Era |
type family ProtVerLow era :: Nat Source #
Lowest major protocol version for this era
Instances
type ProtVerLow (ConwayEra c) | |
Defined in Cardano.Ledger.Conway.Era | |
type ProtVerLow (ByronEra c) | |
Defined in Cardano.Ledger.Core.Era | |
type ProtVerLow (ShelleyEra c) | |
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 #
emptyPParamsIdentity, emptyPParamsStrictMaybe, upgradePParamsHKD, downgradePParamsHKD, hkdMinFeeAL, hkdMinFeeBL, hkdMaxBBSizeL, hkdMaxTxSizeL, hkdMaxBHSizeL, hkdKeyDepositL, hkdPoolDepositL, hkdEMaxL, hkdNOptL, hkdA0L, hkdRhoL, hkdTauL, hkdDL, hkdExtraEntropyL, hkdProtocolVersionL, hkdMinUTxOValueL, hkdMinPoolCostL
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 #
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 Natural) 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 c) | |
Defined in Cardano.Ledger.Allegra.PParams | |
type DowngradePParams f (AlonzoEra c) | |
Defined in Cardano.Ledger.Alonzo.PParams | |
type DowngradePParams f (BabbageEra c) | |
Defined in Cardano.Ledger.Babbage.PParams | |
type DowngradePParams f (ConwayEra c) | |
Defined in Cardano.Ledger.Conway.PParams | |
type DowngradePParams f (MaryEra c) | |
Defined in Cardano.Ledger.Mary.PParams | |
type DowngradePParams f (ShelleyEra c) | |
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 c) | |
Defined in Cardano.Ledger.Allegra.PParams | |
type PParamsHKD f (AlonzoEra c) | |
Defined in Cardano.Ledger.Alonzo.PParams | |
type PParamsHKD f (BabbageEra c) | |
Defined in Cardano.Ledger.Babbage.PParams | |
type PParamsHKD f (ConwayEra c) | |
Defined in Cardano.Ledger.Conway.PParams | |
type PParamsHKD f (MaryEra c) | |
Defined in Cardano.Ledger.Mary.PParams | |
type PParamsHKD f (ShelleyEra c) | |
Defined in Cardano.Ledger.Shelley.PParams |
type family UpgradePParams (f :: Type -> Type) era Source #
Instances
type UpgradePParams f (AllegraEra c) | |
Defined in Cardano.Ledger.Allegra.PParams | |
type UpgradePParams f (AlonzoEra c) | |
Defined in Cardano.Ledger.Alonzo.PParams | |
type UpgradePParams f (BabbageEra c) | |
Defined in Cardano.Ledger.Babbage.PParams | |
type UpgradePParams f (ConwayEra c) | |
Defined in Cardano.Ledger.Conway.PParams | |
type UpgradePParams f (MaryEra c) | |
Defined in Cardano.Ledger.Mary.PParams | |
type UpgradePParams f (ShelleyEra c) | |
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 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 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
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 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 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 def :: PParamsUpdate era # | |||||
NFData (PParamsHKD StrictMaybe era) => NFData (PParamsUpdate era) | |||||
Defined in Cardano.Ledger.Core.PParams rnf :: PParamsUpdate era -> () Source # | |||||
Eq (PParamsHKD StrictMaybe era) => Eq (PParamsUpdate era) | |||||
Defined in Cardano.Ledger.Core.PParams (==) :: 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 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 noThunks :: Context -> PParamsUpdate era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> PParamsUpdate era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (PParamsUpdate era) -> String # | |||||
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.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" 'True) (C1 ('MetaCons "PParamsUpdate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PParamsHKD StrictMaybe era)))) | |||||
type TranslationError (AllegraEra c) PParamsUpdate | |||||
Defined in Cardano.Ledger.Allegra.Translation | |||||
type TranslationError (MaryEra c) PParamsUpdate | |||||
Defined in Cardano.Ledger.Mary.Translation |
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 #
type TxCert era = (r :: Type) | r -> era Source #
type TxCertUpgradeError era Source #
type TxCertUpgradeError era = Void
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 (EraCrypto era)) Source #
Return a witness key whenever a certificate requires one
getScriptWitnessTxCert :: TxCert era -> Maybe (ScriptHash (EraCrypto era)) Source #
Return a ScriptHash for certificate types that require a witness
mkRegPoolTxCert :: PoolParams (EraCrypto era) -> TxCert era Source #
getRegPoolTxCert :: TxCert era -> Maybe (PoolParams (EraCrypto era)) Source #
mkRetirePoolTxCert :: KeyHash 'StakePool (EraCrypto era) -> EpochNo -> TxCert era Source #
getRetirePoolTxCert :: TxCert era -> Maybe (KeyHash 'StakePool (EraCrypto era), EpochNo) Source #
lookupRegStakeTxCert :: TxCert era -> Maybe (Credential 'Staking (EraCrypto era)) Source #
Extract staking credential from any certificate that can register such credential
lookupUnRegStakeTxCert :: TxCert era -> Maybe (Credential 'Staking (EraCrypto era)) Source #
Extract staking credential from any certificate that can unregister such credential
getTotalDepositsTxCerts Source #
:: Foldable f | |
=> PParams era | |
-> (KeyHash 'StakePool (EraCrypto era) -> Bool) | Check whether stake pool is registered or not |
-> f (TxCert era) | |
-> Coin |
Compute the total deposits from a list of certificates.
getTotalRefundsTxCerts Source #
:: Foldable f | |
=> PParams era | |
-> (Credential 'Staking (EraCrypto era) -> Maybe Coin) | Lookup current deposit for Staking credential if one is registered |
-> (Credential 'DRepRole (EraCrypto era) -> 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 c) | |
Defined in Cardano.Ledger.Allegra.TxCert | |
type TxCert (AlonzoEra c) | |
Defined in Cardano.Ledger.Alonzo.TxCert | |
type TxCert (BabbageEra c) | |
Defined in Cardano.Ledger.Babbage.TxCert | |
type TxCert (ConwayEra c) | |
Defined in Cardano.Ledger.Conway.TxCert | |
type TxCert (MaryEra c) | |
Defined in Cardano.Ledger.Mary.TxCert | |
type TxCert (ShelleyEra c) | |
Defined in Cardano.Ledger.Shelley.TxCert |
type family TxCertUpgradeError era Source #
Instances
type TxCertUpgradeError (AllegraEra c) | |
Defined in Cardano.Ledger.Allegra.TxCert | |
type TxCertUpgradeError (AlonzoEra c) | |
Defined in Cardano.Ledger.Alonzo.TxCert | |
type TxCertUpgradeError (BabbageEra c) | |
Defined in Cardano.Ledger.Babbage.TxCert | |
type TxCertUpgradeError (ConwayEra c) | |
Defined in Cardano.Ledger.Conway.TxCert | |
type TxCertUpgradeError (MaryEra c) | |
Defined in Cardano.Ledger.Mary.TxCert | |
type TxCertUpgradeError (ShelleyEra c) | |
Defined in Cardano.Ledger.Shelley.TxCert |
RegPool !(PoolParams c) | A stake pool registration certificate. |
RetirePool !(KeyHash 'StakePool c) !EpochNo | A stake pool retirement certificate. |
Instances
Crypto c => ToJSON (PoolCert c) | |||||
Defined in Cardano.Ledger.Core.TxCert toEncoding :: PoolCert c -> Encoding toJSONList :: [PoolCert c] -> Value toEncodingList :: [PoolCert c] -> Encoding | |||||
Generic (PoolCert c) | |||||
Defined in Cardano.Ledger.Core.TxCert
| |||||
Show (PoolCert c) | |||||
Crypto c => EncCBOR (PoolCert c) | |||||
NFData (PoolCert c) | |||||
Defined in Cardano.Ledger.Core.TxCert | |||||
Eq (PoolCert c) | |||||
Ord (PoolCert c) | |||||
Defined in Cardano.Ledger.Core.TxCert compare :: PoolCert c -> PoolCert c -> Ordering Source # (<) :: PoolCert c -> PoolCert c -> Bool Source # (<=) :: PoolCert c -> PoolCert c -> Bool Source # (>) :: PoolCert c -> PoolCert c -> Bool Source # (>=) :: PoolCert c -> PoolCert c -> Bool Source # | |||||
NoThunks (PoolCert c) | |||||
type Rep (PoolCert c) | |||||
Defined in Cardano.Ledger.Core.TxCert type Rep (PoolCert c) = D1 ('MetaData "PoolCert" "Cardano.Ledger.Core.TxCert" "cardano-ledger-core-1.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" 'False) (C1 ('MetaCons "RegPool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PoolParams c))) :+: C1 ('MetaCons "RetirePool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool c)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 EpochNo))) |
class (EraPParams era, Eq (GovState era), Show (GovState era), NoThunks (GovState era), NFData (GovState era), EncCBOR (GovState era), DecCBOR (GovState era), DecShareCBOR (GovState era), ToCBOR (GovState era), FromCBOR (GovState era), Default (GovState era), ToJSON (GovState era)) => EraGov era Source #
Instances
Crypto c => EraGov (ShelleyEra c) | |||||
Defined in Cardano.Ledger.Shelley.Governance
emptyGovState :: GovState (ShelleyEra c) Source # getProposedPPUpdates :: GovState (ShelleyEra c) -> Maybe (ProposedPPUpdates (ShelleyEra c)) Source # curPParamsGovStateL :: Lens' (GovState (ShelleyEra c)) (PParams (ShelleyEra c)) Source # prevPParamsGovStateL :: Lens' (GovState (ShelleyEra c)) (PParams (ShelleyEra c)) Source # futurePParamsGovStateL :: Lens' (GovState (ShelleyEra c)) (FuturePParams (ShelleyEra c)) Source # obligationGovState :: GovState (ShelleyEra c) -> Obligations Source # |
type family GovState era = (r :: Type) | r -> era Source #
Instances
type GovState (AllegraEra c) | |
Defined in Cardano.Ledger.Allegra.PParams | |
type GovState (AlonzoEra c) | |
Defined in Cardano.Ledger.Alonzo.PParams | |
type GovState (BabbageEra c) | |
Defined in Cardano.Ledger.Babbage.PParams | |
type GovState (ConwayEra c) | |
Defined in Cardano.Ledger.Conway.Governance | |
type GovState (MaryEra c) | |
Defined in Cardano.Ledger.Mary.PParams | |
type GovState (ShelleyEra c) | |
Defined in Cardano.Ledger.Shelley.Governance |
Move instantaneous rewards certificate
MIRCert | |
|
Instances
Crypto c => ToJSON (MIRCert c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert toEncoding :: MIRCert c -> Encoding toJSONList :: [MIRCert c] -> Value toEncodingList :: [MIRCert c] -> Encoding | |||||
Generic (MIRCert c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert
| |||||
Show (MIRCert c) | |||||
Crypto c => DecCBOR (MIRCert c) | |||||
Crypto c => EncCBOR (MIRCert c) | |||||
NFData (MIRCert c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert | |||||
Eq (MIRCert c) | |||||
Ord (MIRCert c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert | |||||
NoThunks (MIRCert c) | |||||
type Rep (MIRCert c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert type Rep (MIRCert c) = D1 ('MetaData "MIRCert" "Cardano.Ledger.Shelley.TxCert" "cardano-ledger-shelley-1.14.1.0-6da62eb4db0139bb466588c0f3bf17f53ad859af8a090c113a1a960870dce943" 'False) (C1 ('MetaCons "MIRCert" 'PrefixI 'True) (S1 ('MetaSel ('Just "mirPot") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MIRPot) :*: S1 ('MetaSel ('Just "mirRewards") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (MIRTarget c)))) |
Instances
ToJSON MIRPot | |||||
Defined in Cardano.Ledger.Shelley.TxCert toEncoding :: MIRPot -> Encoding toJSONList :: [MIRPot] -> Value toEncodingList :: [MIRPot] -> Encoding | |||||
Bounded MIRPot | |||||
Enum MIRPot | |||||
Defined in Cardano.Ledger.Shelley.TxCert 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
| |||||
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.14.1.0-6da62eb4db0139bb466588c0f3bf17f53ad859af8a090c113a1a960870dce943" '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.
Instances
Crypto c => ToJSON (MIRTarget c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert toJSON :: MIRTarget c -> Value toEncoding :: MIRTarget c -> Encoding toJSONList :: [MIRTarget c] -> Value toEncodingList :: [MIRTarget c] -> Encoding | |||||
Generic (MIRTarget c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert
| |||||
Show (MIRTarget c) | |||||
Crypto c => DecCBOR (MIRTarget c) | |||||
Crypto c => EncCBOR (MIRTarget c) | |||||
NFData (MIRTarget c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert | |||||
Eq (MIRTarget c) | |||||
Ord (MIRTarget c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert compare :: MIRTarget c -> MIRTarget c -> Ordering Source # (<) :: MIRTarget c -> MIRTarget c -> Bool Source # (<=) :: MIRTarget c -> MIRTarget c -> Bool Source # (>) :: MIRTarget c -> MIRTarget c -> Bool Source # (>=) :: MIRTarget c -> MIRTarget c -> Bool Source # | |||||
NoThunks (MIRTarget c) | |||||
type Rep (MIRTarget c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert type Rep (MIRTarget c) = D1 ('MetaData "MIRTarget" "Cardano.Ledger.Shelley.TxCert" "cardano-ledger-shelley-1.14.1.0-6da62eb4db0139bb466588c0f3bf17f53ad859af8a090c113a1a960870dce943" 'False) (C1 ('MetaCons "StakeAddressesMIR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (Credential 'Staking c) DeltaCoin))) :+: C1 ('MetaCons "SendToOppositePotMIR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin))) |
class EraTxCert era => ShelleyEraTxCert era where Source #
mkRegTxCert :: StakeCredential (EraCrypto era) -> TxCert era Source #
getRegTxCert :: TxCert era -> Maybe (StakeCredential (EraCrypto era)) Source #
mkUnRegTxCert :: StakeCredential (EraCrypto era) -> TxCert era Source #
getUnRegTxCert :: TxCert era -> Maybe (StakeCredential (EraCrypto era)) Source #
mkDelegStakeTxCert :: StakeCredential (EraCrypto era) -> KeyHash 'StakePool (EraCrypto era) -> TxCert era Source #
getDelegStakeTxCert :: TxCert era -> Maybe (StakeCredential (EraCrypto era), KeyHash 'StakePool (EraCrypto era)) Source #
mkGenesisDelegTxCert :: GenesisDelegCert (EraCrypto era) -> TxCert era Source #
getGenesisDelegTxCert :: TxCert era -> Maybe (GenesisDelegCert (EraCrypto era)) Source #
mkMirTxCert :: MIRCert (EraCrypto era) -> TxCert era Source #
getMirTxCert :: TxCert era -> Maybe (MIRCert (EraCrypto era)) Source #
Instances
Crypto c => ShelleyEraTxCert (ShelleyEra c) | |
Defined in Cardano.Ledger.Shelley.TxCert mkRegTxCert :: StakeCredential (EraCrypto (ShelleyEra c)) -> TxCert (ShelleyEra c) Source # getRegTxCert :: TxCert (ShelleyEra c) -> Maybe (StakeCredential (EraCrypto (ShelleyEra c))) Source # mkUnRegTxCert :: StakeCredential (EraCrypto (ShelleyEra c)) -> TxCert (ShelleyEra c) Source # getUnRegTxCert :: TxCert (ShelleyEra c) -> Maybe (StakeCredential (EraCrypto (ShelleyEra c))) Source # mkDelegStakeTxCert :: StakeCredential (EraCrypto (ShelleyEra c)) -> KeyHash 'StakePool (EraCrypto (ShelleyEra c)) -> TxCert (ShelleyEra c) Source # getDelegStakeTxCert :: TxCert (ShelleyEra c) -> Maybe (StakeCredential (EraCrypto (ShelleyEra c)), KeyHash 'StakePool (EraCrypto (ShelleyEra c))) Source # mkGenesisDelegTxCert :: GenesisDelegCert (EraCrypto (ShelleyEra c)) -> TxCert (ShelleyEra c) Source # getGenesisDelegTxCert :: TxCert (ShelleyEra c) -> Maybe (GenesisDelegCert (EraCrypto (ShelleyEra c))) Source # mkMirTxCert :: MIRCert (EraCrypto (ShelleyEra c)) -> TxCert (ShelleyEra c) Source # getMirTxCert :: TxCert (ShelleyEra c) -> Maybe (MIRCert (EraCrypto (ShelleyEra c))) Source # |
newtype CoinPerWord Source #
Instances
FromJSON CoinPerWord | |
Defined in Cardano.Ledger.Alonzo.PParams parseJSON :: Value -> Parser CoinPerWord parseJSONList :: Value -> Parser [CoinPerWord] | |
ToJSON CoinPerWord | |
Defined in Cardano.Ledger.Alonzo.PParams 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 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 rnf :: CoinPerWord -> () Source # | |
Eq CoinPerWord | |
Defined in Cardano.Ledger.Alonzo.PParams (==) :: CoinPerWord -> CoinPerWord -> Bool Source # (/=) :: CoinPerWord -> CoinPerWord -> Bool Source # | |
Ord CoinPerWord | |
Defined in Cardano.Ledger.Alonzo.PParams 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 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 #
eraMaxLanguage, mkPlutusScript, withPlutusScript, hoistPlutusPurpose, mkSpendingPurpose, toSpendingPurpose, mkMintingPurpose, toMintingPurpose, mkCertifyingPurpose, toCertifyingPurpose, mkRewardingPurpose, toRewardingPurpose, upgradePlutusPurposeAsIx
data PlutusScript era Source #
type PlutusPurpose (f :: Type -> Type -> Type) era = (r :: Type) | r -> era Source #
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 (EraCrypto era)) -> PlutusPurpose f era Source #
toSpendingPurpose :: PlutusPurpose f era -> Maybe (f Word32 (TxIn (EraCrypto era))) Source #
mkMintingPurpose :: f Word32 (PolicyID (EraCrypto era)) -> PlutusPurpose f era Source #
toMintingPurpose :: PlutusPurpose f era -> Maybe (f Word32 (PolicyID (EraCrypto era))) Source #
mkCertifyingPurpose :: f Word32 (TxCert era) -> PlutusPurpose f era Source #
toCertifyingPurpose :: PlutusPurpose f era -> Maybe (f Word32 (TxCert era)) Source #
mkRewardingPurpose :: f Word32 (RewardAccount (EraCrypto era)) -> PlutusPurpose f era Source #
toRewardingPurpose :: PlutusPurpose f era -> Maybe (f Word32 (RewardAccount (EraCrypto era))) Source #
upgradePlutusPurposeAsIx :: PlutusPurpose AsIx (PreviousEra era) -> PlutusPurpose AsIx era Source #
Instances
Crypto c => AlonzoEraScript (AlonzoEra c) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts
eraMaxLanguage :: Language Source # toPlutusScript :: Script (AlonzoEra c) -> Maybe (PlutusScript (AlonzoEra c)) Source # fromPlutusScript :: PlutusScript (AlonzoEra c) -> Script (AlonzoEra c) Source # mkPlutusScript :: forall (l :: Language). PlutusLanguage l => Plutus l -> Maybe (PlutusScript (AlonzoEra c)) Source # withPlutusScript :: PlutusScript (AlonzoEra c) -> (forall (l :: Language). PlutusLanguage l => Plutus l -> a) -> a Source # hoistPlutusPurpose :: (forall ix it. g ix it -> f ix it) -> PlutusPurpose g (AlonzoEra c) -> PlutusPurpose f (AlonzoEra c) Source # mkSpendingPurpose :: f Word32 (TxIn (EraCrypto (AlonzoEra c))) -> PlutusPurpose f (AlonzoEra c) Source # toSpendingPurpose :: PlutusPurpose f (AlonzoEra c) -> Maybe (f Word32 (TxIn (EraCrypto (AlonzoEra c)))) Source # mkMintingPurpose :: f Word32 (PolicyID (EraCrypto (AlonzoEra c))) -> PlutusPurpose f (AlonzoEra c) Source # toMintingPurpose :: PlutusPurpose f (AlonzoEra c) -> Maybe (f Word32 (PolicyID (EraCrypto (AlonzoEra c)))) Source # mkCertifyingPurpose :: f Word32 (TxCert (AlonzoEra c)) -> PlutusPurpose f (AlonzoEra c) Source # toCertifyingPurpose :: PlutusPurpose f (AlonzoEra c) -> Maybe (f Word32 (TxCert (AlonzoEra c))) Source # mkRewardingPurpose :: f Word32 (RewardAccount (EraCrypto (AlonzoEra c))) -> PlutusPurpose f (AlonzoEra c) Source # toRewardingPurpose :: PlutusPurpose f (AlonzoEra c) -> Maybe (f Word32 (RewardAccount (EraCrypto (AlonzoEra c)))) Source # upgradePlutusPurposeAsIx :: PlutusPurpose AsIx (PreviousEra (AlonzoEra c)) -> PlutusPurpose AsIx (AlonzoEra c) Source # |
type family PlutusPurpose (f :: Type -> Type -> Type) era = (r :: Type) | r -> era Source #
Instances
type PlutusPurpose f (AlonzoEra c) | |
Defined in Cardano.Ledger.Alonzo.Scripts | |
type PlutusPurpose f (BabbageEra c) | |
Defined in Cardano.Ledger.Babbage.Scripts | |
type PlutusPurpose f (ConwayEra c) | |
Defined in Cardano.Ledger.Conway.Scripts |
data family PlutusScript era Source #
Instances
Generic (PlutusScript (AlonzoEra c)) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts
from :: PlutusScript (AlonzoEra c) -> Rep (PlutusScript (AlonzoEra c)) x Source # to :: Rep (PlutusScript (AlonzoEra c)) x -> PlutusScript (AlonzoEra c) Source # | |||||
Show (PlutusScript (AlonzoEra c)) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts | |||||
SafeToHash (PlutusScript (AlonzoEra c)) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts originalBytes :: PlutusScript (AlonzoEra c) -> ByteString Source # originalBytesSize :: PlutusScript (AlonzoEra c) -> Int Source # makeHashWithExplicitProxys :: HashAlgorithm (HASH c0) => Proxy c0 -> Proxy index -> PlutusScript (AlonzoEra c) -> SafeHash c0 index Source # | |||||
NFData (PlutusScript (AlonzoEra c)) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts rnf :: PlutusScript (AlonzoEra c) -> () Source # | |||||
Eq (PlutusScript (AlonzoEra c)) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts (==) :: PlutusScript (AlonzoEra c) -> PlutusScript (AlonzoEra c) -> Bool Source # (/=) :: PlutusScript (AlonzoEra c) -> PlutusScript (AlonzoEra c) -> Bool Source # | |||||
Ord (PlutusScript (AlonzoEra c)) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts compare :: PlutusScript (AlonzoEra c) -> PlutusScript (AlonzoEra c) -> Ordering Source # (<) :: PlutusScript (AlonzoEra c) -> PlutusScript (AlonzoEra c) -> Bool Source # (<=) :: PlutusScript (AlonzoEra c) -> PlutusScript (AlonzoEra c) -> Bool Source # (>) :: PlutusScript (AlonzoEra c) -> PlutusScript (AlonzoEra c) -> Bool Source # (>=) :: PlutusScript (AlonzoEra c) -> PlutusScript (AlonzoEra c) -> Bool Source # max :: PlutusScript (AlonzoEra c) -> PlutusScript (AlonzoEra c) -> PlutusScript (AlonzoEra c) Source # min :: PlutusScript (AlonzoEra c) -> PlutusScript (AlonzoEra c) -> PlutusScript (AlonzoEra c) Source # | |||||
NoThunks (PlutusScript (AlonzoEra c)) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts noThunks :: Context -> PlutusScript (AlonzoEra c) -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> PlutusScript (AlonzoEra c) -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (PlutusScript (AlonzoEra c)) -> String # | |||||
type Rep (PlutusScript (AlonzoEra c)) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts | |||||
type Rep (PlutusScript (BabbageEra c)) | |||||
Defined in Cardano.Ledger.Babbage.Scripts type Rep (PlutusScript (BabbageEra c)) = D1 ('MetaData "PlutusScript" "Cardano.Ledger.Babbage.Scripts" "cardano-ledger-babbage-1.10.0.0-f3c8326a40c2e2346763c76d743f6d6dcbb56b346aad9ca2646b7edc52ad0095" '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 c)) | |||||
Defined in Cardano.Ledger.Conway.Scripts type Rep (PlutusScript (ConwayEra c)) = D1 ('MetaData "PlutusScript" "Cardano.Ledger.Conway.Scripts" "cardano-ledger-conway-1.17.0.0-ed41115f30aea12826c7e98271388af39c652244463f16622d3682aa6c1354c0" '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))))) | |||||
newtype PlutusScript (AlonzoEra c) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts | |||||
data PlutusScript (BabbageEra c) | |||||
Defined in Cardano.Ledger.Babbage.Scripts data PlutusScript (BabbageEra c)
| |||||
data PlutusScript (ConwayEra c) | |||||
Defined in Cardano.Ledger.Conway.Scripts data PlutusScript (ConwayEra c)
|
data AlonzoPlutusPurpose (f :: Type -> Type -> Type) era Source #
AlonzoSpending !(f Word32 (TxIn (EraCrypto era))) | |
AlonzoMinting !(f Word32 (PolicyID (EraCrypto era))) | |
AlonzoCertifying !(f Word32 (TxCert era)) | |
AlonzoRewarding !(f Word32 (RewardAccount (EraCrypto era))) |
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 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
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 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 | |||||
Era era => DecCBORGroup (AlonzoPlutusPurpose AsIx era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts decCBORGroup :: Decoder s (AlonzoPlutusPurpose AsIx era) Source # | |||||
Era era => EncCBORGroup (AlonzoPlutusPurpose AsIx era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts 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 rnf :: AlonzoPlutusPurpose f era -> () Source # | |||||
Eq (TxCert era) => Eq (AlonzoPlutusPurpose AsItem era) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts (==) :: 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 (==) :: 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 (==) :: 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 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 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 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 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.11.0.0-754b1457a782849d0e673d10dcc407dd93f78ad06c4c3d55c7d19a0672469a24" 'False) ((C1 ('MetaCons "AlonzoSpending" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f Word32 (TxIn (EraCrypto era))))) :+: C1 ('MetaCons "AlonzoMinting" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f Word32 (PolicyID (EraCrypto era)))))) :+: (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 (EraCrypto era))))))) |
Instances
ToJSON ix => ToJSON (AsIx ix it) | |
Defined in Cardano.Ledger.Alonzo.Scripts 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 | |
(Typeable it, EncCBOR ix) => EncCBOR (AsIx ix it) | |
Era era => DecCBORGroup (AlonzoPlutusPurpose AsIx era) | |
Defined in Cardano.Ledger.Alonzo.Scripts decCBORGroup :: Decoder s (AlonzoPlutusPurpose AsIx era) Source # | |
Era era => EncCBORGroup (AlonzoPlutusPurpose AsIx era) | |
Defined in Cardano.Ledger.Alonzo.Scripts 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 (==) :: 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 (==) :: 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 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 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 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 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 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 |
AsIxItem !ix !it |
Instances
(ToJSON ix, ToJSON it) => ToJSON (AsIxItem ix it) | |||||
Defined in Cardano.Ledger.Alonzo.Scripts 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
| |||||
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 (==) :: 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 (==) :: 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 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 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 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.11.0.0-754b1457a782849d0e673d10dcc407dd93f78ad06c4c3d55c7d19a0672469a24" '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 parseJSON :: Value -> Parser AlonzoGenesis parseJSONList :: Value -> Parser [AlonzoGenesis] | |||||
ToJSON AlonzoGenesis | |||||
Defined in Cardano.Ledger.Alonzo.Genesis toJSON :: AlonzoGenesis -> Value toEncoding :: AlonzoGenesis -> Encoding toJSONList :: [AlonzoGenesis] -> Value toEncodingList :: [AlonzoGenesis] -> Encoding omitField :: AlonzoGenesis -> Bool | |||||
Generic AlonzoGenesis | |||||
Defined in Cardano.Ledger.Alonzo.Genesis
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 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 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 (==) :: AlonzoGenesis -> AlonzoGenesis -> Bool Source # (/=) :: AlonzoGenesis -> AlonzoGenesis -> Bool Source # | |||||
NoThunks AlonzoGenesis | |||||
Defined in Cardano.Ledger.Alonzo.Genesis 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.11.0.0-754b1457a782849d0e673d10dcc407dd93f78ad06c4c3d55c7d19a0672469a24" '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 #
collateralInputsTxBodyL :: Lens' (TxBody era) (Set (TxIn (EraCrypto era))) Source #
reqSignerHashesTxBodyL :: Lens' (TxBody era) (Set (KeyHash 'Witness (EraCrypto era))) Source #
scriptIntegrityHashTxBodyL :: Lens' (TxBody era) (StrictMaybe (ScriptIntegrityHash (EraCrypto era))) 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
Crypto c => AlonzoEraTxBody (AlonzoEra c) | |
Defined in Cardano.Ledger.Alonzo.TxBody.Internal collateralInputsTxBodyL :: Lens' (TxBody (AlonzoEra c)) (Set (TxIn (EraCrypto (AlonzoEra c)))) Source # reqSignerHashesTxBodyL :: Lens' (TxBody (AlonzoEra c)) (Set (KeyHash 'Witness (EraCrypto (AlonzoEra c)))) Source # scriptIntegrityHashTxBodyL :: Lens' (TxBody (AlonzoEra c)) (StrictMaybe (ScriptIntegrityHash (EraCrypto (AlonzoEra c)))) Source # networkIdTxBodyL :: Lens' (TxBody (AlonzoEra c)) (StrictMaybe Network) Source # redeemerPointer :: TxBody (AlonzoEra c) -> PlutusPurpose AsItem (AlonzoEra c) -> StrictMaybe (PlutusPurpose AsIx (AlonzoEra c)) Source # redeemerPointerInverse :: TxBody (AlonzoEra c) -> PlutusPurpose AsIx (AlonzoEra c) -> StrictMaybe (PlutusPurpose AsIxItem (AlonzoEra c)) Source # |
unRedeemers :: Redeemers era -> Map (PlutusPurpose AsIx era) (Data era, ExUnits) Source #
class (EraTxWits era, AlonzoEraScript era) => AlonzoEraTxWits era where Source #
datsTxWitsL :: Lens' (TxWits era) (TxDats era) Source #
rdmrsTxWitsL :: Lens' (TxWits era) (Redeemers era) Source #
Instances
(EraScript (AlonzoEra c), Crypto c) => AlonzoEraTxWits (AlonzoEra c) | |
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.
pattern TxDats :: Era era => Map (DataHash (EraCrypto era)) (Data era) -> TxDats era | |
pattern TxDats' :: Map (DataHash (EraCrypto era)) (Data era) -> TxDats era |
Instances
Memoized TxDats | |||||
Defined in Cardano.Ledger.Alonzo.TxWits getMemoBytes :: TxDats era -> MemoBytes (RawType TxDats) era wrapMemoBytes :: MemoBytes (RawType TxDats) era -> TxDats era | |||||
Era era => Monoid (TxDats era) | |||||
Era era => Semigroup (TxDats era) | |||||
Generic (TxDats era) | |||||
Defined in Cardano.Ledger.Alonzo.TxWits
| |||||
HashAlgorithm (HASH (EraCrypto era)) => Show (TxDats era) | |||||
Typeable era => ToCBOR (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 originalBytes :: TxDats era -> ByteString Source # originalBytesSize :: TxDats era -> Int Source # makeHashWithExplicitProxys :: HashAlgorithm (HASH c) => Proxy c -> Proxy index -> TxDats era -> SafeHash c index Source # | |||||
NFData (TxDats era) | |||||
Defined in Cardano.Ledger.Alonzo.TxWits | |||||
Eq (TxDats era) | |||||
Typeable era => NoThunks (TxDats era) | |||||
type RawType TxDats | |||||
Defined in Cardano.Ledger.Alonzo.TxWits | |||||
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.11.0.0-754b1457a782849d0e673d10dcc407dd93f78ad06c4c3d55c7d19a0672469a24" 'True) (C1 ('MetaCons "TxDatsConstr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MemoBytes TxDatsRaw era)))) |
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 parseJSON :: Value -> Parser Language parseJSONList :: Value -> Parser [Language] | |||||
FromJSONKey Language | |||||
Defined in Cardano.Ledger.Plutus.Language fromJSONKey :: FromJSONKeyFunction Language fromJSONKeyList :: FromJSONKeyFunction [Language] | |||||
ToJSON Language | |||||
Defined in Cardano.Ledger.Plutus.Language toEncoding :: Language -> Encoding toJSONList :: [Language] -> Value toEncodingList :: [Language] -> Encoding | |||||
ToJSONKey Language | |||||
Defined in Cardano.Ledger.Plutus.Language toJSONKey :: ToJSONKeyFunction Language toJSONKeyList :: ToJSONKeyFunction [Language] | |||||
Bounded Language | |||||
Enum Language | |||||
Defined in Cardano.Ledger.Plutus.Language 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
| |||||
Ix Language | |||||
Defined in Cardano.Ledger.Plutus.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.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" '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 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
| |||||
Show (Plutus l) | |||||
PlutusLanguage l => DecCBOR (Plutus l) | |||||
PlutusLanguage l => EncCBOR (Plutus l) | |||||
SafeToHash (Plutus l) | |||||
Defined in Cardano.Ledger.Plutus.Language originalBytes :: Plutus l -> ByteString Source # originalBytesSize :: Plutus l -> Int Source # makeHashWithExplicitProxys :: HashAlgorithm (HASH c) => Proxy c -> Proxy index -> Plutus l -> SafeHash c index Source # | |||||
NFData (Plutus l) | |||||
Defined in Cardano.Ledger.Plutus.Language | |||||
Eq (Plutus l) | |||||
Ord (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.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" 'True) (C1 ('MetaCons "Plutus" 'PrefixI 'True) (S1 ('MetaSel ('Just "plutusBinary") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PlutusBinary))) |
This newtype wrapper of ExUnits' is used to hide an implementation detail inside the ExUnits pattern.
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 parseJSON :: Value -> Parser ExUnits parseJSONList :: Value -> Parser [ExUnits] | |||||
ToJSON ExUnits | |||||
Defined in Cardano.Ledger.Plutus.ExUnits toEncoding :: ExUnits -> Encoding toJSONList :: [ExUnits] -> Value toEncodingList :: [ExUnits] -> Encoding | |||||
Monoid ExUnits | |||||
Semigroup ExUnits | |||||
Generic ExUnits | |||||
Defined in Cardano.Ledger.Plutus.ExUnits
| |||||
Show ExUnits | |||||
DecCBOR ExUnits | |||||
EncCBOR ExUnits | |||||
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.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" 'True) (C1 ('MetaCons "WrapExUnits" 'PrefixI 'True) (S1 ('MetaSel ('Just "unWrapExUnits") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ExUnits' Natural)))) |
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 parseJSON :: Value -> Parser CostModels parseJSONList :: Value -> Parser [CostModels] | |||||
ToJSON CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels toJSON :: CostModels -> Value toEncoding :: CostModels -> Encoding toJSONList :: [CostModels] -> Value toEncodingList :: [CostModels] -> Encoding omitField :: CostModels -> Bool | |||||
Monoid CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels mempty :: CostModels Source # mappend :: CostModels -> CostModels -> CostModels Source # mconcat :: [CostModels] -> CostModels Source # | |||||
Semigroup CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels (<>) :: CostModels -> CostModels -> CostModels Source # sconcat :: NonEmpty CostModels -> CostModels Source # stimes :: Integral b => b -> CostModels -> CostModels Source # | |||||
Generic CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels
from :: CostModels -> Rep CostModels x Source # to :: Rep CostModels x -> CostModels Source # | |||||
Show CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels | |||||
DecCBOR CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels | |||||
EncCBOR CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels 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 # | |||||
NFData CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels rnf :: CostModels -> () Source # | |||||
Eq CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels (==) :: CostModels -> CostModels -> Bool Source # (/=) :: CostModels -> CostModels -> Bool Source # | |||||
Ord CostModels | |||||
Defined in Cardano.Ledger.Plutus.CostModels 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 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.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" '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
Instances
FromJSON Prices | |||||
Defined in Cardano.Ledger.Plutus.ExUnits parseJSON :: Value -> Parser Prices parseJSONList :: Value -> Parser [Prices] | |||||
ToJSON Prices | |||||
Defined in Cardano.Ledger.Plutus.ExUnits toEncoding :: Prices -> Encoding toJSONList :: [Prices] -> Value toEncodingList :: [Prices] -> Encoding | |||||
Generic Prices | |||||
Defined in Cardano.Ledger.Plutus.ExUnits
| |||||
Show Prices | |||||
DecCBOR Prices | |||||
EncCBOR Prices | |||||
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.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" '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 #
Instances
FromJSON CoinPerByte | |
Defined in Cardano.Ledger.Babbage.PParams parseJSON :: Value -> Parser CoinPerByte parseJSONList :: Value -> Parser [CoinPerByte] | |
ToJSON CoinPerByte | |
Defined in Cardano.Ledger.Babbage.PParams 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 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 rnf :: CoinPerByte -> () Source # | |
Eq CoinPerByte | |
Defined in Cardano.Ledger.Babbage.PParams (==) :: CoinPerByte -> CoinPerByte -> Bool Source # (/=) :: CoinPerByte -> CoinPerByte -> Bool Source # | |
Ord CoinPerByte | |
Defined in Cardano.Ledger.Babbage.PParams 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 noThunks :: Context -> CoinPerByte -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> CoinPerByte -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy CoinPerByte -> String # |
Anchor | |
|
Instances
Crypto c => FromJSON (Anchor c) | |||||
Defined in Cardano.Ledger.BaseTypes parseJSON :: Value -> Parser (Anchor c) parseJSONList :: Value -> Parser [Anchor c] omittedField :: Maybe (Anchor c) | |||||
Crypto c => ToJSON (Anchor c) | |||||
Defined in Cardano.Ledger.BaseTypes toEncoding :: Anchor c -> Encoding toJSONList :: [Anchor c] -> Value toEncodingList :: [Anchor c] -> Encoding | |||||
Generic (Anchor c) | |||||
Defined in Cardano.Ledger.BaseTypes
| |||||
Show (Anchor c) | |||||
Crypto c => DecCBOR (Anchor c) | |||||
Crypto c => EncCBOR (Anchor c) | |||||
Crypto c => Default (Anchor c) | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
Crypto c => NFData (Anchor c) | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
Eq (Anchor c) | |||||
Ord (Anchor c) | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
NoThunks (Anchor c) | |||||
type Rep (Anchor c) | |||||
Defined in Cardano.Ledger.BaseTypes type Rep (Anchor c) = D1 ('MetaData "Anchor" "Cardano.Ledger.BaseTypes" "cardano-ledger-core-1.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" 'False) (C1 ('MetaCons "Anchor" 'PrefixI 'True) (S1 ('MetaSel ('Just "anchorUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Url) :*: S1 ('MetaSel ('Just "anchorDataHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SafeHash c AnchorData)))) |
newtype AnchorData Source #
Instances
SafeToHash AnchorData | |
Defined in Cardano.Ledger.BaseTypes originalBytes :: AnchorData -> ByteString Source # originalBytesSize :: AnchorData -> Int Source # makeHashWithExplicitProxys :: HashAlgorithm (HASH c) => Proxy c -> Proxy index -> AnchorData -> SafeHash c index Source # | |
Eq AnchorData | |
Defined in Cardano.Ledger.BaseTypes (==) :: AnchorData -> AnchorData -> Bool Source # (/=) :: AnchorData -> AnchorData -> Bool Source # | |
HashWithCrypto AnchorData AnchorData | |
Defined in Cardano.Ledger.BaseTypes hashWithCrypto :: HashAlgorithm (HASH c) => Proxy c -> AnchorData -> SafeHash c AnchorData Source # |
data Constitution era Source #
Constitution | |
|
Instances
Era era => FromJSON (Constitution era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures 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 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
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 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 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 def :: Constitution era # | |||||
Era era => NFData (Constitution era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures rnf :: Constitution era -> () Source # | |||||
Eq (Constitution era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures (==) :: Constitution era -> Constitution era -> Bool Source # (/=) :: Constitution era -> Constitution era -> Bool Source # | |||||
Ord (Constitution era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures 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 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.17.0.0-ed41115f30aea12826c7e98271388af39c652244463f16622d3682aa6c1354c0" 'False) (C1 ('MetaCons "Constitution" 'PrefixI 'True) (S1 ('MetaSel ('Just "constitutionAnchor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Anchor (EraCrypto era))) :*: S1 ('MetaSel ('Just "constitutionScript") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe (ScriptHash (EraCrypto era)))))) |
Note that the previous governance action id is only optional for the very first governance action of the same purpose.
ParameterChange | |
| |
HardForkInitiation | |
| |
TreasuryWithdrawals | |
| |
NoConfidence | |
| |
UpdateCommittee | |
| |
NewConstitution | |
| |
InfoAction |
Instances
EraPParams era => ToJSON (GovAction era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures 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
| |||||
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 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.17.0.0-ed41115f30aea12826c7e98271388af39c652244463f16622d3682aa6c1354c0" '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 (EraCrypto era)))))) :+: (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 (EraCrypto era)) Coin)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe (ScriptHash (EraCrypto era))))))) :+: ((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 (EraCrypto era))))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (Credential 'ColdCommitteeRole (EraCrypto era)) 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 c Source #
GovActionId | |
|
Instances
Crypto c => ToJSON (GovActionId c) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures toJSON :: GovActionId c -> Value toEncoding :: GovActionId c -> Encoding toJSONList :: [GovActionId c] -> Value toEncodingList :: [GovActionId c] -> Encoding omitField :: GovActionId c -> Bool | |||||
Crypto c => ToJSONKey (GovActionId c) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures toJSONKey :: ToJSONKeyFunction (GovActionId c) toJSONKeyList :: ToJSONKeyFunction [GovActionId c] | |||||
Generic (GovActionId c) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures
from :: GovActionId c -> Rep (GovActionId c) x Source # to :: Rep (GovActionId c) x -> GovActionId c Source # | |||||
Show (GovActionId c) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
Crypto c => DecCBOR (GovActionId c) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
Crypto c => EncCBOR (GovActionId c) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures encCBOR :: GovActionId c -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (GovActionId c) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [GovActionId c] -> Size Source # | |||||
Crypto c => NFData (GovActionId c) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures rnf :: GovActionId c -> () Source # | |||||
Eq (GovActionId c) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures (==) :: GovActionId c -> GovActionId c -> Bool Source # (/=) :: GovActionId c -> GovActionId c -> Bool Source # | |||||
Ord (GovActionId c) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures compare :: GovActionId c -> GovActionId c -> Ordering Source # (<) :: GovActionId c -> GovActionId c -> Bool Source # (<=) :: GovActionId c -> GovActionId c -> Bool Source # (>) :: GovActionId c -> GovActionId c -> Bool Source # (>=) :: GovActionId c -> GovActionId c -> Bool Source # max :: GovActionId c -> GovActionId c -> GovActionId c Source # min :: GovActionId c -> GovActionId c -> GovActionId c Source # | |||||
NoThunks (GovActionId c) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures noThunks :: Context -> GovActionId c -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> GovActionId c -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (GovActionId c) -> String # | |||||
c ~ EraCrypto era => HasOKey (GovActionId c) (GovActionState era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures okeyL :: Lens' (GovActionState era) (GovActionId c) Source # | |||||
type Rep (GovActionId c) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures type Rep (GovActionId c) = D1 ('MetaData "GovActionId" "Cardano.Ledger.Conway.Governance.Procedures" "cardano-ledger-conway-1.17.0.0-ed41115f30aea12826c7e98271388af39c652244463f16622d3682aa6c1354c0" 'False) (C1 ('MetaCons "GovActionId" 'PrefixI 'True) (S1 ('MetaSel ('Just "gaidTxId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TxId c)) :*: S1 ('MetaSel ('Just "gaidGovActionIx") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 GovActionIx))) |
newtype GovActionIx Source #
Instances
ToJSON GovActionIx | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures toJSON :: GovActionIx -> Value toEncoding :: GovActionIx -> Encoding toJSONList :: [GovActionIx] -> Value toEncodingList :: [GovActionIx] -> Encoding omitField :: GovActionIx -> Bool | |||||
Generic GovActionIx | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures
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 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 rnf :: GovActionIx -> () Source # | |||||
Eq GovActionIx | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures (==) :: GovActionIx -> GovActionIx -> Bool Source # (/=) :: GovActionIx -> GovActionIx -> Bool Source # | |||||
Ord GovActionIx | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures 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 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.17.0.0-ed41115f30aea12826c7e98271388af39c652244463f16622d3682aa6c1354c0" 'True) (C1 ('MetaCons "GovActionIx" 'PrefixI 'True) (S1 ('MetaSel ('Just "unGovActionIx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16))) |
data ProposalProcedure era Source #
ProposalProcedure | |
|
Instances
EraPParams era => ToJSON (ProposalProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures 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
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 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 rnf :: ProposalProcedure era -> () Source # | |||||
EraPParams era => Eq (ProposalProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures (==) :: ProposalProcedure era -> ProposalProcedure era -> Bool Source # (/=) :: ProposalProcedure era -> ProposalProcedure era -> Bool Source # | |||||
EraPParams era => Ord (ProposalProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures 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 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.17.0.0-ed41115f30aea12826c7e98271388af39c652244463f16622d3682aa6c1354c0" 'False) (C1 ('MetaCons "ProposalProcedure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "pProcDeposit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin) :*: S1 ('MetaSel ('Just "pProcReturnAddr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (RewardAccount (EraCrypto era)))) :*: (S1 ('MetaSel ('Just "pProcGovAction") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GovAction era)) :*: S1 ('MetaSel ('Just "pProcAnchor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Anchor (EraCrypto era)))))) |
CommitteeVoter !(Credential 'HotCommitteeRole c) | |
DRepVoter !(Credential 'DRepRole c) | |
StakePoolVoter !(KeyHash 'StakePool c) |
Instances
Crypto c => ToJSON (Voter c) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures toEncoding :: Voter c -> Encoding toJSONList :: [Voter c] -> Value toEncodingList :: [Voter c] -> Encoding | |||||
Crypto c => ToJSONKey (Voter c) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures toJSONKey :: ToJSONKeyFunction (Voter c) toJSONKeyList :: ToJSONKeyFunction [Voter c] | |||||
Generic (Voter c) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures
| |||||
Show (Voter c) | |||||
Crypto c => DecCBOR (Voter c) | |||||
Crypto c => EncCBOR (Voter c) | |||||
NFData (Voter c) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
Eq (Voter c) | |||||
Ord (Voter c) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
NoThunks (Voter c) | |||||
c ~ EraCrypto era => Indexable (Voter c) (VotingProcedures era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
type Rep (Voter c) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures type Rep (Voter c) = D1 ('MetaData "Voter" "Cardano.Ledger.Conway.Governance.Procedures" "cardano-ledger-conway-1.17.0.0-ed41115f30aea12826c7e98271388af39c652244463f16622d3682aa6c1354c0" 'False) (C1 ('MetaCons "CommitteeVoter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Credential 'HotCommitteeRole c))) :+: (C1 ('MetaCons "DRepVoter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Credential 'DRepRole c))) :+: C1 ('MetaCons "StakePoolVoter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool c))))) |
data VotingProcedure era Source #
VotingProcedure | |
|
Instances
EraPParams era => ToJSON (VotingProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures 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
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 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 # | |||||
Crypto (EraCrypto era) => NFData (VotingProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures rnf :: VotingProcedure era -> () Source # | |||||
Eq (VotingProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures (==) :: VotingProcedure era -> VotingProcedure era -> Bool Source # (/=) :: VotingProcedure era -> VotingProcedure era -> Bool Source # | |||||
NoThunks (VotingProcedure era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures 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.17.0.0-ed41115f30aea12826c7e98271388af39c652244463f16622d3682aa6c1354c0" '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 (EraCrypto era)))))) |
newtype VotingProcedures era Source #
VotingProcedures | |
|
Instances
EraPParams era => ToJSON (VotingProcedures era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures 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
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 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 rnf :: VotingProcedures era -> () Source # | |||||
Eq (VotingProcedures era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures (==) :: VotingProcedures era -> VotingProcedures era -> Bool Source # (/=) :: VotingProcedures era -> VotingProcedures era -> Bool Source # | |||||
NoThunks (VotingProcedures era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures noThunks :: Context -> VotingProcedures era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> VotingProcedures era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (VotingProcedures era) -> String # | |||||
c ~ EraCrypto era => Indexable (Voter c) (VotingProcedures era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures | |||||
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.17.0.0-ed41115f30aea12826c7e98271388af39c652244463f16622d3682aa6c1354c0" 'True) (C1 ('MetaCons "VotingProcedures" 'PrefixI 'True) (S1 ('MetaSel ('Just "unVotingProcedures") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map (Voter (EraCrypto era)) (Map (GovActionId (EraCrypto era)) (VotingProcedure era)))))) |
pattern AuthCommitteeHotKeyTxCert :: ConwayEraTxCert era => Credential 'ColdCommitteeRole (EraCrypto era) -> Credential 'HotCommitteeRole (EraCrypto era) -> TxCert era Source #
pattern DelegTxCert :: ConwayEraTxCert era => StakeCredential (EraCrypto era) -> Delegatee (EraCrypto era) -> TxCert era Source #
pattern RegDRepTxCert :: ConwayEraTxCert era => Credential 'DRepRole (EraCrypto era) -> Coin -> StrictMaybe (Anchor (EraCrypto era)) -> TxCert era Source #
pattern RegDepositDelegTxCert :: ConwayEraTxCert era => StakeCredential (EraCrypto era) -> Delegatee (EraCrypto era) -> Coin -> TxCert era Source #
pattern RegDepositTxCert :: ConwayEraTxCert era => StakeCredential (EraCrypto era) -> Coin -> TxCert era Source #
pattern ResignCommitteeColdTxCert :: ConwayEraTxCert era => Credential 'ColdCommitteeRole (EraCrypto era) -> StrictMaybe (Anchor (EraCrypto era)) -> TxCert era Source #
pattern UnRegDRepTxCert :: ConwayEraTxCert era => Credential 'DRepRole (EraCrypto era) -> Coin -> TxCert era Source #
pattern UnRegDepositTxCert :: ConwayEraTxCert era => StakeCredential (EraCrypto era) -> Coin -> TxCert era Source #
class ShelleyEraTxCert era => ConwayEraTxCert era where Source #
mkRegDepositTxCert :: StakeCredential (EraCrypto era) -> Coin -> TxCert era Source #
getRegDepositTxCert :: TxCert era -> Maybe (StakeCredential (EraCrypto era), Coin) Source #
mkUnRegDepositTxCert :: StakeCredential (EraCrypto era) -> Coin -> TxCert era Source #
getUnRegDepositTxCert :: TxCert era -> Maybe (StakeCredential (EraCrypto era), Coin) Source #
mkDelegTxCert :: StakeCredential (EraCrypto era) -> Delegatee (EraCrypto era) -> TxCert era Source #
getDelegTxCert :: TxCert era -> Maybe (StakeCredential (EraCrypto era), Delegatee (EraCrypto era)) Source #
mkRegDepositDelegTxCert :: StakeCredential (EraCrypto era) -> Delegatee (EraCrypto era) -> Coin -> TxCert era Source #
getRegDepositDelegTxCert :: TxCert era -> Maybe (StakeCredential (EraCrypto era), Delegatee (EraCrypto era), Coin) Source #
mkAuthCommitteeHotKeyTxCert :: Credential 'ColdCommitteeRole (EraCrypto era) -> Credential 'HotCommitteeRole (EraCrypto era) -> TxCert era Source #
getAuthCommitteeHotKeyTxCert :: TxCert era -> Maybe (Credential 'ColdCommitteeRole (EraCrypto era), Credential 'HotCommitteeRole (EraCrypto era)) Source #
mkResignCommitteeColdTxCert :: Credential 'ColdCommitteeRole (EraCrypto era) -> StrictMaybe (Anchor (EraCrypto era)) -> TxCert era Source #
getResignCommitteeColdTxCert :: TxCert era -> Maybe (Credential 'ColdCommitteeRole (EraCrypto era), StrictMaybe (Anchor (EraCrypto era))) Source #
mkRegDRepTxCert :: Credential 'DRepRole (EraCrypto era) -> Coin -> StrictMaybe (Anchor (EraCrypto era)) -> TxCert era Source #
getRegDRepTxCert :: TxCert era -> Maybe (Credential 'DRepRole (EraCrypto era), Coin, StrictMaybe (Anchor (EraCrypto era))) Source #
mkUnRegDRepTxCert :: Credential 'DRepRole (EraCrypto era) -> Coin -> TxCert era Source #
getUnRegDRepTxCert :: TxCert era -> Maybe (Credential 'DRepRole (EraCrypto era), Coin) Source #
mkUpdateDRepTxCert :: Credential 'DRepRole (EraCrypto era) -> StrictMaybe (Anchor (EraCrypto era)) -> TxCert era Source #
getUpdateDRepTxCert :: TxCert era -> Maybe (Credential 'DRepRole (EraCrypto era), StrictMaybe (Anchor (EraCrypto era))) Source #
Instances
Crypto c => ConwayEraTxCert (ConwayEra c) | |
Defined in Cardano.Ledger.Conway.TxCert mkRegDepositTxCert :: StakeCredential (EraCrypto (ConwayEra c)) -> Coin -> TxCert (ConwayEra c) Source # getRegDepositTxCert :: TxCert (ConwayEra c) -> Maybe (StakeCredential (EraCrypto (ConwayEra c)), Coin) Source # mkUnRegDepositTxCert :: StakeCredential (EraCrypto (ConwayEra c)) -> Coin -> TxCert (ConwayEra c) Source # getUnRegDepositTxCert :: TxCert (ConwayEra c) -> Maybe (StakeCredential (EraCrypto (ConwayEra c)), Coin) Source # mkDelegTxCert :: StakeCredential (EraCrypto (ConwayEra c)) -> Delegatee (EraCrypto (ConwayEra c)) -> TxCert (ConwayEra c) Source # getDelegTxCert :: TxCert (ConwayEra c) -> Maybe (StakeCredential (EraCrypto (ConwayEra c)), Delegatee (EraCrypto (ConwayEra c))) Source # mkRegDepositDelegTxCert :: StakeCredential (EraCrypto (ConwayEra c)) -> Delegatee (EraCrypto (ConwayEra c)) -> Coin -> TxCert (ConwayEra c) Source # getRegDepositDelegTxCert :: TxCert (ConwayEra c) -> Maybe (StakeCredential (EraCrypto (ConwayEra c)), Delegatee (EraCrypto (ConwayEra c)), Coin) Source # mkAuthCommitteeHotKeyTxCert :: Credential 'ColdCommitteeRole (EraCrypto (ConwayEra c)) -> Credential 'HotCommitteeRole (EraCrypto (ConwayEra c)) -> TxCert (ConwayEra c) Source # getAuthCommitteeHotKeyTxCert :: TxCert (ConwayEra c) -> Maybe (Credential 'ColdCommitteeRole (EraCrypto (ConwayEra c)), Credential 'HotCommitteeRole (EraCrypto (ConwayEra c))) Source # mkResignCommitteeColdTxCert :: Credential 'ColdCommitteeRole (EraCrypto (ConwayEra c)) -> StrictMaybe (Anchor (EraCrypto (ConwayEra c))) -> TxCert (ConwayEra c) Source # getResignCommitteeColdTxCert :: TxCert (ConwayEra c) -> Maybe (Credential 'ColdCommitteeRole (EraCrypto (ConwayEra c)), StrictMaybe (Anchor (EraCrypto (ConwayEra c)))) Source # mkRegDRepTxCert :: Credential 'DRepRole (EraCrypto (ConwayEra c)) -> Coin -> StrictMaybe (Anchor (EraCrypto (ConwayEra c))) -> TxCert (ConwayEra c) Source # getRegDRepTxCert :: TxCert (ConwayEra c) -> Maybe (Credential 'DRepRole (EraCrypto (ConwayEra c)), Coin, StrictMaybe (Anchor (EraCrypto (ConwayEra c)))) Source # mkUnRegDRepTxCert :: Credential 'DRepRole (EraCrypto (ConwayEra c)) -> Coin -> TxCert (ConwayEra c) Source # getUnRegDRepTxCert :: TxCert (ConwayEra c) -> Maybe (Credential 'DRepRole (EraCrypto (ConwayEra c)), Coin) Source # mkUpdateDRepTxCert :: Credential 'DRepRole (EraCrypto (ConwayEra c)) -> StrictMaybe (Anchor (EraCrypto (ConwayEra c))) -> TxCert (ConwayEra c) Source # getUpdateDRepTxCert :: TxCert (ConwayEra c) -> Maybe (Credential 'DRepRole (EraCrypto (ConwayEra c)), StrictMaybe (Anchor (EraCrypto (ConwayEra c)))) Source # |
First type argument is the deposit
DelegStake !(KeyHash 'StakePool c) | |
DelegVote !(DRep c) | |
DelegStakeVote !(KeyHash 'StakePool c) !(DRep c) |
Instances
Crypto c => FromJSON (Delegatee c) | |||||
Defined in Cardano.Ledger.Conway.TxCert parseJSON :: Value -> Parser (Delegatee c) parseJSONList :: Value -> Parser [Delegatee c] omittedField :: Maybe (Delegatee c) | |||||
Crypto c => ToJSON (Delegatee c) | |||||
Defined in Cardano.Ledger.Conway.TxCert toJSON :: Delegatee c -> Value toEncoding :: Delegatee c -> Encoding toJSONList :: [Delegatee c] -> Value toEncodingList :: [Delegatee c] -> Encoding | |||||
Generic (Delegatee c) | |||||
Defined in Cardano.Ledger.Conway.TxCert
| |||||
Show (Delegatee c) | |||||
Crypto c => DecCBOR (Delegatee c) | |||||
Crypto c => EncCBOR (Delegatee c) | |||||
NFData (Delegatee c) | |||||
Defined in Cardano.Ledger.Conway.TxCert | |||||
Eq (Delegatee c) | |||||
Ord (Delegatee c) | |||||
Defined in Cardano.Ledger.Conway.TxCert compare :: Delegatee c -> Delegatee c -> Ordering Source # (<) :: Delegatee c -> Delegatee c -> Bool Source # (<=) :: Delegatee c -> Delegatee c -> Bool Source # (>) :: Delegatee c -> Delegatee c -> Bool Source # (>=) :: Delegatee c -> Delegatee c -> Bool Source # | |||||
NoThunks (Delegatee c) | |||||
type Rep (Delegatee c) | |||||
Defined in Cardano.Ledger.Conway.TxCert type Rep (Delegatee c) = D1 ('MetaData "Delegatee" "Cardano.Ledger.Conway.TxCert" "cardano-ledger-conway-1.17.0.0-ed41115f30aea12826c7e98271388af39c652244463f16622d3682aa6c1354c0" 'False) (C1 ('MetaCons "DelegStake" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool c))) :+: (C1 ('MetaCons "DelegVote" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (DRep c))) :+: C1 ('MetaCons "DelegStakeVote" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool c)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (DRep c))))) |
data ConwayPlutusPurpose (f :: Type -> Type -> Type) era Source #
ConwaySpending !(f Word32 (TxIn (EraCrypto era))) | |
ConwayMinting !(f Word32 (PolicyID (EraCrypto era))) | |
ConwayCertifying !(f Word32 (TxCert era)) | |
ConwayRewarding !(f Word32 (RewardAccount (EraCrypto era))) | |
ConwayVoting !(f Word32 (Voter (EraCrypto era))) | |
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 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
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 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 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 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 rnf :: ConwayPlutusPurpose f era -> () Source # | |||||
(Eq (TxCert era), EraPParams era) => Eq (ConwayPlutusPurpose AsItem era) | |||||
Defined in Cardano.Ledger.Conway.Scripts (==) :: 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 (==) :: 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 (==) :: 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 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 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 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 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.17.0.0-ed41115f30aea12826c7e98271388af39c652244463f16622d3682aa6c1354c0" 'False) ((C1 ('MetaCons "ConwaySpending" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f Word32 (TxIn (EraCrypto era))))) :+: (C1 ('MetaCons "ConwayMinting" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f Word32 (PolicyID (EraCrypto era))))) :+: 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 (EraCrypto era))))) :+: (C1 ('MetaCons "ConwayVoting" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f Word32 (Voter (EraCrypto era))))) :+: C1 ('MetaCons "ConwayProposing" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (f Word32 (ProposalProcedure era))))))) |
data ConwayGenesis c Source #
ConwayGenesis | |
|
Instances
Crypto c => FromJSON (ConwayGenesis c) | |||||
Defined in Cardano.Ledger.Conway.Genesis parseJSON :: Value -> Parser (ConwayGenesis c) parseJSONList :: Value -> Parser [ConwayGenesis c] omittedField :: Maybe (ConwayGenesis c) | |||||
Crypto c => ToJSON (ConwayGenesis c) | |||||
Defined in Cardano.Ledger.Conway.Genesis toJSON :: ConwayGenesis c -> Value toEncoding :: ConwayGenesis c -> Encoding toJSONList :: [ConwayGenesis c] -> Value toEncodingList :: [ConwayGenesis c] -> Encoding omitField :: ConwayGenesis c -> Bool | |||||
Generic (ConwayGenesis c) | |||||
Defined in Cardano.Ledger.Conway.Genesis
from :: ConwayGenesis c -> Rep (ConwayGenesis c) x Source # to :: Rep (ConwayGenesis c) x -> ConwayGenesis c Source # | |||||
Show (ConwayGenesis c) | |||||
Defined in Cardano.Ledger.Conway.Genesis | |||||
Crypto c => DecCBOR (ConwayGenesis c) | Genesis are always encoded with the version of era they are defined in. | ||||
Defined in Cardano.Ledger.Conway.Genesis | |||||
Crypto c => EncCBOR (ConwayGenesis c) | |||||
Defined in Cardano.Ledger.Conway.Genesis encCBOR :: ConwayGenesis c -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (ConwayGenesis c) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ConwayGenesis c] -> Size Source # | |||||
Eq (ConwayGenesis c) | |||||
Defined in Cardano.Ledger.Conway.Genesis (==) :: ConwayGenesis c -> ConwayGenesis c -> Bool Source # (/=) :: ConwayGenesis c -> ConwayGenesis c -> Bool Source # | |||||
Crypto c => NoThunks (ConwayGenesis c) | |||||
Defined in Cardano.Ledger.Conway.Genesis noThunks :: Context -> ConwayGenesis c -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> ConwayGenesis c -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (ConwayGenesis c) -> String # | |||||
type Rep (ConwayGenesis c) | |||||
Defined in Cardano.Ledger.Conway.Genesis type Rep (ConwayGenesis c) = D1 ('MetaData "ConwayGenesis" "Cardano.Ledger.Conway.Genesis" "cardano-ledger-conway-1.17.0.0-ed41115f30aea12826c7e98271388af39c652244463f16622d3682aa6c1354c0" '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 c)))) :*: (S1 ('MetaSel ('Just "cgCommittee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Committee (ConwayEra c))) :*: (S1 ('MetaSel ('Just "cgDelegs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListMap (Credential 'Staking c) (Delegatee c))) :*: S1 ('MetaSel ('Just "cgInitialDReps") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListMap (Credential 'DRepRole c) (DRepState c))))))) |
class (HashAlgorithm (HASH c), HashAlgorithm (ADDRHASH c), DSIGNAlgorithm (DSIGN c), KESAlgorithm (KES c), VRFAlgorithm (VRF c), ContextDSIGN (DSIGN c) ~ (), ContextKES (KES c) ~ (), ContextVRF (VRF c) ~ (), Typeable c) => Crypto c Source #
Instances
Crypto StandardCrypto | |||||||||||||||||||||
Defined in Cardano.Ledger.Crypto
|
type family ADDRHASH c Source #
Instances
type ADDRHASH StandardCrypto | |
Defined in Cardano.Ledger.Crypto |
data StandardCrypto Source #
The same crypto used on the net
Instances
Crypto StandardCrypto | |||||||||||||||||||||
Defined in Cardano.Ledger.Crypto
| |||||||||||||||||||||
(CardanoHardForkConstraints StandardCrypto, IOLike m) => Protocol m (CardanoBlock StandardCrypto) | |||||||||||||||||||||
Defined in Cardano.Api.Protocol | |||||||||||||||||||||
(IOLike m, LedgerSupportsProtocol (ShelleyBlock (TPraos StandardCrypto) (ShelleyEra StandardCrypto))) => Protocol m (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) | |||||||||||||||||||||
Defined in Cardano.Api.Protocol | |||||||||||||||||||||
ConvertLedgerEvent (HardForkBlock (CardanoEras StandardCrypto)) | |||||||||||||||||||||
CardanoHardForkConstraints StandardCrypto => ProtocolClient (CardanoBlock StandardCrypto) | |||||||||||||||||||||
Defined in Cardano.Api.Protocol
protocolClientInfo :: ProtocolClientInfoArgs (CardanoBlock StandardCrypto) -> ProtocolClientInfo (CardanoBlock StandardCrypto) | |||||||||||||||||||||
ConvertLedgerEvent (ShelleyBlock protocol (AllegraEra StandardCrypto)) | |||||||||||||||||||||
Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (AllegraEra StandardCrypto)) -> Maybe LedgerEvent # | |||||||||||||||||||||
ConvertLedgerEvent (ShelleyBlock protocol (AlonzoEra StandardCrypto)) | |||||||||||||||||||||
Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (AlonzoEra StandardCrypto)) -> Maybe LedgerEvent # | |||||||||||||||||||||
ConvertLedgerEvent (ShelleyBlock protocol (BabbageEra StandardCrypto)) | |||||||||||||||||||||
Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (BabbageEra StandardCrypto)) -> Maybe LedgerEvent # | |||||||||||||||||||||
ConvertLedgerEvent (ShelleyBlock protocol (ConwayEra StandardCrypto)) | |||||||||||||||||||||
Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (ConwayEra StandardCrypto)) -> Maybe LedgerEvent # | |||||||||||||||||||||
ConvertLedgerEvent (ShelleyBlock protocol (MaryEra StandardCrypto)) | |||||||||||||||||||||
Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (MaryEra StandardCrypto)) -> Maybe LedgerEvent # | |||||||||||||||||||||
ConvertLedgerEvent (ShelleyBlock protocol (ShelleyEra StandardCrypto)) | |||||||||||||||||||||
Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (ShelleyEra StandardCrypto)) -> Maybe LedgerEvent # | |||||||||||||||||||||
LedgerSupportsProtocol (ShelleyBlock (TPraos StandardCrypto) (ShelleyEra StandardCrypto)) => ProtocolClient (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) | |||||||||||||||||||||
Defined in Cardano.Api.Protocol
protocolClientInfo :: ProtocolClientInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) -> ProtocolClientInfo (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) | |||||||||||||||||||||
type ADDRHASH StandardCrypto | |||||||||||||||||||||
Defined in Cardano.Ledger.Crypto | |||||||||||||||||||||
type DSIGN StandardCrypto | |||||||||||||||||||||
Defined in Cardano.Ledger.Crypto | |||||||||||||||||||||
type HASH StandardCrypto | |||||||||||||||||||||
Defined in Cardano.Ledger.Crypto | |||||||||||||||||||||
type KES StandardCrypto | |||||||||||||||||||||
Defined in Cardano.Ledger.Crypto | |||||||||||||||||||||
type VRF StandardCrypto | |||||||||||||||||||||
Defined in Cardano.Ledger.Crypto | |||||||||||||||||||||
data ProtocolClientInfoArgs (CardanoBlock StandardCrypto) | |||||||||||||||||||||
Defined in Cardano.Api.Protocol data ProtocolClientInfoArgs (CardanoBlock StandardCrypto) = ProtocolClientInfoArgsCardano EpochSlots | |||||||||||||||||||||
data ProtocolInfoArgs (CardanoBlock StandardCrypto) | |||||||||||||||||||||
data ProtocolClientInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) | |||||||||||||||||||||
Defined in Cardano.Api.Protocol data ProtocolClientInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) = ProtocolClientInfoArgsShelley | |||||||||||||||||||||
data ProtocolInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) | |||||||||||||||||||||
The role of a key.
Note that a role is not _fixed_, nor is it unique. In particular, keys may
variously be used as witnesses, and so in many case we will change the role
of a key to the Witness
role.
It is also perfectly allowable for a key to be used in many roles; there is nothing prohibiting somebody using the same underlying key as their payment and staking key, as well as the key for their stake pool. So these roles are more intended for two purposes:
- To make explicit how we are using a key in the specifications
- To provide a guide to downstream implementors, for whom the profusion of keys may be confusing.
data WitVKey (kr :: KeyRole) c where Source #
Proof/Witness that a transaction is authorized by the given key holder.
pattern WitVKey :: (Typeable kr, Crypto c) => VKey kr c -> SignedDSIGN c (Hash c EraIndependentTxBody) -> WitVKey kr c |
Instances
(Typeable kr, Crypto c) => DecCBOR (Annotator (WitVKey kr c)) | |||||
Generic (WitVKey kr c) | |||||
Defined in Cardano.Ledger.Keys.WitVKey
| |||||
Crypto c => Show (WitVKey kr c) | |||||
(Typeable kr, Crypto c) => ToCBOR (WitVKey kr c) | |||||
(Typeable kr, Crypto c) => EncCBOR (WitVKey kr c) | Encodes memoized bytes created upon construction. | ||||
(Crypto c, Typeable kr) => EqRaw (WitVKey kr c) | |||||
NFData (WitVKey kr c) | |||||
Defined in Cardano.Ledger.Keys.WitVKey | |||||
Crypto c => Eq (WitVKey kr c) | |||||
(Typeable kr, Crypto c) => Ord (WitVKey kr c) | |||||
Defined in Cardano.Ledger.Keys.WitVKey compare :: WitVKey kr c -> WitVKey kr c -> Ordering Source # (<) :: WitVKey kr c -> WitVKey kr c -> Bool Source # (<=) :: WitVKey kr c -> WitVKey kr c -> Bool Source # (>) :: WitVKey kr c -> WitVKey kr c -> Bool Source # (>=) :: WitVKey kr c -> WitVKey kr c -> Bool Source # max :: WitVKey kr c -> WitVKey kr c -> WitVKey kr c Source # min :: WitVKey kr c -> WitVKey kr c -> WitVKey kr c Source # | |||||
(Crypto c, Typeable kr) => NoThunks (WitVKey kr c) | |||||
type Rep (WitVKey kr c) | |||||
Defined in Cardano.Ledger.Keys.WitVKey type Rep (WitVKey kr c) = D1 ('MetaData "WitVKey" "Cardano.Ledger.Keys.WitVKey" "cardano-ledger-core-1.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" 'False) (C1 ('MetaCons "WitVKeyInternal" 'PrefixI 'True) ((S1 ('MetaSel ('Just "wvkKey") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (VKey kr c)) :*: S1 ('MetaSel ('Just "wvkSig") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SignedDSIGN c (Hash c EraIndependentTxBody)))) :*: (S1 ('MetaSel ('Just "wvkKeyHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (KeyHash 'Witness c)) :*: S1 ('MetaSel ('Just "wvkBytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)))) |
hashAnchorData :: Crypto c => AnchorData -> SafeHash c AnchorData Source #
Hash AnchorData
data NewEpochState era Source #
New Epoch state and environment
NewEpochState | |
|
Instances
Generic (NewEpochState era) | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types
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 (NewEpochState era) | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types | |||||
(EraTxOut era, EraGov era, DecCBOR (StashedAVVMAddresses era)) => FromCBOR (NewEpochState era) | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types | |||||
(EraTxOut era, EraGov era, EncCBOR (StashedAVVMAddresses era)) => ToCBOR (NewEpochState era) | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types 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, DecCBOR (StashedAVVMAddresses era)) => DecCBOR (NewEpochState era) | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types | |||||
(EraTxOut era, EncCBOR (StashedAVVMAddresses era), EncCBOR (GovState era)) => EncCBOR (NewEpochState era) | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types 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 (NewEpochState era) | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types rnf :: NewEpochState era -> () Source # | |||||
(EraTxOut era, Eq (StashedAVVMAddresses era), Eq (GovState era)) => Eq (NewEpochState era) | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types (==) :: NewEpochState era -> NewEpochState era -> Bool Source # (/=) :: NewEpochState era -> NewEpochState era -> Bool Source # | |||||
(Era era, NoThunks (BlocksMade (EraCrypto era)), NoThunks (EpochState era), NoThunks (PulsingRewUpdate (EraCrypto era)), NoThunks (StashedAVVMAddresses era)) => NoThunks (NewEpochState era) | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types noThunks :: Context -> NewEpochState era -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> NewEpochState era -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (NewEpochState era) -> String # | |||||
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.14.1.0-6da62eb4db0139bb466588c0f3bf17f53ad859af8a090c113a1a960870dce943" 'False) (C1 ('MetaCons "NewEpochState" 'PrefixI 'True) ((S1 ('MetaSel ('Just "nesEL") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 EpochNo) :*: (S1 ('MetaSel ('Just "nesBprev") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BlocksMade (EraCrypto era))) :*: S1 ('MetaSel ('Just "nesBcur") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BlocksMade (EraCrypto era))))) :*: ((S1 ('MetaSel ('Just "nesEs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (EpochState era)) :*: S1 ('MetaSel ('Just "nesRu") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe (PulsingRewUpdate (EraCrypto era))))) :*: (S1 ('MetaSel ('Just "nesPd") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PoolDistr (EraCrypto era))) :*: S1 ('MetaSel ('Just "stashedAVVMAddresses") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StashedAVVMAddresses era)))))) | |||||
type TranslationError (AllegraEra c) NewEpochState | |||||
Defined in Cardano.Ledger.Allegra.Translation | |||||
type TranslationError (AlonzoEra c) NewEpochState | |||||
Defined in Cardano.Ledger.Alonzo.Translation | |||||
type TranslationError (BabbageEra c) NewEpochState | |||||
Defined in Cardano.Ledger.Babbage.Translation | |||||
type TranslationError (ConwayEra c) NewEpochState | |||||
Defined in Cardano.Ledger.Conway.Translation | |||||
type TranslationError (MaryEra c) NewEpochState | |||||
Defined in Cardano.Ledger.Mary.Translation |
The amount of value held by a transaction output.
Instances
FromJSON Coin | |||||
Defined in Cardano.Ledger.Coin | |||||
ToJSON Coin | |||||
Defined in Cardano.Ledger.Coin | |||||
Monoid Coin | |||||
Semigroup Coin | |||||
Enum Coin | |||||
Generic Coin | |||||
Defined in Cardano.Ledger.Coin
| |||||
Show Coin | |||||
FromCBOR Coin | |||||
ToCBOR Coin | |||||
DecCBOR Coin | |||||
EncCBOR Coin | |||||
Compactible Coin | |||||
Defined in Cardano.Ledger.Coin
toCompact :: Coin -> Maybe (CompactForm Coin) Source # fromCompact :: CompactForm Coin -> Coin Source # | |||||
NFData Coin | |||||
Defined in Cardano.Ledger.Coin | |||||
Eq Coin | |||||
Ord Coin | |||||
Abelian Coin | |||||
Defined in Cardano.Ledger.Coin | |||||
Group Coin | |||||
HeapWords Coin | |||||
Defined in Cardano.Ledger.Coin | |||||
NoThunks Coin | |||||
PartialOrd Coin | |||||
Uniform Coin | |||||
Defined in Cardano.Ledger.Coin | |||||
UniformRange Coin | |||||
Defined in Cardano.Ledger.Coin | |||||
Inject Coin DeltaCoin | |||||
Inject Coin (MaryValue c) | |||||
FromJSON (CompactForm Coin) | |||||
Defined in Cardano.Ledger.Coin parseJSON :: Value -> Parser (CompactForm Coin) parseJSONList :: Value -> Parser [CompactForm Coin] omittedField :: Maybe (CompactForm Coin) | |||||
ToJSON (CompactForm Coin) | |||||
Defined in Cardano.Ledger.Coin 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 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 (<>) :: 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 rnf :: CompactForm Coin -> () Source # | |||||
Eq (CompactForm Coin) | |||||
Defined in Cardano.Ledger.Coin (==) :: CompactForm Coin -> CompactForm Coin -> Bool Source # (/=) :: CompactForm Coin -> CompactForm Coin -> Bool Source # | |||||
Ord (CompactForm Coin) | |||||
Defined in Cardano.Ledger.Coin 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 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 heapWords :: CompactForm Coin -> Int | |||||
NoThunks (CompactForm Coin) | |||||
Defined in Cardano.Ledger.Coin 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 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 uniformM :: StatefulGen g m => g -> m (CompactForm Coin) | |||||
UniformRange (CompactForm Coin) | |||||
Defined in Cardano.Ledger.Coin 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.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" '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.
toPlainDecoder :: Version -> Decoder s a -> Decoder s a Source #
Extract the underlying Decoder
by specifying the concrete version to be used.
Annotated | |
|
Instances
Bifunctor Annotated | |||||
Functor (Annotated b) | |||||
FromJSON b => FromJSON (Annotated b ()) | |||||
Defined in Cardano.Ledger.Binary.Decoding.Annotated 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 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
| |||||
(Show b, Show a) => Show (Annotated b a) | |||||
Decoded (Annotated b ByteString) | |||||
Defined in Cardano.Ledger.Binary.Decoding.Annotated
recoverBytes :: Annotated b ByteString -> ByteString Source # | |||||
(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 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) | |||||
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.4.0.0-6ccf376d820d8fc3f4af3d96bddfe4df0181f1a72511d8efc8767f769c68c6ed" '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
Instances
ToJSON ByteSpan | |||||
Defined in Cardano.Ledger.Binary.Decoding.Annotated toEncoding :: ByteSpan -> Encoding toJSONList :: [ByteSpan] -> Value toEncodingList :: [ByteSpan] -> Encoding | |||||
Generic ByteSpan | |||||
Defined in Cardano.Ledger.Binary.Decoding.Annotated
| |||||
Show ByteSpan | |||||
FromCBOR (ABlockSignature ByteSpan) | |||||
Defined in Cardano.Chain.Block.Header | |||||
FromCBOR (ACertificate ByteSpan) | |||||
Defined in Cardano.Chain.Delegation.Certificate | |||||
FromCBOR (AMempoolPayload ByteSpan) | |||||
Defined in Cardano.Chain.MempoolPayload | |||||
FromCBOR (ATxAux ByteSpan) | |||||
FromCBOR (AProposal ByteSpan) | |||||
FromCBOR (AVote ByteSpan) | |||||
DecCBOR (ABlockSignature ByteSpan) | |||||
DecCBOR (ACertificate ByteSpan) | |||||
DecCBOR (AMempoolPayload ByteSpan) | |||||
DecCBOR (ATxAux 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.4.0.0-6ccf376d820d8fc3f4af3d96bddfe4df0181f1a72511d8efc8767f769c68c6ed" '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))) |
newtype KeyHash (discriminator :: KeyRole) c Source #
Discriminated hash of public Key
Instances
HasKeyRole KeyHash | |||||
Defined in Cardano.Ledger.Keys.Internal | |||||
Crypto c => FromJSON (KeyHash disc c) | |||||
Defined in Cardano.Ledger.Keys.Internal parseJSON :: Value -> Parser (KeyHash disc c) parseJSONList :: Value -> Parser [KeyHash disc c] omittedField :: Maybe (KeyHash disc c) | |||||
Crypto c => FromJSONKey (KeyHash disc c) | |||||
Defined in Cardano.Ledger.Keys.Internal fromJSONKey :: FromJSONKeyFunction (KeyHash disc c) fromJSONKeyList :: FromJSONKeyFunction [KeyHash disc c] | |||||
Crypto c => ToJSON (KeyHash disc c) | |||||
Defined in Cardano.Ledger.Keys.Internal toJSON :: KeyHash disc c -> Value toEncoding :: KeyHash disc c -> Encoding toJSONList :: [KeyHash disc c] -> Value toEncodingList :: [KeyHash disc c] -> Encoding | |||||
Crypto c => ToJSONKey (KeyHash disc c) | |||||
Defined in Cardano.Ledger.Keys.Internal toJSONKey :: ToJSONKeyFunction (KeyHash disc c) toJSONKeyList :: ToJSONKeyFunction [KeyHash disc c] | |||||
Generic (KeyHash discriminator c) | |||||
Defined in Cardano.Ledger.Keys.Internal
| |||||
Show (KeyHash discriminator c) | |||||
(Crypto c, Typeable disc) => FromCBOR (KeyHash disc c) | |||||
(Crypto c, Typeable disc) => ToCBOR (KeyHash disc c) | |||||
(Crypto c, Typeable disc) => DecCBOR (KeyHash disc c) | |||||
(Crypto c, Typeable disc) => EncCBOR (KeyHash disc c) | |||||
Crypto b => Default (KeyHash a b) | |||||
Defined in Cardano.Ledger.Keys.Internal | |||||
NFData (KeyHash discriminator c) | |||||
Defined in Cardano.Ledger.Keys.Internal | |||||
Eq (KeyHash discriminator c) | |||||
Ord (KeyHash discriminator c) | |||||
Defined in Cardano.Ledger.Keys.Internal compare :: KeyHash discriminator c -> KeyHash discriminator c -> Ordering Source # (<) :: KeyHash discriminator c -> KeyHash discriminator c -> Bool Source # (<=) :: KeyHash discriminator c -> KeyHash discriminator c -> Bool Source # (>) :: KeyHash discriminator c -> KeyHash discriminator c -> Bool Source # (>=) :: KeyHash discriminator c -> KeyHash discriminator c -> Bool Source # max :: KeyHash discriminator c -> KeyHash discriminator c -> KeyHash discriminator c Source # min :: KeyHash discriminator c -> KeyHash discriminator c -> KeyHash discriminator c Source # | |||||
NoThunks (KeyHash discriminator c) | |||||
type Rep (KeyHash discriminator c) | |||||
Defined in Cardano.Ledger.Keys.Internal |
hashKey :: forall c (kd :: KeyRole). Crypto c => VKey kd c -> KeyHash kd c Source #
Hash a given public key
Committee | |
|
Instances
Era era => FromJSON (Committee era) | |||||
Defined in Cardano.Ledger.Conway.Governance.Procedures 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 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
| |||||
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.17.0.0-ed41115f30aea12826c7e98271388af39c652244463f16622d3682aa6c1354c0" 'False) (C1 ('MetaCons "Committee" 'PrefixI 'True) (S1 ('MetaSel ('Just "committeeMembers") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (Credential 'ColdCommitteeRole (EraCrypto era)) EpochNo)) :*: S1 ('MetaSel ('Just "committeeThreshold") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitInterval))) |
data DRepVotingThresholds Source #
DRepVotingThresholds | |
|
Instances
FromJSON DRepVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams parseJSON :: Value -> Parser DRepVotingThresholds parseJSONList :: Value -> Parser [DRepVotingThresholds] | |||||
ToJSON DRepVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams toJSON :: DRepVotingThresholds -> Value toEncoding :: DRepVotingThresholds -> Encoding toJSONList :: [DRepVotingThresholds] -> Value toEncodingList :: [DRepVotingThresholds] -> Encoding | |||||
Generic DRepVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams
| |||||
Show DRepVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams | |||||
DecCBOR DRepVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams | |||||
EncCBOR DRepVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams 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 | |||||
NFData DRepVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams rnf :: DRepVotingThresholds -> () Source # | |||||
Eq DRepVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams (==) :: DRepVotingThresholds -> DRepVotingThresholds -> Bool Source # (/=) :: DRepVotingThresholds -> DRepVotingThresholds -> Bool Source # | |||||
Ord DRepVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams 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 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.17.0.0-ed41115f30aea12826c7e98271388af39c652244463f16622d3682aa6c1354c0" '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 #
Instances
FromJSON PoolVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams parseJSON :: Value -> Parser PoolVotingThresholds parseJSONList :: Value -> Parser [PoolVotingThresholds] | |||||
ToJSON PoolVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams toJSON :: PoolVotingThresholds -> Value toEncoding :: PoolVotingThresholds -> Encoding toJSONList :: [PoolVotingThresholds] -> Value toEncodingList :: [PoolVotingThresholds] -> Encoding | |||||
Generic PoolVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams
| |||||
Show PoolVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams | |||||
DecCBOR PoolVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams | |||||
EncCBOR PoolVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams 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 | |||||
NFData PoolVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams rnf :: PoolVotingThresholds -> () Source # | |||||
Eq PoolVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams (==) :: PoolVotingThresholds -> PoolVotingThresholds -> Bool Source # (/=) :: PoolVotingThresholds -> PoolVotingThresholds -> Bool Source # | |||||
Ord PoolVotingThresholds | |||||
Defined in Cardano.Ledger.Conway.PParams 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 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.17.0.0-ed41115f30aea12826c7e98271388af39c652244463f16622d3682aa6c1354c0" '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 #
UpgradeConwayPParams | |
|
Instances
FromJSON (UpgradeConwayPParams Identity) | |||||
Defined in Cardano.Ledger.Conway.PParams parseJSON :: Value -> Parser (UpgradeConwayPParams Identity) parseJSONList :: Value -> Parser [UpgradeConwayPParams Identity] | |||||
ToJSON (UpgradeConwayPParams Identity) | |||||
Defined in Cardano.Ledger.Conway.PParams 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
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 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 | |||||
Default (UpgradeConwayPParams StrictMaybe) | |||||
Defined in Cardano.Ledger.Conway.PParams | |||||
NFData (UpgradeConwayPParams Identity) | |||||
Defined in Cardano.Ledger.Conway.PParams rnf :: UpgradeConwayPParams Identity -> () Source # | |||||
NFData (UpgradeConwayPParams StrictMaybe) | |||||
Defined in Cardano.Ledger.Conway.PParams rnf :: UpgradeConwayPParams StrictMaybe -> () Source # | |||||
Eq (UpgradeConwayPParams Identity) | |||||
Defined in Cardano.Ledger.Conway.PParams | |||||
Eq (UpgradeConwayPParams StrictMaybe) | |||||
Ord (UpgradeConwayPParams Identity) | |||||
Defined in Cardano.Ledger.Conway.PParams 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 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 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 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.17.0.0-ed41115f30aea12826c7e98271388af39c652244463f16622d3682aa6c1354c0" '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 (EraCrypto era) -> StrictMaybe (Anchor (EraCrypto era)) -> TxCert era Source #
data ConwayDelegCert c 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.
ConwayRegCert !(StakeCredential c) !(StrictMaybe Coin) | Register staking credential. Deposit, when present, must match the expected deposit
amount specified by |
ConwayUnRegCert !(StakeCredential c) !(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 c) !(Delegatee c) | Delegate staking credentials to a delegatee. Staking credential must already be registered. |
ConwayRegDelegCert !(StakeCredential c) !(Delegatee c) !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
Crypto c => ToJSON (ConwayDelegCert c) | |||||
Defined in Cardano.Ledger.Conway.TxCert toJSON :: ConwayDelegCert c -> Value toEncoding :: ConwayDelegCert c -> Encoding toJSONList :: [ConwayDelegCert c] -> Value toEncodingList :: [ConwayDelegCert c] -> Encoding omitField :: ConwayDelegCert c -> Bool | |||||
Generic (ConwayDelegCert c) | |||||
Defined in Cardano.Ledger.Conway.TxCert
from :: ConwayDelegCert c -> Rep (ConwayDelegCert c) x Source # to :: Rep (ConwayDelegCert c) x -> ConwayDelegCert c Source # | |||||
Show (ConwayDelegCert c) | |||||
Defined in Cardano.Ledger.Conway.TxCert | |||||
Crypto c => EncCBOR (ConwayDelegCert c) | |||||
Defined in Cardano.Ledger.Conway.TxCert encCBOR :: ConwayDelegCert c -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (ConwayDelegCert c) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ConwayDelegCert c] -> Size Source # | |||||
NFData (ConwayDelegCert c) | |||||
Defined in Cardano.Ledger.Conway.TxCert rnf :: ConwayDelegCert c -> () Source # | |||||
Eq (ConwayDelegCert c) | |||||
Defined in Cardano.Ledger.Conway.TxCert (==) :: ConwayDelegCert c -> ConwayDelegCert c -> Bool Source # (/=) :: ConwayDelegCert c -> ConwayDelegCert c -> Bool Source # | |||||
Ord (ConwayDelegCert c) | |||||
Defined in Cardano.Ledger.Conway.TxCert compare :: ConwayDelegCert c -> ConwayDelegCert c -> Ordering Source # (<) :: ConwayDelegCert c -> ConwayDelegCert c -> Bool Source # (<=) :: ConwayDelegCert c -> ConwayDelegCert c -> Bool Source # (>) :: ConwayDelegCert c -> ConwayDelegCert c -> Bool Source # (>=) :: ConwayDelegCert c -> ConwayDelegCert c -> Bool Source # max :: ConwayDelegCert c -> ConwayDelegCert c -> ConwayDelegCert c Source # min :: ConwayDelegCert c -> ConwayDelegCert c -> ConwayDelegCert c Source # | |||||
NoThunks (ConwayDelegCert c) | |||||
Defined in Cardano.Ledger.Conway.TxCert noThunks :: Context -> ConwayDelegCert c -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> ConwayDelegCert c -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (ConwayDelegCert c) -> String # | |||||
type Rep (ConwayDelegCert c) | |||||
Defined in Cardano.Ledger.Conway.TxCert type Rep (ConwayDelegCert c) = D1 ('MetaData "ConwayDelegCert" "Cardano.Ledger.Conway.TxCert" "cardano-ledger-conway-1.17.0.0-ed41115f30aea12826c7e98271388af39c652244463f16622d3682aa6c1354c0" 'False) ((C1 ('MetaCons "ConwayRegCert" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StakeCredential c)) :*: 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 c)) :*: 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 c)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Delegatee c))) :+: C1 ('MetaCons "ConwayRegDelegCert" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StakeCredential c)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Delegatee c)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin))))) |
data ConwayGovCert c Source #
ConwayRegDRep !(Credential 'DRepRole c) !Coin !(StrictMaybe (Anchor c)) | |
ConwayUnRegDRep !(Credential 'DRepRole c) !Coin | |
ConwayUpdateDRep !(Credential 'DRepRole c) !(StrictMaybe (Anchor c)) | |
ConwayAuthCommitteeHotKey !(Credential 'ColdCommitteeRole c) !(Credential 'HotCommitteeRole c) | |
ConwayResignCommitteeColdKey !(Credential 'ColdCommitteeRole c) !(StrictMaybe (Anchor c)) |
Instances
Crypto c => ToJSON (ConwayGovCert c) | |||||
Defined in Cardano.Ledger.Conway.TxCert toJSON :: ConwayGovCert c -> Value toEncoding :: ConwayGovCert c -> Encoding toJSONList :: [ConwayGovCert c] -> Value toEncodingList :: [ConwayGovCert c] -> Encoding omitField :: ConwayGovCert c -> Bool | |||||
Generic (ConwayGovCert c) | |||||
Defined in Cardano.Ledger.Conway.TxCert
from :: ConwayGovCert c -> Rep (ConwayGovCert c) x Source # to :: Rep (ConwayGovCert c) x -> ConwayGovCert c Source # | |||||
Show (ConwayGovCert c) | |||||
Defined in Cardano.Ledger.Conway.TxCert | |||||
Crypto c => EncCBOR (ConwayGovCert c) | |||||
Defined in Cardano.Ledger.Conway.TxCert encCBOR :: ConwayGovCert c -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (ConwayGovCert c) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ConwayGovCert c] -> Size Source # | |||||
Crypto c => NFData (ConwayGovCert c) | |||||
Defined in Cardano.Ledger.Conway.TxCert rnf :: ConwayGovCert c -> () Source # | |||||
Eq (ConwayGovCert c) | |||||
Defined in Cardano.Ledger.Conway.TxCert (==) :: ConwayGovCert c -> ConwayGovCert c -> Bool Source # (/=) :: ConwayGovCert c -> ConwayGovCert c -> Bool Source # | |||||
Ord (ConwayGovCert c) | |||||
Defined in Cardano.Ledger.Conway.TxCert compare :: ConwayGovCert c -> ConwayGovCert c -> Ordering Source # (<) :: ConwayGovCert c -> ConwayGovCert c -> Bool Source # (<=) :: ConwayGovCert c -> ConwayGovCert c -> Bool Source # (>) :: ConwayGovCert c -> ConwayGovCert c -> Bool Source # (>=) :: ConwayGovCert c -> ConwayGovCert c -> Bool Source # max :: ConwayGovCert c -> ConwayGovCert c -> ConwayGovCert c Source # min :: ConwayGovCert c -> ConwayGovCert c -> ConwayGovCert c Source # | |||||
NoThunks (ConwayGovCert c) | |||||
Defined in Cardano.Ledger.Conway.TxCert noThunks :: Context -> ConwayGovCert c -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> ConwayGovCert c -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (ConwayGovCert c) -> String # | |||||
type Rep (ConwayGovCert c) | |||||
Defined in Cardano.Ledger.Conway.TxCert type Rep (ConwayGovCert c) = D1 ('MetaData "ConwayGovCert" "Cardano.Ledger.Conway.TxCert" "cardano-ledger-conway-1.17.0.0-ed41115f30aea12826c7e98271388af39c652244463f16622d3682aa6c1354c0" 'False) ((C1 ('MetaCons "ConwayRegDRep" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Credential 'DRepRole c)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe (Anchor c))))) :+: C1 ('MetaCons "ConwayUnRegDRep" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Credential 'DRepRole c)) :*: 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 c)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe (Anchor c)))) :+: (C1 ('MetaCons "ConwayAuthCommitteeHotKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Credential 'ColdCommitteeRole c)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Credential 'HotCommitteeRole c))) :+: C1 ('MetaCons "ConwayResignCommitteeColdKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Credential 'ColdCommitteeRole c)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe (Anchor c))))))) |
data ConwayTxCert era Source #
ConwayTxCertDeleg !(ConwayDelegCert (EraCrypto era)) | |
ConwayTxCertPool !(PoolCert (EraCrypto era)) | |
ConwayTxCertGov !(ConwayGovCert (EraCrypto era)) |
Instances
Era era => ToJSON (ConwayTxCert era) | |||||
Defined in Cardano.Ledger.Conway.TxCert 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
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 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 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 # | |||||
Crypto (EraCrypto era) => NFData (ConwayTxCert era) | |||||
Defined in Cardano.Ledger.Conway.TxCert rnf :: ConwayTxCert era -> () Source # | |||||
Eq (ConwayTxCert era) | |||||
Defined in Cardano.Ledger.Conway.TxCert (==) :: ConwayTxCert era -> ConwayTxCert era -> Bool Source # (/=) :: ConwayTxCert era -> ConwayTxCert era -> Bool Source # | |||||
Ord (ConwayTxCert era) | |||||
Defined in Cardano.Ledger.Conway.TxCert 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 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.17.0.0-ed41115f30aea12826c7e98271388af39c652244463f16622d3682aa6c1354c0" 'False) (C1 ('MetaCons "ConwayTxCertDeleg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ConwayDelegCert (EraCrypto era)))) :+: (C1 ('MetaCons "ConwayTxCertPool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PoolCert (EraCrypto era)))) :+: C1 ('MetaCons "ConwayTxCertGov" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ConwayGovCert (EraCrypto era)))))) |
newtype EpochInterval Source #
Instances
FromJSON EpochInterval | |||||
Defined in Cardano.Slotting.Slot parseJSON :: Value -> Parser EpochInterval parseJSONList :: Value -> Parser [EpochInterval] | |||||
ToJSON EpochInterval | |||||
Defined in Cardano.Slotting.Slot toJSON :: EpochInterval -> Value toEncoding :: EpochInterval -> Encoding toJSONList :: [EpochInterval] -> Value toEncodingList :: [EpochInterval] -> Encoding omitField :: EpochInterval -> Bool | |||||
Generic EpochInterval | |||||
Defined in Cardano.Slotting.Slot
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 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 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 # | |||||
NFData EpochInterval | |||||
Defined in Cardano.Slotting.Slot rnf :: EpochInterval -> () Source # | |||||
Eq EpochInterval | |||||
Defined in Cardano.Slotting.Slot (==) :: EpochInterval -> EpochInterval -> Bool Source # (/=) :: EpochInterval -> EpochInterval -> Bool Source # | |||||
Ord EpochInterval | |||||
Defined in Cardano.Slotting.Slot 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 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-1881c023e0886f672d28a4c45a256e973fe8d96632667e110b19ce5f49f52117" '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 parseJSON :: Value -> Parser EpochNo parseJSONList :: Value -> Parser [EpochNo] | |||||
ToJSON EpochNo | |||||
Defined in Cardano.Slotting.Slot toEncoding :: EpochNo -> Encoding toJSONList :: [EpochNo] -> Value toEncodingList :: [EpochNo] -> Encoding | |||||
Enum EpochNo | |||||
Defined in Cardano.Slotting.Slot 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
| |||||
Show EpochNo | |||||
FromCBOR EpochNo | |||||
ToCBOR EpochNo | |||||
DecCBOR EpochNo | |||||
EncCBOR EpochNo | |||||
NFData EpochNo | |||||
Defined in Cardano.Slotting.Slot | |||||
Eq EpochNo | |||||
Ord EpochNo | |||||
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-1881c023e0886f672d28a4c45a256e973fe8d96632667e110b19ce5f49f52117" 'True) (C1 ('MetaCons "EpochNo" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEpochNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64))) |
data GenDelegPair c Source #
GenDelegPair | |
|
Instances
Crypto c => FromJSON (GenDelegPair c) | |||||
Defined in Cardano.Ledger.Keys.Internal parseJSON :: Value -> Parser (GenDelegPair c) parseJSONList :: Value -> Parser [GenDelegPair c] omittedField :: Maybe (GenDelegPair c) | |||||
Crypto c => ToJSON (GenDelegPair c) | |||||
Defined in Cardano.Ledger.Keys.Internal toJSON :: GenDelegPair c -> Value toEncoding :: GenDelegPair c -> Encoding toJSONList :: [GenDelegPair c] -> Value toEncodingList :: [GenDelegPair c] -> Encoding omitField :: GenDelegPair c -> Bool | |||||
Generic (GenDelegPair c) | |||||
Defined in Cardano.Ledger.Keys.Internal
from :: GenDelegPair c -> Rep (GenDelegPair c) x Source # to :: Rep (GenDelegPair c) x -> GenDelegPair c Source # | |||||
Show (GenDelegPair c) | |||||
Defined in Cardano.Ledger.Keys.Internal | |||||
Crypto c => DecCBOR (GenDelegPair c) | |||||
Defined in Cardano.Ledger.Keys.Internal | |||||
Crypto c => EncCBOR (GenDelegPair c) | |||||
Defined in Cardano.Ledger.Keys.Internal encCBOR :: GenDelegPair c -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (GenDelegPair c) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [GenDelegPair c] -> Size Source # | |||||
NFData (GenDelegPair c) | |||||
Defined in Cardano.Ledger.Keys.Internal rnf :: GenDelegPair c -> () Source # | |||||
Eq (GenDelegPair c) | |||||
Defined in Cardano.Ledger.Keys.Internal (==) :: GenDelegPair c -> GenDelegPair c -> Bool Source # (/=) :: GenDelegPair c -> GenDelegPair c -> Bool Source # | |||||
Ord (GenDelegPair c) | |||||
Defined in Cardano.Ledger.Keys.Internal compare :: GenDelegPair c -> GenDelegPair c -> Ordering Source # (<) :: GenDelegPair c -> GenDelegPair c -> Bool Source # (<=) :: GenDelegPair c -> GenDelegPair c -> Bool Source # (>) :: GenDelegPair c -> GenDelegPair c -> Bool Source # (>=) :: GenDelegPair c -> GenDelegPair c -> Bool Source # max :: GenDelegPair c -> GenDelegPair c -> GenDelegPair c Source # min :: GenDelegPair c -> GenDelegPair c -> GenDelegPair c Source # | |||||
NoThunks (GenDelegPair c) | |||||
Defined in Cardano.Ledger.Keys.Internal noThunks :: Context -> GenDelegPair c -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> GenDelegPair c -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (GenDelegPair c) -> String # | |||||
type Rep (GenDelegPair c) | |||||
Defined in Cardano.Ledger.Keys.Internal type Rep (GenDelegPair c) = D1 ('MetaData "GenDelegPair" "Cardano.Ledger.Keys.Internal" "cardano-ledger-core-1.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" 'False) (C1 ('MetaCons "GenDelegPair" 'PrefixI 'True) (S1 ('MetaSel ('Just "genDelegKeyHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'GenesisDelegate c)) :*: S1 ('MetaSel ('Just "genDelegVrfHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Hash c (VerKeyVRF c))))) |
class HasKeyRole (a :: KeyRole -> Type -> Type) Source #
Instances
HasKeyRole Credential | |
Defined in Cardano.Ledger.Credential coerceKeyRole :: forall (r :: KeyRole) c (r' :: KeyRole). Credential r c -> Credential r' c Source # | |
HasKeyRole KeyHash | |
Defined in Cardano.Ledger.Keys.Internal | |
HasKeyRole VKey | |
Defined in Cardano.Ledger.Keys.Internal |
castSafeHash :: forall i j c. SafeHash c i -> SafeHash c j Source #
To change the index parameter of SafeHash (which is a phantom type) use castSafeHash
unsafeMakeSafeHash :: Hash (HASH c) index -> SafeHash c index Source #
Don't use this except in Testing to make Arbitrary instances, etc. Defined here, only because the Constructor is in scope here.
data SafeHash c index Source #
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 'hashWithCrypto, hashAnnotated
and extractHash
which have constraints
that limit their application to types which preserve their original serialization
bytes.
Instances
Crypto c => FromJSON (SafeHash c index) | |
Defined in Cardano.Ledger.SafeHash parseJSON :: Value -> Parser (SafeHash c index) parseJSONList :: Value -> Parser [SafeHash c index] omittedField :: Maybe (SafeHash c index) | |
Crypto c => ToJSON (SafeHash c index) | |
Defined in Cardano.Ledger.SafeHash toJSON :: SafeHash c index -> Value toEncoding :: SafeHash c index -> Encoding toJSONList :: [SafeHash c index] -> Value toEncodingList :: [SafeHash c index] -> Encoding | |
Show (SafeHash c index) | |
(Typeable index, Crypto c) => FromCBOR (SafeHash c index) | |
(Typeable index, Crypto c) => ToCBOR (SafeHash c index) | |
(Typeable index, Crypto c) => DecCBOR (SafeHash c index) | |
(Typeable index, Crypto c) => EncCBOR (SafeHash c index) | |
HashAlgorithm (HASH c) => SafeToHash (SafeHash c index) | |
Defined in Cardano.Ledger.SafeHash originalBytes :: SafeHash c index -> ByteString Source # originalBytesSize :: SafeHash c index -> Int Source # makeHashWithExplicitProxys :: HashAlgorithm (HASH c0) => Proxy c0 -> Proxy index0 -> SafeHash c index -> SafeHash c0 index0 Source # | |
Crypto c => Default (SafeHash c i) | |
Defined in Cardano.Ledger.SafeHash | |
NFData (SafeHash c index) | |
Defined in Cardano.Ledger.SafeHash | |
Eq (SafeHash c index) | |
Ord (SafeHash c index) | |
Defined in Cardano.Ledger.SafeHash compare :: SafeHash c index -> SafeHash c index -> Ordering Source # (<) :: SafeHash c index -> SafeHash c index -> Bool Source # (<=) :: SafeHash c index -> SafeHash c index -> Bool Source # (>) :: SafeHash c index -> SafeHash c index -> Bool Source # (>=) :: SafeHash c index -> SafeHash c index -> Bool Source # max :: SafeHash c index -> SafeHash c index -> SafeHash c index Source # min :: SafeHash c index -> SafeHash c index -> SafeHash c index Source # | |
HeapWords (SafeHash c i) | |
Defined in Cardano.Ledger.SafeHash | |
NoThunks (SafeHash c index) | |
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 parseJSON :: Value -> Parser DnsName parseJSONList :: Value -> Parser [DnsName] | |||||
ToJSON DnsName | |||||
Defined in Cardano.Ledger.BaseTypes toEncoding :: DnsName -> Encoding toJSONList :: [DnsName] -> Value toEncodingList :: [DnsName] -> Encoding | |||||
Generic DnsName | |||||
Defined in Cardano.Ledger.BaseTypes
| |||||
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.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" 'True) (C1 ('MetaCons "DnsName" 'PrefixI 'True) (S1 ('MetaSel ('Just "dnsToText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
Instances
FromJSON Network | |||||
Defined in Cardano.Ledger.BaseTypes parseJSON :: Value -> Parser Network parseJSONList :: Value -> Parser [Network] | |||||
ToJSON Network | |||||
Defined in Cardano.Ledger.BaseTypes toEncoding :: Network -> Encoding toJSONList :: [Network] -> Value toEncodingList :: [Network] -> Encoding | |||||
Bounded Network | |||||
Enum Network | |||||
Defined in Cardano.Ledger.BaseTypes 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
| |||||
Show 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.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" '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 parseJSON :: Value -> Parser NonNegativeInterval parseJSONList :: Value -> Parser [NonNegativeInterval] | |||||
ToJSON NonNegativeInterval | |||||
Defined in Cardano.Ledger.BaseTypes 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
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 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 | |||||
NFData NonNegativeInterval | |||||
Defined in Cardano.Ledger.BaseTypes rnf :: NonNegativeInterval -> () Source # | |||||
Eq NonNegativeInterval | |||||
Defined in Cardano.Ledger.BaseTypes (==) :: NonNegativeInterval -> NonNegativeInterval -> Bool Source # (/=) :: NonNegativeInterval -> NonNegativeInterval -> Bool Source # | |||||
Ord NonNegativeInterval | |||||
Defined in Cardano.Ledger.BaseTypes 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 noThunks :: Context -> NonNegativeInterval -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> NonNegativeInterval -> IO (Maybe ThunkInfo) # | |||||
Bounded (BoundedRatio NonNegativeInterval Word64) | |||||
Defined in Cardano.Ledger.BaseTypes 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.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" '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 parseJSON :: Value -> Parser UnitInterval parseJSONList :: Value -> Parser [UnitInterval] | |||||
ToJSON UnitInterval | |||||
Defined in Cardano.Ledger.BaseTypes 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
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 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 | |||||
Default UnitInterval | |||||
Defined in Cardano.Ledger.BaseTypes def :: UnitInterval # | |||||
NFData UnitInterval | |||||
Defined in Cardano.Ledger.BaseTypes rnf :: UnitInterval -> () Source # | |||||
Eq UnitInterval | |||||
Defined in Cardano.Ledger.BaseTypes (==) :: UnitInterval -> UnitInterval -> Bool Source # (/=) :: UnitInterval -> UnitInterval -> Bool Source # | |||||
Ord UnitInterval | |||||
Defined in Cardano.Ledger.BaseTypes 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 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 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.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" '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 | |||||
ToJSON Url | |||||
Defined in Cardano.Ledger.BaseTypes | |||||
Generic Url | |||||
Defined in Cardano.Ledger.BaseTypes
| |||||
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.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" 'True) (C1 ('MetaCons "Url" 'PrefixI 'True) (S1 ('MetaSel ('Just "urlToText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) |
credToText :: forall (kr :: KeyRole) c. Credential kr c -> Text Source #
data Credential (kr :: KeyRole) c 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.
ScriptHashObj !(ScriptHash c) | |
KeyHashObj !(KeyHash kr c) |
Instances
HasKeyRole Credential | |||||
Defined in Cardano.Ledger.Credential coerceKeyRole :: forall (r :: KeyRole) c (r' :: KeyRole). Credential r c -> Credential r' c Source # | |||||
Crypto c => FromJSON (Credential kr c) | |||||
Defined in Cardano.Ledger.Credential parseJSON :: Value -> Parser (Credential kr c) parseJSONList :: Value -> Parser [Credential kr c] omittedField :: Maybe (Credential kr c) | |||||
Crypto c => FromJSONKey (Credential kr c) | |||||
Defined in Cardano.Ledger.Credential fromJSONKey :: FromJSONKeyFunction (Credential kr c) fromJSONKeyList :: FromJSONKeyFunction [Credential kr c] | |||||
Crypto c => ToJSON (Credential kr c) | |||||
Defined in Cardano.Ledger.Credential toJSON :: Credential kr c -> Value toEncoding :: Credential kr c -> Encoding toJSONList :: [Credential kr c] -> Value toEncodingList :: [Credential kr c] -> Encoding omitField :: Credential kr c -> Bool | |||||
Crypto c => ToJSONKey (Credential kr c) | |||||
Defined in Cardano.Ledger.Credential toJSONKey :: ToJSONKeyFunction (Credential kr c) toJSONKeyList :: ToJSONKeyFunction [Credential kr c] | |||||
Generic (Credential kr c) | |||||
Defined in Cardano.Ledger.Credential
from :: Credential kr c -> Rep (Credential kr c) x Source # to :: Rep (Credential kr c) x -> Credential kr c Source # | |||||
Show (Credential kr c) | |||||
Defined in Cardano.Ledger.Credential | |||||
(Typeable kr, Crypto c) => FromCBOR (Credential kr c) | |||||
Defined in Cardano.Ledger.Credential | |||||
(Typeable kr, Crypto c) => ToCBOR (Credential kr c) | |||||
Defined in Cardano.Ledger.Credential toCBOR :: Credential kr c -> Encoding Source # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Credential kr c) -> Size Source # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Credential kr c] -> Size Source # | |||||
(Typeable kr, Crypto c) => DecCBOR (Credential kr c) | |||||
Defined in Cardano.Ledger.Credential | |||||
(Typeable kr, Crypto c) => EncCBOR (Credential kr c) | |||||
Defined in Cardano.Ledger.Credential encCBOR :: Credential kr c -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (Credential kr c) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Credential kr c] -> Size Source # | |||||
Crypto e => Default (Credential r e) | |||||
Defined in Cardano.Ledger.Credential def :: Credential r e # | |||||
NFData (Credential kr c) | |||||
Defined in Cardano.Ledger.Credential rnf :: Credential kr c -> () Source # | |||||
Eq (Credential kr c) | |||||
Defined in Cardano.Ledger.Credential (==) :: Credential kr c -> Credential kr c -> Bool Source # (/=) :: Credential kr c -> Credential kr c -> Bool Source # | |||||
Ord (Credential kr c) | |||||
Defined in Cardano.Ledger.Credential compare :: Credential kr c -> Credential kr c -> Ordering Source # (<) :: Credential kr c -> Credential kr c -> Bool Source # (<=) :: Credential kr c -> Credential kr c -> Bool Source # (>) :: Credential kr c -> Credential kr c -> Bool Source # (>=) :: Credential kr c -> Credential kr c -> Bool Source # max :: Credential kr c -> Credential kr c -> Credential kr c Source # min :: Credential kr c -> Credential kr c -> Credential kr c Source # | |||||
NoThunks (Credential kr c) | |||||
Defined in Cardano.Ledger.Credential noThunks :: Context -> Credential kr c -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> Credential kr c -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (Credential kr c) -> String # | |||||
type Rep (Credential kr c) | |||||
Defined in Cardano.Ledger.Credential type Rep (Credential kr c) = D1 ('MetaData "Credential" "Cardano.Ledger.Credential" "cardano-ledger-core-1.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" 'False) (C1 ('MetaCons "ScriptHashObj" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ScriptHash c))) :+: C1 ('MetaCons "KeyHashObj" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash kr c)))) |
data StakeReference c Source #
Instances
Crypto c => ToJSON (StakeReference c) | |||||
Defined in Cardano.Ledger.Credential toJSON :: StakeReference c -> Value toEncoding :: StakeReference c -> Encoding toJSONList :: [StakeReference c] -> Value toEncodingList :: [StakeReference c] -> Encoding omitField :: StakeReference c -> Bool | |||||
Generic (StakeReference c) | |||||
Defined in Cardano.Ledger.Credential
from :: StakeReference c -> Rep (StakeReference c) x Source # to :: Rep (StakeReference c) x -> StakeReference c Source # | |||||
Show (StakeReference c) | |||||
Defined in Cardano.Ledger.Credential | |||||
NFData (StakeReference c) | |||||
Defined in Cardano.Ledger.Credential rnf :: StakeReference c -> () Source # | |||||
Eq (StakeReference c) | |||||
Defined in Cardano.Ledger.Credential (==) :: StakeReference c -> StakeReference c -> Bool Source # (/=) :: StakeReference c -> StakeReference c -> Bool Source # | |||||
Ord (StakeReference c) | |||||
Defined in Cardano.Ledger.Credential compare :: StakeReference c -> StakeReference c -> Ordering Source # (<) :: StakeReference c -> StakeReference c -> Bool Source # (<=) :: StakeReference c -> StakeReference c -> Bool Source # (>) :: StakeReference c -> StakeReference c -> Bool Source # (>=) :: StakeReference c -> StakeReference c -> Bool Source # max :: StakeReference c -> StakeReference c -> StakeReference c Source # min :: StakeReference c -> StakeReference c -> StakeReference c Source # | |||||
NoThunks (StakeReference c) | |||||
Defined in Cardano.Ledger.Credential noThunks :: Context -> StakeReference c -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> StakeReference c -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (StakeReference c) -> String # | |||||
type Rep (StakeReference c) | |||||
Defined in Cardano.Ledger.Credential type Rep (StakeReference c) = D1 ('MetaData "StakeReference" "Cardano.Ledger.Credential" "cardano-ledger-core-1.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" 'False) (C1 ('MetaCons "StakeRefBase" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StakeCredential c))) :+: (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 :: forall c f. Functor f => (StrictMaybe (Anchor c) -> f (StrictMaybe (Anchor c))) -> DRepState c -> f (DRepState c) Source #
drepDepositL :: forall c f. Functor f => (Coin -> f Coin) -> DRepState c -> f (DRepState c) Source #
drepExpiryL :: forall c f. Functor f => (EpochNo -> f EpochNo) -> DRepState c -> f (DRepState c) Source #
DRepKeyHash !(KeyHash 'DRepRole c) | |
DRepScriptHash !(ScriptHash c) | |
DRepAlwaysAbstain | |
DRepAlwaysNoConfidence |
pattern DRepCredential :: Credential 'DRepRole c -> DRep c |
Instances
Crypto c => FromJSON (DRep c) | |||||
Defined in Cardano.Ledger.DRep parseJSON :: Value -> Parser (DRep c) parseJSONList :: Value -> Parser [DRep c] omittedField :: Maybe (DRep c) | |||||
Crypto c => FromJSONKey (DRep c) | |||||
Defined in Cardano.Ledger.DRep fromJSONKey :: FromJSONKeyFunction (DRep c) fromJSONKeyList :: FromJSONKeyFunction [DRep c] | |||||
Crypto c => ToJSON (DRep c) | |||||
Defined in Cardano.Ledger.DRep toEncoding :: DRep c -> Encoding toJSONList :: [DRep c] -> Value toEncodingList :: [DRep c] -> Encoding | |||||
Crypto c => ToJSONKey (DRep c) | |||||
Defined in Cardano.Ledger.DRep toJSONKey :: ToJSONKeyFunction (DRep c) toJSONKeyList :: ToJSONKeyFunction [DRep c] | |||||
Generic (DRep c) | |||||
Defined in Cardano.Ledger.DRep
| |||||
Show (DRep c) | |||||
Crypto c => DecCBOR (DRep c) | |||||
Crypto c => EncCBOR (DRep c) | |||||
NFData (DRep c) | |||||
Defined in Cardano.Ledger.DRep | |||||
Eq (DRep c) | |||||
Ord (DRep c) | |||||
Defined in Cardano.Ledger.DRep | |||||
NoThunks (DRep c) | |||||
type Rep (DRep c) | |||||
Defined in Cardano.Ledger.DRep type Rep (DRep c) = D1 ('MetaData "DRep" "Cardano.Ledger.DRep" "cardano-ledger-core-1.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" 'False) ((C1 ('MetaCons "DRepKeyHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'DRepRole c))) :+: C1 ('MetaCons "DRepScriptHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ScriptHash c)))) :+: (C1 ('MetaCons "DRepAlwaysAbstain" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DRepAlwaysNoConfidence" 'PrefixI 'False) (U1 :: Type -> Type))) |
DRepState | |
|
Instances
Crypto c => FromJSON (DRepState c) | |||||
Defined in Cardano.Ledger.DRep parseJSON :: Value -> Parser (DRepState c) parseJSONList :: Value -> Parser [DRepState c] omittedField :: Maybe (DRepState c) | |||||
Crypto c => ToJSON (DRepState c) | |||||
Defined in Cardano.Ledger.DRep toJSON :: DRepState c -> Value toEncoding :: DRepState c -> Encoding toJSONList :: [DRepState c] -> Value toEncodingList :: [DRepState c] -> Encoding | |||||
Generic (DRepState c) | |||||
Defined in Cardano.Ledger.DRep
| |||||
Show (DRepState c) | |||||
Crypto c => DecCBOR (DRepState c) | |||||
Crypto c => EncCBOR (DRepState c) | |||||
Crypto c => NFData (DRepState c) | |||||
Defined in Cardano.Ledger.DRep | |||||
Eq (DRepState c) | |||||
Ord (DRepState c) | |||||
Defined in Cardano.Ledger.DRep compare :: DRepState c -> DRepState c -> Ordering Source # (<) :: DRepState c -> DRepState c -> Bool Source # (<=) :: DRepState c -> DRepState c -> Bool Source # (>) :: DRepState c -> DRepState c -> Bool Source # (>=) :: DRepState c -> DRepState c -> Bool Source # | |||||
NoThunks (DRepState era) | |||||
type Rep (DRepState c) | |||||
Defined in Cardano.Ledger.DRep type Rep (DRepState c) = D1 ('MetaData "DRepState" "Cardano.Ledger.DRep" "cardano-ledger-core-1.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" '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 c)))) :*: (S1 ('MetaSel ('Just "drepDeposit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin) :*: S1 ('MetaSel ('Just "drepDelegs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set (Credential 'Staking c)))))) |
data PoolMetadata Source #
PoolMetadata | |
|
Instances
FromJSON PoolMetadata | |||||
Defined in Cardano.Ledger.PoolParams parseJSON :: Value -> Parser PoolMetadata parseJSONList :: Value -> Parser [PoolMetadata] | |||||
ToJSON PoolMetadata | |||||
Defined in Cardano.Ledger.PoolParams toJSON :: PoolMetadata -> Value toEncoding :: PoolMetadata -> Encoding toJSONList :: [PoolMetadata] -> Value toEncodingList :: [PoolMetadata] -> Encoding omitField :: PoolMetadata -> Bool | |||||
Generic PoolMetadata | |||||
Defined in Cardano.Ledger.PoolParams
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 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 rnf :: PoolMetadata -> () Source # | |||||
Eq PoolMetadata | |||||
Defined in Cardano.Ledger.PoolParams (==) :: PoolMetadata -> PoolMetadata -> Bool Source # (/=) :: PoolMetadata -> PoolMetadata -> Bool Source # | |||||
Ord PoolMetadata | |||||
Defined in Cardano.Ledger.PoolParams 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 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.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" '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 c Source #
A stake pool.
PoolParams | |
|
Instances
Crypto c => FromJSON (PoolParams c) | |||||
Defined in Cardano.Ledger.PoolParams parseJSON :: Value -> Parser (PoolParams c) parseJSONList :: Value -> Parser [PoolParams c] omittedField :: Maybe (PoolParams c) | |||||
Crypto c => ToJSON (PoolParams c) | |||||
Defined in Cardano.Ledger.PoolParams toJSON :: PoolParams c -> Value toEncoding :: PoolParams c -> Encoding toJSONList :: [PoolParams c] -> Value toEncodingList :: [PoolParams c] -> Encoding omitField :: PoolParams c -> Bool | |||||
Generic (PoolParams c) | |||||
Defined in Cardano.Ledger.PoolParams
from :: PoolParams c -> Rep (PoolParams c) x Source # to :: Rep (PoolParams c) x -> PoolParams c Source # | |||||
Show (PoolParams c) | |||||
Defined in Cardano.Ledger.PoolParams | |||||
Crypto c => DecCBOR (PoolParams c) | |||||
Defined in Cardano.Ledger.PoolParams | |||||
Crypto c => EncCBOR (PoolParams c) | |||||
Defined in Cardano.Ledger.PoolParams encCBOR :: PoolParams c -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (PoolParams c) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [PoolParams c] -> Size Source # | |||||
Crypto c => DecCBORGroup (PoolParams c) | |||||
Defined in Cardano.Ledger.PoolParams decCBORGroup :: Decoder s (PoolParams c) Source # | |||||
Crypto c => EncCBORGroup (PoolParams c) | |||||
Defined in Cardano.Ledger.PoolParams encCBORGroup :: PoolParams c -> Encoding Source # encodedGroupSizeExpr :: (forall x. EncCBOR x => Proxy x -> Size) -> Proxy (PoolParams c) -> Size Source # listLen :: PoolParams c -> Word Source # listLenBound :: Proxy (PoolParams c) -> Word Source # | |||||
Crypto c => Default (PoolParams c) | |||||
Defined in Cardano.Ledger.PoolParams def :: PoolParams c # | |||||
NFData (PoolParams c) | |||||
Defined in Cardano.Ledger.PoolParams rnf :: PoolParams c -> () Source # | |||||
Eq (PoolParams c) | |||||
Defined in Cardano.Ledger.PoolParams (==) :: PoolParams c -> PoolParams c -> Bool Source # (/=) :: PoolParams c -> PoolParams c -> Bool Source # | |||||
Ord (PoolParams c) | |||||
Defined in Cardano.Ledger.PoolParams compare :: PoolParams c -> PoolParams c -> Ordering Source # (<) :: PoolParams c -> PoolParams c -> Bool Source # (<=) :: PoolParams c -> PoolParams c -> Bool Source # (>) :: PoolParams c -> PoolParams c -> Bool Source # (>=) :: PoolParams c -> PoolParams c -> Bool Source # max :: PoolParams c -> PoolParams c -> PoolParams c Source # min :: PoolParams c -> PoolParams c -> PoolParams c Source # | |||||
NoThunks (PoolParams c) | |||||
Defined in Cardano.Ledger.PoolParams noThunks :: Context -> PoolParams c -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> PoolParams c -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (PoolParams c) -> String # | |||||
type Rep (PoolParams c) | |||||
Defined in Cardano.Ledger.PoolParams type Rep (PoolParams c) = D1 ('MetaData "PoolParams" "Cardano.Ledger.PoolParams" "cardano-ledger-core-1.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" 'False) (C1 ('MetaCons "PoolParams" 'PrefixI 'True) (((S1 ('MetaSel ('Just "ppId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool c)) :*: S1 ('MetaSel ('Just "ppVrf") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Hash c (VerKeyVRF c)))) :*: (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 c))) :*: (S1 ('MetaSel ('Just "ppOwners") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set (KeyHash 'Staking c))) :*: (S1 ('MetaSel ('Just "ppRelays") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictSeq StakePoolRelay)) :*: S1 ('MetaSel ('Just "ppMetadata") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe PoolMetadata))))))) |
data StakePoolRelay Source #
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 parseJSON :: Value -> Parser StakePoolRelay parseJSONList :: Value -> Parser [StakePoolRelay] | |||||
ToJSON StakePoolRelay | |||||
Defined in Cardano.Ledger.PoolParams toJSON :: StakePoolRelay -> Value toEncoding :: StakePoolRelay -> Encoding toJSONList :: [StakePoolRelay] -> Value toEncodingList :: [StakePoolRelay] -> Encoding omitField :: StakePoolRelay -> Bool | |||||
Generic StakePoolRelay | |||||
Defined in Cardano.Ledger.PoolParams
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 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 rnf :: StakePoolRelay -> () Source # | |||||
Eq StakePoolRelay | |||||
Defined in Cardano.Ledger.PoolParams (==) :: StakePoolRelay -> StakePoolRelay -> Bool Source # (/=) :: StakePoolRelay -> StakePoolRelay -> Bool Source # | |||||
Ord StakePoolRelay | |||||
Defined in Cardano.Ledger.PoolParams 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 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.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" '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 (EraCrypto era)) (CommitteeAuthorization (EraCrypto era)) -> f (Map (Credential 'ColdCommitteeRole (EraCrypto era)) (CommitteeAuthorization (EraCrypto era)))) -> CommitteeState era -> f (CommitteeState era) Source #
The state used by the POOL rule, which tracks stake pool information.
PState | |
|
Instances
Era era => ToJSON (PState era) | |||||
Defined in Cardano.Ledger.CertState toEncoding :: PState era -> Encoding toJSONList :: [PState era] -> Value toEncodingList :: [PState era] -> Encoding | |||||
Generic (PState era) | |||||
Defined in Cardano.Ledger.CertState
| |||||
Show (PState era) | |||||
(Era era, DecShareCBOR (PState era)) => DecCBOR (PState era) | |||||
Era era => DecShareCBOR (PState era) | |||||
Era era => EncCBOR (PState era) | |||||
Default (PState c) | |||||
Defined in Cardano.Ledger.CertState | |||||
NFData (PState era) | |||||
Defined in Cardano.Ledger.CertState | |||||
Eq (PState era) | |||||
NoThunks (PState era) | |||||
type Rep (PState era) | |||||
Defined in Cardano.Ledger.CertState type Rep (PState era) = D1 ('MetaData "PState" "Cardano.Ledger.CertState" "cardano-ledger-core-1.15.0.0-2e27acc191d04ed2274d46f93f1cbbd0e33c9b0ece6c9a0c5701a53b3db5b148" 'False) (C1 ('MetaCons "PState" 'PrefixI 'True) ((S1 ('MetaSel ('Just "psStakePoolParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era)))) :*: S1 ('MetaSel ('Just "psFutureStakePoolParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (KeyHash 'StakePool (EraCrypto era)) (PoolParams (EraCrypto era))))) :*: (S1 ('MetaSel ('Just "psRetiring") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (KeyHash 'StakePool (EraCrypto era)) EpochNo)) :*: S1 ('MetaSel ('Just "psDeposits") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (KeyHash 'StakePool (EraCrypto era)) Coin))))) | |||||
type Share (PState era) | |||||
type TranslationError (AllegraEra c) PState | |||||
Defined in Cardano.Ledger.Allegra.Translation | |||||
type TranslationError (AlonzoEra c) PState | |||||
Defined in Cardano.Ledger.Alonzo.Translation | |||||
type TranslationError (BabbageEra c) PState | |||||
Defined in Cardano.Ledger.Babbage.Translation | |||||
type TranslationError (ConwayEra c) PState | |||||
Defined in Cardano.Ledger.Conway.Translation | |||||
type TranslationError (MaryEra c) PState | |||||
Defined in Cardano.Ledger.Mary.Translation |
maybeToStrictMaybe :: Maybe a -> StrictMaybe a Source #
strictMaybeToMaybe :: StrictMaybe a -> Maybe a Source #
data ShelleyGenesisStaking c 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.
ShelleyGenesisStaking | |
|
Instances
Crypto c => FromJSON (ShelleyGenesisStaking c) | |||||
Defined in Cardano.Ledger.Shelley.Genesis parseJSON :: Value -> Parser (ShelleyGenesisStaking c) parseJSONList :: Value -> Parser [ShelleyGenesisStaking c] | |||||
Crypto c => ToJSON (ShelleyGenesisStaking c) | |||||
Defined in Cardano.Ledger.Shelley.Genesis toJSON :: ShelleyGenesisStaking c -> Value toEncoding :: ShelleyGenesisStaking c -> Encoding toJSONList :: [ShelleyGenesisStaking c] -> Value toEncodingList :: [ShelleyGenesisStaking c] -> Encoding omitField :: ShelleyGenesisStaking c -> Bool | |||||
Monoid (ShelleyGenesisStaking c) | |||||
Defined in Cardano.Ledger.Shelley.Genesis mempty :: ShelleyGenesisStaking c Source # mappend :: ShelleyGenesisStaking c -> ShelleyGenesisStaking c -> ShelleyGenesisStaking c Source # mconcat :: [ShelleyGenesisStaking c] -> ShelleyGenesisStaking c Source # | |||||
Semigroup (ShelleyGenesisStaking c) | |||||
Defined in Cardano.Ledger.Shelley.Genesis (<>) :: ShelleyGenesisStaking c -> ShelleyGenesisStaking c -> ShelleyGenesisStaking c Source # sconcat :: NonEmpty (ShelleyGenesisStaking c) -> ShelleyGenesisStaking c Source # stimes :: Integral b => b -> ShelleyGenesisStaking c -> ShelleyGenesisStaking c Source # | |||||
Generic (ShelleyGenesisStaking c) | |||||
Defined in Cardano.Ledger.Shelley.Genesis
from :: ShelleyGenesisStaking c -> Rep (ShelleyGenesisStaking c) x Source # to :: Rep (ShelleyGenesisStaking c) x -> ShelleyGenesisStaking c Source # | |||||
Show (ShelleyGenesisStaking c) | |||||
Defined in Cardano.Ledger.Shelley.Genesis | |||||
Crypto c => DecCBOR (ShelleyGenesisStaking c) | |||||
Defined in Cardano.Ledger.Shelley.Genesis | |||||
Crypto c => EncCBOR (ShelleyGenesisStaking c) | |||||
Defined in Cardano.Ledger.Shelley.Genesis encCBOR :: ShelleyGenesisStaking c -> Encoding Source # encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (ShelleyGenesisStaking c) -> Size Source # encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ShelleyGenesisStaking c] -> Size Source # | |||||
Eq (ShelleyGenesisStaking c) | |||||
Defined in Cardano.Ledger.Shelley.Genesis (==) :: ShelleyGenesisStaking c -> ShelleyGenesisStaking c -> Bool Source # (/=) :: ShelleyGenesisStaking c -> ShelleyGenesisStaking c -> Bool Source # | |||||
NoThunks (ShelleyGenesisStaking c) | |||||
Defined in Cardano.Ledger.Shelley.Genesis noThunks :: Context -> ShelleyGenesisStaking c -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> ShelleyGenesisStaking c -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (ShelleyGenesisStaking c) -> String # | |||||
type Rep (ShelleyGenesisStaking c) | |||||
Defined in Cardano.Ledger.Shelley.Genesis type Rep (ShelleyGenesisStaking c) = D1 ('MetaData "ShelleyGenesisStaking" "Cardano.Ledger.Shelley.Genesis" "cardano-ledger-shelley-1.14.1.0-6da62eb4db0139bb466588c0f3bf17f53ad859af8a090c113a1a960870dce943" 'False) (C1 ('MetaCons "ShelleyGenesisStaking" 'PrefixI 'True) (S1 ('MetaSel ('Just "sgsPools") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListMap (KeyHash 'StakePool c) (PoolParams c))) :*: S1 ('MetaSel ('Just "sgsStake") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListMap (KeyHash 'Staking c) (KeyHash 'StakePool c))))) |
data GenesisDelegCert c Source #
Genesis key delegation certificate
GenesisDelegCert !(KeyHash 'Genesis c) !(KeyHash 'GenesisDelegate c) !(Hash c (VerKeyVRF c)) |
Instances
Crypto c => ToJSON (GenesisDelegCert c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert toJSON :: GenesisDelegCert c -> Value toEncoding :: GenesisDelegCert c -> Encoding toJSONList :: [GenesisDelegCert c] -> Value toEncodingList :: [GenesisDelegCert c] -> Encoding omitField :: GenesisDelegCert c -> Bool | |||||
Generic (GenesisDelegCert c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert
from :: GenesisDelegCert c -> Rep (GenesisDelegCert c) x Source # to :: Rep (GenesisDelegCert c) x -> GenesisDelegCert c Source # | |||||
Show (GenesisDelegCert c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert | |||||
NFData (GenesisDelegCert c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert rnf :: GenesisDelegCert c -> () Source # | |||||
Eq (GenesisDelegCert c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert (==) :: GenesisDelegCert c -> GenesisDelegCert c -> Bool Source # (/=) :: GenesisDelegCert c -> GenesisDelegCert c -> Bool Source # | |||||
Ord (GenesisDelegCert c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert compare :: GenesisDelegCert c -> GenesisDelegCert c -> Ordering Source # (<) :: GenesisDelegCert c -> GenesisDelegCert c -> Bool Source # (<=) :: GenesisDelegCert c -> GenesisDelegCert c -> Bool Source # (>) :: GenesisDelegCert c -> GenesisDelegCert c -> Bool Source # (>=) :: GenesisDelegCert c -> GenesisDelegCert c -> Bool Source # max :: GenesisDelegCert c -> GenesisDelegCert c -> GenesisDelegCert c Source # min :: GenesisDelegCert c -> GenesisDelegCert c -> GenesisDelegCert c Source # | |||||
NoThunks (GenesisDelegCert c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert noThunks :: Context -> GenesisDelegCert c -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> GenesisDelegCert c -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (GenesisDelegCert c) -> String # | |||||
type Rep (GenesisDelegCert c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert type Rep (GenesisDelegCert c) = D1 ('MetaData "GenesisDelegCert" "Cardano.Ledger.Shelley.TxCert" "cardano-ledger-shelley-1.14.1.0-6da62eb4db0139bb466588c0f3bf17f53ad859af8a090c113a1a960870dce943" 'False) (C1 ('MetaCons "GenesisDelegCert" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'Genesis c)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'GenesisDelegate c)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Hash c (VerKeyVRF c)))))) |
data ShelleyDelegCert c Source #
ShelleyRegCert !(StakeCredential c) | A stake credential registration certificate. |
ShelleyUnRegCert !(StakeCredential c) | A stake credential deregistration certificate. |
ShelleyDelegCert !(StakeCredential c) !(KeyHash 'StakePool c) | A stake delegation certificate. |
pattern DeRegKey :: StakeCredential c -> ShelleyDelegCert c | |
pattern Delegate :: Delegation c -> ShelleyDelegCert c | |
pattern RegKey :: StakeCredential c -> ShelleyDelegCert c |
Instances
Crypto c => ToJSON (ShelleyDelegCert c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert toJSON :: ShelleyDelegCert c -> Value toEncoding :: ShelleyDelegCert c -> Encoding toJSONList :: [ShelleyDelegCert c] -> Value toEncodingList :: [ShelleyDelegCert c] -> Encoding omitField :: ShelleyDelegCert c -> Bool | |||||
Generic (ShelleyDelegCert c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert
from :: ShelleyDelegCert c -> Rep (ShelleyDelegCert c) x Source # to :: Rep (ShelleyDelegCert c) x -> ShelleyDelegCert c Source # | |||||
Show (ShelleyDelegCert c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert | |||||
NFData (ShelleyDelegCert c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert rnf :: ShelleyDelegCert c -> () Source # | |||||
Eq (ShelleyDelegCert c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert (==) :: ShelleyDelegCert c -> ShelleyDelegCert c -> Bool Source # (/=) :: ShelleyDelegCert c -> ShelleyDelegCert c -> Bool Source # | |||||
Ord (ShelleyDelegCert c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert compare :: ShelleyDelegCert c -> ShelleyDelegCert c -> Ordering Source # (<) :: ShelleyDelegCert c -> ShelleyDelegCert c -> Bool Source # (<=) :: ShelleyDelegCert c -> ShelleyDelegCert c -> Bool Source # (>) :: ShelleyDelegCert c -> ShelleyDelegCert c -> Bool Source # (>=) :: ShelleyDelegCert c -> ShelleyDelegCert c -> Bool Source # max :: ShelleyDelegCert c -> ShelleyDelegCert c -> ShelleyDelegCert c Source # min :: ShelleyDelegCert c -> ShelleyDelegCert c -> ShelleyDelegCert c Source # | |||||
NoThunks (ShelleyDelegCert c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert noThunks :: Context -> ShelleyDelegCert c -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> ShelleyDelegCert c -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy (ShelleyDelegCert c) -> String # | |||||
type Rep (ShelleyDelegCert c) | |||||
Defined in Cardano.Ledger.Shelley.TxCert type Rep (ShelleyDelegCert c) = D1 ('MetaData "ShelleyDelegCert" "Cardano.Ledger.Shelley.TxCert" "cardano-ledger-shelley-1.14.1.0-6da62eb4db0139bb466588c0f3bf17f53ad859af8a090c113a1a960870dce943" 'False) (C1 ('MetaCons "ShelleyRegCert" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StakeCredential c))) :+: (C1 ('MetaCons "ShelleyUnRegCert" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StakeCredential c))) :+: C1 ('MetaCons "ShelleyDelegCert" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StakeCredential c)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool c))))) |
data ShelleyTxCert era Source #
A heavyweight certificate.
ShelleyTxCertDelegCert !(ShelleyDelegCert (EraCrypto era)) | |
ShelleyTxCertPool !(PoolCert (EraCrypto era)) | |
ShelleyTxCertGenesisDeleg !(GenesisDelegCert (EraCrypto era)) | |
ShelleyTxCertMir !(MIRCert (EraCrypto era)) |
Instances
Era era => ToJSON (ShelleyTxCert era) | |||||
Defined in Cardano.Ledger.Shelley.TxCert 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
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 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 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 rnf :: ShelleyTxCert era -> () Source # | |||||
Eq (ShelleyTxCert era) | |||||
Defined in Cardano.Ledger.Shelley.TxCert (==) :: ShelleyTxCert era -> ShelleyTxCert era -> Bool Source # (/=) :: ShelleyTxCert era -> ShelleyTxCert era -> Bool Source # | |||||
Ord (ShelleyTxCert era) | |||||
Defined in Cardano.Ledger.Shelley.TxCert 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 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.14.1.0-6da62eb4db0139bb466588c0f3bf17f53ad859af8a090c113a1a960870dce943" 'False) ((C1 ('MetaCons "ShelleyTxCertDelegCert" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ShelleyDelegCert (EraCrypto era)))) :+: C1 ('MetaCons "ShelleyTxCertPool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PoolCert (EraCrypto era))))) :+: (C1 ('MetaCons "ShelleyTxCertGenesisDeleg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GenesisDelegCert (EraCrypto era)))) :+: C1 ('MetaCons "ShelleyTxCertMir" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (MIRCert (EraCrypto era)))))) |
data AccountState Source #
AccountState | |
|
Instances
ToJSON AccountState | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types toJSON :: AccountState -> Value toEncoding :: AccountState -> Encoding toJSONList :: [AccountState] -> Value toEncodingList :: [AccountState] -> Encoding omitField :: AccountState -> Bool | |||||
Generic AccountState | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types
from :: AccountState -> Rep AccountState x Source # to :: Rep AccountState x -> AccountState Source # | |||||
Show AccountState | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types | |||||
DecCBOR AccountState | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types | |||||
EncCBOR AccountState | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types 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.Shelley.LedgerState.Types def :: AccountState # | |||||
NFData AccountState | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types rnf :: AccountState -> () Source # | |||||
Eq AccountState | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types (==) :: AccountState -> AccountState -> Bool Source # (/=) :: AccountState -> AccountState -> Bool Source # | |||||
NoThunks AccountState | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types noThunks :: Context -> AccountState -> IO (Maybe ThunkInfo) # wNoThunks :: Context -> AccountState -> IO (Maybe ThunkInfo) # showTypeOf :: Proxy AccountState -> String # | |||||
type Rep AccountState | |||||
Defined in Cardano.Ledger.Shelley.LedgerState.Types type Rep AccountState = D1 ('MetaData "AccountState" "Cardano.Ledger.Shelley.LedgerState.Types" "cardano-ledger-shelley-1.14.1.0-6da62eb4db0139bb466588c0f3bf17f53ad859af8a090c113a1a960870dce943" 'False) (C1 ('MetaCons "AccountState" 'PrefixI 'True) (S1 ('MetaSel ('Just "asTreasury") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin) :*: S1 ('MetaSel ('Just "asReserves") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin))) |