cardano-ledger-test-9.9.9.9: Testing harness, tests and benchmarks for Shelley style cardano ledgers
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.Cardano.Ledger.Generic.Proof

Synopsis

Documentation

data Proof era where Source #

Proof of a valid (predefined) era

Instances

Instances details
Singleton Proof Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Proof

Methods

testEql ∷ ∀ (i ∷ k) (j ∷ k). Proof i → Proof j → Maybe (i :~: j) Source #

cmpIndex ∷ ∀ (a ∷ k) (b ∷ k). Proof a → Proof b → Ordering Source #

Shaped Proof any Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Proof

Methods

shape ∷ ∀ (i ∷ k). Proof i → Shape any Source #

Show (Proof e) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Proof

Methods

showsPrecIntProof e → ShowS Source #

showProof e → String Source #

showList ∷ [Proof e] → ShowS Source #

Eq (Proof e) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Env

Methods

(==)Proof e → Proof e → Bool Source #

(/=)Proof e → Proof e → Bool Source #

Hashable (Proof e) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Env

Methods

hashWithSaltIntProof e → Int Source #

hashProof e → Int Source #

Show (Some Proof) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Proof

class (EraGov era, EraTx era, EraUTxO era, EraTxAuxData era, ShelleyEraTxCert era, EraCrypto era ~ StandardCrypto) ⇒ Reflect era where Source #

Minimal complete definition

reify

Methods

reifyProof era Source #

lift ∷ ∀ a. (Proof era → a) → a Source #

data Some (t ∷ k → Type) where Source #

Hide the index for a singleton type t

Constructors

Some ∷ ∀ {k} (t ∷ k → Type) (i ∷ k). Singleton t ⇒ t i → Some t 

Instances

Instances details
Show (Some Proof) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Proof

Eq (Some r) 
Instance details

Defined in Data.Universe

Methods

(==)Some r → Some r → Bool Source #

(/=)Some r → Some r → Bool Source #

Ord (Some r) 
Instance details

Defined in Data.Universe

Methods

compareSome r → Some r → Ordering Source #

(<)Some r → Some r → Bool Source #

(<=)Some r → Some r → Bool Source #

(>)Some r → Some r → Bool Source #

(>=)Some r → Some r → Bool Source #

maxSome r → Some r → Some r Source #

minSome r → Some r → Some r Source #

data WitRule (s ∷ Symbol) (e ∷ Type) where Source #

Constructors

UTXOProof era → WitRule "UTXO" era 
UTXOWProof era → WitRule "UTXOW" era 
LEDGERProof era → WitRule "LEDGER" era 
BBODYProof era → WitRule "BBODY" era 
LEDGERSProof era → WitRule "LEDGERS" era 
MOCKCHAINProof era → WitRule "MOCKCHAIN" era 
RATIFYProof era → WitRule "RATIFY" era 
ENACTProof era → WitRule "ENACT" era 
TALLYProof era → WitRule "TALLY" era 
EPOCHProof era → WitRule "EPOCH" era 
NEWEPOCHProof era → WitRule "NEWEPOCH" era 
CERTProof era → WitRule "CERT" era 
CERTSProof era → WitRule "CERTS" era 
DELEGProof era → WitRule "DELEG" era 
POOLProof era → WitRule "POOL" era 
GOVCERTProof era → WitRule "GOVCERT" era 
GOVProof era → WitRule "GOV" era 

runSTS ∷ ∀ s e ans. (BaseM (EraRule s e) ~ ShelleyBase, STS (EraRule s e)) ⇒ WitRule s e → TRC (EraRule s e) → (Either (NonEmpty (PredicateFailure (EraRule s e))) (State (EraRule s e)) → ans) → ans Source #

goSTS ∷ ∀ s e ans env state sig. (BaseM (EraRule s e) ~ ShelleyBase, STS (EraRule s e), env ~ Environment (EraRule s e), state ~ State (EraRule s e), sig ~ Signal (EraRule s e)) ⇒ WitRule s e → env → state → sig → (Either (NonEmpty (PredicateFailure (EraRule s e))) (State (EraRule s e)) → ans) → ans Source #

Like runSTS, but makes the components of the TRC triple explicit. in case you can't remember, in ghci type @@ :t goSTS (UTXOW Babbage) goSTS (LEDGER Babbage) :: LedgerEnv (BabbageEra StandardCrypto) -> (UTxOState (BabbageEra StandardCrypto), CertState StandardCrypto) -> Cardano.Ledger.Alonzo.Tx.AlonzoTx (BabbageEra StandardCrypto) -> (Either [LedgerPredicateFailure (BabbageEra StandardCrypto)] (UTxOState (BabbageEra StandardCrypto), CertState StandardCrypto) -> ans) -> ans @@ it will tell you what type env state and sig are for Babbage

data ShelleyEra c Source #

Instances

Instances details
EraPP Shelley Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.SimplePParams

IsConwayUniv fn ⇒ LedgerEra Shelley fn Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.LedgerTypes.Specs

