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

Ouroboros.Consensus.Cardano.Block

Synopsis

Eras

type CardanoEras c = ByronBlock ': CardanoShelleyEras c Source #

The eras in the Cardano blockchain.

We parameterise over the crypto used in the post-Byron eras: c.

TODO: parameterise ByronBlock over crypto too

type CardanoShelleyEras c = '[ShelleyBlock (TPraos c) (ShelleyEra c), ShelleyBlock (TPraos c) (AllegraEra c), ShelleyBlock (TPraos c) (MaryEra c), ShelleyBlock (TPraos c) (AlonzoEra c), ShelleyBlock (Praos c) (BabbageEra c), ShelleyBlock (Praos c) (ConwayEra c)] Source #

Block

type CardanoBlock c = HardForkBlock (CardanoEras c) Source #

The Cardano block.

Thanks to the pattern synonyms, you can treat this as a sum type with constructors BlockByron and BlockShelley.

f :: CardanoBlock c -> _
f (BlockByron   b) = _
f (BlockShelley s) = _
f (BlockAllegra a) = _
f (BlockMary    m) = _
f (BlockAlonzo  m) = _

data HardForkBlock (xs :: [Type]) where #

Bundled Patterns

pattern BlockAllegra :: ShelleyBlock (TPraos c) (AllegraEra c) -> CardanoBlock c 
pattern BlockAlonzo :: ShelleyBlock (TPraos c) (AlonzoEra c) -> CardanoBlock c 
pattern BlockByron :: ByronBlock -> CardanoBlock c 
pattern BlockMary :: ShelleyBlock (TPraos c) (MaryEra c) -> CardanoBlock c 
pattern BlockShelley :: ShelleyBlock (TPraos c) (ShelleyEra c) -> CardanoBlock c 
pattern BlockBabbage :: ShelleyBlock (Praos c) (BabbageEra c) -> CardanoBlock c 
pattern BlockConway :: ShelleyBlock (Praos c) (ConwayEra c) -> CardanoBlock c 

Instances

Instances details
SupportedNetworkProtocolVersion ByronBlockHFC

Forward to the ByronBlock instance. Only supports HardForkNodeToNodeDisabled, which is compatible with nodes running with ByronBlock.

Instance details

Defined in Ouroboros.Consensus.Cardano.ByronHFC

Methods

supportedNodeToNodeVersions :: Proxy ByronBlockHFC -> Map NodeToNodeVersion (BlockNodeToNodeVersion ByronBlockHFC)

supportedNodeToClientVersions :: Proxy ByronBlockHFC -> Map NodeToClientVersion (BlockNodeToClientVersion ByronBlockHFC)

latestReleasedNodeVersion :: Proxy ByronBlockHFC -> (Maybe NodeToNodeVersion, Maybe NodeToClientVersion)

CanHardFork xs => Show (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

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

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

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

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

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

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

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

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

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

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

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

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

CardanoHardForkConstraints c => CondenseConstraints (CardanoBlock c) 
Instance details

Defined in Ouroboros.Consensus.Cardano.Condense

CardanoHardForkConstraints c => SupportedNetworkProtocolVersion (CardanoBlock c) 
Instance details

Defined in Ouroboros.Consensus.Cardano.Node

Methods

supportedNodeToNodeVersions :: Proxy (CardanoBlock c) -> Map NodeToNodeVersion (BlockNodeToNodeVersion (CardanoBlock c))

supportedNodeToClientVersions :: Proxy (CardanoBlock c) -> Map NodeToClientVersion (BlockNodeToClientVersion (CardanoBlock c))

latestReleasedNodeVersion :: Proxy (CardanoBlock c) -> (Maybe NodeToNodeVersion, Maybe NodeToClientVersion)

Typeable xs => ShowProxy (HardForkBlock xs :: TYPE LiftedRep) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era)) => SupportedNetworkProtocolVersion (ShelleyBlockHFC proto era)

Forward to the ShelleyBlock instance. Only supports HardForkNodeToNodeDisabled, which is compatible with nodes running with ShelleyBlock.

Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Methods

supportedNodeToNodeVersions :: Proxy (ShelleyBlockHFC proto era) -> Map NodeToNodeVersion (BlockNodeToNodeVersion (ShelleyBlockHFC proto era))

supportedNodeToClientVersions :: Proxy (ShelleyBlockHFC proto era) -> Map NodeToClientVersion (BlockNodeToClientVersion (ShelleyBlockHFC proto era))

latestReleasedNodeVersion :: Proxy (ShelleyBlockHFC proto era) -> (Maybe NodeToNodeVersion, Maybe NodeToClientVersion)

