ouroboros-consensus-0.3.1.0: Consensus layer for the Ouroboros blockchain protocol
Safe HaskellNone
LanguageHaskell2010

Ouroboros.Consensus.TypeFamilyWrappers

Description

Newtypes around type families so that they can be partially applied

Synopsis

Block based

newtype WrapApplyTxErr blk Source #

Constructors

WrapApplyTxErr 

Instances

Instances details
Isomorphic WrapApplyTxErr Source # 
Instance details

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

Inject WrapApplyTxErr Source # 
Instance details

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

Methods

inject ∷ ∀ x (xs ∷ [Type]). CanHardFork xs ⇒ Exactly xs BoundIndex xs x → WrapApplyTxErr x → WrapApplyTxErr (HardForkBlock xs) Source #

SerialiseNodeToClient blk (ApplyTxErr blk) ⇒ SerialiseNodeToClient blk (WrapApplyTxErr blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Node.Serialisation

Eq (ApplyTxErr blk) ⇒ Eq (WrapApplyTxErr blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Show (ApplyTxErr blk) ⇒ Show (WrapApplyTxErr blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

newtype WrapGenTxId blk Source #

Constructors

WrapGenTxId 

Fields

Instances

Instances details
Isomorphic WrapGenTxId Source # 
Instance details

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

Inject WrapGenTxId Source # 
Instance details

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

Methods

inject ∷ ∀ x (xs ∷ [Type]). CanHardFork xs ⇒ Exactly xs BoundIndex xs x → WrapGenTxId x → WrapGenTxId (HardForkBlock xs) Source #

SerialiseNodeToClient blk (GenTxId blk) ⇒ SerialiseNodeToClient blk (WrapGenTxId blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Node.Serialisation

Methods

encodeNodeToClientCodecConfig blk → BlockNodeToClientVersion blk → WrapGenTxId blk → Encoding Source #

decodeNodeToClientCodecConfig blk → BlockNodeToClientVersion blk → ∀ s. Decoder s (WrapGenTxId blk) Source #

SerialiseNodeToNode blk (GenTxId blk) ⇒ SerialiseNodeToNode blk (WrapGenTxId blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Node.Serialisation

Methods

encodeNodeToNodeCodecConfig blk → BlockNodeToNodeVersion blk → WrapGenTxId blk → Encoding Source #

decodeNodeToNodeCodecConfig blk → BlockNodeToNodeVersion blk → ∀ s. Decoder s (WrapGenTxId blk) Source #

Eq (GenTxId blk) ⇒ Eq (WrapGenTxId blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Methods

(==)WrapGenTxId blk → WrapGenTxId blk → Bool Source #

(/=)WrapGenTxId blk → WrapGenTxId blk → Bool Source #

Ord (GenTxId blk) ⇒ Ord (WrapGenTxId blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Methods

compareWrapGenTxId blk → WrapGenTxId blk → Ordering Source #

(<)WrapGenTxId blk → WrapGenTxId blk → Bool Source #

(<=)WrapGenTxId blk → WrapGenTxId blk → Bool Source #

(>)WrapGenTxId blk → WrapGenTxId blk → Bool Source #

(>=)WrapGenTxId blk → WrapGenTxId blk → Bool Source #

maxWrapGenTxId blk → WrapGenTxId blk → WrapGenTxId blk Source #

minWrapGenTxId blk → WrapGenTxId blk → WrapGenTxId blk Source #

Show (GenTxId blk) ⇒ Show (WrapGenTxId blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Serialise (GenTxId blk) ⇒ Serialise (WrapGenTxId blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Methods

encodeWrapGenTxId blk → Encoding #

decode ∷ Decoder s (WrapGenTxId blk) #

encodeList ∷ [WrapGenTxId blk] → Encoding #

decodeList ∷ Decoder s [WrapGenTxId blk] #

NoThunks (GenTxId blk) ⇒ NoThunks (WrapGenTxId blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Methods

noThunks ∷ Context → WrapGenTxId blk → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → WrapGenTxId blk → IO (Maybe ThunkInfo) #

showTypeOfProxy (WrapGenTxId blk) → String #

Condense (GenTxId blk) ⇒ Condense (WrapGenTxId blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Condense

Methods

condenseWrapGenTxId blk → String Source #

newtype WrapLedgerErr blk Source #

Constructors

WrapLedgerErr 

Instances

Instances details
Isomorphic WrapLedgerErr Source # 
Instance details

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

Eq (LedgerError blk) ⇒ Eq (WrapLedgerErr blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Methods

(==)WrapLedgerErr blk → WrapLedgerErr blk → Bool Source #

(/=)WrapLedgerErr blk → WrapLedgerErr blk → Bool Source #

Show (LedgerError blk) ⇒ Show (WrapLedgerErr blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

NoThunks (LedgerError blk) ⇒ NoThunks (WrapLedgerErr blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Methods

noThunks ∷ Context → WrapLedgerErr blk → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → WrapLedgerErr blk → IO (Maybe ThunkInfo) #

showTypeOfProxy (WrapLedgerErr blk) → String #

newtype WrapLedgerUpdate blk Source #

Constructors

WrapLedgerUpdate 

Instances

Instances details
Eq (LedgerUpdate blk) ⇒ Eq (WrapLedgerUpdate blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Show (LedgerUpdate blk) ⇒ Show (WrapLedgerUpdate blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

newtype WrapTipInfo blk Source #

Constructors

WrapTipInfo 

Fields

Instances

Instances details
Isomorphic WrapTipInfo Source # 
Instance details

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

Eq (TipInfo blk) ⇒ Eq (WrapTipInfo blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Methods

(==)WrapTipInfo blk → WrapTipInfo blk → Bool Source #

(/=)WrapTipInfo blk → WrapTipInfo blk → Bool Source #

Show (TipInfo blk) ⇒ Show (WrapTipInfo blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Serialise (TipInfo blk) ⇒ Serialise (WrapTipInfo blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Methods

encodeWrapTipInfo blk → Encoding #

decode ∷ Decoder s (WrapTipInfo blk) #

encodeList ∷ [WrapTipInfo blk] → Encoding #

decodeList ∷ Decoder s [WrapTipInfo blk] #

NoThunks (TipInfo blk) ⇒ NoThunks (WrapTipInfo blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Methods

noThunks ∷ Context → WrapTipInfo blk → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → WrapTipInfo blk → IO (Maybe ThunkInfo) #

showTypeOfProxy (WrapTipInfo blk) → String #

Protocol based

newtype WrapChainDepState blk Source #

Instances

Instances details
Isomorphic WrapChainDepState Source # 
Instance details

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

Inject WrapChainDepState Source # 
Instance details

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

Methods

inject ∷ ∀ x (xs ∷ [Type]). CanHardFork xs ⇒ Exactly xs BoundIndex xs x → WrapChainDepState x → WrapChainDepState (HardForkBlock xs) Source #

DecodeDisk blk (ChainDepState (BlockProtocol blk)) ⇒ DecodeDisk blk (WrapChainDepState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.Serialisation

Methods

decodeDiskCodecConfig blk → ∀ s. Decoder s (WrapChainDepState blk) Source #

EncodeDisk blk (ChainDepState (BlockProtocol blk)) ⇒ EncodeDisk blk (WrapChainDepState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.Serialisation

Methods

encodeDiskCodecConfig blk → WrapChainDepState blk → Encoding Source #

Eq (ChainDepState (BlockProtocol blk)) ⇒ Eq (WrapChainDepState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Show (ChainDepState (BlockProtocol blk)) ⇒ Show (WrapChainDepState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Serialise (ChainDepState (BlockProtocol blk)) ⇒ Serialise (WrapChainDepState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Methods

encodeWrapChainDepState blk → Encoding #

decode ∷ Decoder s (WrapChainDepState blk) #

encodeList ∷ [WrapChainDepState blk] → Encoding #

decodeList ∷ Decoder s [WrapChainDepState blk] #

NoThunks (ChainDepState (BlockProtocol blk)) ⇒ NoThunks (WrapChainDepState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Methods

noThunks ∷ Context → WrapChainDepState blk → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → WrapChainDepState blk → IO (Maybe ThunkInfo) #

showTypeOfProxy (WrapChainDepState blk) → String #

SerialiseHFC xs ⇒ DecodeDisk (HardForkBlock xs) (HardForkChainDepState xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

Methods

decodeDiskCodecConfig (HardForkBlock xs) → ∀ s. Decoder s (HardForkChainDepState xs) Source #

SerialiseHFC xs ⇒ EncodeDisk (HardForkBlock xs) (HardForkChainDepState xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

newtype Ticked (WrapChainDepState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

data Ticked (HardForkChainDepState xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

newtype WrapIsLeader blk Source #

Constructors

WrapIsLeader 

Instances

Instances details
Isomorphic WrapIsLeader Source # 
Instance details

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

newtype WrapSelectView blk Source #

Instances

Instances details
Eq (SelectView (BlockProtocol blk)) ⇒ Eq (WrapSelectView blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Ord (SelectView (BlockProtocol blk)) ⇒ Ord (WrapSelectView blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Show (SelectView (BlockProtocol blk)) ⇒ Show (WrapSelectView blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

NoThunks (SelectView (BlockProtocol blk)) ⇒ NoThunks (WrapSelectView blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Methods

noThunks ∷ Context → WrapSelectView blk → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → WrapSelectView blk → IO (Maybe ThunkInfo) #

showTypeOfProxy (WrapSelectView blk) → String #

newtype WrapValidatedGenTx blk Source #

A data family wrapper for Validated . GenTx

Validated is is data family, so this is an outlier in this module full of type family wrappers. However, the standard functor composition operator f :.: g incurs some type classes instances that are inappropriate when the outer type constructor f is a family and hence non-parametric (eg Eq (f :.: g) requires @Eq1 f)). The bespoke composition WrapValidatedGenTx therefore serves much the same purpose as the other wrappers in this module.

newtype WrapValidationErr blk Source #

Instances

Instances details
Eq (ValidationErr (BlockProtocol blk)) ⇒ Eq (WrapValidationErr blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Show (ValidationErr (BlockProtocol blk)) ⇒ Show (WrapValidationErr blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

NoThunks (ValidationErr (BlockProtocol blk)) ⇒ NoThunks (WrapValidationErr blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Methods

noThunks ∷ Context → WrapValidationErr blk → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → WrapValidationErr blk → IO (Maybe ThunkInfo) #

showTypeOfProxy (WrapValidationErr blk) → String #

Versioning

Type family instances

data family Ticked st ∷ Type Source #

" Ticked " piece of state (LedgerState, LedgerView, ChainIndepState)

Ticking refers to the passage of time (the ticking of the clock). When a piece of state is marked as ticked, it means that time-related changes have been applied to the state (or forecast).

Some examples of time related changes:

  • Scheduled delegations might have been applied in Byron
  • New leader schedule computed for Shelley
  • Transition from Byron to Shelley activated in the hard fork combinator.
  • Nonces switched out at the start of a new epoch.

Instances

Instances details
Show (Ticked ()) Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecIntTicked () → ShowS Source #

showTicked () → String Source #

showList ∷ [Ticked ()] → ShowS Source #

Show (Ticked a) ⇒ Show (Ticked (K a x)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecIntTicked (K a x) → ShowS Source #

showTicked (K a x) → String Source #

showList ∷ [Ticked (K a x)] → ShowS Source #

(SListI xs, Show (Ticked a)) ⇒ Show (Ticked (HardForkLedgerView_ (K a ∷ TypeType) xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol.LedgerView

Generic (Ticked (LedgerState (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Associated Types

type Rep (Ticked (LedgerState (HardForkBlock xs))) ∷ TypeType Source #

NoThunks (Ticked (LedgerState (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

noThunks ∷ Context → Ticked (LedgerState (DualBlock m a)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Ticked (LedgerState (DualBlock m a)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Ticked (LedgerState (DualBlock m a))) → String #

CanHardFork xs ⇒ NoThunks (Ticked (LedgerState (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Methods

noThunks ∷ Context → Ticked (LedgerState (HardForkBlock xs)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Ticked (LedgerState (HardForkBlock xs)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Ticked (LedgerState (HardForkBlock xs))) → String #

Bridge m a ⇒ GetTip (Ticked (LedgerState (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs ⇒ GetTip (Ticked (LedgerState (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

IsLedger (LedgerState blk) ⇒ GetTip (Ticked (ExtLedgerState blk)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Isomorphic (Ticked :.: LedgerState) Source # 
Instance details

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

Show (Ticked (f a)) ⇒ Show ((Ticked :.: f) a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecInt → (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) Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

noThunks ∷ Context → (Ticked :.: f) a → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → (Ticked :.: f) a → IO (Maybe ThunkInfo) #

showTypeOfProxy ((Ticked :.: f) a) → String #

data Ticked () Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

type Rep (Ticked (LedgerState (HardForkBlock xs))) Source # 
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.3.1.0-inplace" '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 HeaderHash (Ticked l) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

data Ticked (LedgerState (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data Ticked (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

data Ticked (HeaderState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

newtype Ticked (WrapLedgerView blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

newtype Ticked (WrapChainDepState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

data Ticked (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

data Ticked (HardForkChainDepState xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

data Ticked (PBftState c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

newtype Ticked (PBftLedgerView c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

data Ticked (HardForkLedgerView_ f xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol.LedgerView

newtype Ticked (K a x) Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

newtype Ticked (K a x) = TickedK {}