InjectRuleFailure "BBODY" ShelleyBbodyPredFailure (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Bbody

InjectRuleFailure "DELEG" ShelleyDelegPredFailure (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Deleg

InjectRuleFailure "DELEGS" ShelleyDelegsPredFailure (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Delegs

InjectRuleFailure "DELPL" ShelleyDelplPredFailure (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Delpl

InjectRuleFailure "LEDGER" ShelleyLedgerPredFailure (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledger

InjectRuleFailure "LEDGERS" ShelleyLedgersPredFailure (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledgers

InjectRuleFailure "POOL" ShelleyPoolPredFailure (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Pool

InjectRuleFailure "PPUP" ShelleyPpupPredFailure (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ppup

InjectRuleFailure "UTXO" ShelleyUtxoPredFailure (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Utxo

InjectRuleFailure "UTXOW" ShelleyUtxowPredFailure (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Utxow

Crypto c ⇒ FromJSON (TransitionConfig (ShelleyEra c)) 
Instance details

Defined in Cardano.Ledger.Shelley.Transition

Crypto c ⇒ ToJSON (TransitionConfig (ShelleyEra c)) 
Instance details

Defined in Cardano.Ledger.Shelley.Transition

Generic (TransitionConfig (ShelleyEra c)) 
Instance details

Defined in Cardano.Ledger.Shelley.Transition

Associated Types

type Rep (TransitionConfig (ShelleyEra c)) ∷ TypeType Source #

Crypto c ⇒ Show (TransitionConfig (ShelleyEra c)) 
Instance details

Defined in Cardano.Ledger.Shelley.Transition

Crypto c ⇒ Era (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

Associated Types

type EraCrypto (ShelleyEra c) Source #

type PreviousEra (ShelleyEra c) = (r ∷ Type) Source #

type ProtVerLow (ShelleyEra c) ∷ Nat Source #

type ProtVerHigh (ShelleyEra c) ∷ Nat Source #

Methods

eraNameString Source #

Crypto c ⇒ CanStartFromGenesis (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.API.Genesis

Associated Types

type AdditionalGenesisConfig (ShelleyEra c) Source #

(EraPParams (ShelleyEra c), DSignable c (Hash c EraIndependentTxBody)) ⇒ ApplyTx (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.API.Mempool

(Crypto c, DSignable c (Hash c EraIndependentTxBody)) ⇒ ApplyBlock (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.API.Validation

Crypto c ⇒ EraGov (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Associated Types

type GovState (ShelleyEra c) = (r ∷ Type) Source #

Crypto c ⇒ ShelleyEraScript (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Scripts

Crypto c ⇒ EraTransition (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Transition

Associated Types

data TransitionConfig (ShelleyEra c) Source #

Crypto c ⇒ ShelleyEraTxBody (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

Crypto c ⇒ ShelleyEraTxCert (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Terse (PParamsUpdate (ShelleyEra c)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Same

Crypto c ⇒ PrettyA (PParamsUpdate (ShelleyEra c)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.PrettyCore

Reflect (ShelleyEra StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Proof

Crypto c ⇒ Scriptic (ShelleyEra c) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Scriptic

Crypto c ⇒ GetLedgerView (ShelleyEra c) 
Instance details

Defined in Cardano.Protocol.TPraos.API

Crypto c ⇒ Eq (TransitionConfig (ShelleyEra c)) 
Instance details

Defined in Cardano.Ledger.Shelley.Transition

Crypto c ⇒ NoThunks (TransitionConfig (ShelleyEra c)) 
Instance details

Defined in Cardano.Ledger.Shelley.Transition

type EraRule "BBODY" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "BBODY" (ShelleyEra c) = ShelleyBBODY (ShelleyEra c)
type EraRule "DELEG" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "DELEG" (ShelleyEra c) = ShelleyDELEG (ShelleyEra c)
type EraRule "DELEGS" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "DELEGS" (ShelleyEra c) = ShelleyDELEGS (ShelleyEra c)
type EraRule "DELPL" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "DELPL" (ShelleyEra c) = ShelleyDELPL (ShelleyEra c)
type EraRule "EPOCH" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "EPOCH" (ShelleyEra c) = ShelleyEPOCH (ShelleyEra c)
type EraRule "LEDGER" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "LEDGER" (ShelleyEra c) = ShelleyLEDGER (ShelleyEra c)
type EraRule "LEDGERS" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "LEDGERS" (ShelleyEra c) = ShelleyLEDGERS (ShelleyEra c)
type EraRule "MIR" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "NEWEPOCH" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "NEWEPOCH" (ShelleyEra c) = ShelleyNEWEPOCH (ShelleyEra c)
type EraRule "NEWPP" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "NEWPP" (ShelleyEra c) = ShelleyNEWPP (ShelleyEra c)
type EraRule "POOL" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "POOLREAP" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "POOLREAP" (ShelleyEra c) = ShelleyPOOLREAP (ShelleyEra c)
type EraRule "PPUP" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "RUPD" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "SNAP" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "TICK" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "TICKF" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "TICKF" (ShelleyEra c) = ShelleyTICKF (ShelleyEra c)
type EraRule "TICKN" (ShelleyEra c) 
Instance details

Defined in Test.Cardano.Ledger.Shelley.Rules.Chain

type EraRule "TICKN" (ShelleyEra c) = TICKN
type EraRule "UPEC" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "UTXO" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "UTXOW" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "UTXOW" (ShelleyEra c) = ShelleyUTXOW (ShelleyEra c)
type EraRuleEvent "LEDGER" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledger

type EraRuleEvent "LEDGERS" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledgers

type EraRuleEvent "NEWEPOCH" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.NewEpoch

type EraRuleEvent "POOLREAP" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.PoolReap

type EraRuleEvent "TICK" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Tick

type EraRuleFailure "BBODY" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Bbody

type EraRuleFailure "DELEG" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Deleg

type EraRuleFailure "DELEGS" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Delegs

type EraRuleFailure "DELPL" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Delpl

type EraRuleFailure "LEDGER" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledger

type EraRuleFailure "LEDGERS" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledgers

type EraRuleFailure "POOL" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Pool

type EraRuleFailure "PPUP" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ppup

type EraRuleFailure "UTXO" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Utxo

type EraRuleFailure "UTXOW" (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Utxow

type DowngradePParams f (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

type PParamsHKD f (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

type UpgradePParams f (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

type Rep (TransitionConfig (ShelleyEra c)) 
Instance details

Defined in Cardano.Ledger.Shelley.Transition

type Rep (TransitionConfig (ShelleyEra c)) = D1 ('MetaData "TransitionConfig" "Cardano.Ledger.Shelley.Transition" "cardano-ledger-shelley-1.14.1.0-inplace" 'True) (C1 ('MetaCons "ShelleyTransitionConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "stcShelleyGenesis") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ShelleyGenesis c))))
type NativeScript (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Scripts

type Script (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Scripts

type Tx (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Tx.Internal

type TxAuxData (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxAuxData

type TxBody (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

type TxBodyUpgradeError (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

type TxOut (ShelleyEra crypto) 
Instance details

Defined in Cardano.Ledger.Shelley.TxOut

type TxOut (ShelleyEra crypto) = ShelleyTxOut (ShelleyEra crypto)
type TxSeq (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.BlockChain

type TxUpgradeError (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Tx.Internal

type TxWits (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxWits

type Value (ShelleyEra _c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

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

Defined in Cardano.Ledger.Shelley.Era

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

Defined in Cardano.Ledger.Shelley.Era

type ProtVerHigh (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type ProtVerLow (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type ProtVerLow (ShelleyEra c) = 2
type TranslationContext (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Translation

type TxCert (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

type TxCertUpgradeError (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

type Genesis (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

type ScriptsNeeded (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.UTxO

type AdditionalGenesisConfig (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.API.Genesis

type GovState (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

newtype TransitionConfig (ShelleyEra c) 
Instance details

Defined in Cardano.Ledger.Shelley.Transition

data AllegraEra c Source #

The Allegra era

Instances

Instances details
EraPP Allegra Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.SimplePParams

IsConwayUniv fn ⇒ LedgerEra Allegra fn Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.LedgerTypes.Specs

InjectRuleFailure "UTXO" AllegraUtxoPredFailure (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Rules.Utxo

Crypto c ⇒ AllegraEraScript (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Scripts

Crypto c ⇒ AllegraEraTxAuxData (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.TxAuxData

Crypto c ⇒ AllegraEraTxBody (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.TxBody.Internal

Crypto c ⇒ Era (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

Associated Types

type EraCrypto (AllegraEra c) Source #

type PreviousEra (AllegraEra c) = (r ∷ Type) Source #

type ProtVerLow (AllegraEra c) ∷ Nat Source #

type ProtVerHigh (AllegraEra c) ∷ Nat Source #

Methods

eraNameString Source #

Crypto c ⇒ EraGenesis (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

Associated Types

type Genesis (AllegraEra c) Source #

Terse (PParamsUpdate (AllegraEra c)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Same

Crypto c ⇒ PrettyA (PParamsUpdate (AllegraEra c)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.PrettyCore

Reflect (AllegraEra StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Proof

Crypto c ⇒ PostShelley (AllegraEra c) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Scriptic

Crypto c ⇒ Scriptic (AllegraEra c) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Scriptic

Crypto c ⇒ GetLedgerView (AllegraEra c) 
Instance details

Defined in Cardano.Protocol.TPraos.API

type EraRule "BBODY" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type EraRule "BBODY" (AllegraEra c) = ShelleyBBODY (AllegraEra c)
type EraRule "DELEG" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type EraRule "DELEG" (AllegraEra c) = ShelleyDELEG (AllegraEra c)
type EraRule "DELEGS" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type EraRule "DELEGS" (AllegraEra c) = ShelleyDELEGS (AllegraEra c)
type EraRule "DELPL" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type EraRule "DELPL" (AllegraEra c) = ShelleyDELPL (AllegraEra c)
type EraRule "EPOCH" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type EraRule "EPOCH" (AllegraEra c) = ShelleyEPOCH (AllegraEra c)
type EraRule "LEDGER" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type EraRule "LEDGER" (AllegraEra c) = ShelleyLEDGER (AllegraEra c)
type EraRule "LEDGERS" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type EraRule "LEDGERS" (AllegraEra c) = ShelleyLEDGERS (AllegraEra c)
type EraRule "MIR" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type EraRule "NEWEPOCH" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type EraRule "NEWEPOCH" (AllegraEra c) = ShelleyNEWEPOCH (AllegraEra c)
type EraRule "NEWPP" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type EraRule "NEWPP" (AllegraEra c) = ShelleyNEWPP (AllegraEra c)
type EraRule "POOL" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type EraRule "POOLREAP" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type EraRule "POOLREAP" (AllegraEra c) = ShelleyPOOLREAP (AllegraEra c)
type EraRule "PPUP" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type EraRule "RUPD" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type EraRule "SNAP" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type EraRule "TICK" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type EraRule "TICKF" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type EraRule "TICKF" (AllegraEra c) = ShelleyTICKF (AllegraEra c)
type EraRule "UPEC" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type EraRule "UTXO" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type EraRule "UTXOW" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type EraRule "UTXOW" (AllegraEra c) = AllegraUTXOW (AllegraEra c)
type EraRuleEvent "LEDGER" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Rules.Ledger

type EraRuleEvent "TICK" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Rules

type EraRuleFailure "BBODY" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Rules.Bbody

type EraRuleFailure "DELEG" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Rules.Deleg

type EraRuleFailure "DELEGS" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Rules.Delegs

type EraRuleFailure "DELPL" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Rules.Delpl

type EraRuleFailure "LEDGER" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Rules.Ledger

type EraRuleFailure "LEDGERS" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Rules.Ledgers

type EraRuleFailure "POOL" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Rules.Pool

type EraRuleFailure "PPUP" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Rules.Ppup

type EraRuleFailure "UTXO" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Rules.Utxo

type EraRuleFailure "UTXOW" (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Rules.Utxow

type DowngradePParams f (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.PParams

type PParamsHKD f (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.PParams

type UpgradePParams f (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.PParams

type UpgradePParams f (AllegraEra c) = ()
type NativeScript (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Scripts

type Script (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Scripts

type Tx (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Tx

type TxAuxData (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.TxAuxData

type TxBody (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.TxBody.Internal

type TxBodyUpgradeError (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.TxBody.Internal

type TxOut (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.TxOut

type TxSeq (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.TxSeq

type TxUpgradeError (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Tx

type TxWits (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.TxWits

type Value (AllegraEra _1) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type Value (AllegraEra _1) = Coin
type EraCrypto (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

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

Defined in Cardano.Ledger.Allegra.Era

type ProtVerHigh (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type ProtVerLow (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type ProtVerLow (AllegraEra c) = 3
type TranslationContext (AllegraEra c)

No context is needed to translate from Shelley to Allegra.

Instance details

Defined in Cardano.Ledger.Allegra.Era

type TxCert (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.TxCert

type TxCertUpgradeError (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.TxCert

type Genesis (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Era

type ScriptsNeeded (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.UTxO

type AdditionalGenesisConfig (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra

type GovState (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.PParams

newtype TransitionConfig (AllegraEra c) 
Instance details

Defined in Cardano.Ledger.Allegra.Transition

type TranslationError (AllegraEra c) CertState 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

type TranslationError (AllegraEra c) CommitteeState 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

type TranslationError (AllegraEra c) DState 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

type TranslationError (AllegraEra c) PState 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

type TranslationError (AllegraEra c) VState 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

type TranslationError (AllegraEra c) PParams 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

type TranslationError (AllegraEra c) PParamsUpdate 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

type TranslationError (AllegraEra c) UTxO 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

type TranslationError (AllegraEra c) FuturePParams 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

type TranslationError (AllegraEra c) ShelleyGovState 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

type TranslationError (AllegraEra c) EpochState 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

type TranslationError (AllegraEra c) LedgerState 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

type TranslationError (AllegraEra c) NewEpochState 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

type TranslationError (AllegraEra c) UTxOState 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

type TranslationError (AllegraEra c) ProposedPPUpdates 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

type TranslationError (AllegraEra c) Update 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

type TranslationError (AllegraEra c) ShelleyTx 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

type TranslationError (AllegraEra c) ShelleyTxOut 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

type TranslationError (AllegraEra c) ShelleyTxWits 
Instance details

Defined in Cardano.Ledger.Allegra.Translation

data MaryEra era Source #

Instances

Instances details
EraPP Mary Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.SimplePParams

IsConwayUniv fn ⇒ LedgerEra Mary fn Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.LedgerTypes.Specs

Crypto c ⇒ Era (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

Associated Types

type EraCrypto (MaryEra c) Source #

type PreviousEra (MaryEra c) = (r ∷ Type) Source #

type ProtVerLow (MaryEra c) ∷ Nat Source #

type ProtVerHigh (MaryEra c) ∷ Nat Source #

Methods

eraNameString Source #

Crypto c ⇒ EraGenesis (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

Associated Types

type Genesis (MaryEra c) Source #

Crypto c ⇒ MaryEraTxBody (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.TxBody.Internal

Terse (PParamsUpdate (MaryEra c)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Same

Crypto c ⇒ PrettyA (PParamsUpdate (MaryEra c)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.PrettyCore

Reflect (MaryEra StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Proof

Crypto c ⇒ HasTokens (MaryEra c) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Scriptic

Crypto c ⇒ PostShelley (MaryEra c) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Scriptic

Crypto c ⇒ Scriptic (MaryEra c) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Scriptic

Crypto c ⇒ GetLedgerView (MaryEra c) 
Instance details

Defined in Cardano.Protocol.TPraos.API

type EraRule "BBODY" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type EraRule "BBODY" (MaryEra c) = ShelleyBBODY (MaryEra c)
type EraRule "DELEG" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type EraRule "DELEG" (MaryEra c) = ShelleyDELEG (MaryEra c)
type EraRule "DELEGS" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type EraRule "DELEGS" (MaryEra c) = ShelleyDELEGS (MaryEra c)
type EraRule "DELPL" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type EraRule "DELPL" (MaryEra c) = ShelleyDELPL (MaryEra c)
type EraRule "EPOCH" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type EraRule "EPOCH" (MaryEra c) = ShelleyEPOCH (MaryEra c)
type EraRule "LEDGER" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type EraRule "LEDGER" (MaryEra c) = ShelleyLEDGER (MaryEra c)
type EraRule "LEDGERS" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type EraRule "LEDGERS" (MaryEra c) = ShelleyLEDGERS (MaryEra c)
type EraRule "MIR" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type EraRule "MIR" (MaryEra c) = ShelleyMIR (MaryEra c)
type EraRule "NEWEPOCH" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type EraRule "NEWEPOCH" (MaryEra c) = ShelleyNEWEPOCH (MaryEra c)
type EraRule "NEWPP" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type EraRule "NEWPP" (MaryEra c) = ShelleyNEWPP (MaryEra c)
type EraRule "POOL" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type EraRule "POOL" (MaryEra c) = ShelleyPOOL (MaryEra c)
type EraRule "POOLREAP" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type EraRule "POOLREAP" (MaryEra c) = ShelleyPOOLREAP (MaryEra c)
type EraRule "PPUP" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type EraRule "PPUP" (MaryEra c) = ShelleyPPUP (MaryEra c)
type EraRule "RUPD" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type EraRule "RUPD" (MaryEra c) = ShelleyRUPD (MaryEra c)
type EraRule "SNAP" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type EraRule "SNAP" (MaryEra c) = ShelleySNAP (MaryEra c)
type EraRule "TICK" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type EraRule "TICK" (MaryEra c) = ShelleyTICK (MaryEra c)
type EraRule "TICKF" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type EraRule "TICKF" (MaryEra c) = ShelleyTICKF (MaryEra c)
type EraRule "UPEC" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type EraRule "UPEC" (MaryEra c) = ShelleyUPEC (MaryEra c)
type EraRule "UTXO" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type EraRule "UTXO" (MaryEra c) = AllegraUTXO (MaryEra c)
type EraRule "UTXOW" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type EraRule "UTXOW" (MaryEra c) = AllegraUTXOW (MaryEra c)
type EraRuleEvent "LEDGER" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Rules.Ledger

type EraRuleEvent "TICK" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Rules

type EraRuleFailure "BBODY" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Rules.Bbody

type EraRuleFailure "DELEG" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Rules.Deleg

type EraRuleFailure "DELEGS" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Rules.Delegs

type EraRuleFailure "DELPL" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Rules.Delpl

type EraRuleFailure "LEDGER" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Rules.Ledger

type EraRuleFailure "LEDGERS" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Rules.Ledgers

type EraRuleFailure "POOL" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Rules.Pool

type EraRuleFailure "PPUP" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Rules.Ppup

type EraRuleFailure "UTXO" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Rules.Utxo

type EraRuleFailure "UTXOW" (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Rules.Utxow

type DowngradePParams f (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.PParams

type DowngradePParams f (MaryEra c) = ()
type PParamsHKD f (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.PParams

type UpgradePParams f (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.PParams

type UpgradePParams f (MaryEra c) = ()
type NativeScript (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Scripts

type Script (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Scripts

type Tx (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Tx

type Tx (MaryEra c) = ShelleyTx (MaryEra c)
type TxAuxData (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.TxAuxData

type TxBody (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.TxBody.Internal

type TxBodyUpgradeError (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.TxBody.Internal

type TxOut (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.TxOut

type TxSeq (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.TxSeq

type TxUpgradeError (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Tx

type TxWits (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.TxWits

type Value (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

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

Defined in Cardano.Ledger.Mary.Era

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

Defined in Cardano.Ledger.Mary.Era

type ProtVerHigh (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type ProtVerLow (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type ProtVerLow (MaryEra c) = 4
type TranslationContext (MaryEra c)

No context is needed to translate from Allegra to Mary.

Instance details

Defined in Cardano.Ledger.Mary.Era

type TxCert (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.TxCert

type TxCertUpgradeError (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.TxCert

type Genesis (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Era

type ScriptsNeeded (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.UTxO

type AdditionalGenesisConfig (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary

type GovState (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.PParams

newtype TransitionConfig (MaryEra c) 
Instance details

Defined in Cardano.Ledger.Mary.Transition

type TranslationError (MaryEra c) Timelock 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) AllegraTxAuxData 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) CertState 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) CommitteeState 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) DState 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) PState 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) VState 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) PParams 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) PParamsUpdate 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) UTxO 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) FuturePParams 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) ShelleyGovState 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) EpochState 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) LedgerState 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) NewEpochState 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) UTxOState 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) ProposedPPUpdates 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) Update 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) ShelleyTx 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) ShelleyTxOut 
Instance details

Defined in Cardano.Ledger.Mary.Translation

type TranslationError (MaryEra c) ShelleyTxWits 
Instance details

Defined in Cardano.Ledger.Mary.Translation

data AlonzoEra c Source #

The Alonzo era

Instances

Instances details
EraPP Alonzo Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.SimplePParams

IsConwayUniv fn ⇒ LedgerEra Alonzo fn Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.LedgerTypes.Specs

InjectRuleFailure "BBODY" AlonzoBbodyPredFailure (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Bbody

InjectRuleFailure "UTXO" AlonzoUtxoPredFailure (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

InjectRuleFailure "UTXOS" AlonzoUtxosPredFailure (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxos

InjectRuleFailure "UTXOW" AlonzoUtxowPredFailure (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxow

Generic (PlutusScript (AlonzoEra c)) 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

Associated Types

type Rep (PlutusScript (AlonzoEra c)) ∷ TypeType Source #

Show (PlutusScript (AlonzoEra c)) 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

Crypto c ⇒ AlonzoEraPParams (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

Crypto c ⇒ AlonzoEraScript (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

Associated Types

data PlutusScript (AlonzoEra c) Source #

type PlutusPurpose f (AlonzoEra c) = (r ∷ Type) Source #

Methods

eraMaxLanguageLanguage Source #

toPlutusScriptScript (AlonzoEra c) → Maybe (PlutusScript (AlonzoEra c)) Source #

fromPlutusScriptPlutusScript (AlonzoEra c) → Script (AlonzoEra c) Source #

mkPlutusScript ∷ ∀ (l ∷ Language). PlutusLanguage l ⇒ Plutus l → Maybe (PlutusScript (AlonzoEra c)) Source #

withPlutusScriptPlutusScript (AlonzoEra c) → (∀ (l ∷ Language). PlutusLanguage l ⇒ Plutus l → a) → a Source #

hoistPlutusPurpose ∷ (∀ ix it. g ix it → f ix it) → PlutusPurpose g (AlonzoEra c) → PlutusPurpose f (AlonzoEra c) Source #

mkSpendingPurpose ∷ f Word32 (TxIn (EraCrypto (AlonzoEra c))) → PlutusPurpose f (AlonzoEra c) Source #

toSpendingPurposePlutusPurpose f (AlonzoEra c) → Maybe (f Word32 (TxIn (EraCrypto (AlonzoEra c)))) Source #

mkMintingPurpose ∷ f Word32 (PolicyID (EraCrypto (AlonzoEra c))) → PlutusPurpose f (AlonzoEra c) Source #

toMintingPurposePlutusPurpose f (AlonzoEra c) → Maybe (f Word32 (PolicyID (EraCrypto (AlonzoEra c)))) Source #

mkCertifyingPurpose ∷ f Word32 (TxCert (AlonzoEra c)) → PlutusPurpose f (AlonzoEra c) Source #

toCertifyingPurposePlutusPurpose f (AlonzoEra c) → Maybe (f Word32 (TxCert (AlonzoEra c))) Source #

mkRewardingPurpose ∷ f Word32 (RewardAccount (EraCrypto (AlonzoEra c))) → PlutusPurpose f (AlonzoEra c) Source #

toRewardingPurposePlutusPurpose f (AlonzoEra c) → Maybe (f Word32 (RewardAccount (EraCrypto (AlonzoEra c)))) Source #

upgradePlutusPurposeAsIxPlutusPurpose AsIx (PreviousEra (AlonzoEra c)) → PlutusPurpose AsIx (AlonzoEra c) Source #

Crypto c ⇒ AlonzoEraTx (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Tx

Crypto c ⇒ AlonzoEraTxAuxData (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxAuxData

Crypto c ⇒ AlonzoEraTxBody (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxBody.Internal

Crypto c ⇒ AlonzoEraTxOut (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxOut

(EraScript (AlonzoEra c), Crypto c) ⇒ AlonzoEraTxWits (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxWits

Crypto c ⇒ AlonzoEraUTxO (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.UTxO

Crypto c ⇒ Era (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

Associated Types

type EraCrypto (AlonzoEra c) Source #

type PreviousEra (AlonzoEra c) = (r ∷ Type) Source #

type ProtVerLow (AlonzoEra c) ∷ Nat Source #

type ProtVerHigh (AlonzoEra c) ∷ Nat Source #

Methods

eraNameString Source #

SafeToHash (PlutusScript (AlonzoEra c)) 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

Terse (PParamsUpdate (AlonzoEra c)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Same

Crypto c ⇒ PrettyA (PParamsUpdate (AlonzoEra c)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.PrettyCore

Reflect (AlonzoEra StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Proof

Crypto c ⇒ HasTokens (AlonzoEra c) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Scriptic

Crypto c ⇒ PostShelley (AlonzoEra c) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Scriptic

Crypto c ⇒ Scriptic (AlonzoEra c) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Scriptic

Crypto c ⇒ GetLedgerView (AlonzoEra c) 
Instance details

Defined in Cardano.Protocol.TPraos.API

NFData (PlutusScript (AlonzoEra c)) 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

Methods

rnfPlutusScript (AlonzoEra c) → () Source #

Eq (PlutusScript (AlonzoEra c)) 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

Ord (PlutusScript (AlonzoEra c)) 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

NoThunks (PlutusScript (AlonzoEra c)) 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

Crypto c ⇒ TranslateEra (AlonzoEra c) Tx 
Instance details

Defined in Cardano.Ledger.Alonzo.Translation

Associated Types

type TranslationError (AlonzoEra c) Tx Source #

Crypto c ⇒ ToJSON (AlonzoPParams Identity (AlonzoEra c)) 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

Crypto c ⇒ ToJSON (AlonzoPParams StrictMaybe (AlonzoEra c)) 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

type PlutusPurpose f (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

type EraRule "BBODY" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type EraRule "BBODY" (AlonzoEra c) = AlonzoBBODY (AlonzoEra c)
type EraRule "DELEG" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type EraRule "DELEG" (AlonzoEra c) = ShelleyDELEG (AlonzoEra c)
type EraRule "DELEGS" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type EraRule "DELEGS" (AlonzoEra c) = ShelleyDELEGS (AlonzoEra c)
type EraRule "DELPL" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type EraRule "DELPL" (AlonzoEra c) = ShelleyDELPL (AlonzoEra c)
type EraRule "EPOCH" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type EraRule "EPOCH" (AlonzoEra c) = ShelleyEPOCH (AlonzoEra c)
type EraRule "LEDGER" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type EraRule "LEDGER" (AlonzoEra c) = AlonzoLEDGER (AlonzoEra c)
type EraRule "LEDGERS" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type EraRule "LEDGERS" (AlonzoEra c) = ShelleyLEDGERS (AlonzoEra c)
type EraRule "MIR" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type EraRule "MIR" (AlonzoEra c) = ShelleyMIR (AlonzoEra c)
type EraRule "NEWEPOCH" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type EraRule "NEWEPOCH" (AlonzoEra c) = ShelleyNEWEPOCH (AlonzoEra c)
type EraRule "NEWPP" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type EraRule "NEWPP" (AlonzoEra c) = ShelleyNEWPP (AlonzoEra c)
type EraRule "POOL" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type EraRule "POOL" (AlonzoEra c) = ShelleyPOOL (AlonzoEra c)
type EraRule "POOLREAP" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type EraRule "POOLREAP" (AlonzoEra c) = ShelleyPOOLREAP (AlonzoEra c)
type EraRule "PPUP" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type EraRule "PPUP" (AlonzoEra c) = ShelleyPPUP (AlonzoEra c)
type EraRule "RUPD" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type EraRule "RUPD" (AlonzoEra c) = ShelleyRUPD (AlonzoEra c)
type EraRule "SNAP" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type EraRule "SNAP" (AlonzoEra c) = ShelleySNAP (AlonzoEra c)
type EraRule "TICK" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type EraRule "TICK" (AlonzoEra c) = ShelleyTICK (AlonzoEra c)
type EraRule "TICKF" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type EraRule "TICKF" (AlonzoEra c) = ShelleyTICKF (AlonzoEra c)
type EraRule "UPEC" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type EraRule "UPEC" (AlonzoEra c) = ShelleyUPEC (AlonzoEra c)
type EraRule "UTXO" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type EraRule "UTXO" (AlonzoEra c) = AlonzoUTXO (AlonzoEra c)
type EraRule "UTXOS" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type EraRule "UTXOS" (AlonzoEra c) = AlonzoUTXOS (AlonzoEra c)
type EraRule "UTXOW" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type EraRule "UTXOW" (AlonzoEra c) = AlonzoUTXOW (AlonzoEra c)
type EraRuleEvent "LEDGER" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules

type EraRuleEvent "PPUP" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Ppup

type EraRuleEvent "TICK" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules

type EraRuleFailure "BBODY" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Bbody

type EraRuleFailure "DELEG" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Deleg

type EraRuleFailure "DELEGS" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Delegs

type EraRuleFailure "DELPL" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Delpl

type EraRuleFailure "LEDGER" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Ledger

type EraRuleFailure "LEDGERS" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Ledgers

type EraRuleFailure "POOL" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Pool

type EraRuleFailure "PPUP" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Ppup

type EraRuleFailure "UTXO" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxo

type EraRuleFailure "UTXOS" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxos

type EraRuleFailure "UTXOW" (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Rules.Utxow

type DowngradePParams f (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

type PParamsHKD f (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

type UpgradePParams f (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

type Rep (PlutusScript (AlonzoEra c)) 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

type Rep (TransitionConfig (AlonzoEra c)) 
Instance details

Defined in Cardano.Ledger.Alonzo.Transition

type Rep (TransitionConfig (AlonzoEra c)) = D1 ('MetaData "TransitionConfig" "Cardano.Ledger.Alonzo.Transition" "cardano-ledger-alonzo-1.11.0.0-inplace" 'False) (C1 ('MetaCons "AlonzoTransitionConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "atcAlonzoGenesis") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 AlonzoGenesis) :*: S1 ('MetaSel ('Just "atcMaryTransitionConfig") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TransitionConfig (MaryEra c)))))
type ContextError (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Plutus.TxInfo

newtype PlutusScript (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

type NativeScript (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

type Script (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

type Tx (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Tx

type TxAuxData (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxAuxData

type TxBody (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxBody.Internal

type TxBodyUpgradeError (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxBody.Internal

type TxOut (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxOut

type TxSeq (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxSeq.Internal

type TxUpgradeError (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Tx

type TxUpgradeError (AlonzoEra c) = AlonzoTxUpgradeError
type TxWits (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxWits

type Value (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type EraCrypto (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

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

Defined in Cardano.Ledger.Alonzo.Era

type ProtVerHigh (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type ProtVerHigh (AlonzoEra c) = 6
type ProtVerLow (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Era

type ProtVerLow (AlonzoEra c) = 5
type TranslationContext (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Translation

type TxCert (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxCert

type TxCertUpgradeError (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxCert

type Genesis (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Genesis

type ScriptsNeeded (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.UTxO

type AdditionalGenesisConfig (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo

type GovState (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

data TransitionConfig (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Transition

type TranslationError (AlonzoEra c) Tx 
Instance details

Defined in Cardano.Ledger.Alonzo.Translation

type TranslationError (AlonzoEra c) CertState 
Instance details

Defined in Cardano.Ledger.Alonzo.Translation

type TranslationError (AlonzoEra c) CommitteeState 
Instance details

Defined in Cardano.Ledger.Alonzo.Translation

type TranslationError (AlonzoEra c) DState 
Instance details

Defined in Cardano.Ledger.Alonzo.Translation

type TranslationError (AlonzoEra c) PState 
Instance details

Defined in Cardano.Ledger.Alonzo.Translation

type TranslationError (AlonzoEra c) VState 
Instance details

Defined in Cardano.Ledger.Alonzo.Translation

type TranslationError (AlonzoEra c) PParams 
Instance details

Defined in Cardano.Ledger.Alonzo.Translation

type TranslationError (AlonzoEra c) UTxO 
Instance details

Defined in Cardano.Ledger.Alonzo.Translation

type TranslationError (AlonzoEra c) FuturePParams 
Instance details

Defined in Cardano.Ledger.Alonzo.Translation

type TranslationError (AlonzoEra c) ShelleyGovState 
Instance details

Defined in Cardano.Ledger.Alonzo.Translation

type TranslationError (AlonzoEra c) EpochState 
Instance details

Defined in Cardano.Ledger.Alonzo.Translation

type TranslationError (AlonzoEra c) LedgerState 
Instance details

Defined in Cardano.Ledger.Alonzo.Translation

type TranslationError (AlonzoEra c) NewEpochState 
Instance details

Defined in Cardano.Ledger.Alonzo.Translation

type TranslationError (AlonzoEra c) UTxOState 
Instance details

Defined in Cardano.Ledger.Alonzo.Translation

type TranslationError (AlonzoEra c) ProposedPPUpdates 
Instance details

Defined in Cardano.Ledger.Alonzo.Translation

data BabbageEra c Source #

The Babbage era

Instances

Instances details
EraPP Babbage Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.SimplePParams

IsConwayUniv fn ⇒ LedgerEra Babbage fn Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.LedgerTypes.Specs

InjectRuleFailure "UTXO" BabbageUtxoPredFailure (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Rules.Utxo

InjectRuleFailure "UTXOW" BabbageUtxowPredFailure (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Rules.Utxow

Crypto c ⇒ BabbageEraPParams (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.PParams

Methods

hkdCoinsPerUTxOByteL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f (BabbageEra c)) (HKD f CoinPerByte) Source #

Crypto c ⇒ BabbageEraTxBody (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.TxBody.Internal

Crypto c ⇒ BabbageEraTxOut (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.TxOut

Crypto c ⇒ Era (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

Associated Types

type EraCrypto (BabbageEra c) Source #

type PreviousEra (BabbageEra c) = (r ∷ Type) Source #

type ProtVerLow (BabbageEra c) ∷ Nat Source #

type ProtVerHigh (BabbageEra c) ∷ Nat Source #

Methods

eraNameString Source #

Crypto c ⇒ EraGenesis (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

Associated Types

type Genesis (BabbageEra c) Source #

Terse (PParamsUpdate (BabbageEra c)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Same

Crypto c ⇒ PrettyA (PParamsUpdate (BabbageEra c)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.PrettyCore

Reflect (BabbageEra StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Proof

Crypto c ⇒ HasTokens (BabbageEra c) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Scriptic

Crypto c ⇒ PostShelley (BabbageEra c) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Scriptic

Crypto c ⇒ Scriptic (BabbageEra c) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Scriptic

Crypto c ⇒ GetLedgerView (BabbageEra c) 
Instance details

Defined in Cardano.Protocol.TPraos.API

Crypto c ⇒ TranslateEra (BabbageEra c) Tx 
Instance details

Defined in Cardano.Ledger.Babbage.Translation

Associated Types

type TranslationError (BabbageEra c) Tx Source #

type PlutusPurpose f (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Scripts

type EraRule "BBODY" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type EraRule "BBODY" (BabbageEra c) = AlonzoBBODY (BabbageEra c)
type EraRule "DELEG" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type EraRule "DELEG" (BabbageEra c) = ShelleyDELEG (BabbageEra c)
type EraRule "DELEGS" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type EraRule "DELEGS" (BabbageEra c) = ShelleyDELEGS (BabbageEra c)
type EraRule "DELPL" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type EraRule "DELPL" (BabbageEra c) = ShelleyDELPL (BabbageEra c)
type EraRule "EPOCH" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type EraRule "EPOCH" (BabbageEra c) = ShelleyEPOCH (BabbageEra c)
type EraRule "LEDGER" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type EraRule "LEDGER" (BabbageEra c) = BabbageLEDGER (BabbageEra c)
type EraRule "LEDGERS" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type EraRule "LEDGERS" (BabbageEra c) = ShelleyLEDGERS (BabbageEra c)
type EraRule "MIR" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type EraRule "NEWEPOCH" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type EraRule "NEWEPOCH" (BabbageEra c) = ShelleyNEWEPOCH (BabbageEra c)
type EraRule "NEWPP" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type EraRule "NEWPP" (BabbageEra c) = ShelleyNEWPP (BabbageEra c)
type EraRule "POOL" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type EraRule "POOLREAP" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type EraRule "POOLREAP" (BabbageEra c) = ShelleyPOOLREAP (BabbageEra c)
type EraRule "PPUP" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type EraRule "RUPD" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type EraRule "SNAP" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type EraRule "TICK" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type EraRule "TICKF" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type EraRule "TICKF" (BabbageEra c) = ShelleyTICKF (BabbageEra c)
type EraRule "UPEC" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type EraRule "UTXO" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type EraRule "UTXOS" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type EraRule "UTXOS" (BabbageEra c) = BabbageUTXOS (BabbageEra c)
type EraRule "UTXOW" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type EraRule "UTXOW" (BabbageEra c) = BabbageUTXOW (BabbageEra c)
type EraRuleEvent "LEDGER" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Rules

type EraRuleEvent "PPUP" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Rules

type EraRuleEvent "TICK" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Rules

type EraRuleEvent "UTXOS" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Rules.Utxos

type EraRuleFailure "BBODY" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Rules.Bbody

type EraRuleFailure "DELEG" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Rules.Deleg

type EraRuleFailure "DELEGS" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Rules.Delegs

type EraRuleFailure "DELPL" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Rules.Delpl

type EraRuleFailure "LEDGER" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Rules.Ledger

type EraRuleFailure "LEDGERS" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Rules.Ledgers

type EraRuleFailure "POOL" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Rules.Pool

type EraRuleFailure "PPUP" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Rules.Ppup

type EraRuleFailure "UTXO" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Rules.Utxo

type EraRuleFailure "UTXOS" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Rules.Utxos

type EraRuleFailure "UTXOW" (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Rules.Utxow

type DowngradePParams f (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.PParams

type PParamsHKD f (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.PParams

type UpgradePParams f (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.PParams

type UpgradePParams f (BabbageEra c) = ()
type Rep (PlutusScript (BabbageEra c)) 
Instance details

Defined in Cardano.Ledger.Babbage.Scripts

type Rep (PlutusScript (BabbageEra c)) = D1 ('MetaData "PlutusScript" "Cardano.Ledger.Babbage.Scripts" "cardano-ledger-babbage-1.10.0.0-inplace" 'False) (C1 ('MetaCons "BabbagePlutusV1" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 (Plutus 'PlutusV1))) :+: C1 ('MetaCons "BabbagePlutusV2" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 (Plutus 'PlutusV2))))
type ContextError (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.TxInfo

data PlutusScript (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Scripts

type NativeScript (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Scripts

type Script (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Scripts

type Tx (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Tx

type TxAuxData (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.TxAuxData

type TxBody (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.TxBody.Internal

type TxBodyUpgradeError (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.TxBody.Internal

type TxOut (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.TxOut

type TxSeq (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Tx

type TxUpgradeError (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Tx

type TxUpgradeError (BabbageEra c) = BabbageTxUpgradeError
type TxWits (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.TxWits

type Value (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type EraCrypto (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

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

Defined in Cardano.Ledger.Babbage.Era

type ProtVerHigh (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type ProtVerHigh (BabbageEra c) = 8
type ProtVerLow (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type ProtVerLow (BabbageEra c) = 7
type TranslationContext (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type TxCert (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.TxCert

type TxCertUpgradeError (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.TxCert

type Genesis (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Era

type ScriptsNeeded (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.UTxO

type AdditionalGenesisConfig (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage

type GovState (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.PParams

newtype TransitionConfig (BabbageEra c) 
Instance details

Defined in Cardano.Ledger.Babbage.Transition

type TranslationError (BabbageEra c) Tx 
Instance details

Defined in Cardano.Ledger.Babbage.Translation

type TranslationError (BabbageEra c) CertState 
Instance details

Defined in Cardano.Ledger.Babbage.Translation

type TranslationError (BabbageEra c) CommitteeState 
Instance details

Defined in Cardano.Ledger.Babbage.Translation

type TranslationError (BabbageEra c) DState 
Instance details

Defined in Cardano.Ledger.Babbage.Translation

type TranslationError (BabbageEra c) PState 
Instance details

Defined in Cardano.Ledger.Babbage.Translation

type TranslationError (BabbageEra c) VState 
Instance details

Defined in Cardano.Ledger.Babbage.Translation

type TranslationError (BabbageEra c) PParams 
Instance details

Defined in Cardano.Ledger.Babbage.Translation

type TranslationError (BabbageEra c) UTxO 
Instance details

Defined in Cardano.Ledger.Babbage.Translation

type TranslationError (BabbageEra c) FuturePParams 
Instance details

Defined in Cardano.Ledger.Babbage.Translation

type TranslationError (BabbageEra c) ShelleyGovState 
Instance details

Defined in Cardano.Ledger.Babbage.Translation

type TranslationError (BabbageEra c) EpochState 
Instance details

Defined in Cardano.Ledger.Babbage.Translation

type TranslationError (BabbageEra c) LedgerState 
Instance details

Defined in Cardano.Ledger.Babbage.Translation

type TranslationError (BabbageEra c) NewEpochState 
Instance details

Defined in Cardano.Ledger.Babbage.Translation

type TranslationError (BabbageEra c) UTxOState 
Instance details

Defined in Cardano.Ledger.Babbage.Translation

type TranslationError (BabbageEra c) ProposedPPUpdates 
Instance details

Defined in Cardano.Ledger.Babbage.Translation

data ConwayEra c Source #

The Conway era

Instances

Instances details
EraPP Conway Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.SimplePParams

IsConwayUniv fn ⇒ LedgerEra Conway fn Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.LedgerTypes.Specs

InjectRuleEvent "UTXOS" ConwayUtxosEvent (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Utxos

InjectRuleFailure "BBODY" ConwayBbodyPredFailure (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Bbody

InjectRuleFailure "CERT" ConwayCertPredFailure (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Cert

InjectRuleFailure "CERTS" ConwayCertsPredFailure (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Certs

InjectRuleFailure "DELEG" ConwayDelegPredFailure (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Deleg

InjectRuleFailure "GOV" ConwayGovPredFailure (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Gov

InjectRuleFailure "GOVCERT" ConwayGovCertPredFailure (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.GovCert

InjectRuleFailure "LEDGER" ConwayLedgerPredFailure (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Ledger

InjectRuleFailure "MEMPOOL" ConwayMempoolPredFailure (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Mempool

InjectRuleFailure "UTXO" ConwayUtxoPredFailure (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Utxo

InjectRuleFailure "UTXOS" ConwayUtxosPredFailure (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Utxos

InjectRuleFailure "UTXOW" ConwayUtxowPredFailure (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Utxow

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (AlonzoTx Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type TypeSpec fn (AlonzoTx Conway) Source #

type Prerequisites fn (AlonzoTx Conway) Source #

IsConwayUniv fn ⇒ HasSpec fn (AlonzoTxAuxData Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

IsConwayUniv fn ⇒ HasSpec fn (AlonzoTxWits Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (ConwayGovState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (DRepPulsingState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (PulsingSnapshot Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (EnactState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

IsConwayUniv fn ⇒ HasSpec fn (RatifyEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type TypeSpec fn (RatifyEnv Conway) Source #

type Prerequisites fn (RatifyEnv Conway) Source #

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (RatifySignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (RatifyState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

IsConwayUniv fn ⇒ HasSpec fn (Committee Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type TypeSpec fn (Committee Conway) Source #

type Prerequisites fn (Committee Conway) Source #

(IsConwayUniv fn, EraPP Conway) ⇒ HasSpec fn (GovAction Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type TypeSpec fn (GovAction Conway) Source #

type Prerequisites fn (GovAction Conway) Source #

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (GovActionState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

(IsConwayUniv fn, EraPP Conway) ⇒ HasSpec fn (ProposalProcedure Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (Proposals Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type TypeSpec fn (Proposals Conway) Source #

type Prerequisites fn (Proposals Conway) Source #

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (CertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type TypeSpec fn (CertEnv Conway) Source #

type Prerequisites fn (CertEnv Conway) Source #

(IsConwayUniv fn, EraPP Conway) ⇒ HasSpec fn (CertsEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type TypeSpec fn (CertsEnv Conway) Source #

type Prerequisites fn (CertsEnv Conway) Source #

(IsConwayUniv fn, EraPP Conway) ⇒ HasSpec fn (EnactSignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

(EraTxCert Conway, EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (GovSignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type TypeSpec fn (GovSignal Conway) Source #

type Prerequisites fn (GovSignal Conway) Source #

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (ConwayGovCertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

(EraPP (ConwayEra c), IsConwayUniv fn, Crypto c) ⇒ HasSpec fn (ConwayTxBody (ConwayEra c)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type TypeSpec fn (ConwayTxBody (ConwayEra c)) Source #

type Prerequisites fn (ConwayTxBody (ConwayEra c)) Source #

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (PoolEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type TypeSpec fn (PoolEnv Conway) Source #

type Prerequisites fn (PoolEnv Conway) Source #

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (DRepPulser Conway Identity (RatifyState Conway)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Methods

emptySpecTypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) Source #

combineSpecTypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) → TypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) → Specification fn (DRepPulser Conway Identity (RatifyState Conway)) Source #

genFromTypeSpec ∷ ∀ (m ∷ TypeType). (HasCallStack, MonadGenError m) ⇒ TypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) → GenT m (DRepPulser Conway Identity (RatifyState Conway)) Source #

conformsToDRepPulser Conway Identity (RatifyState Conway) → TypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) → Bool Source #

shrinkWithTypeSpecTypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) → DRepPulser Conway Identity (RatifyState Conway) → [DRepPulser Conway Identity (RatifyState Conway)] Source #

toPredsTerm fn (DRepPulser Conway Identity (RatifyState Conway)) → TypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) → Pred fn Source #

cardinalTypeSpecTypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) → Specification fn Integer Source #

cardinalTrueSpecSpecification fn Integer Source #

typeSpecHasErrorTypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) → Maybe (NonEmpty String) Source #

alternateShowTypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) → BinaryShow Source #

monadConformsToDRepPulser Conway Identity (RatifyState Conway) → TypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) → Writer [String] Bool Source #

typeSpecOptTypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) → [DRepPulser Conway Identity (RatifyState Conway)] → Specification fn (DRepPulser Conway Identity (RatifyState Conway)) Source #

prerequisitesEvidence (Prerequisites fn (DRepPulser Conway Identity (RatifyState Conway))) Source #

Crypto c ⇒ ConwayEraGov (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Crypto c ⇒ ConwayEraPParams (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

Crypto c ⇒ ConwayEraScript (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Scripts

Crypto c ⇒ ConwayEraTransition (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Transition

Crypto c ⇒ ConwayEraTxBody (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.TxBody.Internal

Crypto c ⇒ ConwayEraTxCert (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

mkRegDepositTxCertStakeCredential (EraCrypto (ConwayEra c)) → CoinTxCert (ConwayEra c) Source #

getRegDepositTxCertTxCert (ConwayEra c) → Maybe (StakeCredential (EraCrypto (ConwayEra c)), Coin) Source #

mkUnRegDepositTxCertStakeCredential (EraCrypto (ConwayEra c)) → CoinTxCert (ConwayEra c) Source #

getUnRegDepositTxCertTxCert (ConwayEra c) → Maybe (StakeCredential (EraCrypto (ConwayEra c)), Coin) Source #

mkDelegTxCertStakeCredential (EraCrypto (ConwayEra c)) → Delegatee (EraCrypto (ConwayEra c)) → TxCert (ConwayEra c) Source #

getDelegTxCertTxCert (ConwayEra c) → Maybe (StakeCredential (EraCrypto (ConwayEra c)), Delegatee (EraCrypto (ConwayEra c))) Source #

mkRegDepositDelegTxCertStakeCredential (EraCrypto (ConwayEra c)) → Delegatee (EraCrypto (ConwayEra c)) → CoinTxCert (ConwayEra c) Source #

getRegDepositDelegTxCertTxCert (ConwayEra c) → Maybe (StakeCredential (EraCrypto (ConwayEra c)), Delegatee (EraCrypto (ConwayEra c)), Coin) Source #

mkAuthCommitteeHotKeyTxCertCredential 'ColdCommitteeRole (EraCrypto (ConwayEra c)) → Credential 'HotCommitteeRole (EraCrypto (ConwayEra c)) → TxCert (ConwayEra c) Source #

getAuthCommitteeHotKeyTxCertTxCert (ConwayEra c) → Maybe (Credential 'ColdCommitteeRole (EraCrypto (ConwayEra c)), Credential 'HotCommitteeRole (EraCrypto (ConwayEra c))) Source #

mkResignCommitteeColdTxCertCredential 'ColdCommitteeRole (EraCrypto (ConwayEra c)) → StrictMaybe (Anchor (EraCrypto (ConwayEra c))) → TxCert (ConwayEra c) Source #

getResignCommitteeColdTxCertTxCert (ConwayEra c) → Maybe (Credential 'ColdCommitteeRole (EraCrypto (ConwayEra c)), StrictMaybe (Anchor (EraCrypto (ConwayEra c)))) Source #

mkRegDRepTxCertCredential 'DRepRole (EraCrypto (ConwayEra c)) → CoinStrictMaybe (Anchor (EraCrypto (ConwayEra c))) → TxCert (ConwayEra c) Source #

getRegDRepTxCertTxCert (ConwayEra c) → Maybe (Credential 'DRepRole (EraCrypto (ConwayEra c)), Coin, StrictMaybe (Anchor (EraCrypto (ConwayEra c)))) Source #

mkUnRegDRepTxCertCredential 'DRepRole (EraCrypto (ConwayEra c)) → CoinTxCert (ConwayEra c) Source #

getUnRegDRepTxCertTxCert (ConwayEra c) → Maybe (Credential 'DRepRole (EraCrypto (ConwayEra c)), Coin) Source #

mkUpdateDRepTxCertCredential 'DRepRole (EraCrypto (ConwayEra c)) → StrictMaybe (Anchor (EraCrypto (ConwayEra c))) → TxCert (ConwayEra c) Source #

getUpdateDRepTxCertTxCert (ConwayEra c) → Maybe (Credential 'DRepRole (EraCrypto (ConwayEra c)), StrictMaybe (Anchor (EraCrypto (ConwayEra c)))) Source #

Crypto c ⇒ Era (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

Associated Types

type EraCrypto (ConwayEra c) Source #

type PreviousEra (ConwayEra c) = (r ∷ Type) Source #

type ProtVerLow (ConwayEra c) ∷ Nat Source #

type ProtVerHigh (ConwayEra c) ∷ Nat Source #

Methods

eraNameString Source #

Terse (PParamsUpdate (ConwayEra c)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Same

Crypto c ⇒ PrettyA (PParamsUpdate (ConwayEra c)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.PrettyCore

Reflect (ConwayEra StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Proof

Crypto c ⇒ HasTokens (ConwayEra c) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Scriptic

Crypto c ⇒ PostShelley (ConwayEra c) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Scriptic

Crypto c ⇒ Scriptic (ConwayEra c) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Scriptic

Crypto c ⇒ GetLedgerView (ConwayEra c) 
Instance details

Defined in Cardano.Protocol.TPraos.API

HasSimpleRep (AlonzoTxAuxData Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

HasSimpleRep (AlonzoTxWits Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

HasSimpleRep (ConwayGovState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

HasSimpleRep (DRepPulsingState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

HasSimpleRep (PulsingSnapshot Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

HasSimpleRep (EnactState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type SimpleRep (EnactState Conway) Source #

type TheSop (EnactState Conway) ∷ [Type] Source #

HasSimpleRep (RatifyEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type SimpleRep (RatifyEnv Conway) Source #

type TheSop (RatifyEnv Conway) ∷ [Type] Source #

HasSimpleRep (RatifySignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

HasSimpleRep (RatifyState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type SimpleRep (RatifyState Conway) Source #

type TheSop (RatifyState Conway) ∷ [Type] Source #

HasSimpleRep (Committee Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type SimpleRep (Committee Conway) Source #

type TheSop (Committee Conway) ∷ [Type] Source #

HasSimpleRep (GovActionState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

HasSimpleRep (Proposals Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type SimpleRep (Proposals Conway) Source #

type TheSop (Proposals Conway) ∷ [Type] Source #

HasSimpleRep (CertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type SimpleRep (CertEnv Conway) Source #

type TheSop (CertEnv Conway) ∷ [Type] Source #

HasSimpleRep (CertsEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type SimpleRep (CertsEnv Conway) Source #

type TheSop (CertsEnv Conway) ∷ [Type] Source #

HasSimpleRep (ConwayGovCertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Crypto c ⇒ HasSimpleRep (ConwayTxBody (ConwayEra c)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type SimpleRep (ConwayTxBody (ConwayEra c)) Source #

type TheSop (ConwayTxBody (ConwayEra c)) ∷ [Type] Source #

HasSimpleRep (PoolEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type SimpleRep (PoolEnv Conway) Source #

type TheSop (PoolEnv Conway) ∷ [Type] Source #

Crypto c ⇒ TranslateEra (ConwayEra c) Tx 
Instance details

Defined in Cardano.Ledger.Conway.Translation

Associated Types

type TranslationError (ConwayEra c) Tx Source #

WellFormed (ConwayGovState Conway) Conway Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.LedgerTypes.WellFormed

WellFormed (GovEnv Conway) Conway Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.LedgerTypes.WellFormed

Crypto c ⇒ ToJSON (ConwayPParams Identity (ConwayEra c)) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

HasSimpleRep (DRepPulser Conway Identity (RatifyState Conway)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type PlutusPurpose f (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Scripts

type EraRule "BBODY" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "BBODY" (ConwayEra c) = ConwayBBODY (ConwayEra c)
type EraRule "CERT" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "CERT" (ConwayEra c) = ConwayCERT (ConwayEra c)
type EraRule "CERTS" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "CERTS" (ConwayEra c) = ConwayCERTS (ConwayEra c)
type EraRule "DELEG" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "DELEG" (ConwayEra c) = ConwayDELEG (ConwayEra c)
type EraRule "DELEGS" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "DELEGS" (ConwayEra c) = VoidEraRule "DELEGS" (ConwayEra c)
type EraRule "ENACT" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "ENACT" (ConwayEra c) = ConwayENACT (ConwayEra c)
type EraRule "EPOCH" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "EPOCH" (ConwayEra c) = ConwayEPOCH (ConwayEra c)
type EraRule "GOV" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "GOV" (ConwayEra c) = ConwayGOV (ConwayEra c)
type EraRule "GOVCERT" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "GOVCERT" (ConwayEra c) = ConwayGOVCERT (ConwayEra c)
type EraRule "HARDFORK" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "HARDFORK" (ConwayEra c) = ConwayHARDFORK (ConwayEra c)
type EraRule "LEDGER" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "LEDGER" (ConwayEra c) = ConwayLEDGER (ConwayEra c)
type EraRule "LEDGERS" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "LEDGERS" (ConwayEra c) = ShelleyLEDGERS (ConwayEra c)
type EraRule "MEMPOOL" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "MEMPOOL" (ConwayEra c) = ConwayMEMPOOL (ConwayEra c)
type EraRule "MIR" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "MIR" (ConwayEra c) = VoidEraRule "MIR" (ConwayEra c)
type EraRule "NEWEPOCH" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "NEWEPOCH" (ConwayEra c) = ConwayNEWEPOCH (ConwayEra c)
type EraRule "NEWPP" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "NEWPP" (ConwayEra c) = VoidEraRule "NEWPP" (ConwayEra c)
type EraRule "POOL" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "POOL" (ConwayEra c) = ShelleyPOOL (ConwayEra c)
type EraRule "POOLREAP" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "POOLREAP" (ConwayEra c) = ShelleyPOOLREAP (ConwayEra c)
type EraRule "PPUP" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "PPUP" (ConwayEra c) = VoidEraRule "PPUP" (ConwayEra c)
type EraRule "RATIFY" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "RATIFY" (ConwayEra c) = ConwayRATIFY (ConwayEra c)
type EraRule "RUPD" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "RUPD" (ConwayEra c) = ShelleyRUPD (ConwayEra c)
type EraRule "SNAP" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "SNAP" (ConwayEra c) = ShelleySNAP (ConwayEra c)
type EraRule "TICK" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "TICK" (ConwayEra c) = ShelleyTICK (ConwayEra c)
type EraRule "TICKF" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "TICKF" (ConwayEra c) = ConwayTICKF (ConwayEra c)
type EraRule "UPEC" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "UPEC" (ConwayEra c) = VoidEraRule "UPEC" (ConwayEra c)
type EraRule "UTXO" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "UTXO" (ConwayEra c) = ConwayUTXO (ConwayEra c)
type EraRule "UTXOS" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "UTXOS" (ConwayEra c) = ConwayUTXOS (ConwayEra c)
type EraRule "UTXOW" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRule "UTXOW" (ConwayEra c) = ConwayUTXOW (ConwayEra c)
type EraRuleEvent "BBODY" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Bbody

type EraRuleEvent "CERT" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Cert

type EraRuleEvent "CERTS" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Certs

type EraRuleEvent "DELEG" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Deleg

type EraRuleEvent "DELEG" (ConwayEra c) = VoidEraRule "DELEG" (ConwayEra c)
type EraRuleEvent "DELEGS" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRuleEvent "DELEGS" (ConwayEra c) = VoidEraRule "DELEGS" (ConwayEra c)
type EraRuleEvent "ENACT" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Enact

type EraRuleEvent "ENACT" (ConwayEra c) = VoidEraRule "ENACT" (ConwayEra c)
type EraRuleEvent "EPOCH" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Epoch

type EraRuleEvent "GOV" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Gov

type EraRuleEvent "GOVCERT" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.GovCert

type EraRuleEvent "GOVCERT" (ConwayEra c) = VoidEraRule "GOVCERT" (ConwayEra c)
type EraRuleEvent "HARDFORK" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.HardFork

type EraRuleEvent "LEDGER" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Ledger

type EraRuleEvent "LEDGERS" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Ledgers

type EraRuleEvent "MEMPOOL" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Mempool

type EraRuleEvent "MIR" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRuleEvent "MIR" (ConwayEra c) = VoidEraRule "MIR" (ConwayEra c)
type EraRuleEvent "NEWEPOCH" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.NewEpoch

type EraRuleEvent "NEWPP" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRuleEvent "NEWPP" (ConwayEra c) = VoidEraRule "NEWPP" (ConwayEra c)
type EraRuleEvent "POOL" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Pool

type EraRuleEvent "PPUP" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRuleEvent "PPUP" (ConwayEra c) = VoidEraRule "PPUP" (ConwayEra c)
type EraRuleEvent "TICK" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules

type EraRuleEvent "UPEC" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRuleEvent "UPEC" (ConwayEra c) = VoidEraRule "UPEC" (ConwayEra c)
type EraRuleEvent "UTXO" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Utxo

type EraRuleEvent "UTXOS" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Utxos

type EraRuleEvent "UTXOW" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Utxow

type EraRuleFailure "BBODY" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Bbody

type EraRuleFailure "CERT" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Cert

type EraRuleFailure "CERTS" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Certs

type EraRuleFailure "DELEG" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Deleg

type EraRuleFailure "DELEGS" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRuleFailure "DELEGS" (ConwayEra c) = VoidEraRule "DELEGS" (ConwayEra c)
type EraRuleFailure "GOV" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Gov

type EraRuleFailure "GOVCERT" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.GovCert

type EraRuleFailure "LEDGER" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Ledger

type EraRuleFailure "LEDGERS" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Ledgers

type EraRuleFailure "MEMPOOL" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Mempool

type EraRuleFailure "MIR" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRuleFailure "MIR" (ConwayEra c) = VoidEraRule "MIR" (ConwayEra c)
type EraRuleFailure "NEWPP" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRuleFailure "NEWPP" (ConwayEra c) = VoidEraRule "NEWPP" (ConwayEra c)
type EraRuleFailure "POOL" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Pool

type EraRuleFailure "PPUP" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRuleFailure "PPUP" (ConwayEra c) = VoidEraRule "PPUP" (ConwayEra c)
type EraRuleFailure "UPEC" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraRuleFailure "UPEC" (ConwayEra c) = VoidEraRule "UPEC" (ConwayEra c)
type EraRuleFailure "UTXO" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Utxo

type EraRuleFailure "UTXOS" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Utxos

type EraRuleFailure "UTXOW" (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Utxow

type DowngradePParams f (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

type DowngradePParams f (ConwayEra c) = ()
type PParamsHKD f (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

type UpgradePParams f (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

type Prerequisites fn (AlonzoTx Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (AlonzoTxAuxData Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (AlonzoTxWits Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (ConwayGovState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (DRepPulsingState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (PulsingSnapshot Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (EnactState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (RatifyEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (RatifySignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (RatifyState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (Committee Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (GovAction Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (GovActionState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (ProposalProcedure Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (Proposals Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (CertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (CertsEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (EnactSignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (GovSignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (ConwayGovCertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (ConwayTxBody (ConwayEra c)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (PoolEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (AlonzoTx Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (AlonzoTxAuxData Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (AlonzoTxWits Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (ConwayGovState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (DRepPulsingState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (PulsingSnapshot Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (EnactState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (RatifyEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (RatifySignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (RatifyState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (Committee Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (GovAction Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (GovActionState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (ProposalProcedure Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (Proposals Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (CertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (CertsEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (EnactSignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (GovSignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (ConwayGovCertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (ConwayTxBody (ConwayEra c)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (PoolEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (DRepPulser Conway Identity (RatifyState Conway)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Rep (PlutusScript (ConwayEra c)) 
Instance details

Defined in Cardano.Ledger.Conway.Scripts

type Rep (PlutusScript (ConwayEra c)) = D1 ('MetaData "PlutusScript" "Cardano.Ledger.Conway.Scripts" "cardano-ledger-conway-1.18.0.0-inplace" 'False) (C1 ('MetaCons "ConwayPlutusV1" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 (Plutus 'PlutusV1))) :+: (C1 ('MetaCons "ConwayPlutusV2" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 (Plutus 'PlutusV2))) :+: C1 ('MetaCons "ConwayPlutusV3" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 (Plutus 'PlutusV3)))))
type Rep (TransitionConfig (ConwayEra c)) 
Instance details

Defined in Cardano.Ledger.Conway.Transition

type Rep (TransitionConfig (ConwayEra c)) = D1 ('MetaData "TransitionConfig" "Cardano.Ledger.Conway.Transition" "cardano-ledger-conway-1.18.0.0-inplace" 'False) (C1 ('MetaCons "ConwayTransitionConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "ctcConwayGenesis") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ConwayGenesis c)) :*: S1 ('MetaSel ('Just "ctcBabbageTransitionConfig") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TransitionConfig (BabbageEra c)))))
type ContextError (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.TxInfo

data PlutusScript (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Scripts

type NativeScript (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Scripts

type Script (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Scripts

type Tx (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Tx

type TxAuxData (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.TxAuxData

type TxBody (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.TxBody.Internal

type TxBodyUpgradeError (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.TxBody.Internal

type TxBodyUpgradeError (ConwayEra c) = ConwayTxBodyUpgradeError c
type TxOut (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.TxOut

type TxSeq (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Tx

type TxUpgradeError (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Tx

type TxWits (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.TxWits

type Value (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type EraCrypto (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

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

Defined in Cardano.Ledger.Conway.Era

type ProtVerHigh (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type ProtVerHigh (ConwayEra c) = 10
type ProtVerLow (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Era

type ProtVerLow (ConwayEra c) = 9
type TranslationContext (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Translation

type TxCert (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

type TxCertUpgradeError (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

type Genesis (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Genesis

type ScriptsNeeded (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.UTxO

type AdditionalGenesisConfig (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway

type GovState (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

data TransitionConfig (ConwayEra c) 
Instance details

Defined in Cardano.Ledger.Conway.Transition

type SimpleRep (AlonzoTxAuxData Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (AlonzoTxWits Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (ConwayGovState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (DRepPulsingState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (PulsingSnapshot Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (EnactState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (RatifyEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (RatifySignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (RatifyState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (Committee Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (GovActionState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (Proposals Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (CertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (CertsEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (ConwayGovCertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (ConwayTxBody (ConwayEra c)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (PoolEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (AlonzoTxAuxData Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (AlonzoTxWits Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (ConwayGovState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (DRepPulsingState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (PulsingSnapshot Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (EnactState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (RatifyEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (RatifySignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (RatifyState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (Committee Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (GovActionState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (Proposals Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (CertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (CertsEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (ConwayGovCertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (ConwayTxBody (ConwayEra c)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (PoolEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TranslationError (ConwayEra c) Tx 
Instance details

Defined in Cardano.Ledger.Conway.Translation

type TranslationError (ConwayEra c) CertState 
Instance details

Defined in Cardano.Ledger.Conway.Translation

type TranslationError (ConwayEra c) CommitteeState 
Instance details

Defined in Cardano.Ledger.Conway.Translation

type TranslationError (ConwayEra c) DState 
Instance details

Defined in Cardano.Ledger.Conway.Translation

type TranslationError (ConwayEra c) PState 
Instance details

Defined in Cardano.Ledger.Conway.Translation

type TranslationError (ConwayEra c) VState 
Instance details

Defined in Cardano.Ledger.Conway.Translation

type TranslationError (ConwayEra c) PParams 
Instance details

Defined in Cardano.Ledger.Conway.Translation

type TranslationError (ConwayEra c) UTxO 
Instance details

Defined in Cardano.Ledger.Conway.Translation

type TranslationError (ConwayEra c) FuturePParams 
Instance details

Defined in Cardano.Ledger.Conway.Translation

type TranslationError (ConwayEra c) EpochState 
Instance details

Defined in Cardano.Ledger.Conway.Translation

type TranslationError (ConwayEra c) LedgerState 
Instance details

Defined in Cardano.Ledger.Conway.Translation

type TranslationError (ConwayEra c) NewEpochState 
Instance details

Defined in Cardano.Ledger.Conway.Translation

type TranslationError (ConwayEra c) UTxOState 
Instance details

Defined in Cardano.Ledger.Conway.Translation

type SimpleRep (DRepPulser Conway Identity (RatifyState Conway)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (DRepPulser Conway Identity (RatifyState Conway)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

data StandardCrypto Source #

The same crypto used on the net

Instances

Instances details
Crypto StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

EraPP Allegra Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.SimplePParams

EraPP Alonzo Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.SimplePParams

EraPP Babbage Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.SimplePParams

EraPP Conway Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.SimplePParams

EraPP Mary Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.SimplePParams

EraPP Shelley Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.SimplePParams

PraosCrypto StandardCrypto 
Instance details

Defined in Cardano.Protocol.TPraos.API

IsConwayUniv fn ⇒ LedgerEra Allegra fn Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.LedgerTypes.Specs

IsConwayUniv fn ⇒ LedgerEra Alonzo fn Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.LedgerTypes.Specs

IsConwayUniv fn ⇒ LedgerEra Babbage fn Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.LedgerTypes.Specs

IsConwayUniv fn ⇒ LedgerEra Conway fn Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.LedgerTypes.Specs

IsConwayUniv fn ⇒ LedgerEra Mary fn Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.LedgerTypes.Specs

IsConwayUniv fn ⇒ LedgerEra Shelley fn Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.LedgerTypes.Specs

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (AlonzoTx Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type TypeSpec fn (AlonzoTx Conway) Source #

type Prerequisites fn (AlonzoTx Conway) Source #

IsConwayUniv fn ⇒ HasSpec fn (AlonzoTxAuxData Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

IsConwayUniv fn ⇒ HasSpec fn (AlonzoTxWits Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (ConwayGovState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (DRepPulsingState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (PulsingSnapshot Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (EnactState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

IsConwayUniv fn ⇒ HasSpec fn (RatifyEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type TypeSpec fn (RatifyEnv Conway) Source #

type Prerequisites fn (RatifyEnv Conway) Source #

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (RatifySignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (RatifyState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

IsConwayUniv fn ⇒ HasSpec fn (Committee Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type TypeSpec fn (Committee Conway) Source #

type Prerequisites fn (Committee Conway) Source #

(IsConwayUniv fn, EraPP Conway) ⇒ HasSpec fn (GovAction Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type TypeSpec fn (GovAction Conway) Source #

type Prerequisites fn (GovAction Conway) Source #

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (GovActionState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

(IsConwayUniv fn, EraPP Conway) ⇒ HasSpec fn (ProposalProcedure Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (Proposals Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type TypeSpec fn (Proposals Conway) Source #

type Prerequisites fn (Proposals Conway) Source #

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (CertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type TypeSpec fn (CertEnv Conway) Source #

type Prerequisites fn (CertEnv Conway) Source #

(IsConwayUniv fn, EraPP Conway) ⇒ HasSpec fn (CertsEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type TypeSpec fn (CertsEnv Conway) Source #

type Prerequisites fn (CertsEnv Conway) Source #

(IsConwayUniv fn, EraPP Conway) ⇒ HasSpec fn (EnactSignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

(EraTxCert Conway, EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (GovSignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type TypeSpec fn (GovSignal Conway) Source #

type Prerequisites fn (GovSignal Conway) Source #

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (ConwayGovCertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

IsConwayUniv fn ⇒ HasSpec fn (FreeVars StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

IsConwayUniv fn ⇒ HasSpec fn (Pulser StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

IsConwayUniv fn ⇒ HasSpec fn (RewardAns StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

IsConwayUniv fn ⇒ HasSpec fn (RewardSnapShot StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Methods

emptySpecTypeSpec fn (RewardSnapShot StandardCrypto) Source #

combineSpecTypeSpec fn (RewardSnapShot StandardCrypto) → TypeSpec fn (RewardSnapShot StandardCrypto) → Specification fn (RewardSnapShot StandardCrypto) Source #

genFromTypeSpec ∷ ∀ (m ∷ TypeType). (HasCallStack, MonadGenError m) ⇒ TypeSpec fn (RewardSnapShot StandardCrypto) → GenT m (RewardSnapShot StandardCrypto) Source #

conformsToRewardSnapShot StandardCryptoTypeSpec fn (RewardSnapShot StandardCrypto) → Bool Source #

shrinkWithTypeSpecTypeSpec fn (RewardSnapShot StandardCrypto) → RewardSnapShot StandardCrypto → [RewardSnapShot StandardCrypto] Source #

toPredsTerm fn (RewardSnapShot StandardCrypto) → TypeSpec fn (RewardSnapShot StandardCrypto) → Pred fn Source #

cardinalTypeSpecTypeSpec fn (RewardSnapShot StandardCrypto) → Specification fn Integer Source #

cardinalTrueSpecSpecification fn Integer Source #

typeSpecHasErrorTypeSpec fn (RewardSnapShot StandardCrypto) → Maybe (NonEmpty String) Source #

alternateShowTypeSpec fn (RewardSnapShot StandardCrypto) → BinaryShow Source #

monadConformsToRewardSnapShot StandardCryptoTypeSpec fn (RewardSnapShot StandardCrypto) → Writer [String] Bool Source #

typeSpecOptTypeSpec fn (RewardSnapShot StandardCrypto) → [RewardSnapShot StandardCrypto] → Specification fn (RewardSnapShot StandardCrypto) Source #

prerequisitesEvidence (Prerequisites fn (RewardSnapShot StandardCrypto)) Source #

IsConwayUniv fn ⇒ HasSpec fn (LeaderOnlyReward StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Methods

emptySpecTypeSpec fn (LeaderOnlyReward StandardCrypto) Source #

combineSpecTypeSpec fn (LeaderOnlyReward StandardCrypto) → TypeSpec fn (LeaderOnlyReward StandardCrypto) → Specification fn (LeaderOnlyReward StandardCrypto) Source #

genFromTypeSpec ∷ ∀ (m ∷ TypeType). (HasCallStack, MonadGenError m) ⇒ TypeSpec fn (LeaderOnlyReward StandardCrypto) → GenT m (LeaderOnlyReward StandardCrypto) Source #

conformsToLeaderOnlyReward StandardCryptoTypeSpec fn (LeaderOnlyReward StandardCrypto) → Bool Source #

shrinkWithTypeSpecTypeSpec fn (LeaderOnlyReward StandardCrypto) → LeaderOnlyReward StandardCrypto → [LeaderOnlyReward StandardCrypto] Source #

toPredsTerm fn (LeaderOnlyReward StandardCrypto) → TypeSpec fn (LeaderOnlyReward StandardCrypto) → Pred fn Source #

cardinalTypeSpecTypeSpec fn (LeaderOnlyReward StandardCrypto) → Specification fn Integer Source #

cardinalTrueSpecSpecification fn Integer Source #

typeSpecHasErrorTypeSpec fn (LeaderOnlyReward StandardCrypto) → Maybe (NonEmpty String) Source #

alternateShowTypeSpec fn (LeaderOnlyReward StandardCrypto) → BinaryShow Source #

monadConformsToLeaderOnlyReward StandardCryptoTypeSpec fn (LeaderOnlyReward StandardCrypto) → Writer [String] Bool Source #

typeSpecOptTypeSpec fn (LeaderOnlyReward StandardCrypto) → [LeaderOnlyReward StandardCrypto] → Specification fn (LeaderOnlyReward StandardCrypto) Source #

prerequisitesEvidence (Prerequisites fn (LeaderOnlyReward StandardCrypto)) Source #

IsConwayUniv fn ⇒ HasSpec fn (PoolRewardInfo StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Methods

emptySpecTypeSpec fn (PoolRewardInfo StandardCrypto) Source #

combineSpecTypeSpec fn (PoolRewardInfo StandardCrypto) → TypeSpec fn (PoolRewardInfo StandardCrypto) → Specification fn (PoolRewardInfo StandardCrypto) Source #

genFromTypeSpec ∷ ∀ (m ∷ TypeType). (HasCallStack, MonadGenError m) ⇒ TypeSpec fn (PoolRewardInfo StandardCrypto) → GenT m (PoolRewardInfo StandardCrypto) Source #

conformsToPoolRewardInfo StandardCryptoTypeSpec fn (PoolRewardInfo StandardCrypto) → Bool Source #

shrinkWithTypeSpecTypeSpec fn (PoolRewardInfo StandardCrypto) → PoolRewardInfo StandardCrypto → [PoolRewardInfo StandardCrypto] Source #

toPredsTerm fn (PoolRewardInfo StandardCrypto) → TypeSpec fn (PoolRewardInfo StandardCrypto) → Pred fn Source #

cardinalTypeSpecTypeSpec fn (PoolRewardInfo StandardCrypto) → Specification fn Integer Source #

cardinalTrueSpecSpecification fn Integer Source #

typeSpecHasErrorTypeSpec fn (PoolRewardInfo StandardCrypto) → Maybe (NonEmpty String) Source #

alternateShowTypeSpec fn (PoolRewardInfo StandardCrypto) → BinaryShow Source #

monadConformsToPoolRewardInfo StandardCryptoTypeSpec fn (PoolRewardInfo StandardCrypto) → Writer [String] Bool Source #

typeSpecOptTypeSpec fn (PoolRewardInfo StandardCrypto) → [PoolRewardInfo StandardCrypto] → Specification fn (PoolRewardInfo StandardCrypto) Source #

prerequisitesEvidence (Prerequisites fn (PoolRewardInfo StandardCrypto)) Source #

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (PoolEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type TypeSpec fn (PoolEnv Conway) Source #

type Prerequisites fn (PoolEnv Conway) Source #

(EraPP Conway, IsConwayUniv fn) ⇒ HasSpec fn (DRepPulser Conway Identity (RatifyState Conway)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Methods

emptySpecTypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) Source #

combineSpecTypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) → TypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) → Specification fn (DRepPulser Conway Identity (RatifyState Conway)) Source #

genFromTypeSpec ∷ ∀ (m ∷ TypeType). (HasCallStack, MonadGenError m) ⇒ TypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) → GenT m (DRepPulser Conway Identity (RatifyState Conway)) Source #

conformsToDRepPulser Conway Identity (RatifyState Conway) → TypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) → Bool Source #

shrinkWithTypeSpecTypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) → DRepPulser Conway Identity (RatifyState Conway) → [DRepPulser Conway Identity (RatifyState Conway)] Source #

toPredsTerm fn (DRepPulser Conway Identity (RatifyState Conway)) → TypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) → Pred fn Source #

cardinalTypeSpecTypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) → Specification fn Integer Source #

cardinalTrueSpecSpecification fn Integer Source #

typeSpecHasErrorTypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) → Maybe (NonEmpty String) Source #

alternateShowTypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) → BinaryShow Source #

monadConformsToDRepPulser Conway Identity (RatifyState Conway) → TypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) → Writer [String] Bool Source #

typeSpecOptTypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) → [DRepPulser Conway Identity (RatifyState Conway)] → Specification fn (DRepPulser Conway Identity (RatifyState Conway)) Source #

prerequisitesEvidence (Prerequisites fn (DRepPulser Conway Identity (RatifyState Conway))) Source #

Reflect (AllegraEra StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Proof

Reflect (AlonzoEra StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Proof

Reflect (BabbageEra StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Proof

Reflect (ConwayEra StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Proof

Reflect (MaryEra StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Proof

Reflect (ShelleyEra StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Generic.Proof

HasSimpleRep (AlonzoTxAuxData Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

HasSimpleRep (AlonzoTxWits Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

HasSimpleRep (ConwayGovState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

HasSimpleRep (DRepPulsingState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

HasSimpleRep (PulsingSnapshot Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

HasSimpleRep (EnactState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type SimpleRep (EnactState Conway) Source #

type TheSop (EnactState Conway) ∷ [Type] Source #

HasSimpleRep (RatifyEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type SimpleRep (RatifyEnv Conway) Source #

type TheSop (RatifyEnv Conway) ∷ [Type] Source #

HasSimpleRep (RatifySignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

HasSimpleRep (RatifyState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type SimpleRep (RatifyState Conway) Source #

type TheSop (RatifyState Conway) ∷ [Type] Source #

HasSimpleRep (Committee Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type SimpleRep (Committee Conway) Source #

type TheSop (Committee Conway) ∷ [Type] Source #

HasSimpleRep (GovActionState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

HasSimpleRep (Proposals Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type SimpleRep (Proposals Conway) Source #

type TheSop (Proposals Conway) ∷ [Type] Source #

HasSimpleRep (CertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type SimpleRep (CertEnv Conway) Source #

type TheSop (CertEnv Conway) ∷ [Type] Source #

HasSimpleRep (CertsEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type SimpleRep (CertsEnv Conway) Source #

type TheSop (CertsEnv Conway) ∷ [Type] Source #

HasSimpleRep (ConwayGovCertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

HasSimpleRep (FreeVars StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

HasSimpleRep (RewardAns StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

HasSimpleRep (RewardSnapShot StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

HasSimpleRep (LeaderOnlyReward StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

HasSimpleRep (PoolRewardInfo StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

HasSimpleRep (PoolEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

Associated Types

type SimpleRep (PoolEnv Conway) Source #

type TheSop (PoolEnv Conway) ∷ [Type] Source #

WellFormed (ConwayGovState Conway) Conway Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.LedgerTypes.WellFormed

WellFormed (GovEnv Conway) Conway Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.LedgerTypes.WellFormed

HasSimpleRep (DRepPulser Conway Identity (RatifyState Conway)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type ADDRHASH StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

type DSIGN StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

type HASH StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

type KES StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

type VRF StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

type Prerequisites fn (AlonzoTx Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (AlonzoTxAuxData Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (AlonzoTxWits Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (ConwayGovState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (DRepPulsingState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (PulsingSnapshot Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (EnactState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (RatifyEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (RatifySignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (RatifyState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (Committee Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (GovAction Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (GovActionState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (ProposalProcedure Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (Proposals Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (CertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (CertsEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (EnactSignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (GovSignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (ConwayGovCertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (FreeVars StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (Pulser StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (RewardAns StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (RewardSnapShot StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (LeaderOnlyReward StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (PoolRewardInfo StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (PoolEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (AlonzoTx Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (AlonzoTxAuxData Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (AlonzoTxWits Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (ConwayGovState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (DRepPulsingState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (PulsingSnapshot Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (EnactState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (RatifyEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (RatifySignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (RatifyState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (Committee Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (GovAction Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (GovActionState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (ProposalProcedure Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (Proposals Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (CertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (CertsEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (EnactSignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (GovSignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (ConwayGovCertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (FreeVars StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (Pulser StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (RewardAns StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (RewardSnapShot StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (LeaderOnlyReward StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (PoolRewardInfo StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (PoolEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type Prerequisites fn (DRepPulser Conway Identity (RatifyState Conway)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TypeSpec fn (DRepPulser Conway Identity (RatifyState Conway)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (AlonzoTxAuxData Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (AlonzoTxWits Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (ConwayGovState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (DRepPulsingState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (PulsingSnapshot Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (EnactState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (RatifyEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (RatifySignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (RatifyState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (Committee Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (GovActionState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (Proposals Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (CertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (CertsEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (ConwayGovCertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (FreeVars StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (RewardAns StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (RewardSnapShot StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (LeaderOnlyReward StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (PoolRewardInfo StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (PoolEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (AlonzoTxAuxData Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (AlonzoTxWits Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (ConwayGovState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (DRepPulsingState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (PulsingSnapshot Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (EnactState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (RatifyEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (RatifySignal Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (RatifyState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (Committee Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (GovActionState Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (Proposals Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (CertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (CertsEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (ConwayGovCertEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (FreeVars StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (RewardAns StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (RewardSnapShot StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (LeaderOnlyReward StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (PoolRewardInfo StandardCrypto) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (PoolEnv Conway) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type SimpleRep (DRepPulser Conway Identity (RatifyState Conway)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

type TheSop (DRepPulser Conway Identity (RatifyState Conway)) Source # 
Instance details

Defined in Test.Cardano.Ledger.Constrained.Conway.Instances

specialize ∷ ∀ constraint era t. (constraint (ShelleyEra (EraCrypto era)), constraint (AllegraEra (EraCrypto era)), constraint (MaryEra (EraCrypto era)), constraint (AlonzoEra (EraCrypto era)), constraint (BabbageEra (EraCrypto era)), constraint (ConwayEra (EraCrypto era))) ⇒ Proof era → (constraint era ⇒ t) → t Source #

Specialize (action :: (constraint era => t)) to all known era, because we know (constraint era) holds for all known era. In order for this to work it is best to type apply specialize to a concrete constraint. So a call site looks like '(specialize @EraSegWits proof action). This way the constraint does not percolate upwards, past the call site of action

unReflect ∷ (Reflect era ⇒ Proof era → a) → Proof era → a Source #

lift a function (Proof era -> a) that has a (Reflect era) constraint to one that does not. This is possible because every inhabited term of type (Proof era) packs a (Reflect era) instance. so instead of writing: f proof arg1 .. argn one writes: unReflect f proof arg1 .. argn which will not require a (Reflect era) instance

runSTS' ∷ ∀ s e. (BaseM (EraRule s e) ~ ShelleyBase, STS (EraRule s e)) ⇒ WitRule s e → TRC (EraRule s e) → Either (NonEmpty (PredicateFailure (EraRule s e))) (State (EraRule s e)) Source #

data ValueWit era where Source #

Constructors

ValueShelleyToAllegraValue era ~ CoinValueWit era 
ValueMaryToConwayValue era ~ MaryValue (EraCrypto era) ⇒ ValueWit era 

data TxOutWit era where Source #

Constructors

TxOutShelleyToMary ∷ (TxOut era ~ ShelleyTxOut era, EraTxOut era, ProtVerAtMost era 8) ⇒ TxOutWit era 
TxOutAlonzoToAlonzo ∷ (TxOut era ~ AlonzoTxOut era, AlonzoEraTxOut era, ProtVerAtMost era 8) ⇒ TxOutWit era 
TxOutBabbageToConway ∷ (TxOut era ~ BabbageTxOut era, BabbageEraTxOut era) ⇒ TxOutWit era 

data ScriptWit era where Source #

Constructors

ScriptShelleyToShelley ∷ (Script era ~ MultiSig era, EraScript era) ⇒ ScriptWit era 
ScriptAllegraToMary ∷ (Script era ~ Timelock era, EraScript era) ⇒ ScriptWit era 
ScriptAlonzoToConway ∷ (Script era ~ AlonzoScript era, EraScript era) ⇒ ScriptWit era 

whichValueProof era → ValueWit era Source #

whichTxOutProof era → TxOutWit era Source #

whichUTxOProof era → UTxOWit era Source #