ouroboros-consensus-cardano-0.12.1.0: The instantation of the Ouroboros consensus layer used by Cardano
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ouroboros.Consensus.Byron.Ledger.Ledger

Description

Instances requires for consensus/ledger integration

Synopsis

Documentation

data ByronTransition Source #

Information required to determine the transition from Byron to Shelley

Constructors

ByronTransitionInfo !(Map ProtocolVersion BlockNo)

Per candidate proposal, the BlockNo in which it became a candidate

The HFC needs to know when a candidate proposal becomes stable. We cannot reliably do this using SlotNo: doing so would mean that if we were to switch to a denser fork, something that was previously deemed stable is suddenly not deemed stable anymore (although in actuality it still is). We therefore must do this based on BlockNo instead, but unfortunately the Byron ledger does not record this information. Therefore, we record it here instead.

Invariant: the domain of this map should equal the set of candidate proposals.

Instances

Instances details
Generic ByronTransition Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Associated Types

type Rep ByronTransition :: Type -> Type Source #

Show ByronTransition Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Eq ByronTransition Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

NoThunks ByronTransition Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Methods

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

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

showTypeOf :: Proxy ByronTransition -> String

type Rep ByronTransition Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

type Rep ByronTransition = D1 ('MetaData "ByronTransition" "Ouroboros.Consensus.Byron.Ledger.Ledger" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ByronTransitionInfo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map ProtocolVersion BlockNo))))

Ledger integration

byronEraParams :: Config -> EraParams Source #

To be used for a Byron-to-X (where X is typically Shelley) chain.

byronEraParamsNeverHardForks :: Config -> EraParams Source #

Separate variant of byronEraParams to be used for a Byron-only chain.

initByronLedgerState Source #

Arguments

:: Config 
-> Maybe UTxO

Optionally override UTxO

-> LedgerState ByronBlock 

Serialisation

decodeByronAnnTip :: Decoder s (AnnTip ByronBlock) Source #

decodeByronQuery :: Decoder s (SomeSecond BlockQuery ByronBlock) Source #

decodeByronResult :: BlockQuery ByronBlock result -> forall s. Decoder s result Source #

encodeByronAnnTip :: AnnTip ByronBlock -> Encoding Source #

encodeByronExtLedgerState :: ExtLedgerState ByronBlock -> Encoding Source #

encodeByronHeaderState :: HeaderState ByronBlock -> Encoding Source #

encodeByronResult :: BlockQuery ByronBlock result -> result -> Encoding Source #

Type family instances

data family BlockQuery blk :: Type -> Type #

Instances

Instances details
SerialiseResult ByronBlock (BlockQuery ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

encodeResult :: CodecConfig ByronBlock -> BlockNodeToClientVersion ByronBlock -> BlockQuery ByronBlock result -> result -> Encoding

decodeResult :: CodecConfig ByronBlock -> BlockNodeToClientVersion ByronBlock -> BlockQuery ByronBlock result -> forall s. Decoder s result

SerialiseNodeToClient ByronBlock (SomeSecond BlockQuery ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

encodeNodeToClient :: CodecConfig ByronBlock -> BlockNodeToClientVersion ByronBlock -> SomeSecond BlockQuery ByronBlock -> Encoding

decodeNodeToClient :: CodecConfig ByronBlock -> BlockNodeToClientVersion ByronBlock -> forall s. Decoder s (SomeSecond BlockQuery ByronBlock)

Inject (SomeSecond BlockQuery) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Nary

Methods

inject :: forall x (xs :: [Type]). CanHardFork xs => Exactly xs Bound -> Index xs x -> SomeSecond BlockQuery x -> SomeSecond BlockQuery (HardForkBlock xs)

SameDepIndex (BlockQuery ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

SameDepIndex (BlockQuery (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

sameDepIndex :: BlockQuery (ShelleyBlock proto era) a -> BlockQuery (ShelleyBlock proto era) b -> Maybe (a :~: b)

ShowQuery (BlockQuery ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Methods

showResult :: BlockQuery ByronBlock result -> result -> String

ShelleyCompatible proto era => ShowQuery (BlockQuery (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

showResult :: BlockQuery (ShelleyBlock proto era) result -> result -> String

Show (BlockQuery ByronBlock result) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Show (BlockQuery (ShelleyBlock proto era) result) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

showsPrec :: Int -> BlockQuery (ShelleyBlock proto era) result -> ShowS Source #

show :: BlockQuery (ShelleyBlock proto era) result -> String Source #

showList :: [BlockQuery (ShelleyBlock proto era) result] -> ShowS Source #

(forall result. Show (BlockQuery blk result)) => Show (SomeSecond BlockQuery blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Query

Methods

showsPrec :: Int -> SomeSecond BlockQuery blk -> ShowS Source #

show :: SomeSecond BlockQuery blk -> String Source #

showList :: [SomeSecond BlockQuery blk] -> ShowS Source #

Eq (BlockQuery ByronBlock result) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Eq (BlockQuery (ShelleyBlock proto era) result) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

(==) :: BlockQuery (ShelleyBlock proto era) result -> BlockQuery (ShelleyBlock proto era) result -> Bool Source #

(/=) :: BlockQuery (ShelleyBlock proto era) result -> BlockQuery (ShelleyBlock proto era) result -> Bool Source #

SameDepIndex (BlockQuery blk) => Eq (SomeSecond BlockQuery blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Query

Methods

(==) :: SomeSecond BlockQuery blk -> SomeSecond BlockQuery blk -> Bool Source #

(/=) :: SomeSecond BlockQuery blk -> SomeSecond BlockQuery blk -> Bool Source #

ShelleyCompatible proto era => SerialiseResult (ShelleyBlock proto era) (BlockQuery (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeResult :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> BlockQuery (ShelleyBlock proto era) result -> result -> Encoding

decodeResult :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> BlockQuery (ShelleyBlock proto era) result -> forall s. Decoder s result

ShowProxy (BlockQuery ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

(Typeable era, Typeable proto) => ShowProxy (BlockQuery (ShelleyBlock proto era) :: Type -> Type) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

showProxy :: Proxy (BlockQuery (ShelleyBlock proto era)) -> String

ShelleyCompatible proto era => SerialiseNodeToClient (ShelleyBlock proto era) (SomeSecond BlockQuery (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToClient :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> SomeSecond BlockQuery (ShelleyBlock proto era) -> Encoding

decodeNodeToClient :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> forall s. Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))

data BlockQuery ByronBlock a Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

data BlockQuery (HardForkBlock xs) a 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger.Query

data BlockQuery (HardForkBlock xs) a where
data BlockQuery (ShelleyBlock proto era) a Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

data BlockQuery (ShelleyBlock proto era) a where

data family LedgerState blk #

Instances

Instances details
Inject LedgerState 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Nary

Methods

inject :: forall x (xs :: [Type]). CanHardFork xs => Exactly xs Bound -> Index xs x -> LedgerState x -> LedgerState (HardForkBlock xs)

DecodeDisk ByronBlock (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

decodeDisk :: CodecConfig ByronBlock -> forall s. Decoder s (LedgerState ByronBlock)

EncodeDisk ByronBlock (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

(ShelleyBasedEra era, TranslateEra era (ShelleyTip proto), TranslateEra era NewEpochState, TranslationError era NewEpochState ~ Void) => TranslateEra era (LedgerState :.: ShelleyBlock proto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type TranslationError era (LedgerState :.: ShelleyBlock proto)

Methods

translateEra :: TranslationContext era -> (LedgerState :.: ShelleyBlock proto) (PreviousEra era) -> Except (TranslationError era (LedgerState :.: ShelleyBlock proto)) ((LedgerState :.: ShelleyBlock proto) era)

Generic (LedgerState ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Associated Types

type Rep (LedgerState ByronBlock) :: Type -> Type Source #

Generic (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (LedgerState (ShelleyBlock proto era)) :: Type -> Type Source #

Methods

from :: LedgerState (ShelleyBlock proto era) -> Rep (LedgerState (ShelleyBlock proto era)) x Source #

to :: Rep (LedgerState (ShelleyBlock proto era)) x -> LedgerState (ShelleyBlock proto era) Source #

Generic (Ticked (LedgerState ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Associated Types

type Rep (Ticked (LedgerState ByronBlock)) :: Type -> Type Source #

Generic (Ticked (LedgerState (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (Ticked (LedgerState (ShelleyBlock proto era))) :: Type -> Type Source #

Methods

from :: Ticked (LedgerState (ShelleyBlock proto era)) -> Rep (Ticked (LedgerState (ShelleyBlock proto era))) x Source #

to :: Rep (Ticked (LedgerState (ShelleyBlock proto era))) x -> Ticked (LedgerState (ShelleyBlock proto era)) Source #

CanHardFork xs => Show (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Show (LedgerState ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

ShelleyBasedEra era => Show (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

CanHardFork xs => Eq (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Eq (LedgerState ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

ShelleyBasedEra era => Eq (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

(==) :: LedgerState (ShelleyBlock proto era) -> LedgerState (ShelleyBlock proto era) -> Bool Source #

(/=) :: LedgerState (ShelleyBlock proto era) -> LedgerState (ShelleyBlock proto era) -> Bool Source #

CanHardFork xs => NoThunks (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

noThunks :: Context -> LedgerState (HardForkBlock xs) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> LedgerState (HardForkBlock xs) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (LedgerState (HardForkBlock xs)) -> String

NoThunks (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Methods

noThunks :: Context -> LedgerState ByronBlock -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> LedgerState ByronBlock -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (LedgerState ByronBlock) -> String

ShelleyBasedEra era => NoThunks (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

noThunks :: Context -> LedgerState (ShelleyBlock proto era) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> LedgerState (ShelleyBlock proto era) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (LedgerState (ShelleyBlock proto era)) -> String

NoThunks (Ticked (LedgerState ByronBlock)) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Methods

noThunks :: Context -> Ticked (LedgerState ByronBlock) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Ticked (LedgerState ByronBlock) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (Ticked (LedgerState ByronBlock)) -> String

ShelleyBasedEra era => NoThunks (Ticked (LedgerState (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

noThunks :: Context -> Ticked (LedgerState (ShelleyBlock proto era)) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Ticked (LedgerState (ShelleyBlock proto era)) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (Ticked (LedgerState (ShelleyBlock proto era))) -> String

GetTip (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

GetTip (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

getTip :: LedgerState (ShelleyBlock proto era) -> Point (LedgerState (ShelleyBlock proto era))

GetTip (Ticked (LedgerState ByronBlock)) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

GetTip (Ticked (LedgerState (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

getTip :: Ticked (LedgerState (ShelleyBlock proto era)) -> Point (Ticked (LedgerState (ShelleyBlock proto era)))

IsLedger (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Associated Types

type LedgerErr (LedgerState ByronBlock)

type AuxLedgerEvent (LedgerState ByronBlock)

ShelleyBasedEra era => IsLedger (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type LedgerErr (LedgerState (ShelleyBlock proto era))

type AuxLedgerEvent (LedgerState (ShelleyBlock proto era))

Methods

applyChainTickLedgerResult :: LedgerCfg (LedgerState (ShelleyBlock proto era)) -> SlotNo -> LedgerState (ShelleyBlock proto era) -> LedgerResult (LedgerState (ShelleyBlock proto era)) (Ticked (LedgerState (ShelleyBlock proto era)))

ApplyBlock (LedgerState ByronBlock) ByronBlock 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

ShelleyCompatible proto era => ApplyBlock (LedgerState (ShelleyBlock proto era)) (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

applyBlockLedgerResult :: LedgerCfg (LedgerState (ShelleyBlock proto era)) -> ShelleyBlock proto era -> Ticked (LedgerState (ShelleyBlock proto era)) -> Except (LedgerErr (LedgerState (ShelleyBlock proto era))) (LedgerResult (LedgerState (ShelleyBlock proto era)) (LedgerState (ShelleyBlock proto era)))

reapplyBlockLedgerResult :: LedgerCfg (LedgerState (ShelleyBlock proto era)) -> ShelleyBlock proto era -> Ticked (LedgerState (ShelleyBlock proto era)) -> LedgerResult (LedgerState (ShelleyBlock proto era)) (LedgerState (ShelleyBlock proto era))

ShelleyCompatible proto era => DecodeDisk (ShelleyBlock proto era) (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDisk :: CodecConfig (ShelleyBlock proto era) -> forall s. Decoder s (LedgerState (ShelleyBlock proto era))

ShelleyCompatible proto era => EncodeDisk (ShelleyBlock proto era) (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDisk :: CodecConfig (ShelleyBlock proto era) -> LedgerState (ShelleyBlock proto era) -> Encoding

data LedgerState ByronBlock Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

type HeaderHash (LedgerState blk :: Type) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

type HeaderHash (LedgerState blk :: Type) = HeaderHash blk
type TranslationError era (LedgerState :.: ShelleyBlock proto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type TranslationError era (LedgerState :.: ShelleyBlock proto) = Void
type Rep (LedgerState ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

type Rep (LedgerState ByronBlock) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.Byron.Ledger.Ledger" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ByronLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "byronLedgerTipBlockNo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (WithOrigin BlockNo)) :*: (S1 ('MetaSel ('Just "byronLedgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ChainValidationState) :*: S1 ('MetaSel ('Just "byronLedgerTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByronTransition))))
type Rep (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (LedgerState (ShelleyBlock proto era)) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ShelleyLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "shelleyLedgerTip") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (WithOrigin (ShelleyTip proto era))) :*: (S1 ('MetaSel ('Just "shelleyLedgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NewEpochState era)) :*: S1 ('MetaSel ('Just "shelleyLedgerTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShelleyTransition))))
type Rep (Ticked (LedgerState (HardForkBlock xs))) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type Rep (Ticked (LedgerState (HardForkBlock xs))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.HardFork.Combinator.Ledger" "ouroboros-consensus-0.14.0.0-121Znn1OCbJFCod8haNyF" 'False) (C1 ('MetaCons "TickedHardForkLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "tickedHardForkLedgerStateTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TransitionInfo) :*: S1 ('MetaSel ('Just "tickedHardForkLedgerStatePerEra") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HardForkState (Ticked :.: LedgerState) xs))))
type Rep (Ticked (LedgerState ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

type Rep (Ticked (LedgerState ByronBlock)) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Byron.Ledger.Ledger" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "TickedByronLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "tickedByronLedgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ChainValidationState) :*: S1 ('MetaSel ('Just "untickedByronLedgerTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByronTransition)))
type Rep (Ticked (LedgerState (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (Ticked (LedgerState (ShelleyBlock proto era))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "TickedShelleyLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "untickedShelleyLedgerTip") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (WithOrigin (ShelleyTip proto era))) :*: (S1 ('MetaSel ('Just "tickedShelleyLedgerTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShelleyTransition) :*: S1 ('MetaSel ('Just "tickedShelleyLedgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NewEpochState era)))))
type AuxLedgerEvent (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type AuxLedgerEvent (LedgerState (HardForkBlock xs)) = OneEraLedgerEvent xs
type AuxLedgerEvent (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

type AuxLedgerEvent (LedgerState ByronBlock) = VoidLedgerEvent (LedgerState ByronBlock)
type AuxLedgerEvent (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type AuxLedgerEvent (LedgerState (ShelleyBlock proto era)) = ShelleyLedgerEvent era
type LedgerCfg (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type LedgerCfg (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

type LedgerCfg (LedgerState ByronBlock) = Config
type LedgerCfg (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type LedgerCfg (LedgerState (ShelleyBlock proto era)) = ShelleyLedgerConfig era
type LedgerErr (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type LedgerErr (LedgerState (HardForkBlock xs)) = HardForkLedgerError xs
type LedgerErr (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

type LedgerErr (LedgerState ByronBlock) = ChainValidationError
type LedgerErr (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type LedgerErr (LedgerState (ShelleyBlock proto era)) = ShelleyLedgerError era
newtype LedgerState (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data Ticked (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

data Ticked (LedgerState ByronBlock) Source #

The ticked Byron ledger state

Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

data Ticked (LedgerState (ShelleyBlock proto era)) Source #

Ticking only affects the state itself

Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

data LedgerState (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

data family Ticked st #

Instances

Instances details
Generic (Ticked (LedgerState ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Associated Types

type Rep (Ticked (LedgerState ByronBlock)) :: Type -> Type Source #

Generic (Ticked (LedgerState (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (Ticked (LedgerState (ShelleyBlock proto era))) :: Type -> Type Source #

Methods

from :: Ticked (LedgerState (ShelleyBlock proto era)) -> Rep (Ticked (LedgerState (ShelleyBlock proto era))) x Source #

to :: Rep (Ticked (LedgerState (ShelleyBlock proto era))) x -> Ticked (LedgerState (ShelleyBlock proto era)) Source #

Show (Ticked ()) 
Instance details

Defined in Ouroboros.Consensus.Ticked

NoThunks (Ticked (LedgerState ByronBlock)) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Methods

noThunks :: Context -> Ticked (LedgerState ByronBlock) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Ticked (LedgerState ByronBlock) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (Ticked (LedgerState ByronBlock)) -> String

ShelleyBasedEra era => NoThunks (Ticked (LedgerState (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

noThunks :: Context -> Ticked (LedgerState (ShelleyBlock proto era)) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Ticked (LedgerState (ShelleyBlock proto era)) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (Ticked (LedgerState (ShelleyBlock proto era))) -> String

GetTip (Ticked (LedgerState ByronBlock)) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

GetTip (Ticked (LedgerState (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

getTip :: Ticked (LedgerState (ShelleyBlock proto era)) -> Point (Ticked (LedgerState (ShelleyBlock proto era)))

IsLedger (LedgerState blk) => GetTip (Ticked (ExtLedgerState blk)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

getTip :: Ticked (ExtLedgerState blk) -> Point (Ticked (ExtLedgerState blk))

Show (Ticked (f a)) => Show ((Ticked :.: f) a) 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrec :: Int -> (Ticked :.: f) a -> ShowS Source #

show :: (Ticked :.: f) a -> String Source #

showList :: [(Ticked :.: f) a] -> ShowS Source #

NoThunks (Ticked (f a)) => NoThunks ((Ticked :.: f) a) 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

noThunks :: Context -> (Ticked :.: f) a -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> (Ticked :.: f) a -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy ((Ticked :.: f) a) -> String

data Ticked () 
Instance details

Defined in Ouroboros.Consensus.Ticked

type HeaderHash (Ticked l :: Type) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

type HeaderHash (Ticked l :: Type) = HeaderHash l
type Rep (Ticked (LedgerState (HardForkBlock xs))) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type Rep (Ticked (LedgerState (HardForkBlock xs))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.HardFork.Combinator.Ledger" "ouroboros-consensus-0.14.0.0-121Znn1OCbJFCod8haNyF" 'False) (C1 ('MetaCons "TickedHardForkLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "tickedHardForkLedgerStateTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TransitionInfo) :*: S1 ('MetaSel ('Just "tickedHardForkLedgerStatePerEra") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HardForkState (Ticked :.: LedgerState) xs))))
type Rep (Ticked (LedgerState ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

type Rep (Ticked (LedgerState ByronBlock)) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Byron.Ledger.Ledger" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "TickedByronLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "tickedByronLedgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ChainValidationState) :*: S1 ('MetaSel ('Just "untickedByronLedgerTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByronTransition)))
type Rep (Ticked (LedgerState (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (Ticked (LedgerState (ShelleyBlock proto era))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "TickedShelleyLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "untickedShelleyLedgerTip") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (WithOrigin (ShelleyTip proto era))) :*: (S1 ('MetaSel ('Just "tickedShelleyLedgerTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShelleyTransition) :*: S1 ('MetaSel ('Just "tickedShelleyLedgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NewEpochState era)))))
data Ticked (HardForkChainDepState xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

data Ticked (HardForkChainDepState xs) = TickedHardForkChainDepState {}
data Ticked (HeaderState blk) 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

data Ticked (HeaderState blk) = TickedHeaderState {}
data Ticked (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

data Ticked (LedgerState ByronBlock) Source #

The ticked Byron ledger state

Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

data Ticked (LedgerState (ShelleyBlock proto era)) Source #

Ticking only affects the state itself

Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

data Ticked (ExtLedgerState blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

data Ticked (ExtLedgerState blk) = TickedExtLedgerState {}
data Ticked (PBftState c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

data Ticked (PBftState c) = TickedPBftState {}
newtype Ticked (WrapChainDepState blk) 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

newtype Ticked (WrapChainDepState blk) = WrapTickedChainDepState {}
data Ticked (PraosState c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

data Ticked (PraosState c) = TickedPraosState {}
data Ticked (TPraosState c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

data Ticked (TPraosState c) = TickedChainDepState {}

Auxiliary

validationErrorImpossible :: forall err a. Except err a -> a Source #

Mark computation as validation error free

Given a BlockValidationMode of NoBlockValidation, a call to applyByronBlock shouldn't fail since the ledger layer won't be performing any block validation checks. However, because applyByronBlock can fail in the event it is given a BlockValidationMode of BlockValidation, it still looks like it can fail (since its type doesn't change based on the ValidationMode) and we must still treat it as such.

Orphan instances

HasHardForkHistory ByronBlock Source # 
Instance details

Associated Types

type HardForkIndices ByronBlock :: [Type]

Methods

hardForkSummary :: LedgerConfig ByronBlock -> LedgerState ByronBlock -> Summary (HardForkIndices ByronBlock)

UpdateLedger ByronBlock Source # 
Instance details

CommonProtocolParams ByronBlock Source # 
Instance details

QueryLedger ByronBlock Source # 
Instance details

Methods

answerBlockQuery :: ExtLedgerCfg ByronBlock -> BlockQuery ByronBlock result -> ExtLedgerState ByronBlock -> result

LedgerSupportsPeerSelection ByronBlock Source # 
Instance details

Methods

getPeers :: LedgerState ByronBlock -> [(PoolStake, NonEmpty StakePoolRelay)]

LedgerSupportsProtocol ByronBlock Source # 
Instance details

Methods

protocolLedgerView :: LedgerConfig ByronBlock -> Ticked (LedgerState ByronBlock) -> LedgerView (BlockProtocol ByronBlock)

ledgerViewForecastAt :: LedgerConfig ByronBlock -> LedgerState ByronBlock -> Forecast (LedgerView (BlockProtocol ByronBlock))

Generic (LedgerState ByronBlock) Source # 
Instance details

Associated Types

type Rep (LedgerState ByronBlock) :: Type -> Type Source #

Generic (Ticked (LedgerState ByronBlock)) Source # 
Instance details

Associated Types

type Rep (Ticked (LedgerState ByronBlock)) :: Type -> Type Source #

Show (LedgerState ByronBlock) Source # 
Instance details

Eq (LedgerState ByronBlock) Source # 
Instance details

NoThunks (LedgerState ByronBlock) Source # 
Instance details

Methods

noThunks :: Context -> LedgerState ByronBlock -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> LedgerState ByronBlock -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (LedgerState ByronBlock) -> String

NoThunks (Ticked (LedgerState ByronBlock)) Source # 
Instance details

Methods

noThunks :: Context -> Ticked (LedgerState ByronBlock) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Ticked (LedgerState ByronBlock) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (Ticked (LedgerState ByronBlock)) -> String

GetTip (LedgerState ByronBlock) Source # 
Instance details

GetTip (Ticked (LedgerState ByronBlock)) Source # 
Instance details

IsLedger (LedgerState ByronBlock) Source # 
Instance details

Associated Types

type LedgerErr (LedgerState ByronBlock)

type AuxLedgerEvent (LedgerState ByronBlock)

SameDepIndex (BlockQuery ByronBlock) Source # 
Instance details

ShowQuery (BlockQuery ByronBlock) Source # 
Instance details

Methods

showResult :: BlockQuery ByronBlock result -> result -> String

ApplyBlock (LedgerState ByronBlock) ByronBlock Source # 
Instance details

Show (BlockQuery ByronBlock result) Source # 
Instance details

Eq (BlockQuery ByronBlock result) Source # 
Instance details

ShowProxy (BlockQuery ByronBlock) Source # 
Instance details