type Rep (Validated (GenTx (HardForkBlock xs))) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (Validated (GenTx (HardForkBlock xs))) = D1 ('MetaData "Validated" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.14.0.0-121Znn1OCbJFCod8haNyF" 'True) (C1 ('MetaCons "HardForkValidatedGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkValidatedGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraValidatedGenTx xs))))
type Rep (GenTx (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (GenTx (HardForkBlock xs)) = D1 ('MetaData "GenTx" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.14.0.0-121Znn1OCbJFCod8haNyF" 'True) (C1 ('MetaCons "HardForkGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTx xs))))
type Rep (TxId (GenTx (HardForkBlock xs))) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (TxId (GenTx (HardForkBlock xs))) = D1 ('MetaData "TxId" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.14.0.0-121Znn1OCbJFCod8haNyF" 'True) (C1 ('MetaCons "HardForkGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTxId xs))))
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))))
newtype BlockConfig (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type BlockProtocol (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type BlockProtocol (HardForkBlock xs) = HardForkProtocol xs
newtype CodecConfig (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

newtype Header (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

newtype Header (HardForkBlock xs) = HardForkHeader {}
newtype StorageConfig (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type CannotForge (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Forging

type CannotForge (HardForkBlock xs) = HardForkCannotForge xs
type ForgeStateInfo (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Forging

type ForgeStateInfo (HardForkBlock xs) = HardForkForgeStateInfo xs
type ForgeStateUpdateError (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Forging

type ForgeStateUpdateError (HardForkBlock xs) = HardForkForgeStateUpdateError xs
data NestedCtxt_ (HardForkBlock xs) a b 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

data NestedCtxt_ (HardForkBlock xs) a b where
type HardForkIndices (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type HardForkIndices (HardForkBlock xs) = xs
type OtherHeaderEnvelopeError (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type OtherHeaderEnvelopeError (HardForkBlock xs) = HardForkEnvelopeErr xs
type TipInfo (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

type TipInfo (HardForkBlock xs) = OneEraTipInfo xs
newtype Validated (GenTx (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

newtype Validated (GenTx (HardForkBlock xs)) = HardForkValidatedGenTx {}
type AuxLedgerEvent (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type LedgerErr (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type LedgerUpdate (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type LedgerUpdate (HardForkBlock xs) = HardForkLedgerUpdate xs
type LedgerWarning (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type LedgerWarning (HardForkBlock xs) = HardForkLedgerWarning xs
data BlockQuery (HardForkBlock xs) a 
Instance details

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

data BlockQuery (HardForkBlock xs) a where
type ApplyTxErr (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type ApplyTxErr (HardForkBlock xs) = HardForkApplyTxErr xs
newtype GenTx (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

newtype GenTx (HardForkBlock xs) = HardForkGenTx {}
newtype TxId (GenTx (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

newtype TxId (GenTx (HardForkBlock xs)) = HardForkGenTxId {}
type BlockNodeToClientVersion (HardForkBlock xs) 
Instance details

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

type BlockNodeToClientVersion (HardForkBlock xs) = HardForkNodeToClientVersion xs
type BlockNodeToNodeVersion (HardForkBlock xs) 
Instance details

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

type BlockNodeToNodeVersion (HardForkBlock xs) = HardForkNodeToNodeVersion xs
data ProtocolParams (CardanoBlock c) Source #

Parameters needed to run Cardano.

Instance details

Defined in Ouroboros.Consensus.Cardano.Node

data Ticked (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type HeaderHash (HardForkBlock xs :: TYPE LiftedRep) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type HeaderHash (HardForkBlock xs :: TYPE LiftedRep) = OneEraHash xs

Headers

type CardanoHeader c = Header (CardanoBlock c) Source #

The Cardano header.

data family Header blk #

Instances

Instances details
Inject Header 
Instance details

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

Methods

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

HasNestedContent Header ByronBlock 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Serialisation

Methods

unnest :: Header ByronBlock -> DepPair (NestedCtxt Header ByronBlock)

nest :: DepPair (NestedCtxt Header ByronBlock) -> Header ByronBlock

ReconstructNestedCtxt Header ByronBlock 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

reconstructPrefixLen :: proxy (Header ByronBlock) -> PrefixLen

reconstructNestedCtxt :: proxy (Header ByronBlock) -> ShortByteString -> SizeInBytes -> SomeSecond (NestedCtxt Header) ByronBlock

SerialiseNodeToNode ByronBlock (Header ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

encodeNodeToNode :: CodecConfig ByronBlock -> BlockNodeToNodeVersion ByronBlock -> Header ByronBlock -> Encoding

decodeNodeToNode :: CodecConfig ByronBlock -> BlockNodeToNodeVersion ByronBlock -> forall s. Decoder s (Header ByronBlock)

HasHeader blk => StandardHash (Header blk :: Type) 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

ShowProxy (Header ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

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

ShelleyBasedEra era => ReconstructNestedCtxt Header (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

reconstructPrefixLen :: proxy (Header (ShelleyBlock proto era)) -> PrefixLen

reconstructNestedCtxt :: proxy (Header (ShelleyBlock proto era)) -> ShortByteString -> SizeInBytes -> SomeSecond (NestedCtxt Header) (ShelleyBlock proto era)

Generic (Header ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

Associated Types

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Associated Types

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

Methods

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

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

Show (Header ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

ShelleyCompatible proto era => Show (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

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

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

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

ShelleyCompatible proto era => DecCBOR (Annotator (Header (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

decCBOR :: Decoder s (Annotator (Header (ShelleyBlock proto era)))

dropCBOR :: Proxy (Annotator (Header (ShelleyBlock proto era))) -> Decoder s ()

label :: Proxy (Annotator (Header (ShelleyBlock proto era))) -> Text

ShelleyCompatible proto era => EncCBOR (Header (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

encCBOR :: Header (ShelleyBlock proto era) -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (Header (ShelleyBlock proto era)) -> Size

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

Eq (Header ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

ShelleyCompatible proto era => Eq (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

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

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

NoThunks (Header ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

Methods

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

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

showTypeOf :: Proxy (Header ByronBlock) -> String

ShelleyCompatible proto era => NoThunks (Header (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

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

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

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

SignedHeader (ShelleyProtocolHeader proto) => SignedHeader (Header (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Protocol

Methods

headerSigned :: Header (ShelleyBlock proto era) -> Signed (Header (ShelleyBlock proto era))

Condense (Header ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

ShelleyCompatible proto era => Condense (Header (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

condense :: Header (ShelleyBlock proto era) -> String

HasHeader (Header ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

Methods

getHeaderFields :: Header ByronBlock -> HeaderFields (Header ByronBlock)

ShelleyCompatible proto era => HasHeader (Header (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

getHeaderFields :: Header (ShelleyBlock proto era) -> HeaderFields (Header (ShelleyBlock proto era))

DecodeDiskDep (NestedCtxt Header) ByronBlock 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

decodeDiskDep :: CodecConfig ByronBlock -> NestedCtxt Header ByronBlock a -> forall s. Decoder s (ByteString -> a)

DecodeDiskDepIx (NestedCtxt Header) ByronBlock 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

decodeDiskDepIx :: CodecConfig ByronBlock -> Decoder s (SomeSecond (NestedCtxt Header) ByronBlock)

EncodeDiskDep (NestedCtxt Header) ByronBlock 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

encodeDiskDep :: CodecConfig ByronBlock -> NestedCtxt Header ByronBlock a -> a -> Encoding

EncodeDiskDepIx (NestedCtxt Header) ByronBlock 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

encodeDiskDepIx :: CodecConfig ByronBlock -> SomeSecond (NestedCtxt Header) ByronBlock -> Encoding

ShelleyCompatible proto era => DecodeDiskDep (NestedCtxt Header) (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDiskDep :: CodecConfig (ShelleyBlock proto era) -> NestedCtxt Header (ShelleyBlock proto era) a -> forall s. Decoder s (ByteString -> a)

ShelleyBasedEra era => DecodeDiskDepIx (NestedCtxt Header) (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDiskDepIx :: CodecConfig (ShelleyBlock proto era) -> Decoder s (SomeSecond (NestedCtxt Header) (ShelleyBlock proto era))

ShelleyCompatible proto era => EncodeDiskDep (NestedCtxt Header) (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDiskDep :: CodecConfig (ShelleyBlock proto era) -> NestedCtxt Header (ShelleyBlock proto era) a -> a -> Encoding

ShelleyBasedEra era => EncodeDiskDepIx (NestedCtxt Header) (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDiskDepIx :: CodecConfig (ShelleyBlock proto era) -> SomeSecond (NestedCtxt Header) (ShelleyBlock proto era) -> Encoding

ShelleyCompatible proto era => SerialiseNodeToNode (ShelleyBlock proto era) (Header (ShelleyBlock proto era))

CBOR-in-CBOR to be compatible with the wrapped (Serialised) variant.

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToNode :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToNodeVersion (ShelleyBlock proto era) -> Header (ShelleyBlock proto era) -> Encoding

decodeNodeToNode :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToNodeVersion (ShelleyBlock proto era) -> forall s. Decoder s (Header (ShelleyBlock proto era))

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

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

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

ShelleyCompatible proto era => DecodeDisk (ShelleyBlock proto era) (ByteString -> Header (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

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

data Header ByronBlock Source #

Byron header

See ByronBlock for comments on why we cache certain values.

Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

data Header ByronBlock = ByronHeader {}
type HeaderHash (Header blk :: Type) 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

type HeaderHash (Header blk :: Type) = HeaderHash blk
type Rep (Header ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

type Rep (Header ByronBlock) = D1 ('MetaData "Header" "Ouroboros.Consensus.Byron.Ledger.Block" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ByronHeader" 'PrefixI 'True) ((S1 ('MetaSel ('Just "byronHeaderRaw") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ABlockOrBoundaryHdr ByteString)) :*: S1 ('MetaSel ('Just "byronHeaderSlotNo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo)) :*: (S1 ('MetaSel ('Just "byronHeaderHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByronHash) :*: S1 ('MetaSel ('Just "byronHeaderBlockSizeHint") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SizeInBytes))))
type Rep (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

type Rep (Header (ShelleyBlock proto era)) = D1 ('MetaData "Header" "Ouroboros.Consensus.Shelley.Ledger.Block" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ShelleyHeader" 'PrefixI 'True) (S1 ('MetaSel ('Just "shelleyHeaderRaw") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ShelleyProtocolHeader proto)) :*: S1 ('MetaSel ('Just "shelleyHeaderHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ShelleyHash (ProtoCrypto proto)))))
type BlockProtocol (Header blk) 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

type BlockProtocol (Header blk) = BlockProtocol blk
newtype Header (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

newtype Header (HardForkBlock xs) = HardForkHeader {}
type Signed (Header (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Protocol

type Signed (Header (ShelleyBlock proto era)) = Signed (ShelleyProtocolHeader proto)
data Header (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Generalised transactions

type CardanoApplyTxErr c = HardForkApplyTxErr (CardanoEras c) Source #

An error resulting from applying a CardanoGenTx to the ledger.

Thanks to the pattern synonyms, you can treat this as a sum type with constructors ApplyTxByronErr, ApplyTxErrShelley, and ApplyTxErrWrongEra.

toText :: CardanoApplyTxErr c -> Text
toText (ApplyTxErrByron b) = byronApplyTxErrToText b
toText (ApplyTxErrShelley s) = shelleyApplyTxErrToText s
toText (ApplyTxErrAllegra a) = allegraApplyTxErrToText a
toText (ApplyTxErrMary m) = maryApplyTxErrToText m
toText (ApplyTxErrWrongEra eraMismatch) =
  "Transaction from the " <> otherEraName eraMismatch <>
  " era applied to a ledger from the " <>
  ledgerEraName eraMismatch <> " era"

type CardanoGenTx c = GenTx (CardanoBlock c) Source #

The Cardano transaction.

type CardanoGenTxId c = GenTxId (CardanoBlock c) Source #

The ID of a Cardano transaction.

data family GenTx blk #

Instances

Instances details
Inject GenTx 
Instance details

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

Methods

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

SerialiseNodeToClient ByronBlock (GenTx ByronBlock)

No CBOR-in-CBOR, because we check for canonical encodings, which means we can use the recomputed encoding for the annotation.

Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

encodeNodeToClient :: CodecConfig ByronBlock -> BlockNodeToClientVersion ByronBlock -> GenTx ByronBlock -> Encoding

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

SerialiseNodeToClient ByronBlock (GenTxId ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

encodeNodeToClient :: CodecConfig ByronBlock -> BlockNodeToClientVersion ByronBlock -> GenTxId ByronBlock -> Encoding

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

SerialiseNodeToNode ByronBlock (GenTx ByronBlock)

No CBOR-in-CBOR, because we check for canonical encodings, which means we can use the recomputed encoding for the annotation.

Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

encodeNodeToNode :: CodecConfig ByronBlock -> BlockNodeToNodeVersion ByronBlock -> GenTx ByronBlock -> Encoding

decodeNodeToNode :: CodecConfig ByronBlock -> BlockNodeToNodeVersion ByronBlock -> forall s. Decoder s (GenTx ByronBlock)

SerialiseNodeToNode ByronBlock (GenTxId ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

encodeNodeToNode :: CodecConfig ByronBlock -> BlockNodeToNodeVersion ByronBlock -> GenTxId ByronBlock -> Encoding

decodeNodeToNode :: CodecConfig ByronBlock -> BlockNodeToNodeVersion ByronBlock -> forall s. Decoder s (GenTxId ByronBlock)

(Typeable era, Typeable proto) => ShowProxy (Validated (GenTx (ShelleyBlock proto era)) :: Type) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showProxy :: Proxy (Validated (GenTx (ShelleyBlock proto era))) -> String

ShowProxy (GenTx ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

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

ShowProxy (TxId (GenTx ByronBlock)) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

(Typeable era, Typeable proto) => ShowProxy (TxId (GenTx (ShelleyBlock proto era)) :: Type) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showProxy :: Proxy (TxId (GenTx (ShelleyBlock proto era))) -> String

(ShelleyBasedEra era, TranslateEra era WrapTx) => TranslateEra era (GenTx :.: ShelleyBlock proto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type TranslationError era (GenTx :.: ShelleyBlock proto)

Methods

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

Generic (Validated (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

Associated Types

type Rep (Validated (GenTx ByronBlock)) :: Type -> Type Source #

Generic (Validated (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

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

Methods

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

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

Generic (GenTx ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

Associated Types

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

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

Methods

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

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

Show (Validated (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Show (GenTx ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

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

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

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

Show (GenTxId ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

Methods

showsPrec :: Int -> GenTxId ByronBlock -> ShowS Source #

show :: GenTxId ByronBlock -> String Source #

showList :: [GenTxId ByronBlock] -> ShowS Source #

Show (GenTxId (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

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

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

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

ShelleyCompatible proto era => FromCBOR (GenTx (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

fromCBOR :: Decoder s (GenTx (ShelleyBlock proto era))

label :: Proxy (GenTx (ShelleyBlock proto era)) -> Text

ShelleyCompatible proto era => ToCBOR (GenTx (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

toCBOR :: GenTx (ShelleyBlock proto era) -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (GenTx (ShelleyBlock proto era)) -> Size

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

(Crypto (EraCrypto era), Typeable era, Typeable proto) => DecCBOR (TxId (GenTx (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

decCBOR :: Decoder s (TxId (GenTx (ShelleyBlock proto era)))

dropCBOR :: Proxy (TxId (GenTx (ShelleyBlock proto era))) -> Decoder s ()

label :: Proxy (TxId (GenTx (ShelleyBlock proto era))) -> Text

(Crypto (EraCrypto era), Typeable era, Typeable proto) => EncCBOR (TxId (GenTx (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

encCBOR :: TxId (GenTx (ShelleyBlock proto era)) -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (TxId (GenTx (ShelleyBlock proto era))) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [TxId (GenTx (ShelleyBlock proto era))] -> Size

Eq (Validated (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

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

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

Eq (GenTx ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

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

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

Eq (TxId (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

Eq (TxId (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

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

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

Ord (TxId (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

Ord (TxId (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

compare :: TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) -> Ordering Source #

(<) :: TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) -> Bool Source #

(<=) :: TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) -> Bool Source #

(>) :: TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) -> Bool Source #

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

max :: TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) Source #

min :: TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) Source #

NoThunks (Validated (GenTx ByronBlock)) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

Methods

noThunks :: Context -> Validated (GenTx ByronBlock) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Validated (GenTx ByronBlock) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (Validated (GenTx ByronBlock)) -> String

ShelleyBasedEra era => NoThunks (Validated (GenTx (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

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

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

showTypeOf :: Proxy (Validated (GenTx (ShelleyBlock proto era))) -> String

NoThunks (GenTx ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

Methods

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

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

showTypeOf :: Proxy (GenTx ByronBlock) -> String

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

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

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

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

NoThunks (TxId (GenTx ByronBlock)) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

Methods

noThunks :: Context -> TxId (GenTx ByronBlock) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> TxId (GenTx ByronBlock) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (TxId (GenTx ByronBlock)) -> String

NoThunks (TxId (GenTx (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

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

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

showTypeOf :: Proxy (TxId (GenTx (ShelleyBlock proto era))) -> String

HasTxId (GenTx ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

ShelleyBasedEra era => HasTxId (GenTx (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

txId :: GenTx (ShelleyBlock proto era) -> TxId (GenTx (ShelleyBlock proto era))

Condense (GenTx ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

ShelleyBasedEra era => Condense (GenTx (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

condense :: GenTx (ShelleyBlock proto era) -> String

Condense (GenTxId ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

Methods

condense :: GenTxId ByronBlock -> String

Condense (GenTxId (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

condense :: GenTxId (ShelleyBlock proto era) -> String

ShelleyCompatible proto era => SerialiseNodeToClient (ShelleyBlock proto era) (GenTx (ShelleyBlock proto era))

Uses CBOR-in-CBOR in the To/FromCBOR instances to get the annotation.

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

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

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

ShelleyCompatible proto era => SerialiseNodeToClient (ShelleyBlock proto era) (GenTxId (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

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

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

ShelleyCompatible proto era => SerialiseNodeToNode (ShelleyBlock proto era) (GenTx (ShelleyBlock proto era))

The To/FromCBOR instances defined in cardano-ledger use CBOR-in-CBOR to get the annotation.

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToNode :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToNodeVersion (ShelleyBlock proto era) -> GenTx (ShelleyBlock proto era) -> Encoding

decodeNodeToNode :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToNodeVersion (ShelleyBlock proto era) -> forall s. Decoder s (GenTx (ShelleyBlock proto era))

ShelleyCompatible proto era => SerialiseNodeToNode (ShelleyBlock proto era) (GenTxId (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToNode :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToNodeVersion (ShelleyBlock proto era) -> GenTxId (ShelleyBlock proto era) -> Encoding

decodeNodeToNode :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToNodeVersion (ShelleyBlock proto era) -> forall s. Decoder s (GenTxId (ShelleyBlock proto era))

data GenTx ByronBlock Source #

Generalized transactions in Byron

This is effectively the same as AMempoolPayload but we cache the transaction ID (a hash).

Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

data GenTx ByronBlock
type TranslationError era (GenTx :.: ShelleyBlock proto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type TranslationError era (GenTx :.: ShelleyBlock proto) = TranslationError era WrapTx
type Rep (Validated (GenTx (HardForkBlock xs))) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (Validated (GenTx (HardForkBlock xs))) = D1 ('MetaData "Validated" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.14.0.0-121Znn1OCbJFCod8haNyF" 'True) (C1 ('MetaCons "HardForkValidatedGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkValidatedGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraValidatedGenTx xs))))
type Rep (Validated (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

type Rep (Validated (GenTx ByronBlock)) = D1 ('MetaData "Validated" "Ouroboros.Consensus.Byron.Ledger.Mempool" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'True) (C1 ('MetaCons "ValidatedByronTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "forgetValidatedByronTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (GenTx ByronBlock))))
type Rep (Validated (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type Rep (Validated (GenTx (ShelleyBlock proto era))) = D1 ('MetaData "Validated" "Ouroboros.Consensus.Shelley.Ledger.Mempool" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ShelleyValidatedTx" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TxId (EraCrypto era))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Validated (Tx era)))))
type Rep (GenTx (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (GenTx (HardForkBlock xs)) = D1 ('MetaData "GenTx" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.14.0.0-121Znn1OCbJFCod8haNyF" 'True) (C1 ('MetaCons "HardForkGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTx xs))))
type Rep (GenTx ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

type Rep (GenTx ByronBlock) = D1 ('MetaData "GenTx" "Ouroboros.Consensus.Byron.Ledger.Mempool" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) ((C1 ('MetaCons "ByronTx" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ATxAux ByteString))) :+: C1 ('MetaCons "ByronDlg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CertificateId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ACertificate ByteString)))) :+: (C1 ('MetaCons "ByronUpdateProposal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UpId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (AProposal ByteString))) :+: C1 ('MetaCons "ByronUpdateVote" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 VoteId) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (AVote ByteString)))))
type Rep (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type Rep (GenTx (ShelleyBlock proto era)) = D1 ('MetaData "GenTx" "Ouroboros.Consensus.Shelley.Ledger.Mempool" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ShelleyTx" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TxId (EraCrypto era))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Tx era))))
type Rep (TxId (GenTx (HardForkBlock xs))) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (TxId (GenTx (HardForkBlock xs))) = D1 ('MetaData "TxId" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.14.0.0-121Znn1OCbJFCod8haNyF" 'True) (C1 ('MetaCons "HardForkGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTxId xs))))
newtype Validated (GenTx (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

newtype Validated (GenTx (HardForkBlock xs)) = HardForkValidatedGenTx {}
newtype Validated (GenTx ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

data Validated (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

data Validated (GenTx (ShelleyBlock proto era)) = ShelleyValidatedTx !(TxId (EraCrypto era)) !(Validated (Tx era))
newtype GenTx (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

newtype GenTx (HardForkBlock xs) = HardForkGenTx {}
newtype TxId (GenTx (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

newtype TxId (GenTx (HardForkBlock xs)) = HardForkGenTxId {}
data TxId (GenTx ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

data TxId (GenTx ByronBlock)
newtype TxId (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

newtype TxId (GenTx (ShelleyBlock proto era)) = ShelleyTxId (TxId (EraCrypto era))
data GenTx (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

data GenTx (ShelleyBlock proto era) = ShelleyTx !(TxId (EraCrypto era)) !(Tx era)

data HardForkApplyTxErr (xs :: [Type]) where #

Bundled Patterns

pattern ApplyTxErrAllegra :: ApplyTxErr (ShelleyBlock (TPraos c) (AllegraEra c)) -> CardanoApplyTxErr c 
pattern ApplyTxErrAlonzo :: ApplyTxErr (ShelleyBlock (TPraos c) (AlonzoEra c)) -> CardanoApplyTxErr c 
pattern ApplyTxErrByron :: ApplyTxErr ByronBlock -> CardanoApplyTxErr c 
pattern ApplyTxErrMary :: ApplyTxErr (ShelleyBlock (TPraos c) (MaryEra c)) -> CardanoApplyTxErr c 
pattern ApplyTxErrShelley :: ApplyTxErr (ShelleyBlock (TPraos c) (ShelleyEra c)) -> CardanoApplyTxErr c 
pattern ApplyTxErrWrongEra :: EraMismatch -> CardanoApplyTxErr c 
pattern ApplyTxErrBabbage :: ApplyTxErr (ShelleyBlock (Praos c) (BabbageEra c)) -> CardanoApplyTxErr c 
pattern ApplyTxErrConway :: ApplyTxErr (ShelleyBlock (Praos c) (ConwayEra c)) -> CardanoApplyTxErr c 

Instances

Instances details
Typeable xs => ShowProxy (HardForkApplyTxErr xs :: Type) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Generic (HardForkApplyTxErr xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Associated Types

type Rep (HardForkApplyTxErr xs) :: Type -> Type Source #

CanHardFork xs => Show (HardForkApplyTxErr xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

CanHardFork xs => Eq (HardForkApplyTxErr xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (HardForkApplyTxErr xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (HardForkApplyTxErr xs) = D1 ('MetaData "HardForkApplyTxErr" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.14.0.0-121Znn1OCbJFCod8haNyF" 'False) (C1 ('MetaCons "HardForkApplyTxErrFromEra" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (OneEraApplyTxErr xs))) :+: C1 ('MetaCons "HardForkApplyTxErrWrongEra" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (MismatchEraInfo xs))))

data family TxId tx #

Instances

Instances details
SerialiseNodeToClient ByronBlock (GenTxId ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

encodeNodeToClient :: CodecConfig ByronBlock -> BlockNodeToClientVersion ByronBlock -> GenTxId ByronBlock -> Encoding

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

SerialiseNodeToNode ByronBlock (GenTxId ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

encodeNodeToNode :: CodecConfig ByronBlock -> BlockNodeToNodeVersion ByronBlock -> GenTxId ByronBlock -> Encoding

decodeNodeToNode :: CodecConfig ByronBlock -> BlockNodeToNodeVersion ByronBlock -> forall s. Decoder s (GenTxId ByronBlock)

ShowProxy (TxId (GenTx ByronBlock)) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

(Typeable era, Typeable proto) => ShowProxy (TxId (GenTx (ShelleyBlock proto era)) :: Type) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showProxy :: Proxy (TxId (GenTx (ShelleyBlock proto era))) -> String

Show (GenTxId ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

Methods

showsPrec :: Int -> GenTxId ByronBlock -> ShowS Source #

show :: GenTxId ByronBlock -> String Source #

showList :: [GenTxId ByronBlock] -> ShowS Source #

Show (GenTxId (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

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

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

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

(Crypto (EraCrypto era), Typeable era, Typeable proto) => DecCBOR (TxId (GenTx (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

decCBOR :: Decoder s (TxId (GenTx (ShelleyBlock proto era)))

dropCBOR :: Proxy (TxId (GenTx (ShelleyBlock proto era))) -> Decoder s ()

label :: Proxy (TxId (GenTx (ShelleyBlock proto era))) -> Text

(Crypto (EraCrypto era), Typeable era, Typeable proto) => EncCBOR (TxId (GenTx (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

encCBOR :: TxId (GenTx (ShelleyBlock proto era)) -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (TxId (GenTx (ShelleyBlock proto era))) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [TxId (GenTx (ShelleyBlock proto era))] -> Size

Eq (TxId (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

Eq (TxId (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

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

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

Ord (TxId (GenTx ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

Ord (TxId (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

compare :: TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) -> Ordering Source #

(<) :: TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) -> Bool Source #

(<=) :: TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) -> Bool Source #

(>) :: TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) -> Bool Source #

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

max :: TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) Source #

min :: TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) Source #

NoThunks (TxId (GenTx ByronBlock)) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

Methods

noThunks :: Context -> TxId (GenTx ByronBlock) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> TxId (GenTx ByronBlock) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (TxId (GenTx ByronBlock)) -> String

NoThunks (TxId (GenTx (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

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

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

showTypeOf :: Proxy (TxId (GenTx (ShelleyBlock proto era))) -> String

Condense (GenTxId ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

Methods

condense :: GenTxId ByronBlock -> String

Condense (GenTxId (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

condense :: GenTxId (ShelleyBlock proto era) -> String

ShelleyCompatible proto era => SerialiseNodeToClient (ShelleyBlock proto era) (GenTxId (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

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

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

ShelleyCompatible proto era => SerialiseNodeToNode (ShelleyBlock proto era) (GenTxId (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToNode :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToNodeVersion (ShelleyBlock proto era) -> GenTxId (ShelleyBlock proto era) -> Encoding

decodeNodeToNode :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToNodeVersion (ShelleyBlock proto era) -> forall s. Decoder s (GenTxId (ShelleyBlock proto era))

type Rep (TxId (GenTx (HardForkBlock xs))) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (TxId (GenTx (HardForkBlock xs))) = D1 ('MetaData "TxId" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.14.0.0-121Znn1OCbJFCod8haNyF" 'True) (C1 ('MetaCons "HardForkGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTxId xs))))
newtype TxId (GenTx (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

newtype TxId (GenTx (HardForkBlock xs)) = HardForkGenTxId {}
data TxId (GenTx ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Mempool

data TxId (GenTx ByronBlock)
newtype TxId (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

newtype TxId (GenTx (ShelleyBlock proto era)) = ShelleyTxId (TxId (EraCrypto era))

LedgerError

type CardanoLedgerError c = HardForkLedgerError (CardanoEras c) Source #

An error resulting from applying a CardanoBlock to the ledger.

Thanks to the pattern synonyms, you can treat this as a sum type with constructors LedgerErrorByron, LedgerErrorShelley, and LedgerErrorWrongEra.

toText :: CardanoLedgerError c -> Text
toText (LedgerErrorByron b) = byronLedgerErrorToText b
toText (LedgerErrorShelley s) = shelleyLedgerErrorToText s
toText (LedgerErrorAllegra a) = allegraLedgerErrorToText a
toText (LedgerErrorMary m) = maryLedgerErrorToText m
toText (LedgerErrorWrongEra eraMismatch) =
  "Block from the " <> otherEraName eraMismatch <>
  " era applied to a ledger from the " <>
  ledgerEraName eraMismatch <> " era"

data HardForkLedgerError (xs :: [Type]) where #

Bundled Patterns

pattern LedgerErrorAllegra :: LedgerError (ShelleyBlock (TPraos c) (AllegraEra c)) -> CardanoLedgerError c 
pattern LedgerErrorAlonzo :: LedgerError (ShelleyBlock (TPraos c) (AlonzoEra c)) -> CardanoLedgerError c 
pattern LedgerErrorByron :: LedgerError ByronBlock -> CardanoLedgerError c 
pattern LedgerErrorMary :: LedgerError (ShelleyBlock (TPraos c) (MaryEra c)) -> CardanoLedgerError c 
pattern LedgerErrorShelley :: LedgerError (ShelleyBlock (TPraos c) (ShelleyEra c)) -> CardanoLedgerError c 
pattern LedgerErrorWrongEra :: EraMismatch -> CardanoLedgerError c 
pattern LedgerErrorBabbage :: LedgerError (ShelleyBlock (Praos c) (BabbageEra c)) -> CardanoLedgerError c 
pattern LedgerErrorConway :: LedgerError (ShelleyBlock (Praos c) (ConwayEra c)) -> CardanoLedgerError c 

Instances

Instances details
Generic (HardForkLedgerError xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Associated Types

type Rep (HardForkLedgerError xs) :: Type -> Type Source #

CanHardFork xs => Show (HardForkLedgerError xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

CanHardFork xs => Eq (HardForkLedgerError xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

CanHardFork xs => NoThunks (HardForkLedgerError xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Methods

noThunks :: Context -> HardForkLedgerError xs -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> HardForkLedgerError xs -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (HardForkLedgerError xs) -> String

type Rep (HardForkLedgerError xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type Rep (HardForkLedgerError xs) = D1 ('MetaData "HardForkLedgerError" "Ouroboros.Consensus.HardFork.Combinator.Ledger" "ouroboros-consensus-0.14.0.0-121Znn1OCbJFCod8haNyF" 'False) (C1 ('MetaCons "HardForkLedgerErrorFromEra" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraLedgerError xs))) :+: C1 ('MetaCons "HardForkLedgerErrorWrongEra" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MismatchEraInfo xs))))

OtherEnvelopeError

type CardanoOtherHeaderEnvelopeError c = HardForkEnvelopeErr (CardanoEras c) Source #

An error resulting from validating a CardanoHeader.

data HardForkEnvelopeErr (xs :: [Type]) where #

Bundled Patterns

pattern OtherHeaderEnvelopeErrorAllegra :: OtherHeaderEnvelopeError (ShelleyBlock (TPraos c) (AllegraEra c)) -> CardanoOtherHeaderEnvelopeError c 
pattern OtherHeaderEnvelopeErrorBabbage :: OtherHeaderEnvelopeError (ShelleyBlock (Praos c) (BabbageEra c)) -> CardanoOtherHeaderEnvelopeError c 
pattern OtherHeaderEnvelopeErrorConway :: OtherHeaderEnvelopeError (ShelleyBlock (Praos c) (ConwayEra c)) -> CardanoOtherHeaderEnvelopeError c 
pattern OtherHeaderEnvelopeErrorAlonzo :: OtherHeaderEnvelopeError (ShelleyBlock (TPraos c) (AlonzoEra c)) -> CardanoOtherHeaderEnvelopeError c 
pattern OtherHeaderEnvelopeErrorByron :: OtherHeaderEnvelopeError ByronBlock -> CardanoOtherHeaderEnvelopeError c 
pattern OtherHeaderEnvelopeErrorMary :: OtherHeaderEnvelopeError (ShelleyBlock (TPraos c) (MaryEra c)) -> CardanoOtherHeaderEnvelopeError c 
pattern OtherHeaderEnvelopeErrorShelley :: OtherHeaderEnvelopeError (ShelleyBlock (TPraos c) (ShelleyEra c)) -> CardanoOtherHeaderEnvelopeError c 
pattern OtherHeaderEnvelopeErrorWrongEra :: EraMismatch -> CardanoOtherHeaderEnvelopeError c 

Instances

Instances details
Generic (HardForkEnvelopeErr xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Associated Types

type Rep (HardForkEnvelopeErr xs) :: Type -> Type Source #

CanHardFork xs => Show (HardForkEnvelopeErr xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

CanHardFork xs => Eq (HardForkEnvelopeErr xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

CanHardFork xs => NoThunks (HardForkEnvelopeErr xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Methods

noThunks :: Context -> HardForkEnvelopeErr xs -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> HardForkEnvelopeErr xs -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (HardForkEnvelopeErr xs) -> String

type Rep (HardForkEnvelopeErr xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type Rep (HardForkEnvelopeErr xs) = D1 ('MetaData "HardForkEnvelopeErr" "Ouroboros.Consensus.HardFork.Combinator.Ledger" "ouroboros-consensus-0.14.0.0-121Znn1OCbJFCod8haNyF" 'False) (C1 ('MetaCons "HardForkEnvelopeErrFromEra" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraEnvelopeErr xs))) :+: C1 ('MetaCons "HardForkEnvelopeErrWrongEra" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MismatchEraInfo xs))))

TipInfo

type CardanoTipInfo c = OneEraTipInfo (CardanoEras c) Source #

The TipInfo of the Cardano chain.

data OneEraTipInfo (xs :: [Type]) where #

Bundled Patterns

pattern TipInfoAllegra :: TipInfo (ShelleyBlock (TPraos c) (AllegraEra c)) -> CardanoTipInfo c 
pattern TipInfoAlonzo :: TipInfo (ShelleyBlock (TPraos c) (AlonzoEra c)) -> CardanoTipInfo c 
pattern TipInfoByron :: TipInfo ByronBlock -> CardanoTipInfo c 
pattern TipInfoBabbage :: TipInfo (ShelleyBlock (Praos c) (BabbageEra c)) -> CardanoTipInfo c 
pattern TipInfoConway :: TipInfo (ShelleyBlock (Praos c) (ConwayEra c)) -> CardanoTipInfo c 
pattern TipInfoMary :: TipInfo (ShelleyBlock (TPraos c) (MaryEra c)) -> CardanoTipInfo c 
pattern TipInfoShelley :: TipInfo (ShelleyBlock (TPraos c) (ShelleyEra c)) -> CardanoTipInfo c 

Instances

Instances details
CanHardFork xs => Show (OneEraTipInfo xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

CanHardFork xs => Eq (OneEraTipInfo xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

CanHardFork xs => NoThunks (OneEraTipInfo xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

Methods

noThunks :: Context -> OneEraTipInfo xs -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> OneEraTipInfo xs -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (OneEraTipInfo xs) -> String

Query

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

type CardanoQuery c = BlockQuery (CardanoBlock c) Source #

The Query of Cardano chain.

type CardanoQueryResult c = HardForkQueryResult (CardanoEras c) Source #

The result of a CardanoQuery

Thanks to the pattern synonyms, you can treat this as a sum type with constructors QueryResultSuccess and QueryResultEraMismatch.

data Either a b where Source #

The Either type represents values with two possibilities: a value of type Either a b is either Left a or Right b.

The Either type is sometimes used to represent a value which is either correct or an error; by convention, the Left constructor is used to hold an error value and the Right constructor is used to hold a correct value (mnemonic: "right" also means "correct").

Examples

Expand

The type Either String Int is the type of values which can be either a String or an Int. The Left constructor can be used only on Strings, and the Right constructor can be used only on Ints:

>>> let s = Left "foo" :: Either String Int
>>> s
Left "foo"
>>> let n = Right 3 :: Either String Int
>>> n
Right 3
>>> :type s
s :: Either String Int
>>> :type n
n :: Either String Int

The fmap from our Functor instance will ignore Left values, but will apply the supplied function to values contained in a Right:

>>> let s = Left "foo" :: Either String Int
>>> let n = Right 3 :: Either String Int
>>> fmap (*2) s
Left "foo"
>>> fmap (*2) n
Right 6

The Monad instance for Either allows us to chain together multiple actions which may fail, and fail overall if any of the individual steps failed. First we'll write a function that can either parse an Int from a Char, or fail.

>>> import Data.Char ( digitToInt, isDigit )
>>> :{
    let parseEither :: Char -> Either String Int
        parseEither c
          | isDigit c = Right (digitToInt c)
          | otherwise = Left "parse error"
>>> :}

The following should work, since both '1' and '2' can be parsed as Ints.

>>> :{
    let parseMultiple :: Either String Int
        parseMultiple = do
          x <- parseEither '1'
          y <- parseEither '2'
          return (x + y)
>>> :}
>>> parseMultiple
Right 3

But the following should fail overall, since the first operation where we attempt to parse 'm' as an Int will fail:

>>> :{
    let parseMultiple :: Either String Int
        parseMultiple = do
          x <- parseEither 'm'
          y <- parseEither '2'
          return (x + y)
>>> :}
>>> parseMultiple
Left "parse error"

Bundled Patterns

pattern QueryResultSuccess :: result -> CardanoQueryResult c result 
pattern QueryResultEraMismatch :: EraMismatch -> CardanoQueryResult c result

A query from a different era than the ledger's era was sent.

Instances

Instances details
FromJSON2 Either 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

liftParseJSON2 :: Maybe a -> (Value -> Parser a) -> (Value -> Parser [a]) -> Maybe b -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (Either a b)

liftParseJSONList2 :: Maybe a -> (Value -> Parser a) -> (Value -> Parser [a]) -> Maybe b -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [Either a b]

liftOmittedField2 :: Maybe a -> Maybe b -> Maybe (Either a b)

ToJSON2 Either 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

liftToJSON2 :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> (b -> Bool) -> (b -> Value) -> ([b] -> Value) -> Either a b -> Value

liftToJSONList2 :: (a -> Bool) -> (a -> Value) -> ([a] -> Value) -> (b -> Bool) -> (b -> Value) -> ([b] -> Value) -> [Either a b] -> Value

liftToEncoding2 :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> (b -> Bool) -> (b -> Encoding) -> ([b] -> Encoding) -> Either a b -> Encoding

liftToEncodingList2 :: (a -> Bool) -> (a -> Encoding) -> ([a] -> Encoding) -> (b -> Bool) -> (b -> Encoding) -> ([b] -> Encoding) -> [Either a b] -> Encoding

liftOmitField2 :: (a -> Bool) -> (b -> Bool) -> Either a b -> Bool

Bifunctor Either

Since: base-4.8.0.0

Instance details

Defined in Data.Bifunctor

Methods

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

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

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

Eq2 Either

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Either a c -> Either b d -> Bool Source #

Ord2 Either

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Either a c -> Either b d -> Ordering Source #

Read2 Either

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Either a b) Source #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Either a b] Source #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Either a b) Source #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Either a b] Source #

Show2 Either

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Either a b -> ShowS Source #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Either a b] -> ShowS Source #

NFData2 Either

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> Either a b -> () Source #

Hashable2 Either 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt2 :: (Int -> a -> Int) -> (Int -> b -> Int) -> Int -> Either a b -> Int

Generic1 (Either a :: Type -> Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (Either a) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). Either a a0 -> Rep1 (Either a) a0 Source #

to1 :: forall (a0 :: k). Rep1 (Either a) a0 -> Either a a0 Source #

MonadError e (Either e) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> Either e a

catchError :: Either e a -> (e -> Either e a) -> Either e a

(Lift a, Lift b) => Lift (Either a b :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Quote m => Either a b -> m Exp Source #

liftTyped :: forall (m :: Type -> Type). Quote m => Either a b -> Code m (Either a b) Source #

FromJSON a => FromJSON1 (Either a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

liftParseJSON :: Maybe a0 -> (Value -> Parser a0) -> (Value -> Parser [a0]) -> Value -> Parser (Either a a0)

liftParseJSONList :: Maybe a0 -> (Value -> Parser a0) -> (Value -> Parser [a0]) -> Value -> Parser [Either a a0]

liftOmittedField :: Maybe a0 -> Maybe (Either a a0)

ToJSON a => ToJSON1 (Either a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

liftToJSON :: (a0 -> Bool) -> (a0 -> Value) -> ([a0] -> Value) -> Either a a0 -> Value

liftToJSONList :: (a0 -> Bool) -> (a0 -> Value) -> ([a0] -> Value) -> [Either a a0] -> Value

liftToEncoding :: (a0 -> Bool) -> (a0 -> Encoding) -> ([a0] -> Encoding) -> Either a a0 -> Encoding

liftToEncodingList :: (a0 -> Bool) -> (a0 -> Encoding) -> ([a0] -> Encoding) -> [Either a a0] -> Encoding

liftOmitField :: (a0 -> Bool) -> Either a a0 -> Bool

MonadFix (Either e)

Since: base-4.3.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Either e a) -> Either e a Source #

Foldable (Either a)

Since: base-4.7.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Either a m -> m Source #

foldMap :: Monoid m => (a0 -> m) -> Either a a0 -> m Source #

foldMap' :: Monoid m => (a0 -> m) -> Either a a0 -> m Source #

foldr :: (a0 -> b -> b) -> b -> Either a a0 -> b Source #

foldr' :: (a0 -> b -> b) -> b -> Either a a0 -> b Source #

foldl :: (b -> a0 -> b) -> b -> Either a a0 -> b Source #

foldl' :: (b -> a0 -> b) -> b -> Either a a0 -> b Source #

foldr1 :: (a0 -> a0 -> a0) -> Either a a0 -> a0 Source #

foldl1 :: (a0 -> a0 -> a0) -> Either a a0 -> a0 Source #

toList :: Either a a0 -> [a0] Source #

null :: Either a a0 -> Bool Source #

length :: Either a a0 -> Int Source #

elem :: Eq a0 => a0 -> Either a a0 -> Bool Source #

maximum :: Ord a0 => Either a a0 -> a0 Source #

minimum :: Ord a0 => Either a a0 -> a0 Source #

sum :: Num a0 => Either a a0 -> a0 Source #

product :: Num a0 => Either a a0 -> a0 Source #

Eq a => Eq1 (Either a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a0 -> b -> Bool) -> Either a a0 -> Either a b -> Bool Source #

Ord a => Ord1 (Either a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a0 -> b -> Ordering) -> Either a a0 -> Either a b -> Ordering Source #

Read a => Read1 (Either a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Either a a0) Source #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Either a a0] Source #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Either a a0) Source #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Either a a0] Source #

Show a => Show1 (Either a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Either a a0 -> ShowS Source #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Either a a0] -> ShowS Source #

Traversable (Either a)

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a0 -> f b) -> Either a a0 -> f (Either a b) Source #

sequenceA :: Applicative f => Either a (f a0) -> f (Either a a0) Source #

mapM :: Monad m => (a0 -> m b) -> Either a a0 -> m (Either a b) Source #

sequence :: Monad m => Either a (m a0) -> m (Either a a0) Source #

Applicative (Either e)

Since: base-3.0

Instance details

Defined in Data.Either

Methods

pure :: a -> Either e a Source #

(<*>) :: Either e (a -> b) -> Either e a -> Either e b Source #

liftA2 :: (a -> b -> c) -> Either e a -> Either e b -> Either e c Source #

(*>) :: Either e a -> Either e b -> Either e b Source #

(<*) :: Either e a -> Either e b -> Either e a Source #

Functor (Either a)

Since: base-3.0

Instance details

Defined in Data.Either

Methods

fmap :: (a0 -> b) -> Either a a0 -> Either a b Source #

(<$) :: a0 -> Either a b -> Either a a0 Source #

Monad (Either e)

Since: base-4.4.0.0

Instance details

Defined in Data.Either

Methods

(>>=) :: Either e a -> (a -> Either e b) -> Either e b Source #

(>>) :: Either e a -> Either e b -> Either e b Source #

return :: a -> Either e a Source #

MonadFailure (Either a) 
Instance details

Defined in Basement.Monad

Associated Types

type Failure (Either a)

Methods

mFail :: Failure (Either a) -> Either a ()

NFData a => NFData1 (Either a)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a0 -> ()) -> Either a a0 -> () Source #

Hashable a => Hashable1 (Either a) 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a0 -> Int) -> Int -> Either a a0 -> Int

MonadBaseControl (Either e) (Either e) 
Instance details

Defined in Control.Monad.Trans.Control

Associated Types

type StM (Either e) a

Methods

liftBaseWith :: (RunInBase (Either e) (Either e) -> Either e a) -> Either e a

restoreM :: StM (Either e) a -> Either e a

(Structured a, Structured b) => Structured (Either a b) 
Instance details

Defined in Distribution.Utils.Structured

Methods

structure :: Proxy (Either a b) -> Structure

structureHash' :: Tagged (Either a b) MD5

(FromJSON a, FromJSON b) => FromJSON (Either a b) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Either a b)

parseJSONList :: Value -> Parser [Either a b]

omittedField :: Maybe (Either a b)

(ToJSON a, ToJSON b) => ToJSON (Either a b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Either a b -> Value

toEncoding :: Either a b -> Encoding

toJSONList :: [Either a b] -> Value

toEncodingList :: [Either a b] -> Encoding

omitField :: Either a b -> Bool

(Data a, Data b) => Data (Either a b)

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Either a b -> c (Either a b) Source #

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Either a b) Source #

toConstr :: Either a b -> Constr Source #

dataTypeOf :: Either a b -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Either a b)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Either a b)) Source #

gmapT :: (forall b0. Data b0 => b0 -> b0) -> Either a b -> Either a b Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Either a b -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Either a b -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Either a b -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Either a b -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) Source #

Semigroup (Either a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Either

Methods

(<>) :: Either a b -> Either a b -> Either a b Source #

sconcat :: NonEmpty (Either a b) -> Either a b Source #

stimes :: Integral b0 => b0 -> Either a b -> Either a b Source #

Generic (Either a b) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

(Read a, Read b) => Read (Either a b)

Since: base-3.0

Instance details

Defined in Data.Either

(Show a, Show b) => Show (Either a b)

Since: base-3.0

Instance details

Defined in Data.Either

Methods

showsPrec :: Int -> Either a b -> ShowS Source #

show :: Either a b -> String Source #

showList :: [Either a b] -> ShowS Source #

(FromCBOR a, FromCBOR b) => FromCBOR (Either a b) 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s (Either a b)

label :: Proxy (Either a b) -> Text

(ToCBOR a, ToCBOR b) => ToCBOR (Either a b) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Either a b -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Either a b) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Either a b] -> Size

(DecCBOR a, DecCBOR b) => DecCBOR (Either a b) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.DecCBOR

Methods

decCBOR :: Decoder s (Either a b)

dropCBOR :: Proxy (Either a b) -> Decoder s ()

label :: Proxy (Either a b) -> Text

(EncCBOR a, EncCBOR b) => EncCBOR (Either a b) 
Instance details

Defined in Cardano.Ledger.Binary.Encoding.EncCBOR

Methods

encCBOR :: Either a b -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (Either a b) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Either a b] -> Size

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

Defined in Control.DeepSeq

Methods

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

(Eq a, Eq b) => Eq (Either a b)

Since: base-2.1

Instance details

Defined in Data.Either

Methods

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

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

(Ord a, Ord b) => Ord (Either a b)

Since: base-2.1

Instance details

Defined in Data.Either

Methods

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

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

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

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

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

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

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

(Hashable a, Hashable b) => Hashable (Either a b) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Either a b -> Int

hash :: Either a b -> Int

MonoFoldable (Either a b) 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (Either a b) -> m) -> Either a b -> m

ofoldr :: (Element (Either a b) -> b0 -> b0) -> b0 -> Either a b -> b0

ofoldl' :: (a0 -> Element (Either a b) -> a0) -> a0 -> Either a b -> a0

otoList :: Either a b -> [Element (Either a b)]

oall :: (Element (Either a b) -> Bool) -> Either a b -> Bool

oany :: (Element (Either a b) -> Bool) -> Either a b -> Bool

onull :: Either a b -> Bool

olength :: Either a b -> Int

olength64 :: Either a b -> Int64

ocompareLength :: Integral i => Either a b -> i -> Ordering

otraverse_ :: Applicative f => (Element (Either a b) -> f b0) -> Either a b -> f ()

ofor_ :: Applicative f => Either a b -> (Element (Either a b) -> f b0) -> f ()

omapM_ :: Applicative m => (Element (Either a b) -> m ()) -> Either a b -> m ()

oforM_ :: Applicative m => Either a b -> (Element (Either a b) -> m ()) -> m ()

ofoldlM :: Monad m => (a0 -> Element (Either a b) -> m a0) -> a0 -> Either a b -> m a0

ofoldMap1Ex :: Semigroup m => (Element (Either a b) -> m) -> Either a b -> m

ofoldr1Ex :: (Element (Either a b) -> Element (Either a b) -> Element (Either a b)) -> Either a b -> Element (Either a b)

ofoldl1Ex' :: (Element (Either a b) -> Element (Either a b) -> Element (Either a b)) -> Either a b -> Element (Either a b)

headEx :: Either a b -> Element (Either a b)

lastEx :: Either a b -> Element (Either a b)

unsafeHead :: Either a b -> Element (Either a b)

unsafeLast :: Either a b -> Element (Either a b)

maximumByEx :: (Element (Either a b) -> Element (Either a b) -> Ordering) -> Either a b -> Element (Either a b)

minimumByEx :: (Element (Either a b) -> Element (Either a b) -> Ordering) -> Either a b -> Element (Either a b)

oelem :: Element (Either a b) -> Either a b -> Bool

onotElem :: Element (Either a b) -> Either a b -> Bool

MonoFunctor (Either a b) 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (Either a b) -> Element (Either a b)) -> Either a b -> Either a b

MonoPointed (Either a b) 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (Either a b) -> Either a b

MonoTraversable (Either a b) 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (Either a b) -> f (Element (Either a b))) -> Either a b -> f (Either a b)

omapM :: Applicative m => (Element (Either a b) -> m (Element (Either a b))) -> Either a b -> m (Either a b)

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

Defined in NoThunks.Class

Methods

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

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

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

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

Defined in PlutusTx.Eq

Methods

(==) :: Either a b -> Either a b -> Bool

(Ord a, Ord b) => Ord (Either a b) 
Instance details

Defined in PlutusTx.Ord

Methods

compare :: Either a b -> Either a b -> Ordering

(<) :: Either a b -> Either a b -> Bool

(<=) :: Either a b -> Either a b -> Bool

(>) :: Either a b -> Either a b -> Bool

(>=) :: Either a b -> Either a b -> Bool

max :: Either a b -> Either a b -> Either a b

min :: Either a b -> Either a b -> Either a b

Corecursive (Either a b) 
Instance details

Defined in Data.Functor.Foldable

Methods

embed :: Base (Either a b) (Either a b) -> Either a b

ana :: (a0 -> Base (Either a b) a0) -> a0 -> Either a b

apo :: (a0 -> Base (Either a b) (Either (Either a b) a0)) -> a0 -> Either a b

postpro :: Recursive (Either a b) => (forall b0. Base (Either a b) b0 -> Base (Either a b) b0) -> (a0 -> Base (Either a b) a0) -> a0 -> Either a b

gpostpro :: (Recursive (Either a b), Monad m) => (forall b0. m (Base (Either a b) b0) -> Base (Either a b) (m b0)) -> (forall c. Base (Either a b) c -> Base (Either a b) c) -> (a0 -> Base (Either a b) (m a0)) -> a0 -> Either a b

Recursive (Either a b) 
Instance details

Defined in Data.Functor.Foldable

Methods

project :: Either a b -> Base (Either a b) (Either a b)

cata :: (Base (Either a b) a0 -> a0) -> Either a b -> a0

para :: (Base (Either a b) (Either a b, a0) -> a0) -> Either a b -> a0

gpara :: (Corecursive (Either a b), Comonad w) => (forall b0. Base (Either a b) (w b0) -> w (Base (Either a b) b0)) -> (Base (Either a b) (EnvT (Either a b) w a0) -> a0) -> Either a b -> a0

prepro :: Corecursive (Either a b) => (forall b0. Base (Either a b) b0 -> Base (Either a b) b0) -> (Base (Either a b) a0 -> a0) -> Either a b -> a0

gprepro :: (Corecursive (Either a b), Comonad w) => (forall b0. Base (Either a b) (w b0) -> w (Base (Either a b) b0)) -> (forall c. Base (Either a b) c -> Base (Either a b) c) -> (Base (Either a b) (w a0) -> a0) -> Either a b -> a0

(Serialise a, Serialise b) => Serialise (Either a b) 
Instance details

Defined in Codec.Serialise.Class

Methods

encode :: Either a b -> Encoding

decode :: Decoder s (Either a b)

encodeList :: [Either a b] -> Encoding

decodeList :: Decoder s [Either a b]

(ToExpr a, ToExpr b) => ToExpr (Either a b) 
Instance details

Defined in Data.TreeDiff.Class

Methods

toExpr :: Either a b -> Expr

listToExpr :: [Either a b] -> Expr

(a ~ a', b ~ b') => Each (Either a a') (Either b b') a b 
Instance details

Defined in Lens.Micro.Internal

Methods

each :: Traversal (Either a a') (Either b b') a b

type Rep1 (Either a :: Type -> Type)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Failure (Either a) 
Instance details

Defined in Basement.Monad

type Failure (Either a) = a
type StM (Either e) a 
Instance details

Defined in Control.Monad.Trans.Control

type StM (Either e) a = a
type Rep (Either a b)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Element (Either a b) 
Instance details

Defined in Data.MonoTraversable

type Element (Either a b) = b
type Base (Either a b) 
Instance details

Defined in Data.Functor.Foldable

type Base (Either a b) = Const (Either a b) :: Type -> Type

CodecConfig

type CardanoCodecConfig c = CodecConfig (CardanoBlock c) Source #

The CodecConfig for CardanoBlock.

Thanks to the pattern synonyms, you can treat this as the product of the Byron, Shelley, ... CodecConfigs.

data family CodecConfig blk #

Instances

Instances details
Generic (CodecConfig ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Config

Associated Types

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Associated Types

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

Methods

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

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

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

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

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

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

NoThunks (CodecConfig ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Config

Methods

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

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

showTypeOf :: Proxy (CodecConfig ByronBlock) -> String

NoThunks (CodecConfig (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Methods

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

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

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

newtype CodecConfig ByronBlock Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Config

type Rep (CodecConfig ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Config

type Rep (CodecConfig ByronBlock) = D1 ('MetaData "CodecConfig" "Ouroboros.Consensus.Byron.Ledger.Config" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'True) (C1 ('MetaCons "ByronCodecConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "getByronEpochSlots") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EpochSlots)))
type Rep (CodecConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

type Rep (CodecConfig (ShelleyBlock proto era)) = D1 ('MetaData "CodecConfig" "Ouroboros.Consensus.Shelley.Ledger.Config" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ShelleyCodecConfig" 'PrefixI 'False) (U1 :: Type -> Type))
newtype CodecConfig (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data CodecConfig (ShelleyBlock proto era) Source #

No particular codec configuration is needed for Shelley

Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

BlockConfig

data family BlockConfig blk #

Instances

Instances details
Generic (BlockConfig ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Config

Associated Types

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Associated Types

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

Methods

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

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

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

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

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

NoThunks (BlockConfig ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Config

Methods

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

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

showTypeOf :: Proxy (BlockConfig ByronBlock) -> String

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Methods

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

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

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

data BlockConfig ByronBlock Source #

Extended configuration we need for Byron

Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Config

data BlockConfig ByronBlock = ByronConfig {}
type Rep (BlockConfig ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Config

type Rep (BlockConfig ByronBlock) = D1 ('MetaData "BlockConfig" "Ouroboros.Consensus.Byron.Ledger.Config" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ByronConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "byronGenesisConfig") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Config) :*: (S1 ('MetaSel ('Just "byronProtocolVersion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ProtocolVersion) :*: S1 ('MetaSel ('Just "byronSoftwareVersion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SoftwareVersion))))
type Rep (BlockConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

type Rep (BlockConfig (ShelleyBlock proto era)) = D1 ('MetaData "BlockConfig" "Ouroboros.Consensus.Shelley.Ledger.Config" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ShelleyConfig" 'PrefixI 'True) ((S1 ('MetaSel ('Just "shelleyProtocolVersion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ProtVer) :*: S1 ('MetaSel ('Just "shelleySystemStart") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SystemStart)) :*: (S1 ('MetaSel ('Just "shelleyNetworkMagic") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetworkMagic) :*: S1 ('MetaSel ('Just "shelleyBlockIssuerVKeys") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (KeyHash 'BlockIssuer (EraCrypto era)) (VKey 'BlockIssuer (EraCrypto era)))))))
newtype BlockConfig (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data BlockConfig (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

data BlockConfig (ShelleyBlock proto era) = ShelleyConfig {}

type CardanoBlockConfig c = BlockConfig (CardanoBlock c) Source #

The BlockConfig for CardanoBlock.

Thanks to the pattern synonyms, you can treat this as the product of the Byron, Shelley, ... BlockConfigs.

StorageConfig

type CardanoStorageConfig c = StorageConfig (CardanoBlock c) Source #

The StorageConfig for CardanoBlock.

Thanks to the pattern synonyms, you can treat this as the product of the Byron, Shelley, ... StorageConfigs.

data family StorageConfig blk #

Instances

Instances details
Generic (StorageConfig ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Config

Associated Types

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Associated Types

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

Methods

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

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

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

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

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

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

NoThunks (StorageConfig ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Config

Methods

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

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

showTypeOf :: Proxy (StorageConfig ByronBlock) -> String

NoThunks (StorageConfig (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Methods

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

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

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

newtype StorageConfig ByronBlock Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Config

type Rep (StorageConfig ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Config

type Rep (StorageConfig ByronBlock) = D1 ('MetaData "StorageConfig" "Ouroboros.Consensus.Byron.Ledger.Config" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'True) (C1 ('MetaCons "ByronStorageConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "getByronBlockConfig") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (BlockConfig ByronBlock))))
type Rep (StorageConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

type Rep (StorageConfig (ShelleyBlock proto era)) = D1 ('MetaData "StorageConfig" "Ouroboros.Consensus.Shelley.Ledger.Config" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ShelleyStorageConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "shelleyStorageConfigSlotsPerKESPeriod") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "shelleyStorageConfigSecurityParam") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SecurityParam)))
newtype StorageConfig (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data StorageConfig (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

ConsensusConfig

type CardanoConsensusConfig c = ConsensusConfig (HardForkProtocol (CardanoEras c)) Source #

The ConsensusConfig for CardanoBlock.

Thanks to the pattern synonyms, you can treat this as the product of the Byron, Shelley, ... PartialConsensusConfigs.

NOTE: not ConsensusConfig, but PartialConsensusConfig.

data family ConsensusConfig p #

Instances

Instances details
Generic (ConsensusConfig (HardForkProtocol xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Associated Types

type Rep (ConsensusConfig (HardForkProtocol xs)) :: Type -> Type Source #

Methods

from :: ConsensusConfig (HardForkProtocol xs) -> Rep (ConsensusConfig (HardForkProtocol xs)) x Source #

to :: Rep (ConsensusConfig (HardForkProtocol xs)) x -> ConsensusConfig (HardForkProtocol xs) Source #

Generic (ConsensusConfig (PBft c)) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Associated Types

type Rep (ConsensusConfig (PBft c)) :: Type -> Type Source #

Methods

from :: ConsensusConfig (PBft c) -> Rep (ConsensusConfig (PBft c)) x Source #

to :: Rep (ConsensusConfig (PBft c)) x -> ConsensusConfig (PBft c) Source #

Generic (ConsensusConfig (Praos c)) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Associated Types

type Rep (ConsensusConfig (Praos c)) :: Type -> Type Source #

Methods

from :: ConsensusConfig (Praos c) -> Rep (ConsensusConfig (Praos c)) x Source #

to :: Rep (ConsensusConfig (Praos c)) x -> ConsensusConfig (Praos c) Source #

Generic (ConsensusConfig (TPraos c)) 
Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

Associated Types

type Rep (ConsensusConfig (TPraos c)) :: Type -> Type Source #

Methods

from :: ConsensusConfig (TPraos c) -> Rep (ConsensusConfig (TPraos c)) x Source #

to :: Rep (ConsensusConfig (TPraos c)) x -> ConsensusConfig (TPraos c) Source #

CanHardFork xs => NoThunks (ConsensusConfig (HardForkProtocol xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

noThunks :: Context -> ConsensusConfig (HardForkProtocol xs) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> ConsensusConfig (HardForkProtocol xs) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (ConsensusConfig (HardForkProtocol xs)) -> String

NoThunks (ConsensusConfig (PBft c)) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

Methods

noThunks :: Context -> ConsensusConfig (PBft c) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> ConsensusConfig (PBft c) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (ConsensusConfig (PBft c)) -> String

PraosCrypto c => NoThunks (ConsensusConfig (Praos c)) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Methods

noThunks :: Context -> ConsensusConfig (Praos c) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> ConsensusConfig (Praos c) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (ConsensusConfig (Praos c)) -> String

PraosCrypto c => NoThunks (ConsensusConfig (TPraos c)) 
Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

Methods

noThunks :: Context -> ConsensusConfig (TPraos c) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> ConsensusConfig (TPraos c) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (ConsensusConfig (TPraos c)) -> String

type Rep (ConsensusConfig (HardForkProtocol xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type Rep (ConsensusConfig (HardForkProtocol xs)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.HardFork.Combinator.Basics" "ouroboros-consensus-0.14.0.0-121Znn1OCbJFCod8haNyF" 'False) (C1 ('MetaCons "HardForkConsensusConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "hardForkConsensusConfigK") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 SecurityParam) :*: (S1 ('MetaSel ('Just "hardForkConsensusConfigShape") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Shape xs)) :*: S1 ('MetaSel ('Just "hardForkConsensusConfigPerEra") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PerEraConsensusConfig xs)))))
type Rep (ConsensusConfig (PBft c)) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

type Rep (ConsensusConfig (PBft c)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.Protocol.PBFT" "ouroboros-consensus-0.14.0.0-121Znn1OCbJFCod8haNyF" 'True) (C1 ('MetaCons "PBftConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "pbftParams") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PBftParams)))
type Rep (ConsensusConfig (Praos c)) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

type Rep (ConsensusConfig (Praos c)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.Protocol.Praos" "ouroboros-consensus-protocol-0.6.0.0-9L9Rwb3KvaS6sYVJ3OHbE2" 'False) (C1 ('MetaCons "PraosConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "praosParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PraosParams) :*: S1 ('MetaSel ('Just "praosEpochInfo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (EpochInfo (Except PastHorizonException)))))
type Rep (ConsensusConfig (TPraos c)) 
Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

type Rep (ConsensusConfig (TPraos c)) = D1 ('MetaData "ConsensusConfig" "Ouroboros.Consensus.Protocol.TPraos" "ouroboros-consensus-protocol-0.6.0.0-9L9Rwb3KvaS6sYVJ3OHbE2" 'False) (C1 ('MetaCons "TPraosConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "tpraosParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TPraosParams) :*: S1 ('MetaSel ('Just "tpraosEpochInfo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (EpochInfo (Except PastHorizonException)))))
data ConsensusConfig (HardForkProtocol xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data ConsensusConfig (HardForkProtocol xs) = HardForkConsensusConfig {}
newtype ConsensusConfig (PBft c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

newtype ConsensusConfig (PBft c) = PBftConfig {}
data ConsensusConfig (Praos c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

data ConsensusConfig (Praos c) = PraosConfig {}
data ConsensusConfig (TPraos c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

data ConsensusConfig (TPraos c) = TPraosConfig {}

LedgerConfig

type CardanoLedgerConfig c = HardForkLedgerConfig (CardanoEras c) Source #

The LedgerConfig for CardanoBlock.

Thanks to the pattern synonyms, you can treat this as the product of the Byron, Shelley, ... PartialLedgerConfigs.

NOTE: not LedgerConfig, but PartialLedgerConfig.

data HardForkLedgerConfig (xs :: [Type]) where #

Bundled Patterns

pattern CardanoLedgerConfig :: PartialLedgerConfig ByronBlock -> PartialLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c)) -> PartialLedgerConfig (ShelleyBlock (TPraos c) (AllegraEra c)) -> PartialLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c)) -> PartialLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c)) -> PartialLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c)) -> PartialLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c)) -> CardanoLedgerConfig c 

Instances

Instances details
Generic (HardForkLedgerConfig xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Associated Types

type Rep (HardForkLedgerConfig xs) :: Type -> Type Source #

CanHardFork xs => NoThunks (HardForkLedgerConfig xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

noThunks :: Context -> HardForkLedgerConfig xs -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> HardForkLedgerConfig xs -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (HardForkLedgerConfig xs) -> String

type Rep (HardForkLedgerConfig xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type Rep (HardForkLedgerConfig xs) = D1 ('MetaData "HardForkLedgerConfig" "Ouroboros.Consensus.HardFork.Combinator.Basics" "ouroboros-consensus-0.14.0.0-121Znn1OCbJFCod8haNyF" 'False) (C1 ('MetaCons "HardForkLedgerConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "hardForkLedgerConfigShape") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Shape xs)) :*: S1 ('MetaSel ('Just "hardForkLedgerConfigPerEra") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PerEraLedgerConfig xs))))

LedgerState

type CardanoLedgerState c = LedgerState (CardanoBlock c) Source #

The LedgerState for CardanoBlock.

NOTE: the CardanoLedgerState contains more than just the current era's LedgerState. We don't give access to those internal details through the pattern synonyms. This is also the reason the pattern synonyms are not bidirectional.

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

ChainDepState

type CardanoChainDepState c = HardForkChainDepState (CardanoEras c) Source #

The ChainDepState for CardanoBlock.

NOTE: the CardanoChainDepState contains more than just the current era's ChainDepState. We don't give access to those internal details through the pattern synonyms. This is also the reason the pattern synonyms are not bidirectional.

data HardForkState (f :: Type -> Type) (xs :: [Type]) where #

Bundled Patterns

pattern ChainDepStateAllegra :: ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (AllegraEra c))) -> CardanoChainDepState c 
pattern ChainDepStateAlonzo :: ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (AlonzoEra c))) -> CardanoChainDepState c 
pattern ChainDepStateBabbage :: ChainDepState (BlockProtocol (ShelleyBlock (Praos c) (BabbageEra c))) -> CardanoChainDepState c 
pattern ChainDepStateConway :: ChainDepState (BlockProtocol (ShelleyBlock (Praos c) (ConwayEra c))) -> CardanoChainDepState c 
pattern ChainDepStateByron :: ChainDepState (BlockProtocol ByronBlock) -> CardanoChainDepState c 
pattern ChainDepStateMary :: ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (MaryEra c))) -> CardanoChainDepState c 
pattern ChainDepStateShelley :: ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c))) -> CardanoChainDepState c 

Instances

Instances details
type Prod HardForkState 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

type Prod HardForkState = NP :: (Type -> Type) -> [Type] -> Type
type SListIN HardForkState 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

type SListIN HardForkState = SListI :: [Type] -> Constraint
type CollapseTo HardForkState a 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

type CollapseTo HardForkState a = a
type AllN HardForkState (c :: Type -> Constraint) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.State.Instances

type AllN HardForkState (c :: Type -> Constraint) = All c
data Ticked (HardForkChainDepState xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

data Ticked (HardForkChainDepState xs) = TickedHardForkChainDepState {}

EraMismatch

data EraMismatch #

Constructors

EraMismatch 

Fields

Instances

Instances details
Generic EraMismatch 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

Associated Types

type Rep EraMismatch :: Type -> Type Source #

Show EraMismatch 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

Eq EraMismatch 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

type Rep EraMismatch 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.AcrossEras

type Rep EraMismatch = D1 ('MetaData "EraMismatch" "Ouroboros.Consensus.HardFork.Combinator.AcrossEras" "ouroboros-consensus-0.14.0.0-121Znn1OCbJFCod8haNyF" 'False) (C1 ('MetaCons "EraMismatch" 'PrefixI 'True) (S1 ('MetaSel ('Just "ledgerEraName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "otherEraName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))