Safe Haskell | None |
---|---|
Language | Haskell2010 |
Cardano.Api.ReexposeLedger
Documentation
data Credential (kr :: KeyRole) c #
Constructors
ScriptHashObj !(ScriptHash c) | |
KeyHashObj !(KeyHash kr c) |
Instances
newtype KeyHash (discriminator :: KeyRole) c #
Constructors
KeyHash (Hash (ADDRHASH c) (VerKeyDSIGN (DSIGN c))) |
Instances
HasKeyRole KeyHash | |
Defined in Cardano.Ledger.Keys Methods coerceKeyRole :: forall (r :: KeyRole) c (r' :: KeyRole). KeyHash r c -> KeyHash r' c | |
Embed (PoolDistr c) (Map (KeyHash 'StakePool c) (IndividualPoolStake c)) | |
HasExp (PoolDistr c) (Map (KeyHash 'StakePool c) (IndividualPoolStake c)) | |
Defined in Cardano.Ledger.PoolDistr | |
Eq (KeyHash discriminator c) | |
Ord (KeyHash discriminator c) | |
Defined in Cardano.Ledger.Keys Methods 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 # | |
Show (KeyHash discriminator c) | |
Generic (KeyHash discriminator c) | |
NFData (KeyHash discriminator c) | |
Defined in Cardano.Ledger.Keys | |
(Crypto c, Typeable disc) => DecCBOR (KeyHash disc c) | |
(Crypto c, Typeable disc) => EncCBOR (KeyHash disc c) | |
Defined in Cardano.Ledger.Keys Methods encCBOR :: KeyHash disc c -> Encoding encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (KeyHash disc c) -> Size encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [KeyHash disc c] -> Size | |
(Crypto c, Typeable disc) => FromCBOR (KeyHash disc c) | |
Crypto c => FromJSON (KeyHash disc c) | |
Defined in Cardano.Ledger.Keys Methods parseJSON :: Value -> Parser (KeyHash disc c) # parseJSONList :: Value -> Parser [KeyHash disc c] # omittedField :: Maybe (KeyHash disc c) # | |
NoThunks (KeyHash discriminator c) | |
(Crypto c, Typeable disc) => ToCBOR (KeyHash disc c) | |
ToExpr (KeyHash keyrole c) | |
Defined in Cardano.Ledger.Keys | |
Crypto c => ToJSON (KeyHash disc c) | |
Defined in Cardano.Ledger.Keys | |
Crypto c => ToJSONKey (KeyHash disc c) | |
Defined in Cardano.Ledger.Keys Methods toJSONKey :: ToJSONKeyFunction (KeyHash disc c) toJSONKeyList :: ToJSONKeyFunction [KeyHash disc c] | |
Crypto c => FromJSONKey (KeyHash disc c) | |
Defined in Cardano.Ledger.Keys Methods fromJSONKey :: FromJSONKeyFunction (KeyHash disc c) fromJSONKeyList :: FromJSONKeyFunction [KeyHash disc c] | |
type Rep (KeyHash discriminator c) | |
Defined in Cardano.Ledger.Keys |
data ShelleyTxCert era #
Constructors
ShelleyTxCertDelegCert !(ShelleyDelegCert (EraCrypto era)) | |
ShelleyTxCertPool !(PoolCert (EraCrypto era)) | |
ShelleyTxCertGenesisDeleg !(GenesisDelegCert (EraCrypto era)) | |
ShelleyTxCertMir !(MIRCert (EraCrypto era)) |
Instances
data ShelleyDelegCert c #
Constructors
ShelleyRegCert !(StakeCredential c) | |
ShelleyUnRegCert !(StakeCredential c) | |
ShelleyDelegCert !(StakeCredential c) !(KeyHash 'StakePool c) |
Bundled Patterns
pattern Delegate :: Delegation c -> ShelleyDelegCert c | |
pattern DeRegKey :: StakeCredential c -> ShelleyDelegCert c | |
pattern RegKey :: StakeCredential c -> ShelleyDelegCert c |
Instances
class EraTxCert era => ShelleyEraTxCert era where #
Methods
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)) #
Instances
Crypto c => ShelleyEraTxCert (ShelleyEra c) | |
Defined in Cardano.Ledger.Shelley.TxCert Methods mkRegTxCert :: StakeCredential (EraCrypto (ShelleyEra c)) -> TxCert (ShelleyEra c) # getRegTxCert :: TxCert (ShelleyEra c) -> Maybe (StakeCredential (EraCrypto (ShelleyEra c))) # mkUnRegTxCert :: StakeCredential (EraCrypto (ShelleyEra c)) -> TxCert (ShelleyEra c) # getUnRegTxCert :: TxCert (ShelleyEra c) -> Maybe (StakeCredential (EraCrypto (ShelleyEra c))) # mkDelegStakeTxCert :: StakeCredential (EraCrypto (ShelleyEra c)) -> KeyHash 'StakePool (EraCrypto (ShelleyEra c)) -> TxCert (ShelleyEra c) # getDelegStakeTxCert :: TxCert (ShelleyEra c) -> Maybe (StakeCredential (EraCrypto (ShelleyEra c)), KeyHash 'StakePool (EraCrypto (ShelleyEra c))) # mkGenesisDelegTxCert :: GenesisDelegCert (EraCrypto (ShelleyEra c)) -> TxCert (ShelleyEra c) # getGenesisDelegTxCert :: TxCert (ShelleyEra c) -> Maybe (GenesisDelegCert (EraCrypto (ShelleyEra c))) # mkMirTxCert :: MIRCert (EraCrypto (ShelleyEra c)) -> TxCert (ShelleyEra c) # getMirTxCert :: TxCert (ShelleyEra c) -> Maybe (MIRCert (EraCrypto (ShelleyEra c))) # |
data GenesisDelegCert c #
Constructors
GenesisDelegCert !(KeyHash 'Genesis c) !(KeyHash 'GenesisDelegate c) !(Hash c (VerKeyVRF c)) |
Instances
data PoolParams c #
Constructors
PoolParams | |
Fields
|
Instances
class HasKeyRole (a :: KeyRole -> Type -> Type) #
Instances
HasKeyRole KeyHash | |
Defined in Cardano.Ledger.Keys Methods coerceKeyRole :: forall (r :: KeyRole) c (r' :: KeyRole). KeyHash r c -> KeyHash r' c | |
HasKeyRole VKey | |
Defined in Cardano.Ledger.Keys Methods coerceKeyRole :: forall (r :: KeyRole) c (r' :: KeyRole). VKey r c -> VKey r' c | |
HasKeyRole Credential | |
Defined in Cardano.Ledger.Credential Methods coerceKeyRole :: forall (r :: KeyRole) c (r' :: KeyRole). Credential r c -> Credential r' c |
Constructors
ReservesMIR | |
TreasuryMIR |
Instances
Bounded MIRPot | |
Enum MIRPot | |
Defined in Cardano.Ledger.Shelley.TxCert Methods succ :: MIRPot -> MIRPot Source # pred :: MIRPot -> MIRPot Source # toEnum :: Int -> MIRPot Source # fromEnum :: MIRPot -> Int Source # enumFrom :: MIRPot -> [MIRPot] Source # enumFromThen :: MIRPot -> MIRPot -> [MIRPot] Source # enumFromTo :: MIRPot -> MIRPot -> [MIRPot] Source # enumFromThenTo :: MIRPot -> MIRPot -> MIRPot -> [MIRPot] Source # | |
Eq MIRPot | |
Ord MIRPot | |
Defined in Cardano.Ledger.Shelley.TxCert | |
Show MIRPot | |
Generic MIRPot | |
NFData MIRPot | |
Defined in Cardano.Ledger.Shelley.TxCert | |
DecCBOR MIRPot | |
EncCBOR MIRPot | |
Defined in Cardano.Ledger.Shelley.TxCert Methods encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy MIRPot -> Size encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [MIRPot] -> Size | |
NoThunks MIRPot | |
ToExpr MIRPot | |
Defined in Cardano.Ledger.Shelley.TxCert | |
ToJSON MIRPot Source # | |
Defined in Cardano.Api.Orphans | |
type Rep MIRPot | |
Defined in Cardano.Ledger.Shelley.TxCert |
Constructors
StakeAddressesMIR !(Map (Credential 'Staking c) DeltaCoin) | |
SendToOppositePotMIR !Coin |
Instances
Constructors
MIRCert | |
Fields
|
Instances
data StakePoolRelay #
Constructors
SingleHostAddr !(StrictMaybe Port) !(StrictMaybe IPv4) !(StrictMaybe IPv6) | |
SingleHostName !(StrictMaybe Port) !DnsName | |
MultiHostName !DnsName |
Instances
data PoolMetadata #
Constructors
PoolMetadata | |
Instances
class (Era era, DecCBOR (TxCert era), EncCBOR (TxCert era), ToCBOR (TxCert era), FromCBOR (TxCert era), NoThunks (TxCert era), NFData (TxCert era), Show (TxCert era), Eq (TxCert era), ToExpr (TxCert era)) => EraTxCert era where #
Associated Types
type TxCert era = (r :: Type) | r -> era #
type TxCertUpgradeError era #
type TxCertUpgradeError era = Void
Methods
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 #
data StrictMaybe a #
Instances
Monad StrictMaybe | |
Defined in Data.Maybe.Strict Methods (>>=) :: StrictMaybe a -> (a -> StrictMaybe b) -> StrictMaybe b Source # (>>) :: StrictMaybe a -> StrictMaybe b -> StrictMaybe b Source # return :: a -> StrictMaybe a Source # | |
Functor StrictMaybe | |
Defined in Data.Maybe.Strict Methods fmap :: (a -> b) -> StrictMaybe a -> StrictMaybe b Source # (<$) :: a -> StrictMaybe b -> StrictMaybe a Source # | |
MonadFail StrictMaybe | |
Defined in Data.Maybe.Strict Methods fail :: String -> StrictMaybe a Source # | |
Applicative StrictMaybe | |
Defined in Data.Maybe.Strict Methods pure :: a -> StrictMaybe a Source # (<*>) :: StrictMaybe (a -> b) -> StrictMaybe a -> StrictMaybe b Source # liftA2 :: (a -> b -> c) -> StrictMaybe a -> StrictMaybe b -> StrictMaybe c Source # (*>) :: StrictMaybe a -> StrictMaybe b -> StrictMaybe b Source # (<*) :: StrictMaybe a -> StrictMaybe b -> StrictMaybe a Source # | |
Foldable StrictMaybe | |
Defined in Data.Maybe.Strict Methods fold :: Monoid m => StrictMaybe m -> m Source # foldMap :: Monoid m => (a -> m) -> StrictMaybe a -> m Source # foldMap' :: Monoid m => (a -> m) -> StrictMaybe a -> m Source # foldr :: (a -> b -> b) -> b -> StrictMaybe a -> b Source # foldr' :: (a -> b -> b) -> b -> StrictMaybe a -> b Source # foldl :: (b -> a -> b) -> b -> StrictMaybe a -> b Source # foldl' :: (b -> a -> b) -> b -> StrictMaybe a -> b Source # foldr1 :: (a -> a -> a) -> StrictMaybe a -> a Source # foldl1 :: (a -> a -> a) -> StrictMaybe a -> a Source # toList :: StrictMaybe a -> [a] Source # null :: StrictMaybe a -> Bool Source # length :: StrictMaybe a -> Int Source # elem :: Eq a => a -> StrictMaybe a -> Bool Source # maximum :: Ord a => StrictMaybe a -> a Source # minimum :: Ord a => StrictMaybe a -> a Source # sum :: Num a => StrictMaybe a -> a Source # product :: Num a => StrictMaybe a -> a Source # | |
Traversable StrictMaybe | |
Defined in Data.Maybe.Strict Methods traverse :: Applicative f => (a -> f b) -> StrictMaybe a -> f (StrictMaybe b) Source # sequenceA :: Applicative f => StrictMaybe (f a) -> f (StrictMaybe a) Source # mapM :: Monad m => (a -> m b) -> StrictMaybe a -> m (StrictMaybe b) Source # sequence :: Monad m => StrictMaybe (m a) -> m (StrictMaybe a) Source # | |
Alternative StrictMaybe | |
Defined in Data.Maybe.Strict Methods empty :: StrictMaybe a Source # (<|>) :: StrictMaybe a -> StrictMaybe a -> StrictMaybe a Source # some :: StrictMaybe a -> StrictMaybe [a] Source # many :: StrictMaybe a -> StrictMaybe [a] Source # | |
HKDFunctor StrictMaybe | |
Defined in Cardano.Ledger.HKD Methods hkdMap :: proxy StrictMaybe -> (a -> b) -> HKD StrictMaybe a -> HKD StrictMaybe b toNoUpdate :: HKD StrictMaybe a -> HKDNoUpdate StrictMaybe a fromNoUpdate :: HKDNoUpdate StrictMaybe a -> HKD StrictMaybe a | |
Eq a => Eq (StrictMaybe a) | |
Defined in Data.Maybe.Strict Methods (==) :: StrictMaybe a -> StrictMaybe a -> Bool Source # (/=) :: StrictMaybe a -> StrictMaybe a -> Bool Source # | |
Eq (UpgradeConwayPParams StrictMaybe) | |
Defined in Cardano.Ledger.Conway.PParams Methods (==) :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> Bool Source # (/=) :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> Bool Source # | |
Ord a => Ord (StrictMaybe a) | |
Defined in Data.Maybe.Strict Methods compare :: StrictMaybe a -> StrictMaybe a -> Ordering Source # (<) :: StrictMaybe a -> StrictMaybe a -> Bool Source # (<=) :: StrictMaybe a -> StrictMaybe a -> Bool Source # (>) :: StrictMaybe a -> StrictMaybe a -> Bool Source # (>=) :: StrictMaybe a -> StrictMaybe a -> Bool Source # max :: StrictMaybe a -> StrictMaybe a -> StrictMaybe a Source # min :: StrictMaybe a -> StrictMaybe a -> StrictMaybe a Source # | |
Ord (UpgradeConwayPParams StrictMaybe) | |
Defined in Cardano.Ledger.Conway.PParams Methods compare :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> Ordering Source # (<) :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> Bool Source # (<=) :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> Bool Source # (>) :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> Bool Source # (>=) :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> Bool Source # max :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe Source # min :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe Source # | |
Show a => Show (StrictMaybe a) | |
Defined in Data.Maybe.Strict | |
Show (UpgradeConwayPParams StrictMaybe) | |
Defined in Cardano.Ledger.Conway.PParams | |
Generic (StrictMaybe a) | |
Defined in Data.Maybe.Strict Methods from :: StrictMaybe a -> Rep (StrictMaybe a) x Source # to :: Rep (StrictMaybe a) x -> StrictMaybe a Source # | |
Semigroup a => Semigroup (StrictMaybe a) | |
Defined in Data.Maybe.Strict Methods (<>) :: StrictMaybe a -> StrictMaybe a -> StrictMaybe a Source # sconcat :: NonEmpty (StrictMaybe a) -> StrictMaybe a Source # stimes :: Integral b => b -> StrictMaybe a -> StrictMaybe a Source # | |
Semigroup a => Monoid (StrictMaybe a) | |
Defined in Data.Maybe.Strict Methods mempty :: StrictMaybe a Source # mappend :: StrictMaybe a -> StrictMaybe a -> StrictMaybe a Source # mconcat :: [StrictMaybe a] -> StrictMaybe a Source # | |
NFData a => NFData (StrictMaybe a) | |
Defined in Data.Maybe.Strict Methods rnf :: StrictMaybe a -> () Source # | |
NFData (UpgradeConwayPParams StrictMaybe) | |
Defined in Cardano.Ledger.Conway.PParams Methods rnf :: UpgradeConwayPParams StrictMaybe -> () Source # | |
DecCBOR a => DecCBOR (StrictMaybe a) | |
Defined in Cardano.Ledger.Binary.Decoding.DecCBOR Methods decCBOR :: Decoder s (StrictMaybe a) dropCBOR :: Proxy (StrictMaybe a) -> Decoder s () label :: Proxy (StrictMaybe a) -> Text | |
Default (StrictMaybe t) | |
Defined in Data.Maybe.Strict Methods def :: StrictMaybe t | |
Default (UpgradeConwayPParams StrictMaybe) | |
Defined in Cardano.Ledger.Conway.PParams Methods def :: UpgradeConwayPParams StrictMaybe | |
Default (UpgradeAlonzoPParams StrictMaybe) | |
Defined in Cardano.Ledger.Alonzo.PParams Methods def :: UpgradeAlonzoPParams StrictMaybe | |
EncCBOR a => EncCBOR (StrictMaybe a) | |
Defined in Cardano.Ledger.Binary.Encoding.EncCBOR Methods encCBOR :: StrictMaybe a -> Encoding encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (StrictMaybe a) -> Size encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [StrictMaybe a] -> Size | |
FromCBOR a => FromCBOR (StrictMaybe a) | |
Defined in Data.Maybe.Strict | |
FromJSON a => FromJSON (StrictMaybe a) | |
Defined in Data.Maybe.Strict Methods parseJSON :: Value -> Parser (StrictMaybe a) # parseJSONList :: Value -> Parser [StrictMaybe a] # omittedField :: Maybe (StrictMaybe a) # | |
NoThunks a => NoThunks (StrictMaybe a) | |
Defined in Data.Maybe.Strict Methods noThunks :: Context -> StrictMaybe a -> IO (Maybe ThunkInfo) wNoThunks :: Context -> StrictMaybe a -> IO (Maybe ThunkInfo) showTypeOf :: Proxy (StrictMaybe a) -> String | |
NoThunks (UpgradeConwayPParams StrictMaybe) | |
Defined in Cardano.Ledger.Conway.PParams Methods noThunks :: Context -> UpgradeConwayPParams StrictMaybe -> IO (Maybe ThunkInfo) wNoThunks :: Context -> UpgradeConwayPParams StrictMaybe -> IO (Maybe ThunkInfo) showTypeOf :: Proxy (UpgradeConwayPParams StrictMaybe) -> String | |
ToCBOR a => ToCBOR (StrictMaybe a) | |
Defined in Data.Maybe.Strict Methods toCBOR :: StrictMaybe a -> Encoding # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (StrictMaybe a) -> Size # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [StrictMaybe a] -> Size # | |
ToJSON a => ToJSON (StrictMaybe a) | |
Defined in Data.Maybe.Strict Methods toJSON :: StrictMaybe a -> Value # toEncoding :: StrictMaybe a -> Encoding # toJSONList :: [StrictMaybe a] -> Value # toEncodingList :: [StrictMaybe a] -> Encoding # omitField :: StrictMaybe a -> Bool # | |
Eq (ShelleyPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Shelley.PParams Methods (==) :: ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era -> Bool Source # (/=) :: ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era -> Bool Source # | |
Eq (BabbagePParams StrictMaybe era) | |
Defined in Cardano.Ledger.Babbage.PParams Methods (==) :: BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era -> Bool Source # (/=) :: BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era -> Bool Source # | |
Eq (ConwayPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Conway.PParams Methods (==) :: ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era -> Bool Source # (/=) :: ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era -> Bool Source # | |
Eq (AlonzoPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Alonzo.PParams Methods (==) :: AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era -> Bool Source # (/=) :: AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era -> Bool Source # | |
Ord (ShelleyPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Shelley.PParams Methods compare :: ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era -> Ordering Source # (<) :: ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era -> Bool Source # (<=) :: ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era -> Bool Source # (>) :: ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era -> Bool Source # (>=) :: ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era -> Bool Source # max :: ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era Source # min :: ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era Source # | |
Ord (BabbagePParams StrictMaybe era) | |
Defined in Cardano.Ledger.Babbage.PParams Methods compare :: BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era -> Ordering Source # (<) :: BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era -> Bool Source # (<=) :: BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era -> Bool Source # (>) :: BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era -> Bool Source # (>=) :: BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era -> Bool Source # max :: BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era Source # min :: BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era Source # | |
Ord (ConwayPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Conway.PParams Methods compare :: ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era -> Ordering Source # (<) :: ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era -> Bool Source # (<=) :: ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era -> Bool Source # (>) :: ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era -> Bool Source # (>=) :: ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era -> Bool Source # max :: ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era Source # min :: ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era Source # | |
Ord (AlonzoPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Alonzo.PParams Methods compare :: AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era -> Ordering Source # (<) :: AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era -> Bool Source # (<=) :: AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era -> Bool Source # (>) :: AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era -> Bool Source # (>=) :: AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era -> Bool Source # max :: AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era Source # min :: AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era Source # | |
Show (ShelleyPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Shelley.PParams | |
Show (BabbagePParams StrictMaybe era) | |
Defined in Cardano.Ledger.Babbage.PParams | |
Show (ConwayPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Conway.PParams | |
Show (AlonzoPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Alonzo.PParams | |
Semigroup (ShelleyPParams StrictMaybe era) Source # | |
Defined in Cardano.Api.Orphans Methods (<>) :: ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era Source # sconcat :: NonEmpty (ShelleyPParams StrictMaybe era) -> ShelleyPParams StrictMaybe era Source # stimes :: Integral b => b -> ShelleyPParams StrictMaybe era -> ShelleyPParams StrictMaybe era Source # | |
Semigroup (BabbagePParams StrictMaybe era) Source # | |
Defined in Cardano.Api.Orphans Methods (<>) :: BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era Source # sconcat :: NonEmpty (BabbagePParams StrictMaybe era) -> BabbagePParams StrictMaybe era Source # stimes :: Integral b => b -> BabbagePParams StrictMaybe era -> BabbagePParams StrictMaybe era Source # | |
Semigroup (ConwayPParams StrictMaybe era) Source # | |
Defined in Cardano.Api.Orphans Methods (<>) :: ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era Source # sconcat :: NonEmpty (ConwayPParams StrictMaybe era) -> ConwayPParams StrictMaybe era Source # stimes :: Integral b => b -> ConwayPParams StrictMaybe era -> ConwayPParams StrictMaybe era Source # | |
Semigroup (AlonzoPParams StrictMaybe era) Source # | |
Defined in Cardano.Api.Orphans Methods (<>) :: AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era Source # sconcat :: NonEmpty (AlonzoPParams StrictMaybe era) -> AlonzoPParams StrictMaybe era Source # stimes :: Integral b => b -> AlonzoPParams StrictMaybe era -> AlonzoPParams StrictMaybe era Source # | |
NFData (ShelleyPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Shelley.PParams Methods rnf :: ShelleyPParams StrictMaybe era -> () Source # | |
NFData (BabbagePParams StrictMaybe era) | |
Defined in Cardano.Ledger.Babbage.PParams Methods rnf :: BabbagePParams StrictMaybe era -> () Source # | |
NFData (ConwayPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Conway.PParams Methods rnf :: ConwayPParams StrictMaybe era -> () Source # | |
NFData (AlonzoPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Alonzo.PParams Methods rnf :: AlonzoPParams StrictMaybe era -> () Source # | |
Era era => DecCBOR (ShelleyPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Shelley.PParams Methods decCBOR :: Decoder s (ShelleyPParams StrictMaybe era) dropCBOR :: Proxy (ShelleyPParams StrictMaybe era) -> Decoder s () label :: Proxy (ShelleyPParams StrictMaybe era) -> Text | |
Era era => DecCBOR (BabbagePParams StrictMaybe era) | |
Defined in Cardano.Ledger.Babbage.PParams Methods decCBOR :: Decoder s (BabbagePParams StrictMaybe era) dropCBOR :: Proxy (BabbagePParams StrictMaybe era) -> Decoder s () label :: Proxy (BabbagePParams StrictMaybe era) -> Text | |
Era era => DecCBOR (ConwayPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Conway.PParams Methods decCBOR :: Decoder s (ConwayPParams StrictMaybe era) dropCBOR :: Proxy (ConwayPParams StrictMaybe era) -> Decoder s () label :: Proxy (ConwayPParams StrictMaybe era) -> Text | |
Era era => DecCBOR (AlonzoPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Alonzo.PParams Methods decCBOR :: Decoder s (AlonzoPParams StrictMaybe era) dropCBOR :: Proxy (AlonzoPParams StrictMaybe era) -> Decoder s () label :: Proxy (AlonzoPParams StrictMaybe era) -> Text | |
Era era => EncCBOR (ShelleyPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Shelley.PParams Methods encCBOR :: ShelleyPParams StrictMaybe era -> Encoding encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (ShelleyPParams StrictMaybe era) -> Size encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ShelleyPParams StrictMaybe era] -> Size | |
Era era => EncCBOR (BabbagePParams StrictMaybe era) | |
Defined in Cardano.Ledger.Babbage.PParams Methods encCBOR :: BabbagePParams StrictMaybe era -> Encoding encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (BabbagePParams StrictMaybe era) -> Size encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [BabbagePParams StrictMaybe era] -> Size | |
Era era => EncCBOR (ConwayPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Conway.PParams Methods encCBOR :: ConwayPParams StrictMaybe era -> Encoding encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (ConwayPParams StrictMaybe era) -> Size encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ConwayPParams StrictMaybe era] -> Size | |
Era era => EncCBOR (AlonzoPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Alonzo.PParams Methods encCBOR :: AlonzoPParams StrictMaybe era -> Encoding encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (AlonzoPParams StrictMaybe era) -> Size encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [AlonzoPParams StrictMaybe era] -> Size | |
Era era => FromCBOR (ShelleyPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Shelley.PParams Methods fromCBOR :: Decoder s (ShelleyPParams StrictMaybe era) # label :: Proxy (ShelleyPParams StrictMaybe era) -> Text # | |
Era era => FromCBOR (BabbagePParams StrictMaybe era) | |
Defined in Cardano.Ledger.Babbage.PParams Methods fromCBOR :: Decoder s (BabbagePParams StrictMaybe era) # label :: Proxy (BabbagePParams StrictMaybe era) -> Text # | |
Era era => FromCBOR (ConwayPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Conway.PParams Methods fromCBOR :: Decoder s (ConwayPParams StrictMaybe era) # label :: Proxy (ConwayPParams StrictMaybe era) -> Text # | |
Era era => FromCBOR (AlonzoPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Alonzo.PParams Methods fromCBOR :: Decoder s (AlonzoPParams StrictMaybe era) # label :: Proxy (AlonzoPParams StrictMaybe era) -> Text # | |
NoThunks (ShelleyPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Shelley.PParams Methods noThunks :: Context -> ShelleyPParams StrictMaybe era -> IO (Maybe ThunkInfo) wNoThunks :: Context -> ShelleyPParams StrictMaybe era -> IO (Maybe ThunkInfo) showTypeOf :: Proxy (ShelleyPParams StrictMaybe era) -> String | |
NoThunks (BabbagePParams StrictMaybe era) | |
Defined in Cardano.Ledger.Babbage.PParams Methods noThunks :: Context -> BabbagePParams StrictMaybe era -> IO (Maybe ThunkInfo) wNoThunks :: Context -> BabbagePParams StrictMaybe era -> IO (Maybe ThunkInfo) showTypeOf :: Proxy (BabbagePParams StrictMaybe era) -> String | |
NoThunks (ConwayPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Conway.PParams Methods noThunks :: Context -> ConwayPParams StrictMaybe era -> IO (Maybe ThunkInfo) wNoThunks :: Context -> ConwayPParams StrictMaybe era -> IO (Maybe ThunkInfo) showTypeOf :: Proxy (ConwayPParams StrictMaybe era) -> String | |
NoThunks (AlonzoPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Alonzo.PParams Methods noThunks :: Context -> AlonzoPParams StrictMaybe era -> IO (Maybe ThunkInfo) wNoThunks :: Context -> AlonzoPParams StrictMaybe era -> IO (Maybe ThunkInfo) showTypeOf :: Proxy (AlonzoPParams StrictMaybe era) -> String | |
Era era => ToCBOR (ShelleyPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Shelley.PParams Methods toCBOR :: ShelleyPParams StrictMaybe era -> Encoding # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyPParams StrictMaybe era) -> Size # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ShelleyPParams StrictMaybe era] -> Size # | |
Era era => ToCBOR (BabbagePParams StrictMaybe era) | |
Defined in Cardano.Ledger.Babbage.PParams Methods toCBOR :: BabbagePParams StrictMaybe era -> Encoding # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (BabbagePParams StrictMaybe era) -> Size # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [BabbagePParams StrictMaybe era] -> Size # | |
Era era => ToCBOR (ConwayPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Conway.PParams Methods toCBOR :: ConwayPParams StrictMaybe era -> Encoding # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ConwayPParams StrictMaybe era) -> Size # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ConwayPParams StrictMaybe era] -> Size # | |
Era era => ToCBOR (AlonzoPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Alonzo.PParams Methods toCBOR :: AlonzoPParams StrictMaybe era -> Encoding # encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (AlonzoPParams StrictMaybe era) -> Size # encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [AlonzoPParams StrictMaybe era] -> Size # | |
ToExpr (ShelleyPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Shelley.PParams Methods toExpr :: ShelleyPParams StrictMaybe era -> Expr listToExpr :: [ShelleyPParams StrictMaybe era] -> Expr | |
ToExpr (BabbagePParams StrictMaybe era) | |
Defined in Cardano.Ledger.Babbage.PParams Methods toExpr :: BabbagePParams StrictMaybe era -> Expr listToExpr :: [BabbagePParams StrictMaybe era] -> Expr | |
ToExpr (ConwayPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Conway.PParams Methods toExpr :: ConwayPParams StrictMaybe era -> Expr listToExpr :: [ConwayPParams StrictMaybe era] -> Expr | |
ToExpr (AlonzoPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Alonzo.PParams Methods toExpr :: AlonzoPParams StrictMaybe era -> Expr listToExpr :: [AlonzoPParams StrictMaybe era] -> Expr | |
(EraPParams era, PParamsHKD StrictMaybe era ~ ShelleyPParams StrictMaybe era, ProtVerAtMost era 4, ProtVerAtMost era 6, ProtVerAtMost era 8) => ToJSON (ShelleyPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Shelley.PParams Methods toJSON :: ShelleyPParams StrictMaybe era -> Value # toEncoding :: ShelleyPParams StrictMaybe era -> Encoding # toJSONList :: [ShelleyPParams StrictMaybe era] -> Value # toEncodingList :: [ShelleyPParams StrictMaybe era] -> Encoding # omitField :: ShelleyPParams StrictMaybe era -> Bool # | |
(PParamsHKD StrictMaybe era ~ BabbagePParams StrictMaybe era, BabbageEraPParams era, ProtVerAtMost era 8) => ToJSON (BabbagePParams StrictMaybe era) | |
Defined in Cardano.Ledger.Babbage.PParams Methods toJSON :: BabbagePParams StrictMaybe era -> Value # toEncoding :: BabbagePParams StrictMaybe era -> Encoding # toJSONList :: [BabbagePParams StrictMaybe era] -> Value # toEncodingList :: [BabbagePParams StrictMaybe era] -> Encoding # omitField :: BabbagePParams StrictMaybe era -> Bool # | |
(ConwayEraPParams era, PParamsHKD StrictMaybe era ~ ConwayPParams StrictMaybe era) => ToJSON (ConwayPParams StrictMaybe era) | |
Defined in Cardano.Ledger.Conway.PParams Methods toJSON :: ConwayPParams StrictMaybe era -> Value # toEncoding :: ConwayPParams StrictMaybe era -> Encoding # toJSONList :: [ConwayPParams StrictMaybe era] -> Value # toEncodingList :: [ConwayPParams StrictMaybe era] -> Encoding # omitField :: ConwayPParams StrictMaybe era -> Bool # | |
Crypto c => ToJSON (AlonzoPParams StrictMaybe (AlonzoEra c)) | |
Defined in Cardano.Ledger.Alonzo.PParams Methods 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 # | |
(Typeable t, DecCBOR a) => DecCBOR (THKD t StrictMaybe a) | |
Defined in Cardano.Ledger.Conway.PParams Methods decCBOR :: Decoder s (THKD t StrictMaybe a) dropCBOR :: Proxy (THKD t StrictMaybe a) -> Decoder s () label :: Proxy (THKD t StrictMaybe a) -> Text | |
(Typeable t, EncCBOR a) => EncCBOR (THKD t StrictMaybe a) | |
Defined in Cardano.Ledger.Conway.PParams Methods encCBOR :: THKD t StrictMaybe a -> Encoding encodedSizeExpr :: (forall t0. EncCBOR t0 => Proxy t0 -> Size) -> Proxy (THKD t StrictMaybe a) -> Size encodedListSizeExpr :: (forall t0. EncCBOR t0 => Proxy t0 -> Size) -> Proxy [THKD t StrictMaybe a] -> Size | |
Updatable (K1 t x a) (K1 t (StrictMaybe x) u) | |
Defined in Cardano.Ledger.Core.PParams Methods applyUpdate :: K1 t x a -> K1 t (StrictMaybe x) u -> K1 t x a | |
type Rep (StrictMaybe a) | |
Defined in Data.Maybe.Strict type Rep (StrictMaybe a) = D1 ('MetaData "StrictMaybe" "Data.Maybe.Strict" "cardano-strict-containers-0.1.2.1-IcZG1bbwutmGVa0TCbpHKO" 'False) (C1 ('MetaCons "SNothing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SJust" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a))) |
pattern DelegTxCert :: ConwayEraTxCert era => StakeCredential (EraCrypto era) -> Delegatee (EraCrypto era) -> TxCert era #
pattern RegPoolTxCert :: EraTxCert era => PoolParams (EraCrypto era) -> TxCert era #
pattern RetirePoolTxCert :: EraTxCert era => KeyHash 'StakePool (EraCrypto era) -> EpochNo -> TxCert era #
pattern RegDepositTxCert :: ConwayEraTxCert era => StakeCredential (EraCrypto era) -> Coin -> TxCert era #
pattern UnRegDepositTxCert :: ConwayEraTxCert era => StakeCredential (EraCrypto era) -> Coin -> TxCert era #
pattern UnRegDRepTxCert :: ConwayEraTxCert era => Credential 'DRepRole (EraCrypto era) -> Coin -> TxCert era #
pattern AuthCommitteeHotKeyTxCert :: ConwayEraTxCert era => Credential 'ColdCommitteeRole (EraCrypto era) -> Credential 'HotCommitteeRole (EraCrypto era) -> TxCert era #
pattern ResignCommitteeColdTxCert :: ConwayEraTxCert era => Credential 'ColdCommitteeRole (EraCrypto era) -> StrictMaybe (Anchor (EraCrypto era)) -> TxCert era #
pattern RegTxCert :: ShelleyEraTxCert era => StakeCredential (EraCrypto era) -> TxCert era #
pattern UnRegTxCert :: ShelleyEraTxCert era => StakeCredential (EraCrypto era) -> TxCert era #
pattern DelegStakeTxCert :: ShelleyEraTxCert era => StakeCredential (EraCrypto era) -> KeyHash 'StakePool (EraCrypto era) -> TxCert era #
pattern RegDepositDelegTxCert :: ConwayEraTxCert era => StakeCredential (EraCrypto era) -> Delegatee (EraCrypto era) -> Coin -> TxCert era #
pattern RegDRepTxCert :: ConwayEraTxCert era => Credential 'DRepRole (EraCrypto era) -> Coin -> StrictMaybe (Anchor (EraCrypto era)) -> TxCert era #
pattern MirTxCert :: (ShelleyEraTxCert era, ProtVerAtMost era 8) => MIRCert (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 UpdateDRepTxCert :: ConwayEraTxCert era => Credential 'DRepRole (EraCrypto era) -> StrictMaybe (Anchor (EraCrypto era)) -> TxCert era #
Instances
Enum Coin | |
Eq Coin | |
Ord Coin | |
Defined in Cardano.Ledger.Coin | |
Show Coin | |
Generic Coin | |
Semigroup Coin | |
Monoid Coin | |
NFData Coin | |
Defined in Cardano.Ledger.Coin | |
DecCBOR Coin | |
EncCBOR Coin | |
Defined in Cardano.Ledger.Coin Methods encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Coin -> Size encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Coin] -> Size | |
FromCBOR Coin | |
FromJSON Coin | |
Defined in Cardano.Ledger.Coin Methods parseJSON :: Value -> Parser Coin # parseJSONList :: Value -> Parser [Coin] # omittedField :: Maybe Coin # | |
NoThunks Coin | |
ToCBOR Coin | |
ToExpr Coin | |
Defined in Cardano.Ledger.Coin | |
ToJSON Coin | |
Defined in Cardano.Ledger.Coin | |
HeapWords Coin | |
Defined in Cardano.Ledger.Coin | |
Abelian Coin | |
Defined in Cardano.Ledger.Coin | |
Compactible Coin | |
Defined in Cardano.Ledger.Coin Associated Types data CompactForm Coin | |
Group Coin | |
PartialOrd Coin | |
Val Coin | |
Defined in Cardano.Ledger.Val Methods (<×>) :: Integral i => i -> Coin -> Coin modifyCoin :: (Coin -> Coin) -> Coin -> Coin pointwise :: (Integer -> Integer -> Bool) -> Coin -> Coin -> Bool isAdaOnlyCompact :: CompactForm Coin -> Bool coinCompact :: CompactForm Coin -> CompactForm Coin injectCompact :: CompactForm Coin -> CompactForm Coin modifyCompactCoin :: (CompactForm Coin -> CompactForm Coin) -> CompactForm Coin -> CompactForm Coin | |
Eq (CompactForm Coin) | |
Ord (CompactForm Coin) | |
Defined in Cardano.Ledger.Coin Methods compare :: CompactForm Coin -> CompactForm Coin -> Ordering Source # (<) :: CompactForm Coin -> CompactForm Coin -> Bool Source # (<=) :: CompactForm Coin -> CompactForm Coin -> Bool Source # (>) :: CompactForm Coin -> CompactForm Coin -> Bool Source # (>=) :: CompactForm Coin -> CompactForm Coin -> Bool Source # max :: CompactForm Coin -> CompactForm Coin -> CompactForm Coin Source # min :: CompactForm Coin -> CompactForm Coin -> CompactForm Coin Source # | |
Show (CompactForm Coin) | |
Semigroup (CompactForm Coin) | |
Monoid (CompactForm Coin) | |
NFData (CompactForm Coin) | |
Defined in Cardano.Ledger.Coin | |
DecCBOR (CompactForm Coin) | |
EncCBOR (CompactForm Coin) | |
Defined in Cardano.Ledger.Coin Methods encCBOR :: CompactForm Coin -> Encoding encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (CompactForm Coin) -> Size encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [CompactForm Coin] -> Size | |
FromJSON (CompactForm Coin) | |
Defined in Cardano.Ledger.Coin Methods parseJSON :: Value -> Parser (CompactForm Coin) # parseJSONList :: Value -> Parser [CompactForm Coin] # omittedField :: Maybe (CompactForm Coin) # | |
NoThunks (CompactForm Coin) | |
ToCBOR (CompactForm Coin) | |
ToExpr (CompactForm Coin) | |
Defined in Cardano.Ledger.Coin | |
ToJSON (CompactForm Coin) | |
Defined in Cardano.Ledger.Coin | |
HeapWords (CompactForm Coin) | |
Defined in Cardano.Ledger.Coin | |
Prim (CompactForm Coin) | |
Defined in Cardano.Ledger.Coin Methods sizeOf# :: 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 | |
Abelian (CompactForm Coin) | |
Defined in Cardano.Ledger.Coin | |
Group (CompactForm Coin) | |
type Rep Coin | |
Defined in Cardano.Ledger.Coin | |
newtype CompactForm Coin | |
Defined in Cardano.Ledger.Coin |
Instances
type EraCrypto (ByronEra c) | |
Defined in Cardano.Ledger.Core.Era type EraCrypto (ByronEra c) = c | |
type EraCrypto (AlonzoEra c) | |
Defined in Cardano.Ledger.Alonzo.Era type EraCrypto (AlonzoEra c) = c | |
type EraCrypto (MaryEra c) | |
Defined in Cardano.Ledger.Mary.Era type EraCrypto (MaryEra c) = c | |
type EraCrypto (ConwayEra c) | |
Defined in Cardano.Ledger.Conway.Era type EraCrypto (ConwayEra c) = c | |
type EraCrypto (ShelleyEra c) | |
Defined in Cardano.Ledger.Shelley.Era type EraCrypto (ShelleyEra c) = c | |
type EraCrypto (BabbageEra c) | |
Defined in Cardano.Ledger.Babbage.Era type EraCrypto (BabbageEra c) = c | |
type EraCrypto (AllegraEra c) | |
Defined in Cardano.Ledger.Allegra.Era type EraCrypto (AllegraEra c) = c |
Instances
Constructors
RegPool !(PoolParams c) | |
RetirePool !(KeyHash 'StakePool c) !EpochNo |
Instances
Instances
Eq (PParamsHKD Identity era) => Eq (PParams era) | |
Ord (PParamsHKD Identity era) => Ord (PParams era) | |
Defined in Cardano.Ledger.Core.PParams Methods compare :: PParams era -> PParams era -> Ordering Source # (<) :: PParams era -> PParams era -> Bool Source # (<=) :: PParams era -> PParams era -> Bool Source # (>) :: PParams era -> PParams era -> Bool Source # (>=) :: PParams era -> PParams era -> Bool Source # | |
Show (PParamsHKD Identity era) => Show (PParams era) | |
Generic (PParams era) | |
NFData (PParamsHKD Identity era) => NFData (PParams era) | |
Defined in Cardano.Ledger.Core.PParams | |
(Typeable era, DecCBOR (PParamsHKD Identity era)) => DecCBOR (PParams era) | |
EraPParams era => Default (PParams era) | |
Defined in Cardano.Ledger.Core.PParams | |
(Typeable era, EncCBOR (PParamsHKD Identity era)) => EncCBOR (PParams era) | |
Defined in Cardano.Ledger.Core.PParams Methods encCBOR :: PParams era -> Encoding encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (PParams era) -> Size encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [PParams era] -> Size | |
(Typeable era, FromCBOR (PParamsHKD Identity era)) => FromCBOR (PParams era) | |
FromJSON (PParamsHKD Identity era) => FromJSON (PParams era) | |
Defined in Cardano.Ledger.Core.PParams Methods parseJSON :: Value -> Parser (PParams era) # parseJSONList :: Value -> Parser [PParams era] # omittedField :: Maybe (PParams era) # | |
NoThunks (PParamsHKD Identity era) => NoThunks (PParams era) | |
(Typeable era, ToCBOR (PParamsHKD Identity era)) => ToCBOR (PParams era) | |
ToExpr (PParamsHKD Identity era) => ToExpr (PParams era) | |
Defined in Cardano.Ledger.Core.PParams | |
ToJSON (PParamsHKD Identity era) => ToJSON (PParams era) | |
Defined in Cardano.Ledger.Core.PParams | |
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.9.0.0-E3793VXyLODIfmloH8Sp2j" 'True) (C1 ('MetaCons "PParams" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PParamsHKD Identity era)))) | |
type TranslationError (AlonzoEra c) PParams | |
Defined in Cardano.Ledger.Alonzo.Translation | |
type TranslationError (MaryEra c) PParams | |
Defined in Cardano.Ledger.Mary.Translation | |
type TranslationError (ConwayEra c) PParams | |
Defined in Cardano.Ledger.Conway.Translation | |
type TranslationError (BabbageEra c) PParams | |
Defined in Cardano.Ledger.Babbage.Translation | |
type TranslationError (AllegraEra c) PParams | |
Defined in Cardano.Ledger.Allegra.Translation |
data PParamsUpdate era #
Instances
Instances
type Value (AlonzoEra c) | |
Defined in Cardano.Ledger.Alonzo.Era type Value (AlonzoEra c) = MaryValue c | |
type Value (MaryEra c) | |
Defined in Cardano.Ledger.Mary.Era type Value (MaryEra c) = MaryValue c | |
type Value (ConwayEra c) | |
Defined in Cardano.Ledger.Conway.Era type Value (ConwayEra c) = MaryValue c | |
type Value (ShelleyEra _c) | |
Defined in Cardano.Ledger.Shelley.Era | |
type Value (BabbageEra c) | |
Defined in Cardano.Ledger.Babbage.Era type Value (BabbageEra c) = MaryValue c | |
type Value (AllegraEra _1) | |
Defined in Cardano.Ledger.Allegra.Era |
addDeltaCoin :: Coin -> DeltaCoin -> Coin #
toDeltaCoin :: Coin -> DeltaCoin #
fromEraCBOR :: (Era era, DecCBOR t) => Decoder s t #
Constructors
Anchor | |
Fields
|
Instances
Eq (Anchor c) | |
Ord (Anchor c) | |
Defined in Cardano.Ledger.BaseTypes | |
Show (Anchor c) | |
Generic (Anchor c) | |
Crypto c => NFData (Anchor c) | |
Defined in Cardano.Ledger.BaseTypes | |
Crypto c => DecCBOR (Anchor c) | |
Crypto c => Default (Anchor c) | |
Defined in Cardano.Ledger.BaseTypes | |
Crypto c => EncCBOR (Anchor c) | |
Defined in Cardano.Ledger.BaseTypes Methods encCBOR :: Anchor c -> Encoding encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (Anchor c) -> Size encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Anchor c] -> Size | |
Crypto c => FromJSON (Anchor c) | |
Defined in Cardano.Ledger.BaseTypes Methods parseJSON :: Value -> Parser (Anchor c) # parseJSONList :: Value -> Parser [Anchor c] # omittedField :: Maybe (Anchor c) # | |
NoThunks (Anchor c) | |
ToExpr (Anchor c) | |
Defined in Cardano.Ledger.BaseTypes | |
Crypto c => ToJSON (Anchor c) | |
Defined in Cardano.Ledger.BaseTypes | |
type Rep (Anchor c) | |
Defined in Cardano.Ledger.BaseTypes type Rep (Anchor c) = D1 ('MetaData "Anchor" "Cardano.Ledger.BaseTypes" "cardano-ledger-core-1.9.0.0-E3793VXyLODIfmloH8Sp2j" '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)))) |
Constructors
DelegStake !(KeyHash 'StakePool c) | |
DelegVote !(DRep c) | |
DelegStakeVote !(KeyHash 'StakePool c) !(DRep c) |
Instances
Constructors
DRepAlwaysAbstain | |
DRepAlwaysNoConfidence |
Bundled Patterns
pattern DRepCredential :: Credential 'DRepRole c -> DRep c |
Instances
Eq (DRep c) | |
Ord (DRep c) | |
Show (DRep c) | |
Generic (DRep c) | |
NFData (DRep c) | |
Defined in Cardano.Ledger.DRep | |
Crypto c => DecCBOR (DRep c) | |
Crypto c => EncCBOR (DRep c) | |
Defined in Cardano.Ledger.DRep Methods encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (DRep c) -> Size encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [DRep c] -> Size | |
Crypto c => FromJSON (DRep c) | |
Defined in Cardano.Ledger.DRep Methods parseJSON :: Value -> Parser (DRep c) # parseJSONList :: Value -> Parser [DRep c] # omittedField :: Maybe (DRep c) # | |
NoThunks (DRep c) | |
ToExpr (DRep c) | |
Defined in Cardano.Ledger.DRep | |
Crypto c => ToJSON (DRep c) | |
Defined in Cardano.Ledger.DRep | |
Crypto c => ToJSONKey (DRep c) | |
Defined in Cardano.Ledger.DRep | |
Crypto c => FromJSONKey (DRep c) | |
Defined in Cardano.Ledger.DRep | |
type Rep (DRep c) | |
Defined in Cardano.Ledger.DRep type Rep (DRep c) = D1 ('MetaData "DRep" "Cardano.Ledger.DRep" "cardano-ledger-core-1.9.0.0-E3793VXyLODIfmloH8Sp2j" '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))) |
Instances
data ConwayTxCert era #
Constructors
ConwayTxCertDeleg !(ConwayDelegCert (EraCrypto era)) | |
ConwayTxCertPool !(PoolCert (EraCrypto era)) | |
ConwayTxCertGov !(ConwayGovCert (EraCrypto era)) |
Instances
data ConwayDelegCert c #
Constructors
ConwayRegCert !(StakeCredential c) !(StrictMaybe Coin) | |
ConwayUnRegCert !(StakeCredential c) !(StrictMaybe Coin) | |
ConwayDelegCert !(StakeCredential c) !(Delegatee c) | |
ConwayRegDelegCert !(StakeCredential c) !(Delegatee c) !Coin |
Instances
class ShelleyEraTxCert era => ConwayEraTxCert era where #
Methods
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))) #
Instances
data ConwayGovCert c #
Constructors
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
type family GovState era = (r :: Type) | r -> era #
Instances
type GovState (AlonzoEra c) | |
Defined in Cardano.Ledger.Alonzo.PParams type GovState (AlonzoEra c) = ShelleyGovState (AlonzoEra c) | |
type GovState (MaryEra c) | |
Defined in Cardano.Ledger.Mary.PParams type GovState (MaryEra c) = ShelleyGovState (MaryEra c) | |
type GovState (ConwayEra c) | |
Defined in Cardano.Ledger.Conway.Governance type GovState (ConwayEra c) = ConwayGovState (ConwayEra c) | |
type GovState (ShelleyEra c) | |
Defined in Cardano.Ledger.Shelley.Governance type GovState (ShelleyEra c) = ShelleyGovState (ShelleyEra c) | |
type GovState (BabbageEra c) | |
Defined in Cardano.Ledger.Babbage.PParams type GovState (BabbageEra c) = ShelleyGovState (BabbageEra c) | |
type GovState (AllegraEra c) | |
Defined in Cardano.Ledger.Allegra.PParams type GovState (AllegraEra c) = ShelleyGovState (AllegraEra c) |
data GovActionId c #
Constructors
GovActionId | |
Fields
|
Instances
Instances
Bounded Vote | |
Enum Vote | |
Eq Vote | |
Show Vote | |
Generic Vote | |
NFData Vote | |
Defined in Cardano.Ledger.Conway.Governance.Procedures | |
DecCBOR Vote | |
EncCBOR Vote | |
Defined in Cardano.Ledger.Conway.Governance.Procedures Methods encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Vote -> Size encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Vote] -> Size | |
NoThunks Vote | |
ToExpr Vote | |
Defined in Cardano.Ledger.Conway.Governance.Procedures | |
ToJSON Vote | |
Defined in Cardano.Ledger.Conway.Governance.Procedures | |
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.11.0.0-IXkLH2MRV78Js391X7GYkZ" '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))) |
Constructors
CommitteeVoter !(Credential 'HotCommitteeRole c) | |
DRepVoter !(Credential 'DRepRole c) | |
StakePoolVoter !(KeyHash 'StakePool c) |
Instances
data VotingProcedure era #
Constructors
VotingProcedure | |
Fields
|
Instances
data PoolVotingThresholds #
Constructors
PoolVotingThresholds | |
Fields
|
Instances
data DRepVotingThresholds #
Constructors
DRepVotingThresholds | |
Fields
|
Instances
dvtPPNetworkGroupL :: Lens' DRepVotingThresholds UnitInterval #
dvtPPGovGroupL :: Lens' DRepVotingThresholds UnitInterval #
dvtPPTechnicalGroupL :: Lens' DRepVotingThresholds UnitInterval #
dvtPPEconomicGroupL :: Lens' DRepVotingThresholds UnitInterval #
dvtUpdateToConstitutionL :: Lens' DRepVotingThresholds UnitInterval #
drepExpiryL :: Lens' (DRepState c) EpochNo #
drepAnchorL :: Lens' (DRepState c) (StrictMaybe (Anchor c)) #
drepDepositL :: Lens' (DRepState c) Coin #
csCommitteeCredsL :: Lens' (CommitteeState era) (Map (Credential 'ColdCommitteeRole (EraCrypto era)) (Maybe (Credential 'HotCommitteeRole (EraCrypto era)))) #
Instances
Constructors
UnsafeTx | |
Fields
|
Instances
Eq Tx | |
Ord Tx | |
Show Tx | |
Generic Tx | |
NFData Tx | |
Defined in Cardano.Chain.UTxO.Tx | |
DecCBOR Tx | |
EncCBOR Tx | |
Defined in Cardano.Chain.UTxO.Tx Methods encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Tx -> Size encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Tx] -> Size | |
FromCBOR Tx | |
ToCBOR Tx | |
ToJSON Tx | |
Defined in Cardano.Chain.UTxO.Tx | |
Buildable Tx | |
Defined in Cardano.Chain.UTxO.Tx | |
type Rep Tx | |
Defined in Cardano.Chain.UTxO.Tx type Rep Tx = D1 ('MetaData "Tx" "Cardano.Chain.UTxO.Tx" "cardano-ledger-byron-1.0.0.3-7XPhaeqCEJ61p5A3PpSRBs" 'False) (C1 ('MetaCons "UnsafeTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "txInputs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty TxIn)) :*: (S1 ('MetaSel ('Just "txOutputs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NonEmpty TxOut)) :*: S1 ('MetaSel ('Just "txAttributes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxAttributes)))) |
newtype CoinPerByte #
Constructors
CoinPerByte | |
Fields |
Instances
newtype CoinPerWord #
Constructors
CoinPerWord | |
Fields |
Instances
Instances
boundRational :: BoundedRational r => Rational -> Maybe r #
unboundRational :: BoundedRational r => r -> Rational #
Instances
Eq DnsName | |
Ord DnsName | |
Defined in Cardano.Ledger.BaseTypes | |
Show DnsName | |
Generic DnsName | |
NFData DnsName | |
Defined in Cardano.Ledger.BaseTypes | |
DecCBOR DnsName | |
EncCBOR DnsName | |
Defined in Cardano.Ledger.BaseTypes Methods encCBOR :: DnsName -> Encoding encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy DnsName -> Size encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [DnsName] -> Size | |
FromJSON DnsName | |
Defined in Cardano.Ledger.BaseTypes | |
NoThunks DnsName | |
ToExpr DnsName | |
Defined in Cardano.Ledger.BaseTypes | |
ToJSON DnsName | |
Defined in Cardano.Ledger.BaseTypes | |
type Rep DnsName | |
Defined in Cardano.Ledger.BaseTypes |
Instances
Eq Url | |
Ord Url | |
Show Url | |
Generic Url | |
NFData Url | |
Defined in Cardano.Ledger.BaseTypes | |
DecCBOR Url | |
EncCBOR Url | |
Defined in Cardano.Ledger.BaseTypes Methods encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Url -> Size encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Url] -> Size | |
FromJSON Url | |
Defined in Cardano.Ledger.BaseTypes Methods parseJSON :: Value -> Parser Url # parseJSONList :: Value -> Parser [Url] # omittedField :: Maybe Url # | |
NoThunks Url | |
ToExpr Url | |
Defined in Cardano.Ledger.BaseTypes | |
ToJSON Url | |
Defined in Cardano.Ledger.BaseTypes | |
type Rep Url | |
Defined in Cardano.Ledger.BaseTypes |
portToWord16 :: Port -> Word16 #
strictMaybeToMaybe :: StrictMaybe a -> Maybe a #
maybeToStrictMaybe :: Maybe a -> StrictMaybe a #
hashToBytes :: Hash h a -> ByteString #
hashFromBytes :: HashAlgorithm h => ByteString -> Maybe (Hash h a) #
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 #
Instances
Crypto StandardCrypto | |
Defined in Cardano.Ledger.Crypto Associated Types type HASH StandardCrypto type ADDRHASH StandardCrypto type DSIGN StandardCrypto type KES StandardCrypto type VRF StandardCrypto |
data StandardCrypto #