cardano-api-8.36.1.1: The cardano api
Safe HaskellNone
LanguageHaskell2010

Cardano.Api.ReexposeLedger

Documentation

data Credential (kr :: KeyRole) c #

Constructors

ScriptHashObj !(ScriptHash c) 
KeyHashObj !(KeyHash kr c) 

Instances

Instances details
HasKeyRole Credential 
Instance details

Defined in Cardano.Ledger.Credential

Methods

coerceKeyRole :: forall (r :: KeyRole) c (r' :: KeyRole). Credential r c -> Credential r' c

Eq (Credential kr c) 
Instance details

Defined in Cardano.Ledger.Credential

Methods

(==) :: Credential kr c -> Credential kr c -> Bool Source #

(/=) :: Credential kr c -> Credential kr c -> Bool Source #

Ord (Credential kr c) 
Instance details

Defined in Cardano.Ledger.Credential

Methods

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 #

Show (Credential kr c) 
Instance details

Defined in Cardano.Ledger.Credential

Generic (Credential kr c) 
Instance details

Defined in Cardano.Ledger.Credential

Associated Types

type Rep (Credential kr c) :: Type -> Type Source #

Methods

from :: Credential kr c -> Rep (Credential kr c) x Source #

to :: Rep (Credential kr c) x -> Credential kr c Source #

NFData (Credential kr c) 
Instance details

Defined in Cardano.Ledger.Credential

Methods

rnf :: Credential kr c -> () Source #

(Typeable kr, Crypto c) => DecCBOR (Credential kr c) 
Instance details

Defined in Cardano.Ledger.Credential

Methods

decCBOR :: Decoder s (Credential kr c)

dropCBOR :: Proxy (Credential kr c) -> Decoder s ()

label :: Proxy (Credential kr c) -> Text

Crypto e => Default (Credential r e) 
Instance details

Defined in Cardano.Ledger.Credential

Methods

def :: Credential r e

(Typeable kr, Crypto c) => EncCBOR (Credential kr c) 
Instance details

Defined in Cardano.Ledger.Credential

Methods

encCBOR :: Credential kr c -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (Credential kr c) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Credential kr c] -> Size

(Typeable kr, Crypto c) => FromCBOR (Credential kr c) 
Instance details

Defined in Cardano.Ledger.Credential

Methods

fromCBOR :: Decoder s (Credential kr c) #

label :: Proxy (Credential kr c) -> Text #

Crypto c => FromJSON (Credential kr c) 
Instance details

Defined in Cardano.Ledger.Credential

Methods

parseJSON :: Value -> Parser (Credential kr c) #

parseJSONList :: Value -> Parser [Credential kr c] #

omittedField :: Maybe (Credential kr c) #

NoThunks (Credential kr c) 
Instance details

Defined in Cardano.Ledger.Credential

Methods

noThunks :: Context -> Credential kr c -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Credential kr c -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (Credential kr c) -> String

(Typeable kr, Crypto c) => ToCBOR (Credential kr c) 
Instance details

Defined in Cardano.Ledger.Credential

Methods

toCBOR :: Credential kr c -> Encoding #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Credential kr c) -> Size #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Credential kr c] -> Size #

ToExpr (Credential keyrole c) 
Instance details

Defined in Cardano.Ledger.Credential

Methods

toExpr :: Credential keyrole c -> Expr

listToExpr :: [Credential keyrole c] -> Expr

Crypto c => ToJSON (Credential kr c) 
Instance details

Defined in Cardano.Ledger.Credential

Methods

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) 
Instance details

Defined in Cardano.Ledger.Credential

Methods

toJSONKey :: ToJSONKeyFunction (Credential kr c)

toJSONKeyList :: ToJSONKeyFunction [Credential kr c]

Crypto c => FromJSONKey (Credential kr c) 
Instance details

Defined in Cardano.Ledger.Credential

Methods

fromJSONKey :: FromJSONKeyFunction (Credential kr c)

fromJSONKeyList :: FromJSONKeyFunction [Credential kr c]

type Rep (Credential kr c) 
Instance details

Defined in Cardano.Ledger.Credential

type Rep (Credential kr c) = D1 ('MetaData "Credential" "Cardano.Ledger.Credential" "cardano-ledger-core-1.9.0.0-E3793VXyLODIfmloH8Sp2j" '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))))

newtype KeyHash (discriminator :: KeyRole) c #

Constructors

KeyHash (Hash (ADDRHASH c) (VerKeyDSIGN (DSIGN c))) 

Instances

Instances details
HasKeyRole KeyHash 
Instance details

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)) 
Instance details

Defined in Cardano.Ledger.PoolDistr

Methods

