cardano-ledger-api-1.7.0.1: Public API for the cardano ledger codebase
Safe HaskellSafe-Inferred
LanguageHaskell2010

Cardano.Ledger.Api.Governance

Synopsis

Documentation

class (EraPParams era, Eq (GovState era), Show (GovState era), NoThunks (GovState era), NFData (GovState era), EncCBOR (GovState era), DecCBOR (GovState era), DecShareCBOR (GovState era), ToCBOR (GovState era), FromCBOR (GovState era), Default (GovState era), ToJSON (GovState era)) => EraGov era #

Minimal complete definition

curPParamsGovStateL, prevPParamsGovStateL, obligationGovState, getDRepDistr

Associated Types

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

Instances

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

Defined in Cardano.Ledger.Shelley.Governance

Associated Types

type GovState (ShelleyEra c) = (r :: Type) #

Methods

emptyGovState :: GovState (ShelleyEra c) #

getProposedPPUpdates :: GovState (ShelleyEra c) -> Maybe (ProposedPPUpdates (ShelleyEra c)) #

getConstitution :: GovState (ShelleyEra c) -> Maybe (Constitution (ShelleyEra c))

getCommitteeMembers :: GovState (ShelleyEra c) -> Maybe (Map (Credential 'ColdCommitteeRole (EraCrypto (ShelleyEra c))) EpochNo, UnitInterval)

curPParamsGovStateL :: Lens' (GovState (ShelleyEra c)) (PParams (ShelleyEra c))

prevPParamsGovStateL :: Lens' (GovState (ShelleyEra c)) (PParams (ShelleyEra c))

obligationGovState :: GovState (ShelleyEra c) -> Obligations

getDRepDistr :: GovState (ShelleyEra c) -> Map (DRep (EraCrypto (ShelleyEra c))) (CompactForm Coin)

Shelley

data ShelleyGovState era #

Constructors

ShelleyGovState 

Instances

Instances details
EraPParams era => ToJSON (ShelleyGovState era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

toJSON :: ShelleyGovState era -> Value

toEncoding :: ShelleyGovState era -> Encoding

toJSONList :: [ShelleyGovState era] -> Value

toEncodingList :: [ShelleyGovState era] -> Encoding

omitField :: ShelleyGovState era -> Bool

Generic (ShelleyGovState era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Associated Types

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

(Show (PParamsUpdate era), Show (PParams era)) => Show (ShelleyGovState era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

(Era era, DecCBOR (PParamsUpdate era), DecCBOR (PParams era)) => FromCBOR (ShelleyGovState era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

fromCBOR :: Decoder s (ShelleyGovState era)

label :: Proxy (ShelleyGovState era) -> Text

(Era era, EncCBOR (PParamsUpdate era), EncCBOR (PParams era)) => ToCBOR (ShelleyGovState era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

toCBOR :: ShelleyGovState era -> Encoding

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

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

(Era era, DecCBOR (PParamsUpdate era), DecCBOR (PParams era)) => DecCBOR (ShelleyGovState era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

decCBOR :: Decoder s (ShelleyGovState era)

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

label :: Proxy (ShelleyGovState era) -> Text

(Era era, DecCBOR (PParamsUpdate era), DecCBOR (PParams era)) => DecShareCBOR (ShelleyGovState era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Associated Types

type Share (ShelleyGovState era)

Methods

getShare :: ShelleyGovState era -> Share (ShelleyGovState era)

decShareCBOR :: Share (ShelleyGovState era) -> Decoder s (ShelleyGovState era)

decSharePlusCBOR :: StateT (Share (ShelleyGovState era)) (Decoder s) (ShelleyGovState era)

(Era era, EncCBOR (PParamsUpdate era), EncCBOR (PParams era)) => EncCBOR (ShelleyGovState era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

encCBOR :: ShelleyGovState era -> Encoding

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

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

EraPParams era => Default (ShelleyGovState era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

def :: ShelleyGovState era

(NFData (PParamsUpdate era), NFData (PParams era)) => NFData (ShelleyGovState era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

rnf :: ShelleyGovState era -> () Source #

(Eq (PParamsUpdate era), Eq (PParams era)) => Eq (ShelleyGovState era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

(NoThunks (PParamsUpdate era), NoThunks (PParams era)) => NoThunks (ShelleyGovState era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

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

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

showTypeOf :: Proxy (ShelleyGovState era) -> String

(ToExpr (PParamsUpdate era), ToExpr (PParams era)) => ToExpr (ShelleyGovState era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

toExpr :: ShelleyGovState era -> Expr

listToExpr :: [ShelleyGovState era] -> Expr

type Rep (ShelleyGovState era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

type Rep (ShelleyGovState era) = D1 ('MetaData "ShelleyGovState" "Cardano.Ledger.Shelley.Governance" "cardano-ledger-shelley-1.8.0.0-K8MVzOrWEQEOdl6Q57XMq" 'False) (C1 ('MetaCons "ShelleyGovState" 'PrefixI 'True) ((S1 ('MetaSel ('Just "proposals") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ProposedPPUpdates era)) :*: S1 ('MetaSel ('Just "futureProposals") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ProposedPPUpdates era))) :*: (S1 ('MetaSel ('Just "sgovPp") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PParams era)) :*: S1 ('MetaSel ('Just "sgovPrevPp") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PParams era)))))
type Share (ShelleyGovState era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

type Share (ShelleyGovState era) = ()
type TranslationError (AllegraEra c) ShelleyGovState 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

type TranslationError (AllegraEra c) ShelleyGovState = Void
type TranslationError (AlonzoEra c) ShelleyGovState 
Instance details

Defined in Cardano.Ledger.Alonzo.Translation

type TranslationError (AlonzoEra c) ShelleyGovState = Void
type TranslationError (BabbageEra c) ShelleyGovState 
Instance details

Defined in Cardano.Ledger.Babbage.Translation

type TranslationError (BabbageEra c) ShelleyGovState = Void
type TranslationError (MaryEra c) ShelleyGovState 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) ShelleyGovState = Void

newtype ProposedPPUpdates era #

Constructors

ProposedPPUpdates (Map (KeyHash 'Genesis (EraCrypto era)) (PParamsUpdate era)) 

Instances

Instances details
EraPParams era => ToJSON (ProposedPPUpdates era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Methods

toJSON :: ProposedPPUpdates era -> Value

toEncoding :: ProposedPPUpdates era -> Encoding

toJSONList :: [ProposedPPUpdates era] -> Value

toEncodingList :: [ProposedPPUpdates era] -> Encoding

omitField :: ProposedPPUpdates era -> Bool

Generic (ProposedPPUpdates era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Associated Types

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

Show (PParamsUpdate era) => Show (ProposedPPUpdates era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

(Era era, FromCBOR (PParamsUpdate era)) => FromCBOR (ProposedPPUpdates era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Methods

fromCBOR :: Decoder s (ProposedPPUpdates era)

label :: Proxy (ProposedPPUpdates era) -> Text

(Era era, ToCBOR (PParamsUpdate era)) => ToCBOR (ProposedPPUpdates era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Methods

toCBOR :: ProposedPPUpdates era -> Encoding

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

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

(Era era, DecCBOR (PParamsUpdate era)) => DecCBOR (ProposedPPUpdates era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Methods

decCBOR :: Decoder s (ProposedPPUpdates era)

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

label :: Proxy (ProposedPPUpdates era) -> Text

(Era era, EncCBOR (PParamsUpdate era)) => EncCBOR (ProposedPPUpdates era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Methods

encCBOR :: ProposedPPUpdates era -> Encoding

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

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

NFData (PParamsUpdate era) => NFData (ProposedPPUpdates era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Methods

rnf :: ProposedPPUpdates era -> () Source #

Eq (PParamsUpdate era) => Eq (ProposedPPUpdates era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

NoThunks (PParamsUpdate era) => NoThunks (ProposedPPUpdates era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Methods

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

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

showTypeOf :: Proxy (ProposedPPUpdates era) -> String

ToExpr (PParamsUpdate era) => ToExpr (ProposedPPUpdates era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Methods

toExpr :: ProposedPPUpdates era -> Expr

listToExpr :: [ProposedPPUpdates era] -> Expr

type Rep (ProposedPPUpdates era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

type Rep (ProposedPPUpdates era) = D1 ('MetaData "ProposedPPUpdates" "Cardano.Ledger.Shelley.PParams" "cardano-ledger-shelley-1.8.0.0-K8MVzOrWEQEOdl6Q57XMq" 'True) (C1 ('MetaCons "ProposedPPUpdates" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map (KeyHash 'Genesis (EraCrypto era)) (PParamsUpdate era)))))
type TranslationError (AllegraEra c) ProposedPPUpdates 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

type TranslationError (AllegraEra c) ProposedPPUpdates = Void
type TranslationError (AlonzoEra c) ProposedPPUpdates 
Instance details

Defined in Cardano.Ledger.Alonzo.Translation

type TranslationError (AlonzoEra c) ProposedPPUpdates = Void
type TranslationError (BabbageEra c) ProposedPPUpdates 
Instance details

Defined in Cardano.Ledger.Babbage.Translation

type TranslationError (BabbageEra c) ProposedPPUpdates = Void
type TranslationError (MaryEra c) ProposedPPUpdates 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) ProposedPPUpdates = Void

Conway

Governance Procedures

data VotingProcedure era #

Constructors

VotingProcedure 

Fields

Instances

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

Generic (VotingProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Associated Types

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

Show (VotingProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

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

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

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

rnf :: VotingProcedure era -> () Source #

Eq (VotingProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

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

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-1XJ0KRTiRBuAzYQI5C9XmE" 'False) (C1 ('MetaCons "VotingProcedure" 'PrefixI 'True) (S1 ('MetaSel ('Just "vProcVote") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Vote) :*: S1 ('MetaSel ('Just "vProcAnchor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe (Anchor (EraCrypto era))))))

newtype VotingProcedures era #

Constructors

VotingProcedures 

Fields

Instances

Instances details
EraPParams era => ToJSON (VotingProcedures era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toJSON :: VotingProcedures era -> Value

toEncoding :: VotingProcedures era -> Encoding

toJSONList :: [VotingProcedures era] -> Value

toEncodingList :: [VotingProcedures era] -> Encoding

omitField :: VotingProcedures era -> Bool

Generic (VotingProcedures era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Associated Types

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

Show (VotingProcedures era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Era era => DecCBOR (VotingProcedures era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

decCBOR :: Decoder s (VotingProcedures era)

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

label :: Proxy (VotingProcedures era) -> Text

Era era => EncCBOR (VotingProcedures era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

encCBOR :: VotingProcedures era -> Encoding

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

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

Era era => NFData (VotingProcedures era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

rnf :: VotingProcedures era -> () Source #

Eq (VotingProcedures era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

NoThunks (VotingProcedures era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

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

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

showTypeOf :: Proxy (VotingProcedures era) -> String

Era era => ToExpr (VotingProcedures era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toExpr :: VotingProcedures era -> Expr

listToExpr :: [VotingProcedures era] -> Expr

type Rep (VotingProcedures era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

type Rep (VotingProcedures era) = D1 ('MetaData "VotingProcedures" "Cardano.Ledger.Conway.Governance.Procedures" "cardano-ledger-conway-1.11.0.0-1XJ0KRTiRBuAzYQI5C9XmE" 'True) (C1 ('MetaCons "VotingProcedures" 'PrefixI 'True) (S1 ('MetaSel ('Just "unVotingProcedures") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map (Voter (EraCrypto era)) (Map (GovActionId (EraCrypto era)) (VotingProcedure era))))))

data ProposalProcedure era #

Constructors

ProposalProcedure 

Fields

Instances

Instances details
EraPParams era => ToJSON (ProposalProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toJSON :: ProposalProcedure era -> Value

toEncoding :: ProposalProcedure era -> Encoding

toJSONList :: [ProposalProcedure era] -> Value

toEncodingList :: [ProposalProcedure era] -> Encoding

omitField :: ProposalProcedure era -> Bool

Generic (ProposalProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Associated Types

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

EraPParams era => Show (ProposalProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

EraPParams era => DecCBOR (ProposalProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

decCBOR :: Decoder s (ProposalProcedure era)

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

label :: Proxy (ProposalProcedure era) -> Text

EraPParams era => EncCBOR (ProposalProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

encCBOR :: ProposalProcedure era -> Encoding

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

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

EraPParams era => NFData (ProposalProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

rnf :: ProposalProcedure era -> () Source #

EraPParams era => Eq (ProposalProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

EraPParams era => Ord (ProposalProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

EraPParams era => NoThunks (ProposalProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

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

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

showTypeOf :: Proxy (ProposalProcedure era) -> String

EraPParams era => ToExpr (ProposalProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toExpr :: ProposalProcedure era -> Expr

listToExpr :: [ProposalProcedure era] -> Expr

type Rep (ProposalProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

type Rep (ProposalProcedure era) = D1 ('MetaData "ProposalProcedure" "Cardano.Ledger.Conway.Governance.Procedures" "cardano-ledger-conway-1.11.0.0-1XJ0KRTiRBuAzYQI5C9XmE" 'False) (C1 ('MetaCons "ProposalProcedure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "pProcDeposit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin) :*: S1 ('MetaSel ('Just "pProcReturnAddr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (RewardAcnt (EraCrypto era)))) :*: (S1 ('MetaSel ('Just "pProcGovAction") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GovAction era)) :*: S1 ('MetaSel ('Just "pProcAnchor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Anchor (EraCrypto era))))))

Constitution

data Constitution era #

Constructors

Constitution 

Fields

Instances

Instances details
Era era => FromJSON (Constitution era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

parseJSON :: Value -> Parser (Constitution era)

parseJSONList :: Value -> Parser [Constitution era]

omittedField :: Maybe (Constitution era)

Era era => ToJSON (Constitution era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

toJSON :: Constitution era -> Value

toEncoding :: Constitution era -> Encoding

toJSONList :: [Constitution era] -> Value

toEncodingList :: [Constitution era] -> Encoding

omitField :: Constitution era -> Bool

Generic (Constitution era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Associated Types

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

Methods

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

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

Show (Constitution era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Era era => FromCBOR (Constitution era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

fromCBOR :: Decoder s (Constitution era)

label :: Proxy (Constitution era) -> Text

Era era => ToCBOR (Constitution era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

toCBOR :: Constitution era -> Encoding

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

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

Era era => DecCBOR (Constitution era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

decCBOR :: Decoder s (Constitution era)

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

label :: Proxy (Constitution era) -> Text

Era era => EncCBOR (Constitution era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

encCBOR :: Constitution era -> Encoding

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

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

Era era => Default (Constitution era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

def :: Constitution era

Era era => NFData (Constitution era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

rnf :: Constitution era -> () Source #

Eq (Constitution era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Ord (Constitution era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Era era => NoThunks (Constitution era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

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

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

showTypeOf :: Proxy (Constitution era) -> String

ToExpr (Constitution era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

toExpr :: Constitution era -> Expr

listToExpr :: [Constitution era] -> Expr

type Rep (Constitution era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

type Rep (Constitution era) = D1 ('MetaData "Constitution" "Cardano.Ledger.Shelley.Governance" "cardano-ledger-shelley-1.8.0.0-K8MVzOrWEQEOdl6Q57XMq" 'False) (C1 ('MetaCons "Constitution" 'PrefixI 'True) (S1 ('MetaSel ('Just "constitutionAnchor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Anchor (EraCrypto era))) :*: S1 ('MetaSel ('Just "constitutionScript") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe (ScriptHash (EraCrypto era))))))

constitutionAnchorL :: forall era f. Functor f => (Anchor (EraCrypto era) -> f (Anchor (EraCrypto era))) -> Constitution era -> f (Constitution era) #

constitutionScriptL :: forall era f. Functor f => (StrictMaybe (ScriptHash (EraCrypto era)) -> f (StrictMaybe (ScriptHash (EraCrypto era)))) -> Constitution era -> f (Constitution era) #

Governance State

data ConwayGovState era #

Constructors

ConwayGovState 

Fields

Instances

Instances details
EraPParams era => ToJSON (ConwayGovState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

toJSON :: ConwayGovState era -> Value

toEncoding :: ConwayGovState era -> Encoding

toJSONList :: [ConwayGovState era] -> Value

toEncodingList :: [ConwayGovState era] -> Encoding

omitField :: ConwayGovState era -> Bool

Generic (ConwayGovState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Associated Types

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

EraPParams era => Show (ConwayGovState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

EraPParams era => FromCBOR (ConwayGovState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

fromCBOR :: Decoder s (ConwayGovState era)

label :: Proxy (ConwayGovState era) -> Text

EraPParams era => ToCBOR (ConwayGovState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

toCBOR :: ConwayGovState era -> Encoding

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

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

EraPParams era => DecCBOR (ConwayGovState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

decCBOR :: Decoder s (ConwayGovState era)

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

label :: Proxy (ConwayGovState era) -> Text

EraPParams era => DecShareCBOR (ConwayGovState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Associated Types

type Share (ConwayGovState era)

Methods

getShare :: ConwayGovState era -> Share (ConwayGovState era)

decShareCBOR :: Share (ConwayGovState era) -> Decoder s (ConwayGovState era)

decSharePlusCBOR :: StateT (Share (ConwayGovState era)) (Decoder s) (ConwayGovState era)

EraPParams era => EncCBOR (ConwayGovState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

encCBOR :: ConwayGovState era -> Encoding

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

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

EraPParams era => Default (ConwayGovState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

def :: ConwayGovState era

EraPParams era => NFData (ConwayGovState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

rnf :: ConwayGovState era -> () Source #

EraPParams era => Eq (ConwayGovState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

EraPParams era => NoThunks (ConwayGovState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

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

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

showTypeOf :: Proxy (ConwayGovState era) -> String

EraPParams era => ToExpr (ConwayGovState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

toExpr :: ConwayGovState era -> Expr

listToExpr :: [ConwayGovState era] -> Expr

type Rep (ConwayGovState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

type Rep (ConwayGovState era) = D1 ('MetaData "ConwayGovState" "Cardano.Ledger.Conway.Governance" "cardano-ledger-conway-1.11.0.0-1XJ0KRTiRBuAzYQI5C9XmE" 'False) (C1 ('MetaCons "ConwayGovState" 'PrefixI 'True) (S1 ('MetaSel ('Just "cgProposals") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Proposals era)) :*: (S1 ('MetaSel ('Just "cgEnactState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (EnactState era)) :*: S1 ('MetaSel ('Just "cgDRepPulsingState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (DRepPulsingState era)))))
type Share (ConwayGovState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

type Share (ConwayGovState era) = ()

cgEnactStateL :: forall era f. Functor f => (EnactState era -> f (EnactState era)) -> ConwayGovState era -> f (ConwayGovState era) #

cgProposalsL :: forall era f. Functor f => (Proposals era -> f (Proposals era)) -> ConwayGovState era -> f (ConwayGovState era) #

data RatifyState era #

Constructors

RatifyState 

Fields

Instances

Instances details
EraPParams era => ToJSON (RatifyState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

toJSON :: RatifyState era -> Value

toEncoding :: RatifyState era -> Encoding

toJSONList :: [RatifyState era] -> Value

toEncodingList :: [RatifyState era] -> Encoding

omitField :: RatifyState era -> Bool

Generic (RatifyState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Associated Types

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

Methods

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

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

EraPParams era => Show (RatifyState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

EraPParams era => DecCBOR (RatifyState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

decCBOR :: Decoder s (RatifyState era)

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

label :: Proxy (RatifyState era) -> Text

EraPParams era => DecShareCBOR (RatifyState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Associated Types

type Share (RatifyState era)

Methods

getShare :: RatifyState era -> Share (RatifyState era)

decShareCBOR :: Share (RatifyState era) -> Decoder s (RatifyState era)

decSharePlusCBOR :: StateT (Share (RatifyState era)) (Decoder s) (RatifyState era)

EraPParams era => EncCBOR (RatifyState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

encCBOR :: RatifyState era -> Encoding

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

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

EraPParams era => Default (RatifyState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

def :: RatifyState era

EraPParams era => NFData (RatifyState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

rnf :: RatifyState era -> () Source #

EraPParams era => Eq (RatifyState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

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

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

EraPParams era => NoThunks (RatifyState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

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

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

showTypeOf :: Proxy (RatifyState era) -> String

EraPParams era => ToExpr (RatifyState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

toExpr :: RatifyState era -> Expr

listToExpr :: [RatifyState era] -> Expr

EraPParams era => NFData (DRepPulser era Identity (RatifyState era)) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

rnf :: DRepPulser era Identity (RatifyState era) -> () Source #

EraPParams era => NoThunks (DRepPulser era Identity (RatifyState era)) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

noThunks :: Context -> DRepPulser era Identity (RatifyState era) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> DRepPulser era Identity (RatifyState era) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (DRepPulser era Identity (RatifyState era)) -> String

type Rep (RatifyState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

type Rep (RatifyState era) = D1 ('MetaData "RatifyState" "Cardano.Ledger.Conway.Governance" "cardano-ledger-conway-1.11.0.0-1XJ0KRTiRBuAzYQI5C9XmE" 'False) (C1 ('MetaCons "RatifyState" 'PrefixI 'True) (S1 ('MetaSel ('Just "rsEnactState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (EnactState era)) :*: (S1 ('MetaSel ('Just "rsRemoved") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set (GovActionId (EraCrypto era)))) :*: S1 ('MetaSel ('Just "rsDelayed") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool))))
type Share (RatifyState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

type Share (RatifyState era) = ()

data EnactState era #

Constructors

EnactState 

Fields

Instances

Instances details
EraPParams era => ToJSON (EnactState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

toJSON :: EnactState era -> Value

toEncoding :: EnactState era -> Encoding

toJSONList :: [EnactState era] -> Value

toEncodingList :: [EnactState era] -> Encoding

omitField :: EnactState era -> Bool

Generic (EnactState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Associated Types

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

Methods

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

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

Show (PParams era) => Show (EnactState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

EraPParams era => FromCBOR (EnactState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

fromCBOR :: Decoder s (EnactState era)

label :: Proxy (EnactState era) -> Text

EraPParams era => ToCBOR (EnactState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

toCBOR :: EnactState era -> Encoding

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

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

EraPParams era => DecCBOR (EnactState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

decCBOR :: Decoder s (EnactState era)

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

label :: Proxy (EnactState era) -> Text

EraPParams era => DecShareCBOR (EnactState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Associated Types

type Share (EnactState era)

Methods

getShare :: EnactState era -> Share (EnactState era)

decShareCBOR :: Share (EnactState era) -> Decoder s (EnactState era)

decSharePlusCBOR :: StateT (Share (EnactState era)) (Decoder s) (EnactState era)

EraPParams era => EncCBOR (EnactState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

encCBOR :: EnactState era -> Encoding

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

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

EraPParams era => Default (EnactState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

def :: EnactState era

EraPParams era => NFData (EnactState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

rnf :: EnactState era -> () Source #

Eq (PParams era) => Eq (EnactState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

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

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

EraPParams era => NoThunks (EnactState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

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

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

showTypeOf :: Proxy (EnactState era) -> String

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

Defined in Cardano.Ledger.Conway.Governance

Methods

toExpr :: EnactState era -> Expr

listToExpr :: [EnactState era] -> Expr

type Rep (EnactState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

type Rep (EnactState era) = D1 ('MetaData "EnactState" "Cardano.Ledger.Conway.Governance" "cardano-ledger-conway-1.11.0.0-1XJ0KRTiRBuAzYQI5C9XmE" 'False) (C1 ('MetaCons "EnactState" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ensCommittee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe (Committee era))) :*: (S1 ('MetaSel ('Just "ensConstitution") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Constitution era)) :*: S1 ('MetaSel ('Just "ensCurPParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PParams era)))) :*: ((S1 ('MetaSel ('Just "ensPrevPParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PParams era)) :*: S1 ('MetaSel ('Just "ensTreasury") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin)) :*: (S1 ('MetaSel ('Just "ensWithdrawals") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (Credential 'Staking (EraCrypto era)) Coin)) :*: S1 ('MetaSel ('Just "ensPrevGovActionIds") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PrevGovActionIds era))))))
type Share (EnactState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

type Share (EnactState era) = ()

data Voter c #

Constructors

CommitteeVoter !(Credential 'HotCommitteeRole c) 
DRepVoter !(Credential 'DRepRole c) 
StakePoolVoter !(KeyHash 'StakePool c) 

Instances

Instances details
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]

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 #

Show (Voter c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

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

NFData (Voter c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

rnf :: Voter c -> () Source #

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 #

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

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-1XJ0KRTiRBuAzYQI5C9XmE" '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 Vote #

Constructors

VoteNo 
VoteYes 
Abstain 

Instances

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

Bounded Vote 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Enum 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 #

Show Vote 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

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

NFData Vote 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

rnf :: Vote -> () Source #

Eq Vote 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

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

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

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

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-1XJ0KRTiRBuAzYQI5C9XmE" '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)))

Governance Action

data GovAction era #

Constructors

ParameterChange !(StrictMaybe (PrevGovActionId 'PParamUpdatePurpose (EraCrypto era))) !(PParamsUpdate era) 
HardForkInitiation !(StrictMaybe (PrevGovActionId 'HardForkPurpose (EraCrypto era))) !ProtVer 
TreasuryWithdrawals !(Map (RewardAcnt (EraCrypto era)) Coin) 
NoConfidence !(StrictMaybe (PrevGovActionId 'CommitteePurpose (EraCrypto era))) 
UpdateCommittee !(StrictMaybe (PrevGovActionId 'CommitteePurpose (EraCrypto era))) !(Set (Credential 'ColdCommitteeRole (EraCrypto era))) !(Map (Credential 'ColdCommitteeRole (EraCrypto era)) EpochNo) !UnitInterval 
NewConstitution !(StrictMaybe (PrevGovActionId 'ConstitutionPurpose (EraCrypto era))) !(Constitution era) 
InfoAction 

Instances

Instances details
EraPParams era => ToJSON (GovAction era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toJSON :: GovAction era -> Value

toEncoding :: GovAction era -> Encoding

toJSONList :: [GovAction era] -> Value

toEncodingList :: [GovAction era] -> Encoding

omitField :: GovAction era -> Bool

Generic (GovAction era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Associated Types

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

Methods

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

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

EraPParams era => Show (GovAction era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

EraPParams era => DecCBOR (GovAction era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

decCBOR :: Decoder s (GovAction era)

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

label :: Proxy (GovAction era) -> Text

EraPParams era => EncCBOR (GovAction era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

encCBOR :: GovAction era -> Encoding

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

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

EraPParams era => NFData (GovAction era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

rnf :: GovAction era -> () Source #

EraPParams era => Eq (GovAction era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

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

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

EraPParams era => Ord (GovAction era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

compare :: GovAction era -> GovAction era -> Ordering Source #

(<) :: GovAction era -> GovAction era -> Bool Source #

(<=) :: GovAction era -> GovAction era -> Bool Source #

(>) :: GovAction era -> GovAction era -> Bool Source #

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

max :: GovAction era -> GovAction era -> GovAction era Source #

min :: GovAction era -> GovAction era -> GovAction era Source #

EraPParams era => NoThunks (GovAction era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

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

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

showTypeOf :: Proxy (GovAction era) -> String

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

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toExpr :: GovAction era -> Expr

listToExpr :: [GovAction era] -> Expr

type Rep (GovAction era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

type Rep (GovAction era) = D1 ('MetaData "GovAction" "Cardano.Ledger.Conway.Governance.Procedures" "cardano-ledger-conway-1.11.0.0-1XJ0KRTiRBuAzYQI5C9XmE" 'False) ((C1 ('MetaCons "ParameterChange" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe (PrevGovActionId 'PParamUpdatePurpose (EraCrypto era)))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PParamsUpdate era))) :+: (C1 ('MetaCons "HardForkInitiation" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe (PrevGovActionId 'HardForkPurpose (EraCrypto era)))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ProtVer)) :+: C1 ('MetaCons "TreasuryWithdrawals" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (RewardAcnt (EraCrypto era)) Coin))))) :+: ((C1 ('MetaCons "NoConfidence" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe (PrevGovActionId 'CommitteePurpose (EraCrypto era))))) :+: C1 ('MetaCons "UpdateCommittee" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe (PrevGovActionId 'CommitteePurpose (EraCrypto era)))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set (Credential 'ColdCommitteeRole (EraCrypto era))))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (Credential 'ColdCommitteeRole (EraCrypto era)) EpochNo)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitInterval)))) :+: (C1 ('MetaCons "NewConstitution" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe (PrevGovActionId 'ConstitutionPurpose (EraCrypto era)))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Constitution era))) :+: C1 ('MetaCons "InfoAction" 'PrefixI 'False) (U1 :: Type -> Type))))

data GovActionId c #

Constructors

GovActionId 

Instances

Instances details
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]

Generic (GovActionId c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Associated Types

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

Show (GovActionId c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

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

Crypto c => NFData (GovActionId c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

rnf :: GovActionId c -> () Source #

Eq (GovActionId c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Ord (GovActionId c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

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

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-1XJ0KRTiRBuAzYQI5C9XmE" 'False) (C1 ('MetaCons "GovActionId" 'PrefixI 'True) (S1 ('MetaSel ('Just "gaidTxId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TxId c)) :*: S1 ('MetaSel ('Just "gaidGovActionIx") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 GovActionIx)))

newtype GovActionIx #

Constructors

GovActionIx Word32 

Instances

Instances details
ToJSON GovActionIx 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toJSON :: GovActionIx -> Value

toEncoding :: GovActionIx -> Encoding

toJSONList :: [GovActionIx] -> Value

toEncodingList :: [GovActionIx] -> Encoding

omitField :: GovActionIx -> Bool

Generic GovActionIx 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Associated Types

type Rep GovActionIx :: Type -> Type Source #

Show GovActionIx 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

DecCBOR GovActionIx 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

decCBOR :: Decoder s GovActionIx

dropCBOR :: Proxy GovActionIx -> Decoder s ()

label :: Proxy GovActionIx -> Text

EncCBOR GovActionIx 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

encCBOR :: GovActionIx -> Encoding

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

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

NFData GovActionIx 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

rnf :: GovActionIx -> () Source #

Eq GovActionIx 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Ord GovActionIx 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

NoThunks GovActionIx 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

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

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

showTypeOf :: Proxy GovActionIx -> String

ToExpr GovActionIx 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toExpr :: GovActionIx -> Expr

listToExpr :: [GovActionIx] -> Expr

type Rep GovActionIx 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

type Rep GovActionIx = D1 ('MetaData "GovActionIx" "Cardano.Ledger.Conway.Governance.Procedures" "cardano-ledger-conway-1.11.0.0-1XJ0KRTiRBuAzYQI5C9XmE" 'True) (C1 ('MetaCons "GovActionIx" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))

data GovActionState era #

Constructors

GovActionState 

Fields

Instances

Instances details
EraPParams era => ToJSON (GovActionState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toJSON :: GovActionState era -> Value

toEncoding :: GovActionState era -> Encoding

toJSONList :: [GovActionState era] -> Value

toEncodingList :: [GovActionState era] -> Encoding

omitField :: GovActionState era -> Bool

Generic (GovActionState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Associated Types

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

EraPParams era => Show (GovActionState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

EraPParams era => DecCBOR (GovActionState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

decCBOR :: Decoder s (GovActionState era)

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

label :: Proxy (GovActionState era) -> Text

EraPParams era => DecShareCBOR (GovActionState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Associated Types

type Share (GovActionState era)

Methods

getShare :: GovActionState era -> Share (GovActionState era)

decShareCBOR :: Share (GovActionState era) -> Decoder s (GovActionState era)

decSharePlusCBOR :: StateT (Share (GovActionState era)) (Decoder s) (GovActionState era)

EraPParams era => EncCBOR (GovActionState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

encCBOR :: GovActionState era -> Encoding

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

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

EraPParams era => NFData (GovActionState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

rnf :: GovActionState era -> () Source #

EraPParams era => Eq (GovActionState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

EraPParams era => NoThunks (GovActionState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

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

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

showTypeOf :: Proxy (GovActionState era) -> String

EraPParams era => ToExpr (GovActionState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toExpr :: GovActionState era -> Expr

listToExpr :: [GovActionState era] -> Expr

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 (GovActionState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

type Rep (GovActionState era) = D1 ('MetaData "GovActionState" "Cardano.Ledger.Conway.Governance.Procedures" "cardano-ledger-conway-1.11.0.0-1XJ0KRTiRBuAzYQI5C9XmE" 'False) (C1 ('MetaCons "GovActionState" 'PrefixI 'True) (((S1 ('MetaSel ('Just "gasId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GovActionId (EraCrypto era))) :*: S1 ('MetaSel ('Just "gasCommitteeVotes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (Credential 'HotCommitteeRole (EraCrypto era)) Vote))) :*: (S1 ('MetaSel ('Just "gasDRepVotes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (Credential 'DRepRole (EraCrypto era)) Vote)) :*: S1 ('MetaSel ('Just "gasStakePoolVotes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (KeyHash 'StakePool (EraCrypto era)) Vote)))) :*: ((S1 ('MetaSel ('Just "gasDeposit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin) :*: S1 ('MetaSel ('Just "gasReturnAddr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (RewardAcnt (EraCrypto era)))) :*: (S1 ('MetaSel ('Just "gasAction") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (GovAction era)) :*: (S1 ('MetaSel ('Just "gasProposedIn") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 EpochNo) :*: S1 ('MetaSel ('Just "gasExpiresAfter") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 EpochNo))))))
type Share (GovActionState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

type Share (GovActionState era) = ()

newtype PrevGovActionId (r :: GovActionPurpose) c #

Instances

Instances details
Crypto c => ToJSON (PrevGovActionId r c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toJSON :: PrevGovActionId r c -> Value

toEncoding :: PrevGovActionId r c -> Encoding

toJSONList :: [PrevGovActionId r c] -> Value

toEncodingList :: [PrevGovActionId r c] -> Encoding

omitField :: PrevGovActionId r c -> Bool

Generic (PrevGovActionId r c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Associated Types

type Rep (PrevGovActionId r c) :: Type -> Type Source #

Show (PrevGovActionId r c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

(Crypto c, Typeable r) => DecCBOR (PrevGovActionId r c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

decCBOR :: Decoder s (PrevGovActionId r c)

dropCBOR :: Proxy (PrevGovActionId r c) -> Decoder s ()

label :: Proxy (PrevGovActionId r c) -> Text

(Crypto c, Typeable r) => EncCBOR (PrevGovActionId r c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

encCBOR :: PrevGovActionId r c -> Encoding

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

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

Crypto c => NFData (PrevGovActionId r c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

rnf :: PrevGovActionId r c -> () Source #

Eq (PrevGovActionId r c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Ord (PrevGovActionId r c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

NoThunks (PrevGovActionId r c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

noThunks :: Context -> PrevGovActionId r c -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> PrevGovActionId r c -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (PrevGovActionId r c) -> String

ToExpr (PrevGovActionId r c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toExpr :: PrevGovActionId r c -> Expr

listToExpr :: [PrevGovActionId r c] -> Expr

type Rep (PrevGovActionId r c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

type Rep (PrevGovActionId r c) = D1 ('MetaData "PrevGovActionId" "Cardano.Ledger.Conway.Governance.Procedures" "cardano-ledger-conway-1.11.0.0-1XJ0KRTiRBuAzYQI5C9XmE" 'True) (C1 ('MetaCons "PrevGovActionId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPrevGovActionId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GovActionId c))))

Anchor

data Anchor c #

Constructors

Anchor 

Fields

Instances

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

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

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 #

Show (Anchor c) 
Instance details

Defined in Cardano.Ledger.BaseTypes

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 => 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 => Default (Anchor c) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

def :: Anchor c

Crypto c => NFData (Anchor c) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

rnf :: Anchor c -> () Source #

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 #

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

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-1dQ7WLDbkZc8aXLEpNIvOr" 'False) (C1 ('MetaCons "Anchor" 'PrefixI 'True) (S1 ('MetaSel ('Just "anchorUrl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Url) :*: S1 ('MetaSel ('Just "anchorDataHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (SafeHash c AnchorData))))

newtype AnchorData #

Constructors

AnchorData ByteString 

Instances

Instances details
SafeToHash AnchorData 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

originalBytes :: AnchorData -> ByteString

makeHashWithExplicitProxys :: HashAlgorithm (HASH c) => Proxy c -> Proxy index -> AnchorData -> SafeHash c index

Eq AnchorData 
Instance details

Defined in Cardano.Ledger.BaseTypes

HashWithCrypto AnchorData AnchorData 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

hashWithCrypto :: HashAlgorithm (HASH c) => Proxy c -> AnchorData -> SafeHash c AnchorData