toBase :: PoolDistr c -> Map (KeyHash 'StakePool c) (IndividualPoolStake c)

fromBase :: Map (KeyHash 'StakePool c) (IndividualPoolStake c) -> PoolDistr c

HasExp (PoolDistr c) (Map (KeyHash 'StakePool c) (IndividualPoolStake c)) 
Instance details

Defined in Cardano.Ledger.PoolDistr

Methods

toExp :: PoolDistr c -> Exp (Map (KeyHash 'StakePool c) (IndividualPoolStake c))

Eq (KeyHash discriminator c) 
Instance details

Defined in Cardano.Ledger.Keys

Methods

(==) :: KeyHash discriminator c -> KeyHash discriminator c -> Bool Source #

(/=) :: KeyHash discriminator c -> KeyHash discriminator c -> Bool Source #

Ord (KeyHash discriminator c) 
Instance details

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) 
Instance details

Defined in Cardano.Ledger.Keys

Methods

showsPrec :: Int -> KeyHash discriminator c -> ShowS Source #

show :: KeyHash discriminator c -> String Source #

showList :: [KeyHash discriminator c] -> ShowS Source #

Generic (KeyHash discriminator c) 
Instance details

Defined in Cardano.Ledger.Keys

Associated Types

type Rep (KeyHash discriminator c) :: Type -> Type Source #

Methods

from :: KeyHash discriminator c -> Rep (KeyHash discriminator c) x Source #

to :: Rep (KeyHash discriminator c) x -> KeyHash discriminator c Source #

NFData (KeyHash discriminator c) 
Instance details

Defined in Cardano.Ledger.Keys

Methods

rnf :: KeyHash discriminator c -> () Source #

(Crypto c, Typeable disc) => DecCBOR (KeyHash disc c) 
Instance details

Defined in Cardano.Ledger.Keys

Methods

decCBOR :: Decoder s (KeyHash disc c)

dropCBOR :: Proxy (KeyHash disc c) -> Decoder s ()

label :: Proxy (KeyHash disc c) -> Text

(Crypto c, Typeable disc) => EncCBOR (KeyHash disc c) 
Instance details

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) 
Instance details

Defined in Cardano.Ledger.Keys

Methods

fromCBOR :: Decoder s (KeyHash disc c) #

label :: Proxy (KeyHash disc c) -> Text #

Crypto c => FromJSON (KeyHash disc c) 
Instance details

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) 
Instance details

Defined in Cardano.Ledger.Keys

Methods

noThunks :: Context -> KeyHash discriminator c -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> KeyHash discriminator c -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (KeyHash discriminator c) -> String

(Crypto c, Typeable disc) => ToCBOR (KeyHash disc c) 
Instance details

Defined in Cardano.Ledger.Keys

Methods

toCBOR :: KeyHash disc c -> Encoding #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (KeyHash disc c) -> Size #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [KeyHash disc c] -> Size #

ToExpr (KeyHash keyrole c) 
Instance details

Defined in Cardano.Ledger.Keys

Methods

toExpr :: KeyHash keyrole c -> Expr

listToExpr :: [KeyHash keyrole c] -> Expr

Crypto c => ToJSON (KeyHash disc c) 
Instance details

Defined in Cardano.Ledger.Keys

Methods

toJSON :: KeyHash disc c -> Value #

toEncoding :: KeyHash disc c -> Encoding #

toJSONList :: [KeyHash disc c] -> Value #

toEncodingList :: [KeyHash disc c] -> Encoding #

omitField :: KeyHash disc c -> Bool #

Crypto c => ToJSONKey (KeyHash disc c) 
Instance details

Defined in Cardano.Ledger.Keys

Methods

toJSONKey :: ToJSONKeyFunction (KeyHash disc c)

toJSONKeyList :: ToJSONKeyFunction [KeyHash disc c]

Crypto c => FromJSONKey (KeyHash disc c) 
Instance details

Defined in Cardano.Ledger.Keys

Methods

fromJSONKey :: FromJSONKeyFunction (KeyHash disc c)

fromJSONKeyList :: FromJSONKeyFunction [KeyHash disc c]

type Rep (KeyHash discriminator c) 
Instance details

Defined in Cardano.Ledger.Keys

type Rep (KeyHash discriminator c) = Rep (Hash (ADDRHASH c) (VerKeyDSIGN (DSIGN c)))

data ShelleyTxCert era #

Instances

Instances details
Eq (ShelleyTxCert era) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Show (ShelleyTxCert era) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Generic (ShelleyTxCert era) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Associated Types

type Rep (ShelleyTxCert era) :: Type -> Type Source #

Methods

from :: ShelleyTxCert era -> Rep (ShelleyTxCert era) x Source #

to :: Rep (ShelleyTxCert era) x -> ShelleyTxCert era Source #

NFData (ShelleyTxCert era) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

rnf :: ShelleyTxCert era -> () Source #

(ShelleyEraTxCert era, TxCert era ~ ShelleyTxCert era) => DecCBOR (ShelleyTxCert era) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

decCBOR :: Decoder s (ShelleyTxCert era)

dropCBOR :: Proxy (ShelleyTxCert era) -> Decoder s ()

label :: Proxy (ShelleyTxCert era) -> Text

Era era => EncCBOR (ShelleyTxCert era) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

encCBOR :: ShelleyTxCert era -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (ShelleyTxCert era) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ShelleyTxCert era] -> Size

(ShelleyEraTxCert era, TxCert era ~ ShelleyTxCert era) => FromCBOR (ShelleyTxCert era) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

fromCBOR :: Decoder s (ShelleyTxCert era) #

label :: Proxy (ShelleyTxCert era) -> Text #

NoThunks (ShelleyTxCert era) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

noThunks :: Context -> ShelleyTxCert era -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> ShelleyTxCert era -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (ShelleyTxCert era) -> String

Era era => ToCBOR (ShelleyTxCert era) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

toCBOR :: ShelleyTxCert era -> Encoding #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyTxCert era) -> Size #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ShelleyTxCert era] -> Size #

ToExpr (ShelleyTxCert era) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

toExpr :: ShelleyTxCert era -> Expr

listToExpr :: [ShelleyTxCert era] -> Expr

(Crypto (EraCrypto ledgerera), ToJSON (GenesisDelegCert (EraCrypto ledgerera)), ToJSON (MIRCert (EraCrypto ledgerera)), ToJSON (PoolCert (EraCrypto ledgerera)), ToJSON (ShelleyDelegCert (EraCrypto ledgerera))) => ToJSON (ShelleyTxCert ledgerera) Source # 
Instance details

Defined in Cardano.Api.Orphans

Methods

toJSON :: ShelleyTxCert ledgerera -> Value #

toEncoding :: ShelleyTxCert ledgerera -> Encoding #

toJSONList :: [ShelleyTxCert ledgerera] -> Value #

toEncodingList :: [ShelleyTxCert ledgerera] -> Encoding #

omitField :: ShelleyTxCert ledgerera -> Bool #

type Rep (ShelleyTxCert era) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

type Rep (ShelleyTxCert era) = D1 ('MetaData "ShelleyTxCert" "Cardano.Ledger.Shelley.TxCert" "cardano-ledger-shelley-1.8.0.0-8zSwDh4GiF3HDtP87S8Ej2" '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 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

Instances details
Eq (ShelleyDelegCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Show (ShelleyDelegCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Generic (ShelleyDelegCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Associated Types

type Rep (ShelleyDelegCert c) :: Type -> Type Source #

NFData (ShelleyDelegCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

rnf :: ShelleyDelegCert c -> () Source #

NoThunks (ShelleyDelegCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

noThunks :: Context -> ShelleyDelegCert c -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> ShelleyDelegCert c -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (ShelleyDelegCert c) -> String

ToExpr (ShelleyDelegCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

toExpr :: ShelleyDelegCert c -> Expr

listToExpr :: [ShelleyDelegCert c] -> Expr

ToJSON (ShelleyDelegCert StandardCrypto) Source # 
Instance details

Defined in Cardano.Api.Orphans

type Rep (ShelleyDelegCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

type Rep (ShelleyDelegCert c) = D1 ('MetaData "ShelleyDelegCert" "Cardano.Ledger.Shelley.TxCert" "cardano-ledger-shelley-1.8.0.0-8zSwDh4GiF3HDtP87S8Ej2" '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)))))

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

Instances details
Crypto c => ShelleyEraTxCert (ShelleyEra c) 
Instance details

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

Instances details
Eq (GenesisDelegCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Show (GenesisDelegCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Generic (GenesisDelegCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Associated Types

type Rep (GenesisDelegCert c) :: Type -> Type Source #

NFData (GenesisDelegCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

rnf :: GenesisDelegCert c -> () Source #

NoThunks (GenesisDelegCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

noThunks :: Context -> GenesisDelegCert c -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> GenesisDelegCert c -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (GenesisDelegCert c) -> String

ToExpr (GenesisDelegCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

toExpr :: GenesisDelegCert c -> Expr

listToExpr :: [GenesisDelegCert c] -> Expr

ToJSON (GenesisDelegCert StandardCrypto) Source # 
Instance details

Defined in Cardano.Api.Orphans

type Rep (GenesisDelegCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

type Rep (GenesisDelegCert c) = D1 ('MetaData "GenesisDelegCert" "Cardano.Ledger.Shelley.TxCert" "cardano-ledger-shelley-1.8.0.0-8zSwDh4GiF3HDtP87S8Ej2" '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 PoolParams c #

Constructors

PoolParams 

Fields

Instances

Instances details
Eq (PoolParams c) 
Instance details

Defined in Cardano.Ledger.PoolParams

Ord (PoolParams c) 
Instance details

Defined in Cardano.Ledger.PoolParams

Show (PoolParams c) 
Instance details

Defined in Cardano.Ledger.PoolParams

Generic (PoolParams c) 
Instance details

Defined in Cardano.Ledger.PoolParams

Associated Types

type Rep (PoolParams c) :: Type -> Type Source #

Methods

from :: PoolParams c -> Rep (PoolParams c) x Source #

to :: Rep (PoolParams c) x -> PoolParams c Source #

NFData (PoolParams c) 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

rnf :: PoolParams c -> () Source #

Crypto c => DecCBOR (PoolParams c) 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

decCBOR :: Decoder s (PoolParams c)

dropCBOR :: Proxy (PoolParams c) -> Decoder s ()

label :: Proxy (PoolParams c) -> Text

Crypto c => DecCBORGroup (PoolParams c) 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

decCBORGroup :: Decoder s (PoolParams c)

Crypto c => Default (PoolParams c) 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

def :: PoolParams c

Crypto c => EncCBOR (PoolParams c) 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

encCBOR :: PoolParams c -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (PoolParams c) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [PoolParams c] -> Size

Crypto c => EncCBORGroup (PoolParams c) 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

encCBORGroup :: PoolParams c -> Encoding

encodedGroupSizeExpr :: (forall x. EncCBOR x => Proxy x -> Size) -> Proxy (PoolParams c) -> Size

listLen :: PoolParams c -> Word

listLenBound :: Proxy (PoolParams c) -> Word

Crypto c => FromJSON (PoolParams c) 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

parseJSON :: Value -> Parser (PoolParams c) #

parseJSONList :: Value -> Parser [PoolParams c] #

omittedField :: Maybe (PoolParams c) #

NoThunks (PoolParams c) 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

noThunks :: Context -> PoolParams c -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> PoolParams c -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (PoolParams c) -> String

ToExpr (PoolParams era) 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

toExpr :: PoolParams era -> Expr

listToExpr :: [PoolParams era] -> Expr

Crypto c => ToJSON (PoolParams c) 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

toJSON :: PoolParams c -> Value #

toEncoding :: PoolParams c -> Encoding #

toJSONList :: [PoolParams c] -> Value #

toEncodingList :: [PoolParams c] -> Encoding #

omitField :: PoolParams c -> Bool #

type Rep (PoolParams c) 
Instance details

Defined in Cardano.Ledger.PoolParams

type Rep (PoolParams c) = D1 ('MetaData "PoolParams" "Cardano.Ledger.PoolParams" "cardano-ledger-core-1.9.0.0-E3793VXyLODIfmloH8Sp2j" '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 "ppRewardAcnt") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (RewardAcnt 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)))))))

class HasKeyRole (a :: KeyRole -> Type -> Type) #

Instances

Instances details
HasKeyRole KeyHash 
Instance details

Defined in Cardano.Ledger.Keys

Methods

coerceKeyRole :: forall (r :: KeyRole) c (r' :: KeyRole). KeyHash r c -> KeyHash r' c

HasKeyRole VKey 
Instance details

Defined in Cardano.Ledger.Keys

Methods

coerceKeyRole :: forall (r :: KeyRole) c (r' :: KeyRole). VKey r c -> VKey r' c

HasKeyRole Credential 
Instance details

Defined in Cardano.Ledger.Credential

Methods

coerceKeyRole :: forall (r :: KeyRole) c (r' :: KeyRole). Credential r c -> Credential r' c

data MIRPot #

Constructors

ReservesMIR 
TreasuryMIR 

Instances

Instances details
Bounded MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Enum MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Eq MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Ord MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Show MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Generic MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Associated Types

type Rep MIRPot :: Type -> Type Source #

NFData MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

rnf :: MIRPot -> () Source #

DecCBOR MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

decCBOR :: Decoder s MIRPot

dropCBOR :: Proxy MIRPot -> Decoder s ()

label :: Proxy MIRPot -> Text

EncCBOR MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

encCBOR :: MIRPot -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy MIRPot -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [MIRPot] -> Size

NoThunks MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

noThunks :: Context -> MIRPot -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> MIRPot -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy MIRPot -> String

ToExpr MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

toExpr :: MIRPot -> Expr

listToExpr :: [MIRPot] -> Expr

ToJSON MIRPot Source # 
Instance details

Defined in Cardano.Api.Orphans

Methods

toJSON :: MIRPot -> Value #

toEncoding :: MIRPot -> Encoding #

toJSONList :: [MIRPot] -> Value #

toEncodingList :: [MIRPot] -> Encoding #

omitField :: MIRPot -> Bool #

type Rep MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

type Rep MIRPot = D1 ('MetaData "MIRPot" "Cardano.Ledger.Shelley.TxCert" "cardano-ledger-shelley-1.8.0.0-8zSwDh4GiF3HDtP87S8Ej2" 'False) (C1 ('MetaCons "ReservesMIR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TreasuryMIR" 'PrefixI 'False) (U1 :: Type -> Type))

data MIRTarget c #

Constructors

StakeAddressesMIR !(Map (Credential 'Staking c) DeltaCoin) 
SendToOppositePotMIR !Coin 

Instances

Instances details
Eq (MIRTarget c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Show (MIRTarget c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Generic (MIRTarget c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Associated Types

type Rep (MIRTarget c) :: Type -> Type Source #

Methods

from :: MIRTarget c -> Rep (MIRTarget c) x Source #

to :: Rep (MIRTarget c) x -> MIRTarget c Source #

NFData (MIRTarget c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

rnf :: MIRTarget c -> () Source #

Crypto c => DecCBOR (MIRTarget c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

decCBOR :: Decoder s (MIRTarget c)

dropCBOR :: Proxy (MIRTarget c) -> Decoder s ()

label :: Proxy (MIRTarget c) -> Text

Crypto c => EncCBOR (MIRTarget c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

encCBOR :: MIRTarget c -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (MIRTarget c) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [MIRTarget c] -> Size

NoThunks (MIRTarget c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

noThunks :: Context -> MIRTarget c -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> MIRTarget c -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (MIRTarget c) -> String

ToExpr (MIRTarget c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

toExpr :: MIRTarget c -> Expr

listToExpr :: [MIRTarget c] -> Expr

ToJSON (MIRTarget StandardCrypto) Source # 
Instance details

Defined in Cardano.Api.Orphans

type Rep (MIRTarget c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

type Rep (MIRTarget c) = D1 ('MetaData "MIRTarget" "Cardano.Ledger.Shelley.TxCert" "cardano-ledger-shelley-1.8.0.0-8zSwDh4GiF3HDtP87S8Ej2" '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)))

data MIRCert c #

Constructors

MIRCert 

Fields

Instances

Instances details
Eq (MIRCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

(==) :: MIRCert c -> MIRCert c -> Bool Source #

(/=) :: MIRCert c -> MIRCert c -> Bool Source #

Show (MIRCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Generic (MIRCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Associated Types

type Rep (MIRCert c) :: Type -> Type Source #

Methods

from :: MIRCert c -> Rep (MIRCert c) x Source #

to :: Rep (MIRCert c) x -> MIRCert c Source #

NFData (MIRCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

rnf :: MIRCert c -> () Source #

Crypto c => DecCBOR (MIRCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

decCBOR :: Decoder s (MIRCert c)

dropCBOR :: Proxy (MIRCert c) -> Decoder s ()

label :: Proxy (MIRCert c) -> Text

Crypto c => EncCBOR (MIRCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

encCBOR :: MIRCert c -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (MIRCert c) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [MIRCert c] -> Size

NoThunks (MIRCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

noThunks :: Context -> MIRCert c -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> MIRCert c -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (MIRCert c) -> String

ToExpr (MIRCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

toExpr :: MIRCert c -> Expr

listToExpr :: [MIRCert c] -> Expr

ToJSON (MIRCert StandardCrypto) Source # 
Instance details

Defined in Cardano.Api.Orphans

type Rep (MIRCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

type Rep (MIRCert c) = D1 ('MetaData "MIRCert" "Cardano.Ledger.Shelley.TxCert" "cardano-ledger-shelley-1.8.0.0-8zSwDh4GiF3HDtP87S8Ej2" '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))))

data StakePoolRelay #

Instances

Instances details
Eq StakePoolRelay 
Instance details

Defined in Cardano.Ledger.PoolParams

Ord StakePoolRelay 
Instance details

Defined in Cardano.Ledger.PoolParams

Show StakePoolRelay 
Instance details

Defined in Cardano.Ledger.PoolParams

Generic StakePoolRelay 
Instance details

Defined in Cardano.Ledger.PoolParams

Associated Types

type Rep StakePoolRelay :: Type -> Type Source #

NFData StakePoolRelay 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

rnf :: StakePoolRelay -> () Source #

DecCBOR StakePoolRelay 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

decCBOR :: Decoder s StakePoolRelay

dropCBOR :: Proxy StakePoolRelay -> Decoder s ()

label :: Proxy StakePoolRelay -> Text

EncCBOR StakePoolRelay 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

encCBOR :: StakePoolRelay -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy StakePoolRelay -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [StakePoolRelay] -> Size

FromJSON StakePoolRelay 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

parseJSON :: Value -> Parser StakePoolRelay #

parseJSONList :: Value -> Parser [StakePoolRelay] #

omittedField :: Maybe StakePoolRelay #

NoThunks StakePoolRelay 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

noThunks :: Context -> StakePoolRelay -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> StakePoolRelay -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy StakePoolRelay -> String

ToExpr StakePoolRelay 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

toExpr :: StakePoolRelay -> Expr

listToExpr :: [StakePoolRelay] -> Expr

ToJSON StakePoolRelay 
Instance details

Defined in Cardano.Ledger.PoolParams

type Rep StakePoolRelay 
Instance details

Defined in Cardano.Ledger.PoolParams

data PoolMetadata #

Constructors

PoolMetadata 

Fields

Instances

Instances details
Eq PoolMetadata 
Instance details

Defined in Cardano.Ledger.PoolParams

Ord PoolMetadata 
Instance details

Defined in Cardano.Ledger.PoolParams

Show PoolMetadata 
Instance details

Defined in Cardano.Ledger.PoolParams

Generic PoolMetadata 
Instance details

Defined in Cardano.Ledger.PoolParams

Associated Types

type Rep PoolMetadata :: Type -> Type Source #

NFData PoolMetadata 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

rnf :: PoolMetadata -> () Source #

DecCBOR PoolMetadata 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

decCBOR :: Decoder s PoolMetadata

dropCBOR :: Proxy PoolMetadata -> Decoder s ()

label :: Proxy PoolMetadata -> Text

EncCBOR PoolMetadata 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

encCBOR :: PoolMetadata -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy PoolMetadata -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [PoolMetadata] -> Size

FromJSON PoolMetadata 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

parseJSON :: Value -> Parser PoolMetadata #

parseJSONList :: Value -> Parser [PoolMetadata] #

omittedField :: Maybe PoolMetadata #

NoThunks PoolMetadata 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

noThunks :: Context -> PoolMetadata -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> PoolMetadata -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy PoolMetadata -> String

ToExpr PoolMetadata 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

toExpr :: PoolMetadata -> Expr

listToExpr :: [PoolMetadata] -> Expr

ToJSON PoolMetadata 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

toJSON :: PoolMetadata -> Value #

toEncoding :: PoolMetadata -> Encoding #

toJSONList :: [PoolMetadata] -> Value #

toEncodingList :: [PoolMetadata] -> Encoding #

omitField :: PoolMetadata -> Bool #

type Rep PoolMetadata 
Instance details

Defined in Cardano.Ledger.PoolParams

type Rep PoolMetadata = D1 ('MetaData "PoolMetadata" "Cardano.Ledger.PoolParams" "cardano-ledger-core-1.9.0.0-E3793VXyLODIfmloH8Sp2j" 'False) (C1 ('MetaCons "PoolMetadata" 'PrefixI 'True) (S1 ('MetaSel ('Just "pmUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Url) :*: S1 ('MetaSel ('Just "pmHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteString)))

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 #

data StrictMaybe a #

Constructors

SNothing 
SJust !a 

Instances

Instances details
Monad StrictMaybe 
Instance details

Defined in Data.Maybe.Strict

Functor StrictMaybe 
Instance details

Defined in Data.Maybe.Strict

Methods

fmap :: (a -> b) -> StrictMaybe a -> StrictMaybe b Source #

(<$) :: a -> StrictMaybe b -> StrictMaybe a Source #

MonadFail StrictMaybe 
Instance details

Defined in Data.Maybe.Strict

Methods

fail :: String -> StrictMaybe a Source #

Applicative StrictMaybe 
Instance details

Defined in Data.Maybe.Strict

Foldable StrictMaybe 
Instance details

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 
Instance details

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 
Instance details

Defined in Data.Maybe.Strict

HKDFunctor StrictMaybe 
Instance details

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) 
Instance details

Defined in Data.Maybe.Strict

Eq (UpgradeConwayPParams StrictMaybe) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

Methods

(==) :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> Bool Source #

(/=) :: UpgradeConwayPParams StrictMaybe -> UpgradeConwayPParams StrictMaybe -> Bool Source #

Ord a => Ord (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

Ord (UpgradeConwayPParams StrictMaybe) 
Instance details

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) 
Instance details

Defined in Data.Maybe.Strict

Show (UpgradeConwayPParams StrictMaybe) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

Methods

showsPrec :: Int -> UpgradeConwayPParams StrictMaybe -> ShowS Source #

show :: UpgradeConwayPParams StrictMaybe -> String Source #

showList :: [UpgradeConwayPParams StrictMaybe] -> ShowS Source #

Generic (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

Associated Types

type Rep (StrictMaybe a) :: Type -> Type Source #

Semigroup a => Semigroup (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

Semigroup a => Monoid (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

NFData a => NFData (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

Methods

rnf :: StrictMaybe a -> () Source #

NFData (UpgradeConwayPParams StrictMaybe) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

Methods

rnf :: UpgradeConwayPParams StrictMaybe -> () Source #

DecCBOR a => DecCBOR (StrictMaybe a) 
Instance details

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) 
Instance details

Defined in Data.Maybe.Strict

Methods

def :: StrictMaybe t

Default (UpgradeConwayPParams StrictMaybe) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

Methods

def :: UpgradeConwayPParams StrictMaybe

Default (UpgradeAlonzoPParams StrictMaybe) 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

Methods

def :: UpgradeAlonzoPParams StrictMaybe

EncCBOR a => EncCBOR (StrictMaybe a) 
Instance details

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) 
Instance details

Defined in Data.Maybe.Strict

Methods

fromCBOR :: Decoder s (StrictMaybe a) #

label :: Proxy (StrictMaybe a) -> Text #

FromJSON a => FromJSON (StrictMaybe a) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Methods

showsPrec :: Int -> ShelleyPParams StrictMaybe era -> ShowS Source #

show :: ShelleyPParams StrictMaybe era -> String Source #

showList :: [ShelleyPParams StrictMaybe era] -> ShowS Source #

Show (BabbagePParams StrictMaybe era) 
Instance details

Defined in Cardano.Ledger.Babbage.PParams

Methods

showsPrec :: Int -> BabbagePParams StrictMaybe era -> ShowS Source #

show :: BabbagePParams StrictMaybe era -> String Source #

showList :: [BabbagePParams StrictMaybe era] -> ShowS Source #

Show (ConwayPParams StrictMaybe era) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

Methods

showsPrec :: Int -> ConwayPParams StrictMaybe era -> ShowS Source #

show :: ConwayPParams StrictMaybe era -> String Source #

showList :: [ConwayPParams StrictMaybe era] -> ShowS Source #

Show (AlonzoPParams StrictMaybe era) 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

Methods

showsPrec :: Int -> AlonzoPParams StrictMaybe era -> ShowS Source #

show :: AlonzoPParams StrictMaybe era -> String Source #

showList :: [AlonzoPParams StrictMaybe era] -> ShowS Source #

Semigroup (ShelleyPParams StrictMaybe era) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

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) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Methods

rnf :: ShelleyPParams StrictMaybe era -> () Source #

NFData (BabbagePParams StrictMaybe era) 
Instance details

Defined in Cardano.Ledger.Babbage.PParams

Methods

rnf :: BabbagePParams StrictMaybe era -> () Source #

NFData (ConwayPParams StrictMaybe era) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

Methods

rnf :: ConwayPParams StrictMaybe era -> () Source #

NFData (AlonzoPParams StrictMaybe era) 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

Methods

rnf :: AlonzoPParams StrictMaybe era -> () Source #

Era era => DecCBOR (ShelleyPParams StrictMaybe era) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

Methods

fromCBOR :: Decoder s (AlonzoPParams StrictMaybe era) #

label :: Proxy (AlonzoPParams StrictMaybe era) -> Text #

NoThunks (ShelleyPParams StrictMaybe era) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Methods

toExpr :: ShelleyPParams StrictMaybe era -> Expr

listToExpr :: [ShelleyPParams StrictMaybe era] -> Expr

ToExpr (BabbagePParams StrictMaybe era) 
Instance details

Defined in Cardano.Ledger.Babbage.PParams

Methods

toExpr :: BabbagePParams StrictMaybe era -> Expr

listToExpr :: [BabbagePParams StrictMaybe era] -> Expr

ToExpr (ConwayPParams StrictMaybe era) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

Methods

toExpr :: ConwayPParams StrictMaybe era -> Expr

listToExpr :: [ConwayPParams StrictMaybe era] -> Expr

ToExpr (AlonzoPParams StrictMaybe era) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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)) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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 RegDepositTxCert :: ConwayEraTxCert era => StakeCredential (EraCrypto era) -> Coin -> TxCert era #

pattern UnRegDepositTxCert :: ConwayEraTxCert era => StakeCredential (EraCrypto era) -> Coin -> 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 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 #

newtype Coin #

Constructors

Coin 

Fields

Instances

Instances details
Enum Coin 
Instance details

Defined in Cardano.Ledger.Coin

Eq Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

(==) :: Coin -> Coin -> Bool Source #

(/=) :: Coin -> Coin -> Bool Source #

Ord Coin 
Instance details

Defined in Cardano.Ledger.Coin

Show Coin 
Instance details

Defined in Cardano.Ledger.Coin

Generic Coin 
Instance details

Defined in Cardano.Ledger.Coin

Associated Types

type Rep Coin :: Type -> Type Source #

Methods

from :: Coin -> Rep Coin x Source #

to :: Rep Coin x -> Coin Source #

Semigroup Coin 
Instance details

Defined in Cardano.Ledger.Coin

Monoid Coin 
Instance details

Defined in Cardano.Ledger.Coin

NFData Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

rnf :: Coin -> () Source #

DecCBOR Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

decCBOR :: Decoder s Coin

dropCBOR :: Proxy Coin -> Decoder s ()

label :: Proxy Coin -> Text

EncCBOR Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

encCBOR :: Coin -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Coin -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Coin] -> Size

FromCBOR Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

fromCBOR :: Decoder s Coin #

label :: Proxy Coin -> Text #

FromJSON Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

parseJSON :: Value -> Parser Coin #

parseJSONList :: Value -> Parser [Coin] #

omittedField :: Maybe Coin #

NoThunks Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

noThunks :: Context -> Coin -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Coin -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy Coin -> String

ToCBOR Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

toCBOR :: Coin -> Encoding #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Coin -> Size #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Coin] -> Size #

ToExpr Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

toExpr :: Coin -> Expr

listToExpr :: [Coin] -> Expr

ToJSON Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

toJSON :: Coin -> Value #

toEncoding :: Coin -> Encoding #

toJSONList :: [Coin] -> Value #

toEncodingList :: [Coin] -> Encoding #

omitField :: Coin -> Bool #

HeapWords Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

heapWords :: Coin -> Int

Abelian Coin 
Instance details

Defined in Cardano.Ledger.Coin

Compactible Coin 
Instance details

Defined in Cardano.Ledger.Coin

Associated Types

data CompactForm Coin

Methods

toCompact :: Coin -> Maybe (CompactForm Coin)

fromCompact :: CompactForm Coin -> Coin

Group Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

invert :: Coin -> Coin

(~~) :: Coin -> Coin -> Coin

pow :: Integral x => Coin -> x -> Coin

PartialOrd Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

(<=) :: Coin -> Coin -> Bool

(>=) :: Coin -> Coin -> Bool

(==) :: Coin -> Coin -> Bool

(/=) :: Coin -> Coin -> Bool

(<) :: Coin -> Coin -> Bool

(>) :: Coin -> Coin -> Bool

compare :: Coin -> Coin -> Maybe Ordering

Val Coin 
Instance details

Defined in Cardano.Ledger.Val

Methods

zero :: Coin

(<+>) :: Coin -> Coin -> Coin

(<×>) :: Integral i => i -> Coin -> Coin

(<->) :: Coin -> Coin -> Coin

isZero :: Coin -> Bool

coin :: Coin -> Coin

inject :: Coin -> Coin

modifyCoin :: (Coin -> Coin) -> Coin -> Coin

size :: Coin -> Integer

pointwise :: (Integer -> Integer -> Bool) -> Coin -> Coin -> Bool

isAdaOnly :: 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) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

(==) :: CompactForm Coin -> CompactForm Coin -> Bool Source #

(/=) :: CompactForm Coin -> CompactForm Coin -> Bool Source #

Ord (CompactForm Coin) 
Instance details

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) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

showsPrec :: Int -> CompactForm Coin -> ShowS Source #

show :: CompactForm Coin -> String Source #

showList :: [CompactForm Coin] -> ShowS Source #

Semigroup (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

(<>) :: CompactForm Coin -> CompactForm Coin -> CompactForm Coin Source #

sconcat :: NonEmpty (CompactForm Coin) -> CompactForm Coin Source #

stimes :: Integral b => b -> CompactForm Coin -> CompactForm Coin Source #

Monoid (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

mempty :: CompactForm Coin Source #

mappend :: CompactForm Coin -> CompactForm Coin -> CompactForm Coin Source #

mconcat :: [CompactForm Coin] -> CompactForm Coin Source #

NFData (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

rnf :: CompactForm Coin -> () Source #

DecCBOR (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

decCBOR :: Decoder s (CompactForm Coin)

dropCBOR :: Proxy (CompactForm Coin) -> Decoder s ()

label :: Proxy (CompactForm Coin) -> Text

EncCBOR (CompactForm Coin) 
Instance details

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) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

parseJSON :: Value -> Parser (CompactForm Coin) #

parseJSONList :: Value -> Parser [CompactForm Coin] #

omittedField :: Maybe (CompactForm Coin) #

NoThunks (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

noThunks :: Context -> CompactForm Coin -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> CompactForm Coin -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (CompactForm Coin) -> String

ToCBOR (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

toCBOR :: CompactForm Coin -> Encoding #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (CompactForm Coin) -> Size #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [CompactForm Coin] -> Size #

ToExpr (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

toExpr :: CompactForm Coin -> Expr

listToExpr :: [CompactForm Coin] -> Expr

ToJSON (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

toJSON :: CompactForm Coin -> Value #

toEncoding :: CompactForm Coin -> Encoding #

toJSONList :: [CompactForm Coin] -> Value #

toEncodingList :: [CompactForm Coin] -> Encoding #

omitField :: CompactForm Coin -> Bool #

HeapWords (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

heapWords :: CompactForm Coin -> Int

Prim (CompactForm Coin) 
Instance details

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) 
Instance details

Defined in Cardano.Ledger.Coin

Group (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

invert :: CompactForm Coin -> CompactForm Coin

(~~) :: CompactForm Coin -> CompactForm Coin -> CompactForm Coin

pow :: Integral x => CompactForm Coin -> x -> CompactForm Coin

type Rep Coin 
Instance details

Defined in Cardano.Ledger.Coin

type Rep Coin = D1 ('MetaData "Coin" "Cardano.Ledger.Coin" "cardano-ledger-core-1.9.0.0-E3793VXyLODIfmloH8Sp2j" 'True) (C1 ('MetaCons "Coin" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCoin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))
newtype CompactForm Coin 
Instance details

Defined in Cardano.Ledger.Coin

newtype CompactForm Coin = CompactCoin Word64

type family EraCrypto era #

Instances

Instances details
type EraCrypto (ByronEra c) 
Instance details

Defined in Cardano.Ledger.Core.Era

type EraCrypto (ByronEra c) = c
type EraCrypto (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type EraCrypto (AlonzoEra c) = c
type EraCrypto (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type EraCrypto (MaryEra c) = c
type EraCrypto (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraCrypto (ConwayEra c) = c
type EraCrypto (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraCrypto (ShelleyEra c) = c
type EraCrypto (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type EraCrypto (BabbageEra c) = c
type EraCrypto (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type EraCrypto (AllegraEra c) = c

data Network #

Constructors

Testnet 
Mainnet 

Instances

Instances details
Bounded Network 
Instance details

Defined in Cardano.Ledger.BaseTypes

Enum Network 
Instance details

Defined in Cardano.Ledger.BaseTypes

Eq Network 
Instance details

Defined in Cardano.Ledger.BaseTypes

Ord Network 
Instance details

Defined in Cardano.Ledger.BaseTypes

Show Network 
Instance details

Defined in Cardano.Ledger.BaseTypes

Generic Network 
Instance details

Defined in Cardano.Ledger.BaseTypes

Associated Types

type Rep Network :: Type -> Type Source #

NFData Network 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

rnf :: Network -> () Source #

DecCBOR Network 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

decCBOR :: Decoder s Network

dropCBOR :: Proxy Network -> Decoder s ()

label :: Proxy Network -> Text

Default Network 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

def :: Network

EncCBOR Network 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

encCBOR :: Network -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Network -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Network] -> Size

FromJSON Network 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

parseJSON :: Value -> Parser Network #

parseJSONList :: Value -> Parser [Network] #

omittedField :: Maybe Network #

NoThunks Network 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

noThunks :: Context -> Network -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Network -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy Network -> String

ToExpr Network 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toExpr :: Network -> Expr

listToExpr :: [Network] -> Expr

ToJSON Network 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: Network -> Value #

toEncoding :: Network -> Encoding #

toJSONList :: [Network] -> Value #

toEncodingList :: [Network] -> Encoding #

omitField :: Network -> Bool #

type Rep Network 
Instance details

Defined in Cardano.Ledger.BaseTypes

type Rep Network = D1 ('MetaData "Network" "Cardano.Ledger.BaseTypes" "cardano-ledger-core-1.9.0.0-E3793VXyLODIfmloH8Sp2j" 'False) (C1 ('MetaCons "Testnet" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mainnet" 'PrefixI 'False) (U1 :: Type -> Type))

data PoolCert c #

Instances

Instances details
Eq (PoolCert c) 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Methods

(==) :: PoolCert c -> PoolCert c -> Bool Source #

(/=) :: PoolCert c -> PoolCert c -> Bool Source #

Ord (PoolCert c) 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Show (PoolCert c) 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Generic (PoolCert c) 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Associated Types

type Rep (PoolCert c) :: Type -> Type Source #

Methods

from :: PoolCert c -> Rep (PoolCert c) x Source #

to :: Rep (PoolCert c) x -> PoolCert c Source #

NFData (PoolCert c) 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Methods

rnf :: PoolCert c -> () Source #

NoThunks (PoolCert c) 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Methods

noThunks :: Context -> PoolCert c -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> PoolCert c -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (PoolCert c) -> String

ToExpr (PoolCert c) 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Methods

toExpr :: PoolCert c -> Expr

listToExpr :: [PoolCert c] -> Expr

ToJSON (PoolCert StandardCrypto) Source # 
Instance details

Defined in Cardano.Api.Orphans

type Rep (PoolCert c) 
Instance details

Defined in Cardano.Ledger.Core.TxCert

type Rep (PoolCert c) = D1 ('MetaData "PoolCert" "Cardano.Ledger.Core.TxCert" "cardano-ledger-core-1.9.0.0-E3793VXyLODIfmloH8Sp2j" '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)))

newtype PParams era #

Constructors

PParams (PParamsHKD Identity era) 

Instances

Instances details
Eq (PParamsHKD Identity era) => Eq (PParams era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

(==) :: PParams era -> PParams era -> Bool Source #

(/=) :: PParams era -> PParams era -> Bool Source #

Ord (PParamsHKD Identity era) => Ord (PParams era) 
Instance details

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 #

max :: PParams era -> PParams era -> PParams era Source #

min :: PParams era -> PParams era -> PParams era Source #

Show (PParamsHKD Identity era) => Show (PParams era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

showsPrec :: Int -> PParams era -> ShowS Source #

show :: PParams era -> String Source #

showList :: [PParams era] -> ShowS Source #

Generic (PParams era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Associated Types

type Rep (PParams era) :: Type -> Type Source #

Methods

from :: PParams era -> Rep (PParams era) x Source #

to :: Rep (PParams era) x -> PParams era Source #

NFData (PParamsHKD Identity era) => NFData (PParams era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

rnf :: PParams era -> () Source #

(Typeable era, DecCBOR (PParamsHKD Identity era)) => DecCBOR (PParams era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

decCBOR :: Decoder s (PParams era)

dropCBOR :: Proxy (PParams era) -> Decoder s ()

label :: Proxy (PParams era) -> Text

EraPParams era => Default (PParams era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

def :: PParams era

(Typeable era, EncCBOR (PParamsHKD Identity era)) => EncCBOR (PParams era) 
Instance details

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) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

fromCBOR :: Decoder s (PParams era) #

label :: Proxy (PParams era) -> Text #

FromJSON (PParamsHKD Identity era) => FromJSON (PParams era) 
Instance details

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) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

noThunks :: Context -> PParams era -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> PParams era -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (PParams era) -> String

(Typeable era, ToCBOR (PParamsHKD Identity era)) => ToCBOR (PParams era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

toCBOR :: PParams era -> Encoding #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (PParams era) -> Size #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [PParams era] -> Size #

ToExpr (PParamsHKD Identity era) => ToExpr (PParams era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

toExpr :: PParams era -> Expr

listToExpr :: [PParams era] -> Expr

ToJSON (PParamsHKD Identity era) => ToJSON (PParams era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

toJSON :: PParams era -> Value #

toEncoding :: PParams era -> Encoding #

toJSONList :: [PParams era] -> Value #

toEncodingList :: [PParams era] -> Encoding #

omitField :: PParams era -> Bool #

type Rep (PParams era) 
Instance details

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 
Instance details

Defined in Cardano.Ledger.Alonzo.Translation

type TranslationError (AlonzoEra c) PParams = Void
type TranslationError (MaryEra c) PParams 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) PParams = Void
type TranslationError (ConwayEra c) PParams 
Instance details

Defined in Cardano.Ledger.Conway.Translation

type TranslationError (ConwayEra c) PParams = Void
type TranslationError (BabbageEra c) PParams 
Instance details

Defined in Cardano.Ledger.Babbage.Translation

type TranslationError (BabbageEra c) PParams = Void
type TranslationError (AllegraEra c) PParams 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

type TranslationError (AllegraEra c) PParams = Void

data PParamsUpdate era #

Instances

Instances details
Eq (PParamsHKD StrictMaybe era) => Eq (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Ord (PParamsHKD StrictMaybe era) => Ord (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Show (PParamsHKD StrictMaybe era) => Show (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Generic (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Associated Types

type Rep (PParamsUpdate era) :: Type -> Type Source #

Methods

from :: PParamsUpdate era -> Rep (PParamsUpdate era) x Source #

to :: Rep (PParamsUpdate era) x -> PParamsUpdate era Source #

NFData (PParamsHKD StrictMaybe era) => NFData (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

rnf :: PParamsUpdate era -> () Source #

(Typeable era, DecCBOR (PParamsHKD StrictMaybe era)) => DecCBOR (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

decCBOR :: Decoder s (PParamsUpdate era)

dropCBOR :: Proxy (PParamsUpdate era) -> Decoder s ()

label :: Proxy (PParamsUpdate era) -> Text

EraPParams era => Default (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

def :: PParamsUpdate era

(Typeable era, EncCBOR (PParamsHKD StrictMaybe era)) => EncCBOR (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

encCBOR :: PParamsUpdate era -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (PParamsUpdate era) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [PParamsUpdate era] -> Size

(Typeable era, FromCBOR (PParamsHKD StrictMaybe era)) => FromCBOR (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

fromCBOR :: Decoder s (PParamsUpdate era) #

label :: Proxy (PParamsUpdate era) -> Text #

FromJSON (PParamsHKD StrictMaybe era) => FromJSON (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

parseJSON :: Value -> Parser (PParamsUpdate era) #

parseJSONList :: Value -> Parser [PParamsUpdate era] #

omittedField :: Maybe (PParamsUpdate era) #

NoThunks (PParamsHKD StrictMaybe era) => NoThunks (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

noThunks :: Context -> PParamsUpdate era -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> PParamsUpdate era -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (PParamsUpdate era) -> String

(Typeable era, ToCBOR (PParamsHKD StrictMaybe era)) => ToCBOR (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

toCBOR :: PParamsUpdate era -> Encoding #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (PParamsUpdate era) -> Size #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [PParamsUpdate era] -> Size #

ToExpr (PParamsHKD StrictMaybe era) => ToExpr (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

toExpr :: PParamsUpdate era -> Expr

listToExpr :: [PParamsUpdate era] -> Expr

ToJSON (PParamsHKD StrictMaybe era) => ToJSON (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

toJSON :: PParamsUpdate era -> Value #

toEncoding :: PParamsUpdate era -> Encoding #

toJSONList :: [PParamsUpdate era] -> Value #

toEncodingList :: [PParamsUpdate era] -> Encoding #

omitField :: PParamsUpdate era -> Bool #

type Rep (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

type Rep (PParamsUpdate era) = D1 ('MetaData "PParamsUpdate" "Cardano.Ledger.Core.PParams" "cardano-ledger-core-1.9.0.0-E3793VXyLODIfmloH8Sp2j" 'True) (C1 ('MetaCons "PParamsUpdate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PParamsHKD StrictMaybe era))))
type TranslationError (MaryEra c) PParamsUpdate 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) PParamsUpdate = Void
type TranslationError (AllegraEra c) PParamsUpdate 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

type TranslationError (AllegraEra c) PParamsUpdate = Void

type family Value era #

Instances

Instances details
type Value (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type Value (AlonzoEra c) = MaryValue c
type Value (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type Value (MaryEra c) = MaryValue c
type Value (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type Value (ConwayEra c) = MaryValue c
type Value (ShelleyEra _c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type Value (ShelleyEra _c) = Coin
type Value (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type Value (BabbageEra c) = MaryValue c
type Value (AllegraEra _1) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type Value (AllegraEra _1) = Coin

addDeltaCoin :: Coin -> DeltaCoin -> Coin #

toDeltaCoin :: Coin -> DeltaCoin #

toEraCBOR :: (Era era, EncCBOR t) => t -> Encoding #

fromEraCBOR :: (Era era, DecCBOR t) => Decoder s t #

data Anchor c #

Constructors

Anchor 

Fields

Instances

Instances details
Eq (Anchor c) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

(==) :: Anchor c -> Anchor c -> Bool Source #

(/=) :: Anchor c -> Anchor c -> Bool Source #

Ord (Anchor c) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

compare :: Anchor c -> Anchor c -> Ordering Source #

(<) :: Anchor c -> Anchor c -> Bool Source #

(<=) :: Anchor c -> Anchor c -> Bool Source #

(>) :: Anchor c -> Anchor c -> Bool Source #

(>=) :: Anchor c -> Anchor c -> Bool Source #

max :: Anchor c -> Anchor c -> Anchor c Source #

min :: Anchor c -> Anchor c -> Anchor c Source #

Show (Anchor c) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Generic (Anchor c) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Associated Types

type Rep (Anchor c) :: Type -> Type Source #

Methods

from :: Anchor c -> Rep (Anchor c) x Source #

to :: Rep (Anchor c) x -> Anchor c Source #

Crypto c => NFData (Anchor c) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

rnf :: Anchor c -> () Source #

Crypto c => DecCBOR (Anchor c) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

decCBOR :: Decoder s (Anchor c)

dropCBOR :: Proxy (Anchor c) -> Decoder s ()

label :: Proxy (Anchor c) -> Text

Crypto c => Default (Anchor c) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

def :: Anchor c

Crypto c => EncCBOR (Anchor c) 
Instance details

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) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

parseJSON :: Value -> Parser (Anchor c) #

parseJSONList :: Value -> Parser [Anchor c] #

omittedField :: Maybe (Anchor c) #

NoThunks (Anchor c) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

noThunks :: Context -> Anchor c -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Anchor c -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (Anchor c) -> String

ToExpr (Anchor c) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toExpr :: Anchor c -> Expr

listToExpr :: [Anchor c] -> Expr

Crypto c => ToJSON (Anchor c) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: Anchor c -> Value #

toEncoding :: Anchor c -> Encoding #

toJSONList :: [Anchor c] -> Value #

toEncodingList :: [Anchor c] -> Encoding #

omitField :: Anchor c -> Bool #

type Rep (Anchor c) 
Instance details

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))))

data Delegatee c #

Instances

Instances details
Eq (Delegatee c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Ord (Delegatee c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Show (Delegatee c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Generic (Delegatee c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Associated Types

type Rep (Delegatee c) :: Type -> Type Source #

Methods

from :: Delegatee c -> Rep (Delegatee c) x Source #

to :: Rep (Delegatee c) x -> Delegatee c Source #

NFData (Delegatee c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

rnf :: Delegatee c -> () Source #

NoThunks (Delegatee c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

noThunks :: Context -> Delegatee c -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Delegatee c -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (Delegatee c) -> String

ToExpr (Delegatee c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

toExpr :: Delegatee c -> Expr

listToExpr :: [Delegatee c] -> Expr

type Rep (Delegatee c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

type Rep (Delegatee c) = D1 ('MetaData "Delegatee" "Cardano.Ledger.Conway.TxCert" "cardano-ledger-conway-1.11.0.0-IXkLH2MRV78Js391X7GYkZ" '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 DRep c #

Bundled Patterns

pattern DRepCredential :: Credential 'DRepRole c -> DRep c 

Instances

Instances details
Eq (DRep c) 
Instance details

Defined in Cardano.Ledger.DRep

Methods

(==) :: DRep c -> DRep c -> Bool Source #

(/=) :: DRep c -> DRep c -> Bool Source #

Ord (DRep c) 
Instance details

Defined in Cardano.Ledger.DRep

Methods

compare :: DRep c -> DRep c -> Ordering Source #

(<) :: DRep c -> DRep c -> Bool Source #

(<=) :: DRep c -> DRep c -> Bool Source #

(>) :: DRep c -> DRep c -> Bool Source #

(>=) :: DRep c -> DRep c -> Bool Source #

max :: DRep c -> DRep c -> DRep c Source #

min :: DRep c -> DRep c -> DRep c Source #

Show (DRep c) 
Instance details

Defined in Cardano.Ledger.DRep

Methods

showsPrec :: Int -> DRep c -> ShowS Source #

show :: DRep c -> String Source #

showList :: [DRep c] -> ShowS Source #

Generic (DRep c) 
Instance details

Defined in Cardano.Ledger.DRep

Associated Types

type Rep (DRep c) :: Type -> Type Source #

Methods

from :: DRep c -> Rep (DRep c) x Source #

to :: Rep (DRep c) x -> DRep c Source #

NFData (DRep c) 
Instance details

Defined in Cardano.Ledger.DRep

Methods

rnf :: DRep c -> () Source #

Crypto c => DecCBOR (DRep c) 
Instance details

Defined in Cardano.Ledger.DRep

Methods

decCBOR :: Decoder s (DRep c)

dropCBOR :: Proxy (DRep c) -> Decoder s ()

label :: Proxy (DRep c) -> Text

Crypto c => EncCBOR (DRep c) 
Instance details

Defined in Cardano.Ledger.DRep

Methods

encCBOR :: DRep c -> Encoding

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) 
Instance details

Defined in Cardano.Ledger.DRep

Methods

parseJSON :: Value -> Parser (DRep c) #

parseJSONList :: Value -> Parser [DRep c] #

omittedField :: Maybe (DRep c) #

NoThunks (DRep c) 
Instance details

Defined in Cardano.Ledger.DRep

Methods

noThunks :: Context -> DRep c -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> DRep c -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (DRep c) -> String

ToExpr (DRep c) 
Instance details

Defined in Cardano.Ledger.DRep

Methods

toExpr :: DRep c -> Expr

listToExpr :: [DRep c] -> Expr

Crypto c => ToJSON (DRep c) 
Instance details

Defined in Cardano.Ledger.DRep

Methods

toJSON :: DRep c -> Value #

toEncoding :: DRep c -> Encoding #

toJSONList :: [DRep c] -> Value #

toEncodingList :: [DRep c] -> Encoding #

omitField :: DRep c -> Bool #

Crypto c => ToJSONKey (DRep c) 
Instance details

Defined in Cardano.Ledger.DRep

Methods

toJSONKey :: ToJSONKeyFunction (DRep c)

toJSONKeyList :: ToJSONKeyFunction [DRep c]

Crypto c => FromJSONKey (DRep c) 
Instance details

Defined in Cardano.Ledger.DRep

Methods

fromJSONKey :: FromJSONKeyFunction (DRep c)

fromJSONKeyList :: FromJSONKeyFunction [DRep c]

type Rep (DRep c) 
Instance details

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)))

data DRepState c #

Instances

Instances details
Eq (DRepState c) 
Instance details

Defined in Cardano.Ledger.DRep

Ord (DRepState c) 
Instance details

Defined in Cardano.Ledger.DRep

Show (DRepState c) 
Instance details

Defined in Cardano.Ledger.DRep

Generic (DRepState c) 
Instance details

Defined in Cardano.Ledger.DRep

Associated Types

type Rep (DRepState c) :: Type -> Type Source #

Methods

from :: DRepState c -> Rep (DRepState c) x Source #

to :: Rep (DRepState c) x -> DRepState c Source #

Crypto c => NFData (DRepState c) 
Instance details

Defined in Cardano.Ledger.DRep

Methods

rnf :: DRepState c -> () Source #

Crypto c => DecCBOR (DRepState c) 
Instance details

Defined in Cardano.Ledger.DRep

Methods

decCBOR :: Decoder s (DRepState c)

dropCBOR :: Proxy (DRepState c) -> Decoder s ()

label :: Proxy (DRepState c) -> Text

Crypto c => EncCBOR (DRepState c) 
Instance details

Defined in Cardano.Ledger.DRep

Methods

encCBOR :: DRepState c -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (DRepState c) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [DRepState c] -> Size

NoThunks (DRepState era) 
Instance details

Defined in Cardano.Ledger.DRep

Methods

noThunks :: Context -> DRepState era -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> DRepState era -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (DRepState era) -> String

ToExpr (DRepState c) 
Instance details

Defined in Cardano.Ledger.DRep

Methods

toExpr :: DRepState c -> Expr

listToExpr :: [DRepState c] -> Expr

Crypto c => ToJSON (DRepState c) 
Instance details

Defined in Cardano.Ledger.DRep

Methods

toJSON :: DRepState c -> Value #

toEncoding :: DRepState c -> Encoding #

toJSONList :: [DRepState c] -> Value #

toEncodingList :: [DRepState c] -> Encoding #

omitField :: DRepState c -> Bool #

type Rep (DRepState c) 
Instance details

Defined in Cardano.Ledger.DRep

type Rep (DRepState c) = D1 ('MetaData "DRepState" "Cardano.Ledger.DRep" "cardano-ledger-core-1.9.0.0-E3793VXyLODIfmloH8Sp2j" '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))))

data ConwayTxCert era #

Instances

Instances details
Eq (ConwayTxCert era) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Ord (ConwayTxCert era) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Show (ConwayTxCert era) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Generic (ConwayTxCert era) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Associated Types

type Rep (ConwayTxCert era) :: Type -> Type Source #

Methods

from :: ConwayTxCert era -> Rep (ConwayTxCert era) x Source #

to :: Rep (ConwayTxCert era) x -> ConwayTxCert era Source #

Crypto (EraCrypto era) => NFData (ConwayTxCert era) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

rnf :: ConwayTxCert era -> () Source #

(ConwayEraTxCert era, TxCert era ~ ConwayTxCert era) => DecCBOR (ConwayTxCert era) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

decCBOR :: Decoder s (ConwayTxCert era)

dropCBOR :: Proxy (ConwayTxCert era) -> Decoder s ()

label :: Proxy (ConwayTxCert era) -> Text

(Era era, Val (Value era)) => EncCBOR (ConwayTxCert era) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

encCBOR :: ConwayTxCert era -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (ConwayTxCert era) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ConwayTxCert era] -> Size

(ShelleyEraTxCert era, TxCert era ~ ConwayTxCert era) => FromCBOR (ConwayTxCert era) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

fromCBOR :: Decoder s (ConwayTxCert era) #

label :: Proxy (ConwayTxCert era) -> Text #

NoThunks (ConwayTxCert era) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

noThunks :: Context -> ConwayTxCert era -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> ConwayTxCert era -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (ConwayTxCert era) -> String

(Era era, Val (Value era)) => ToCBOR (ConwayTxCert era) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

toCBOR :: ConwayTxCert era -> Encoding #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ConwayTxCert era) -> Size #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ConwayTxCert era] -> Size #

ToExpr (ConwayTxCert c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

toExpr :: ConwayTxCert c -> Expr

listToExpr :: [ConwayTxCert c] -> Expr

Show (ConwayTxCert c) => ToJSON (ConwayTxCert c) Source # 
Instance details

Defined in Cardano.Api.Orphans

Methods

toJSON :: ConwayTxCert c -> Value #

toEncoding :: ConwayTxCert c -> Encoding #

toJSONList :: [ConwayTxCert c] -> Value #

toEncodingList :: [ConwayTxCert c] -> Encoding #

omitField :: ConwayTxCert c -> Bool #

type Rep (ConwayTxCert era) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

type Rep (ConwayTxCert era) = D1 ('MetaData "ConwayTxCert" "Cardano.Ledger.Conway.TxCert" "cardano-ledger-conway-1.11.0.0-IXkLH2MRV78Js391X7GYkZ" '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))))))

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

Instances details
Eq (ConwayDelegCert c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Ord (ConwayDelegCert c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Show (ConwayDelegCert c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Generic (ConwayDelegCert c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Associated Types

type Rep (ConwayDelegCert c) :: Type -> Type Source #

NFData (ConwayDelegCert c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

rnf :: ConwayDelegCert c -> () Source #

NoThunks (ConwayDelegCert c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

noThunks :: Context -> ConwayDelegCert c -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> ConwayDelegCert c -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (ConwayDelegCert c) -> String

ToExpr (ConwayDelegCert c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

toExpr :: ConwayDelegCert c -> Expr

listToExpr :: [ConwayDelegCert c] -> Expr

type Rep (ConwayDelegCert c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

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

Instances details
Crypto c => ConwayEraTxCert (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

mkRegDepositTxCert :: StakeCredential (EraCrypto (ConwayEra c)) -> Coin -> TxCert (ConwayEra c) #

getRegDepositTxCert :: TxCert (ConwayEra c) -> Maybe (StakeCredential (EraCrypto (ConwayEra c)), Coin) #

mkUnRegDepositTxCert :: StakeCredential (EraCrypto (ConwayEra c)) -> Coin -> TxCert (ConwayEra c) #

getUnRegDepositTxCert :: TxCert (ConwayEra c) -> Maybe (StakeCredential (EraCrypto (ConwayEra c)), Coin) #

mkDelegTxCert :: StakeCredential (EraCrypto (ConwayEra c)) -> Delegatee (EraCrypto (ConwayEra c)) -> TxCert (ConwayEra c) #

getDelegTxCert :: TxCert (ConwayEra c) -> Maybe (StakeCredential (EraCrypto (ConwayEra c)), Delegatee (EraCrypto (ConwayEra c))) #

mkRegDepositDelegTxCert :: StakeCredential (EraCrypto (ConwayEra c)) -> Delegatee (EraCrypto (ConwayEra c)) -> Coin -> TxCert (ConwayEra c) #

getRegDepositDelegTxCert :: TxCert (ConwayEra c) -> Maybe (StakeCredential (EraCrypto (ConwayEra c)), Delegatee (EraCrypto (ConwayEra c)), Coin) #

mkAuthCommitteeHotKeyTxCert :: Credential 'ColdCommitteeRole (EraCrypto (ConwayEra c)) -> Credential 'HotCommitteeRole (EraCrypto (ConwayEra c)) -> TxCert (ConwayEra c) #

getAuthCommitteeHotKeyTxCert :: TxCert (ConwayEra c) -> Maybe (Credential 'ColdCommitteeRole (EraCrypto (ConwayEra c)), Credential 'HotCommitteeRole (EraCrypto (ConwayEra c))) #

mkResignCommitteeColdTxCert :: Credential 'ColdCommitteeRole (EraCrypto (ConwayEra c)) -> StrictMaybe (Anchor (EraCrypto (ConwayEra c))) -> TxCert (ConwayEra c) #

getResignCommitteeColdTxCert :: TxCert (ConwayEra c) -> Maybe (Credential 'ColdCommitteeRole (EraCrypto (ConwayEra c)), StrictMaybe (Anchor (EraCrypto (ConwayEra c)))) #

mkRegDRepTxCert :: Credential 'DRepRole (EraCrypto (ConwayEra c)) -> Coin -> StrictMaybe (Anchor (EraCrypto (ConwayEra c))) -> TxCert (ConwayEra c) #

getRegDRepTxCert :: TxCert (ConwayEra c) -> Maybe (Credential 'DRepRole (EraCrypto (ConwayEra c)), Coin, StrictMaybe (Anchor (EraCrypto (ConwayEra c)))) #

mkUnRegDRepTxCert :: Credential 'DRepRole (EraCrypto (ConwayEra c)) -> Coin -> TxCert (ConwayEra c) #

getUnRegDRepTxCert :: TxCert (ConwayEra c) -> Maybe (Credential 'DRepRole (EraCrypto (ConwayEra c)), Coin) #

mkUpdateDRepTxCert :: Credential 'DRepRole (EraCrypto (ConwayEra c)) -> StrictMaybe (Anchor (EraCrypto (ConwayEra c))) -> TxCert (ConwayEra c) #

getUpdateDRepTxCert :: TxCert (ConwayEra c) -> Maybe (Credential 'DRepRole (EraCrypto (ConwayEra c)), StrictMaybe (Anchor (EraCrypto (ConwayEra c)))) #

data ConwayGovCert c #

Instances

Instances details
Eq (ConwayGovCert c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Ord (ConwayGovCert c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Show (ConwayGovCert c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Generic (ConwayGovCert c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Associated Types

type Rep (ConwayGovCert c) :: Type -> Type Source #

Crypto c => NFData (ConwayGovCert c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

rnf :: ConwayGovCert c -> () Source #

NoThunks (ConwayGovCert c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

noThunks :: Context -> ConwayGovCert c -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> ConwayGovCert c -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (ConwayGovCert c) -> String

ToExpr (ConwayGovCert c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

toExpr :: ConwayGovCert c -> Expr

listToExpr :: [ConwayGovCert c] -> Expr

type Rep (ConwayGovCert c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

type Rep (ConwayGovCert c) = D1 ('MetaData "ConwayGovCert" "Cardano.Ledger.Conway.TxCert" "cardano-ledger-conway-1.11.0.0-IXkLH2MRV78Js391X7GYkZ" '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)))))))

type family GovState era = (r :: Type) | r -> era #

Instances

Instances details
type GovState (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

type GovState (AlonzoEra c) = ShelleyGovState (AlonzoEra c)
type GovState (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.PParams

type GovState (MaryEra c) = ShelleyGovState (MaryEra c)
type GovState (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

type GovState (ConwayEra c) = ConwayGovState (ConwayEra c)
type GovState (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

type GovState (ShelleyEra c) = ShelleyGovState (ShelleyEra c)
type GovState (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.PParams

type GovState (BabbageEra c) = ShelleyGovState (BabbageEra c)
type GovState (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.PParams

type GovState (AllegraEra c) = ShelleyGovState (AllegraEra c)

data GovActionId c #

Constructors

GovActionId 

Fields

Instances

Instances details
Eq (GovActionId c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Ord (GovActionId c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Show (GovActionId c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Generic (GovActionId c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Associated Types

type Rep (GovActionId c) :: Type -> Type Source #

Crypto c => NFData (GovActionId c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

rnf :: GovActionId c -> () Source #

Crypto c => DecCBOR (GovActionId c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

decCBOR :: Decoder s (GovActionId c)

dropCBOR :: Proxy (GovActionId c) -> Decoder s ()

label :: Proxy (GovActionId c) -> Text

Crypto c => EncCBOR (GovActionId c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

encCBOR :: GovActionId c -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (GovActionId c) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [GovActionId c] -> Size

NoThunks (GovActionId c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

noThunks :: Context -> GovActionId c -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> GovActionId c -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (GovActionId c) -> String

ToExpr (GovActionId c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toExpr :: GovActionId c -> Expr

listToExpr :: [GovActionId c] -> Expr

Crypto c => ToJSON (GovActionId c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

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) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toJSONKey :: ToJSONKeyFunction (GovActionId c)

toJSONKeyList :: ToJSONKeyFunction [GovActionId c]

c ~ EraCrypto era => HasOKey (GovActionId c) (GovActionState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

okeyL :: Lens' (GovActionState era) (GovActionId c)

type Rep (GovActionId c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

type Rep (GovActionId c) = D1 ('MetaData "GovActionId" "Cardano.Ledger.Conway.Governance.Procedures" "cardano-ledger-conway-1.11.0.0-IXkLH2MRV78Js391X7GYkZ" '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)))

data Vote #

Constructors

VoteNo 
VoteYes 
Abstain 

Instances

Instances details
Bounded Vote 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Enum Vote 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Eq Vote 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

(==) :: Vote -> Vote -> Bool Source #

(/=) :: Vote -> Vote -> Bool Source #

Show Vote 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Generic Vote 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Associated Types

type Rep Vote :: Type -> Type Source #

Methods

from :: Vote -> Rep Vote x Source #

to :: Rep Vote x -> Vote Source #

NFData Vote 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

rnf :: Vote -> () Source #

DecCBOR Vote 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

decCBOR :: Decoder s Vote

dropCBOR :: Proxy Vote -> Decoder s ()

label :: Proxy Vote -> Text

EncCBOR Vote 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

encCBOR :: Vote -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Vote -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Vote] -> Size

NoThunks Vote 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

noThunks :: Context -> Vote -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Vote -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy Vote -> String

ToExpr Vote 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toExpr :: Vote -> Expr

listToExpr :: [Vote] -> Expr

ToJSON Vote 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toJSON :: Vote -> Value #

toEncoding :: Vote -> Encoding #

toJSONList :: [Vote] -> Value #

toEncodingList :: [Vote] -> Encoding #

omitField :: Vote -> Bool #

type Rep Vote 
Instance details

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)))

data Voter c #

Instances

Instances details
Eq (Voter c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

(==) :: Voter c -> Voter c -> Bool Source #

(/=) :: Voter c -> Voter c -> Bool Source #

Ord (Voter c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

compare :: Voter c -> Voter c -> Ordering Source #

(<) :: Voter c -> Voter c -> Bool Source #

(<=) :: Voter c -> Voter c -> Bool Source #

(>) :: Voter c -> Voter c -> Bool Source #

(>=) :: Voter c -> Voter c -> Bool Source #

max :: Voter c -> Voter c -> Voter c Source #

min :: Voter c -> Voter c -> Voter c Source #

Show (Voter c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Generic (Voter c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Associated Types

type Rep (Voter c) :: Type -> Type Source #

Methods

from :: Voter c -> Rep (Voter c) x Source #

to :: Rep (Voter c) x -> Voter c Source #

NFData (Voter c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

rnf :: Voter c -> () Source #

Crypto c => DecCBOR (Voter c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

decCBOR :: Decoder s (Voter c)

dropCBOR :: Proxy (Voter c) -> Decoder s ()

label :: Proxy (Voter c) -> Text

Crypto c => EncCBOR (Voter c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

encCBOR :: Voter c -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (Voter c) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Voter c] -> Size

NoThunks (Voter c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

noThunks :: Context -> Voter c -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Voter c -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (Voter c) -> String

Crypto c => ToExpr (Voter c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toExpr :: Voter c -> Expr

listToExpr :: [Voter c] -> Expr

Crypto c => ToJSON (Voter c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toJSON :: Voter c -> Value #

toEncoding :: Voter c -> Encoding #

toJSONList :: [Voter c] -> Value #

toEncodingList :: [Voter c] -> Encoding #

omitField :: Voter c -> Bool #

Crypto c => ToJSONKey (Voter c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toJSONKey :: ToJSONKeyFunction (Voter c)

toJSONKeyList :: ToJSONKeyFunction [Voter c]

type Rep (Voter c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

type Rep (Voter c) = D1 ('MetaData "Voter" "Cardano.Ledger.Conway.Governance.Procedures" "cardano-ledger-conway-1.11.0.0-IXkLH2MRV78Js391X7GYkZ" '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 #

Constructors

VotingProcedure 

Instances

Instances details
Eq (VotingProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Show (VotingProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Generic (VotingProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Associated Types

type Rep (VotingProcedure era) :: Type -> Type Source #

Crypto (EraCrypto era) => NFData (VotingProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

rnf :: VotingProcedure era -> () Source #

Era era => DecCBOR (VotingProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

decCBOR :: Decoder s (VotingProcedure era)

dropCBOR :: Proxy (VotingProcedure era) -> Decoder s ()

label :: Proxy (VotingProcedure era) -> Text

Era era => EncCBOR (VotingProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

encCBOR :: VotingProcedure era -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (VotingProcedure era) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [VotingProcedure era] -> Size

NoThunks (VotingProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

noThunks :: Context -> VotingProcedure era -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> VotingProcedure era -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (VotingProcedure era) -> String

ToExpr (VotingProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toExpr :: VotingProcedure era -> Expr

listToExpr :: [VotingProcedure era] -> Expr

EraPParams era => ToJSON (VotingProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toJSON :: VotingProcedure era -> Value #

toEncoding :: VotingProcedure era -> Encoding #

toJSONList :: [VotingProcedure era] -> Value #

toEncodingList :: [VotingProcedure era] -> Encoding #

omitField :: VotingProcedure era -> Bool #

type Rep (VotingProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

type Rep (VotingProcedure era) = D1 ('MetaData "VotingProcedure" "Cardano.Ledger.Conway.Governance.Procedures" "cardano-ledger-conway-1.11.0.0-IXkLH2MRV78Js391X7GYkZ" '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))))))

data PoolVotingThresholds #

Constructors

PoolVotingThresholds 

Fields

Instances

Instances details
Eq PoolVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

Ord PoolVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

Show PoolVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

Generic PoolVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

Associated Types

type Rep PoolVotingThresholds :: Type -> Type Source #

NFData PoolVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

DecCBOR PoolVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

Default PoolVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

EncCBOR PoolVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

Methods

encCBOR :: PoolVotingThresholds -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy PoolVotingThresholds -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [PoolVotingThresholds] -> Size

NoThunks PoolVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

Methods

noThunks :: Context -> PoolVotingThresholds -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> PoolVotingThresholds -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy PoolVotingThresholds -> String

ToExpr PoolVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

ToJSON PoolVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

type Rep PoolVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

type Rep PoolVotingThresholds = D1 ('MetaData "PoolVotingThresholds" "Cardano.Ledger.Conway.Core" "cardano-ledger-conway-1.11.0.0-IXkLH2MRV78Js391X7GYkZ" '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))))

data DRepVotingThresholds #

Constructors

DRepVotingThresholds 

Fields

Instances

Instances details
Eq DRepVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

Ord DRepVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

Show DRepVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

Generic DRepVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

Associated Types

type Rep DRepVotingThresholds :: Type -> Type Source #

NFData DRepVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

DecCBOR DRepVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

Default DRepVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

EncCBOR DRepVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

Methods

encCBOR :: DRepVotingThresholds -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy DRepVotingThresholds -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [DRepVotingThresholds] -> Size

NoThunks DRepVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

Methods

noThunks :: Context -> DRepVotingThresholds -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> DRepVotingThresholds -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy DRepVotingThresholds -> String

ToExpr DRepVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

ToJSON DRepVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

type Rep DRepVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.Core

type Rep DRepVotingThresholds = D1 ('MetaData "DRepVotingThresholds" "Cardano.Ledger.Conway.Core" "cardano-ledger-conway-1.11.0.0-IXkLH2MRV78Js391X7GYkZ" '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))))))

dvtPPGovGroupL :: Lens' DRepVotingThresholds UnitInterval #

csCommitteeCredsL :: Lens' (CommitteeState era) (Map (Credential 'ColdCommitteeRole (EraCrypto era)) (Maybe (Credential 'HotCommitteeRole (EraCrypto era)))) #

data Annotated b a #

Instances

Instances details
Bifunctor Annotated 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Methods

bimap :: (a -> b) -> (c -> d) -> Annotated a c -> Annotated b d Source #

first :: (a -> b) -> Annotated a c -> Annotated b c Source #

second :: (b -> c) -> Annotated a b -> Annotated a c Source #

Functor (Annotated b) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Methods

fmap :: (a -> b0) -> Annotated b a -> Annotated b b0 Source #

(<$) :: a -> Annotated b b0 -> Annotated b a Source #

(Eq b, Eq a) => Eq (Annotated b a) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Methods

(==) :: Annotated b a -> Annotated b a -> Bool Source #

(/=) :: Annotated b a -> Annotated b a -> Bool Source #

(Eq a, Ord b) => Ord (Annotated b a) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Methods

compare :: Annotated b a -> Annotated b a -> Ordering Source #

(<) :: Annotated b a -> Annotated b a -> Bool Source #

(<=) :: Annotated b a -> Annotated b a -> Bool Source #

(>) :: Annotated b a -> Annotated b a -> Bool Source #

(>=) :: Annotated b a -> Annotated b a -> Bool Source #

max :: Annotated b a -> Annotated b a -> Annotated b a Source #

min :: Annotated b a -> Annotated b a -> Annotated b a Source #

(Show b, Show a) => Show (Annotated b a) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Generic (Annotated b a) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Associated Types

type Rep (Annotated b a) :: Type -> Type Source #

Methods

from :: Annotated b a -> Rep (Annotated b a) x Source #

to :: Rep (Annotated b a) x -> Annotated b a Source #

(NFData b, NFData a) => NFData (Annotated b a) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Methods

rnf :: Annotated b a -> () Source #

FromJSON b => FromJSON (Annotated b ()) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Methods

parseJSON :: Value -> Parser (Annotated b ()) #

parseJSONList :: Value -> Parser [Annotated b ()] #

omittedField :: Maybe (Annotated b ()) #

(NoThunks b, NoThunks a) => NoThunks (Annotated b a) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Methods

noThunks :: Context -> Annotated b a -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Annotated b a -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (Annotated b a) -> String

ToJSON b => ToJSON (Annotated b a) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Methods

toJSON :: Annotated b a -> Value #

toEncoding :: Annotated b a -> Encoding #

toJSONList :: [Annotated b a] -> Value #

toEncodingList :: [Annotated b a] -> Encoding #

omitField :: Annotated b a -> Bool #

Decoded (Annotated b ByteString) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Associated Types

type BaseType (Annotated b ByteString)

Methods

recoverBytes :: Annotated b ByteString -> ByteString

HasSignTag (Annotated ToSign ByteString) 
Instance details

Defined in Ouroboros.Consensus.Byron.Crypto.DSIGN

Methods

signTag :: VerKeyDSIGN ByronDSIGN -> proxy (Annotated ToSign ByteString) -> SignTag

type Rep (Annotated b a) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

type Rep (Annotated b a) = D1 ('MetaData "Annotated" "Cardano.Ledger.Binary.Decoding.Annotated" "cardano-ledger-binary-1.2.1.0-EQt4PWZgpPV1fB4boyuZZq" '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) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

type BaseType (Annotated b ByteString) = b

data Tx #

Constructors

UnsafeTx 

Fields

Instances

Instances details
Eq Tx 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Methods

(==) :: Tx -> Tx -> Bool Source #

(/=) :: Tx -> Tx -> Bool Source #

Ord Tx 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Methods

compare :: Tx -> Tx -> Ordering Source #

(<) :: Tx -> Tx -> Bool Source #

(<=) :: Tx -> Tx -> Bool Source #

(>) :: Tx -> Tx -> Bool Source #

(>=) :: Tx -> Tx -> Bool Source #

max :: Tx -> Tx -> Tx Source #

min :: Tx -> Tx -> Tx Source #

Show Tx 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Generic Tx 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Associated Types

type Rep Tx :: Type -> Type Source #

Methods

from :: Tx -> Rep Tx x Source #

to :: Rep Tx x -> Tx Source #

NFData Tx 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Methods

rnf :: Tx -> () Source #

DecCBOR Tx 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Methods

decCBOR :: Decoder s Tx

dropCBOR :: Proxy Tx -> Decoder s ()

label :: Proxy Tx -> Text

EncCBOR Tx 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Methods

encCBOR :: Tx -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Tx -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Tx] -> Size

FromCBOR Tx 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Methods

fromCBOR :: Decoder s Tx #

label :: Proxy Tx -> Text #

ToCBOR Tx 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Methods

toCBOR :: Tx -> Encoding #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy Tx -> Size #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Tx] -> Size #

ToJSON Tx 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Methods

toJSON :: Tx -> Value #

toEncoding :: Tx -> Encoding #

toJSONList :: [Tx] -> Value #

toEncodingList :: [Tx] -> Encoding #

omitField :: Tx -> Bool #

Buildable Tx 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Methods

build :: Tx -> Builder

type Rep Tx 
Instance details

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

Instances details
Eq CoinPerByte 
Instance details

Defined in Cardano.Ledger.Babbage.Core

Ord CoinPerByte 
Instance details

Defined in Cardano.Ledger.Babbage.Core

Show CoinPerByte 
Instance details

Defined in Cardano.Ledger.Babbage.Core

NFData CoinPerByte 
Instance details

Defined in Cardano.Ledger.Babbage.Core

Methods

rnf :: CoinPerByte -> () Source #

DecCBOR CoinPerByte 
Instance details

Defined in Cardano.Ledger.Babbage.Core

Methods

decCBOR :: Decoder s CoinPerByte

dropCBOR :: Proxy CoinPerByte -> Decoder s ()

label :: Proxy CoinPerByte -> Text

EncCBOR CoinPerByte 
Instance details

Defined in Cardano.Ledger.Babbage.Core

Methods

encCBOR :: CoinPerByte -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy CoinPerByte -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [CoinPerByte] -> Size

FromJSON CoinPerByte 
Instance details

Defined in Cardano.Ledger.Babbage.Core

Methods

parseJSON :: Value -> Parser CoinPerByte #

parseJSONList :: Value -> Parser [CoinPerByte] #

omittedField :: Maybe CoinPerByte #

NoThunks CoinPerByte 
Instance details

Defined in Cardano.Ledger.Babbage.Core

Methods

noThunks :: Context -> CoinPerByte -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> CoinPerByte -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy CoinPerByte -> String

ToExpr CoinPerByte 
Instance details

Defined in Cardano.Ledger.Babbage.Core

Methods

toExpr :: CoinPerByte -> Expr

listToExpr :: [CoinPerByte] -> Expr

ToJSON CoinPerByte 
Instance details

Defined in Cardano.Ledger.Babbage.Core

Methods

toJSON :: CoinPerByte -> Value #

toEncoding :: CoinPerByte -> Encoding #

toJSONList :: [CoinPerByte] -> Value #

toEncodingList :: [CoinPerByte] -> Encoding #

omitField :: CoinPerByte -> Bool #

newtype CoinPerWord #

Constructors

CoinPerWord 

Fields

Instances

Instances details
Eq CoinPerWord 
Instance details

Defined in Cardano.Ledger.Alonzo.Core

Ord CoinPerWord 
Instance details

Defined in Cardano.Ledger.Alonzo.Core

Show CoinPerWord 
Instance details

Defined in Cardano.Ledger.Alonzo.Core

NFData CoinPerWord 
Instance details

Defined in Cardano.Ledger.Alonzo.Core

Methods

rnf :: CoinPerWord -> () Source #

DecCBOR CoinPerWord 
Instance details

Defined in Cardano.Ledger.Alonzo.Core

Methods

decCBOR :: Decoder s CoinPerWord

dropCBOR :: Proxy CoinPerWord -> Decoder s ()

label :: Proxy CoinPerWord -> Text

EncCBOR CoinPerWord 
Instance details

Defined in Cardano.Ledger.Alonzo.Core

Methods

encCBOR :: CoinPerWord -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy CoinPerWord -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [CoinPerWord] -> Size

FromJSON CoinPerWord 
Instance details

Defined in Cardano.Ledger.Alonzo.Core

Methods

parseJSON :: Value -> Parser CoinPerWord #

parseJSONList :: Value -> Parser [CoinPerWord] #

omittedField :: Maybe CoinPerWord #

NoThunks CoinPerWord 
Instance details

Defined in Cardano.Ledger.Alonzo.Core

Methods

noThunks :: Context -> CoinPerWord -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> CoinPerWord -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy CoinPerWord -> String

ToExpr CoinPerWord 
Instance details

Defined in Cardano.Ledger.Alonzo.Core

Methods

toExpr :: CoinPerWord -> Expr

listToExpr :: [CoinPerWord] -> Expr

ToJSON CoinPerWord 
Instance details

Defined in Cardano.Ledger.Alonzo.Core

Methods

toJSON :: CoinPerWord -> Value #

toEncoding :: CoinPerWord -> Encoding #

toJSONList :: [CoinPerWord] -> Value #

toEncodingList :: [CoinPerWord] -> Encoding #

omitField :: CoinPerWord -> Bool #

data Prices #

Constructors

Prices 

Fields

  • prMem :: !NonNegativeInterval
     
  • prSteps :: !NonNegativeInterval
     

Instances

Instances details
Eq Prices 
Instance details

Defined in Cardano.Ledger.Plutus.ExUnits

Ord Prices 
Instance details

Defined in Cardano.Ledger.Plutus.ExUnits

Show Prices 
Instance details

Defined in Cardano.Ledger.Plutus.ExUnits

Generic Prices 
Instance details

Defined in Cardano.Ledger.Plutus.ExUnits

Associated Types

type Rep Prices :: Type -> Type Source #

NFData Prices 
Instance details

Defined in Cardano.Ledger.Plutus.ExUnits

Methods

rnf :: Prices -> () Source #

DecCBOR Prices 
Instance details

Defined in Cardano.Ledger.Plutus.ExUnits

Methods

decCBOR :: Decoder s Prices

dropCBOR :: Proxy Prices -> Decoder s ()

label :: Proxy Prices -> Text

EncCBOR Prices 
Instance details

Defined in Cardano.Ledger.Plutus.ExUnits

Methods

encCBOR :: Prices -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Prices -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Prices] -> Size

FromJSON Prices 
Instance details

Defined in Cardano.Ledger.Plutus.ExUnits

Methods

parseJSON :: Value -> Parser Prices #

parseJSONList :: Value -> Parser [Prices] #

omittedField :: Maybe Prices #

NoThunks Prices 
Instance details

Defined in Cardano.Ledger.Plutus.ExUnits

Methods

noThunks :: Context -> Prices -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Prices -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy Prices -> String

ToExpr Prices 
Instance details

Defined in Cardano.Ledger.Plutus.ExUnits

Methods

toExpr :: Prices -> Expr

listToExpr :: [Prices] -> Expr

ToJSON Prices 
Instance details

Defined in Cardano.Ledger.Plutus.ExUnits

Methods

toJSON :: Prices -> Value #

toEncoding :: Prices -> Encoding #

toJSONList :: [Prices] -> Value #

toEncodingList :: [Prices] -> Encoding #

omitField :: Prices -> Bool #

type Rep Prices 
Instance details

Defined in Cardano.Ledger.Plutus.ExUnits

type Rep Prices = D1 ('MetaData "Prices" "Cardano.Ledger.Plutus.ExUnits" "cardano-ledger-core-1.9.0.0-E3793VXyLODIfmloH8Sp2j" 'False) (C1 ('MetaCons "Prices" 'PrefixI 'True) (S1 ('MetaSel ('Just "prMem") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NonNegativeInterval) :*: S1 ('MetaSel ('Just "prSteps") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NonNegativeInterval)))

boundRational :: BoundedRational r => Rational -> Maybe r #

unboundRational :: BoundedRational r => r -> Rational #

data DnsName #

Instances

Instances details
Eq DnsName 
Instance details

Defined in Cardano.Ledger.BaseTypes

Ord DnsName 
Instance details

Defined in Cardano.Ledger.BaseTypes

Show DnsName 
Instance details

Defined in Cardano.Ledger.BaseTypes

Generic DnsName 
Instance details

Defined in Cardano.Ledger.BaseTypes

Associated Types

type Rep DnsName :: Type -> Type Source #

NFData DnsName 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

rnf :: DnsName -> () Source #

DecCBOR DnsName 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

decCBOR :: Decoder s DnsName

dropCBOR :: Proxy DnsName -> Decoder s ()

label :: Proxy DnsName -> Text

EncCBOR DnsName 
Instance details

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 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

parseJSON :: Value -> Parser DnsName #

parseJSONList :: Value -> Parser [DnsName] #

omittedField :: Maybe DnsName #

NoThunks DnsName 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

noThunks :: Context -> DnsName -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> DnsName -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy DnsName -> String

ToExpr DnsName 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toExpr :: DnsName -> Expr

listToExpr :: [DnsName] -> Expr

ToJSON DnsName 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: DnsName -> Value #

toEncoding :: DnsName -> Encoding #

toJSONList :: [DnsName] -> Value #

toEncodingList :: [DnsName] -> Encoding #

omitField :: DnsName -> Bool #

type Rep DnsName 
Instance details

Defined in Cardano.Ledger.BaseTypes

type Rep DnsName = D1 ('MetaData "DnsName" "Cardano.Ledger.BaseTypes" "cardano-ledger-core-1.9.0.0-E3793VXyLODIfmloH8Sp2j" 'True) (C1 ('MetaCons "DnsName" 'PrefixI 'True) (S1 ('MetaSel ('Just "dnsToText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

dnsToText :: DnsName -> Text #

data Url #

Instances

Instances details
Eq Url 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

(==) :: Url -> Url -> Bool Source #

(/=) :: Url -> Url -> Bool Source #

Ord Url 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

compare :: Url -> Url -> Ordering Source #

(<) :: Url -> Url -> Bool Source #

(<=) :: Url -> Url -> Bool Source #

(>) :: Url -> Url -> Bool Source #

(>=) :: Url -> Url -> Bool Source #

max :: Url -> Url -> Url Source #

min :: Url -> Url -> Url Source #

Show Url 
Instance details

Defined in Cardano.Ledger.BaseTypes

Generic Url 
Instance details

Defined in Cardano.Ledger.BaseTypes

Associated Types

type Rep Url :: Type -> Type Source #

Methods

from :: Url -> Rep Url x Source #

to :: Rep Url x -> Url Source #

NFData Url 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

rnf :: Url -> () Source #

DecCBOR Url 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

decCBOR :: Decoder s Url

dropCBOR :: Proxy Url -> Decoder s ()

label :: Proxy Url -> Text

EncCBOR Url 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

encCBOR :: Url -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Url -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Url] -> Size

FromJSON Url 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

parseJSON :: Value -> Parser Url #

parseJSONList :: Value -> Parser [Url] #

omittedField :: Maybe Url #

NoThunks Url 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

noThunks :: Context -> Url -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Url -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy Url -> String

ToExpr Url 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toExpr :: Url -> Expr

listToExpr :: [Url] -> Expr

ToJSON Url 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: Url -> Value #

toEncoding :: Url -> Encoding #

toJSONList :: [Url] -> Value #

toEncodingList :: [Url] -> Encoding #

omitField :: Url -> Bool #

type Rep Url 
Instance details

Defined in Cardano.Ledger.BaseTypes

type Rep Url = D1 ('MetaData "Url" "Cardano.Ledger.BaseTypes" "cardano-ledger-core-1.9.0.0-E3793VXyLODIfmloH8Sp2j" 'True) (C1 ('MetaCons "Url" 'PrefixI 'True) (S1 ('MetaSel ('Just "urlToText") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

urlToText :: Url -> Text #

textToUrl :: Text -> Maybe Url #

portToWord16 :: Port -> Word16 #

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

Instances details
Crypto StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

Associated Types

type HASH StandardCrypto

type ADDRHASH StandardCrypto

type DSIGN StandardCrypto

type KES StandardCrypto

type VRF StandardCrypto

data StandardCrypto #

Instances

Instances details
Crypto StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

Associated Types

type HASH StandardCrypto

type ADDRHASH StandardCrypto

type DSIGN StandardCrypto

type KES StandardCrypto

type VRF StandardCrypto

PraosCrypto StandardCrypto 
Instance details

Defined in Cardano.Protocol.TPraos.API

PraosCrypto StandardCrypto 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

(CardanoHardForkConstraints StandardCrypto, IOLike m) => Protocol m (CardanoBlock StandardCrypto) Source # 
Instance details

Defined in Cardano.Api.Protocol

Associated Types

data ProtocolInfoArgs (CardanoBlock StandardCrypto) Source #

Methods

protocolInfo :: ProtocolInfoArgs (CardanoBlock StandardCrypto) -> (ProtocolInfo (CardanoBlock StandardCrypto), m [BlockForging m (CardanoBlock StandardCrypto)]) Source #

(IOLike m, LedgerSupportsProtocol (ShelleyBlock (TPraos StandardCrypto) (ShelleyEra StandardCrypto))) => Protocol m (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) Source # 
Instance details

Defined in Cardano.Api.Protocol

Associated Types

data ProtocolInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) Source #

Methods

protocolInfo :: ProtocolInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) -> (ProtocolInfo (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley), m [BlockForging m (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley)]) Source #

ToJSON (PoolCert StandardCrypto) Source # 
Instance details

Defined in Cardano.Api.Orphans

ToJSON (GenesisDelegCert StandardCrypto) Source # 
Instance details

Defined in Cardano.Api.Orphans

ToJSON (MIRCert StandardCrypto) Source # 
Instance details

Defined in Cardano.Api.Orphans

ToJSON (ShelleyDelegCert StandardCrypto) Source # 
Instance details

Defined in Cardano.Api.Orphans

ToJSON (MIRTarget StandardCrypto) Source # 
Instance details

Defined in Cardano.Api.Orphans

ToJSON (PraosState StandardCrypto) Source # 
Instance details

Defined in Cardano.Api.Orphans

Methods

toJSON :: PraosState StandardCrypto -> Value #

toEncoding :: PraosState StandardCrypto -> Encoding #

toJSONList :: [PraosState StandardCrypto] -> Value #

toEncodingList :: [PraosState StandardCrypto] -> Encoding #

omitField :: PraosState StandardCrypto -> Bool #

ToJSON (TPraosState StandardCrypto) Source # 
Instance details

Defined in Cardano.Api.Orphans

Methods

toJSON :: TPraosState StandardCrypto -> Value #

toEncoding :: TPraosState StandardCrypto -> Encoding #

toJSONList :: [TPraosState StandardCrypto] -> Value #

toEncodingList :: [TPraosState StandardCrypto] -> Encoding #

omitField :: TPraosState StandardCrypto -> Bool #

ToJSON (ChainDepState StandardCrypto) Source # 
Instance details

Defined in Cardano.Api.Orphans

Methods

toJSON :: ChainDepState StandardCrypto -> Value #

toEncoding :: ChainDepState StandardCrypto -> Encoding #

toJSONList :: [ChainDepState StandardCrypto] -> Value #

toEncodingList :: [ChainDepState StandardCrypto] -> Encoding #

omitField :: ChainDepState StandardCrypto -> Bool #

ToJSON (PrtclState StandardCrypto) Source # 
Instance details

Defined in Cardano.Api.Orphans

Methods

toJSON :: PrtclState StandardCrypto -> Value #

toEncoding :: PrtclState StandardCrypto -> Encoding #

toJSONList :: [PrtclState StandardCrypto] -> Value #

toEncodingList :: [PrtclState StandardCrypto] -> Encoding #

omitField :: PrtclState StandardCrypto -> Bool #

CardanoHardForkConstraints StandardCrypto => ProtocolClient (CardanoBlock StandardCrypto) Source # 
Instance details

Defined in Cardano.Api.Protocol

Associated Types

data ProtocolClientInfoArgs (CardanoBlock StandardCrypto) Source #

Methods

protocolClientInfo :: ProtocolClientInfoArgs (CardanoBlock StandardCrypto) -> ProtocolClientInfo (CardanoBlock StandardCrypto) Source #

LedgerSupportsProtocol (ShelleyBlock (TPraos StandardCrypto) (ShelleyEra StandardCrypto)) => ProtocolClient (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) Source # 
Instance details

Defined in Cardano.Api.Protocol

Associated Types

data ProtocolClientInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) Source #

Methods

protocolClientInfo :: ProtocolClientInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) -> ProtocolClientInfo (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) Source #

type HASH StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

type HASH StandardCrypto = Blake2b_256
type ADDRHASH StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

type ADDRHASH StandardCrypto = Blake2b_224
type DSIGN StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

type DSIGN StandardCrypto = Ed25519DSIGN
type KES StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

type KES StandardCrypto = Sum6KES Ed25519DSIGN Blake2b_256
type VRF StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

type VRF StandardCrypto = PraosVRF
data ProtocolClientInfoArgs (CardanoBlock StandardCrypto) Source # 
Instance details

Defined in Cardano.Api.Protocol

data ProtocolInfoArgs (CardanoBlock StandardCrypto) Source # 
Instance details

Defined in Cardano.Api.Protocol

data ProtocolInfoArgs (CardanoBlock StandardCrypto) = ProtocolInfoArgsCardano (CardanoProtocolParams StandardCrypto)
data ProtocolClientInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) Source # 
Instance details

Defined in Cardano.Api.Protocol

data ProtocolClientInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) = ProtocolClientInfoArgsShelley
data ProtocolInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) Source # 
Instance details

Defined in Cardano.Api.Protocol

data ProtocolInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) = ProtocolInfoArgsShelley (ShelleyGenesis StandardCrypto) (ProtocolParamsShelleyBased StandardCrypto) (ProtocolParams (ShelleyBlock (TPraos StandardCrypto) StandardShelley))

newtype EpochNo #

Constructors

EpochNo 

Fields

Instances

Instances details
Enum EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Eq EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Num EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Ord EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Show EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Generic EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Associated Types

type Rep EpochNo :: Type -> Type Source #

NFData EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

rnf :: EpochNo -> () Source #

DecCBOR EpochNo 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.DecCBOR

Methods

decCBOR :: Decoder s EpochNo

dropCBOR :: Proxy EpochNo -> Decoder s ()

label :: Proxy EpochNo -> Text

EncCBOR EpochNo 
Instance details

Defined in Cardano.Ledger.Binary.Encoding.EncCBOR

Methods

encCBOR :: EpochNo -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy EpochNo -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [EpochNo] -> Size

FromCBOR EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

fromCBOR :: Decoder s EpochNo #

label :: Proxy EpochNo -> Text #

FromJSON EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

parseJSON :: Value -> Parser EpochNo #

parseJSONList :: Value -> Parser [EpochNo] #

omittedField :: Maybe EpochNo #

NoThunks EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

noThunks :: Context -> EpochNo -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> EpochNo -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy EpochNo -> String

ToCBOR EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toCBOR :: EpochNo -> Encoding #

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy EpochNo -> Size #

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [EpochNo] -> Size #

ToJSON EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toJSON :: EpochNo -> Value #

toEncoding :: EpochNo -> Encoding #

toJSONList :: [EpochNo] -> Value #

toEncodingList :: [EpochNo] -> Encoding #

omitField :: EpochNo -> Bool #

Serialise EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

encode :: EpochNo -> Encoding

decode :: Decoder s EpochNo

encodeList :: [EpochNo] -> Encoding

decodeList :: Decoder s [EpochNo]

Condense EpochNo 
Instance details

Defined in Ouroboros.Consensus.Util.Condense

Methods

condense :: EpochNo -> String

type Rep EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

type Rep EpochNo = D1 ('MetaData "EpochNo" "Cardano.Slotting.Slot" "cardano-slotting-0.1.2.0-JZWCVEKQdJpCQ0vwyYdDil" 'True) (C1 ('MetaCons "EpochNo" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEpochNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))