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

Ouroboros.Consensus.Shelley.Ledger

Synopsis

Documentation

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 {}

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

class HasHeader (Header blk) => GetHeader blk where #

Methods

getHeader :: blk -> Header blk #

blockMatchesHeader :: Header blk -> blk -> Bool #

headerIsEBB :: Header blk -> Maybe EpochNo #

Instances

Instances details
GetHeader ByronBlock Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

getHeader :: ShelleyBlock proto era -> Header (ShelleyBlock proto era) #

blockMatchesHeader :: Header (ShelleyBlock proto era) -> ShelleyBlock proto era -> Bool #

headerIsEBB :: Header (ShelleyBlock proto era) -> Maybe EpochNo #

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

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

data family NestedCtxt_ blk :: (Type -> Type) -> Type -> Type #

Instances

Instances details
SameDepIndex (NestedCtxt_ ByronBlock f) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Serialisation

SameDepIndex (NestedCtxt_ (ShelleyBlock proto era) f) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

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

TrivialDependency (NestedCtxt_ (ShelleyBlock proto era) f) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Associated Types

type TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f)

Methods

hasSingleIndex :: NestedCtxt_ (ShelleyBlock proto era) f a -> NestedCtxt_ (ShelleyBlock proto era) f b -> a :~: b

indexIsTrivial :: NestedCtxt_ (ShelleyBlock proto era) f (TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f))

Show (NestedCtxt_ ByronBlock f a) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Serialisation

Show (NestedCtxt_ (ShelleyBlock proto era) f a) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

showsPrec :: Int -> NestedCtxt_ (ShelleyBlock proto era) f a -> ShowS Source #

show :: NestedCtxt_ (ShelleyBlock proto era) f a -> String Source #

showList :: [NestedCtxt_ (ShelleyBlock proto era) f a] -> ShowS Source #

data NestedCtxt_ ByronBlock f a Source #

Since the Byron header does not contain the size, we include it in the nested type instead.

Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Serialisation

data NestedCtxt_ (HardForkBlock xs) a b 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

data NestedCtxt_ (HardForkBlock xs) a b where
data NestedCtxt_ (ShelleyBlock proto era) f a Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

data NestedCtxt_ (ShelleyBlock proto era) f a where
type TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

type TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f) = f (ShelleyBlock proto era)

data family LedgerState blk #

Instances

Instances details
Inject LedgerState 
Instance details

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

Methods

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

DecodeDisk ByronBlock (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

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

EncodeDisk ByronBlock (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

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

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type TranslationError era (LedgerState :.: ShelleyBlock proto)

Methods

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

Generic (LedgerState ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Associated Types

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

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

Methods

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

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

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

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Associated Types

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

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

Methods

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

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

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Show (LedgerState ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Eq (LedgerState ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

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

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

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

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

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

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

NoThunks (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Methods

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

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

showTypeOf :: Proxy (LedgerState ByronBlock) -> String

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

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

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

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

NoThunks (Ticked (LedgerState ByronBlock)) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Methods

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

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

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

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

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

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

GetTip (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

GetTip (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

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

GetTip (Ticked (LedgerState ByronBlock)) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

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

IsLedger (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Associated Types

type LedgerErr (LedgerState ByronBlock)

type AuxLedgerEvent (LedgerState ByronBlock)

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type LedgerErr (LedgerState (ShelleyBlock proto era))

type AuxLedgerEvent (LedgerState (ShelleyBlock proto era))

Methods

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

ApplyBlock (LedgerState ByronBlock) ByronBlock 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

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

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

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

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

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

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

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

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

data LedgerState ByronBlock Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

type HeaderHash (LedgerState blk :: Type) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

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

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

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

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type LedgerCfg (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data Ticked (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

data Ticked (LedgerState ByronBlock) Source #

The ticked Byron ledger state

Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Ticking only affects the state itself

Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

data LedgerState (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

data family Ticked st #

Instances

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

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Associated Types

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

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

Methods

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

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

Show (Ticked ()) 
Instance details

Defined in Ouroboros.Consensus.Ticked

NoThunks (Ticked (LedgerState ByronBlock)) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Methods

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

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

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

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

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

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

GetTip (Ticked (LedgerState ByronBlock)) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

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

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

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

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

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

Defined in Ouroboros.Consensus.Ticked

Methods

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

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

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

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

Defined in Ouroboros.Consensus.Ticked

Methods

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

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

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

data Ticked () 
Instance details

Defined in Ouroboros.Consensus.Ticked

type HeaderHash (Ticked l :: Type) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

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

Defined in Ouroboros.Consensus.HeaderValidation

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

data Ticked (LedgerState ByronBlock) Source #

The ticked Byron ledger state

Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Ticking only affects the state itself

Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

data Ticked (ExtLedgerState blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

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

Defined in Ouroboros.Consensus.Protocol.PBFT

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

Defined in Ouroboros.Consensus.TypeFamilyWrappers

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

Defined in Ouroboros.Consensus.Protocol.Praos

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

Defined in Ouroboros.Consensus.Protocol.TPraos

data Ticked (TPraosState c) = TickedChainDepState {}

data family Validated x #

Instances

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

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 #

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

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 #

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

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

data family BlockQuery blk :: Type -> Type #

Instances

Instances details
SerialiseResult ByronBlock (BlockQuery ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

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

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

SerialiseNodeToClient ByronBlock (SomeSecond BlockQuery ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

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

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

Inject (SomeSecond BlockQuery) 
Instance details

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

Methods

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

SameDepIndex (BlockQuery ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

SameDepIndex (BlockQuery (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

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

ShowQuery (BlockQuery ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Methods

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

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

Show (BlockQuery ByronBlock result) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

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

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

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

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

Defined in Ouroboros.Consensus.Ledger.Query

Methods

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

show :: SomeSecond BlockQuery blk -> String Source #

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

Eq (BlockQuery ByronBlock result) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

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

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

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

Defined in Ouroboros.Consensus.Ledger.Query

Methods

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

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

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

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

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

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

ShowProxy (BlockQuery ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

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

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

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

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

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

data BlockQuery ByronBlock a Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

data BlockQuery (HardForkBlock xs) a 
Instance details

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

data BlockQuery (ShelleyBlock proto era) a where

data family 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 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))

newtype ApplyTxError era #

Constructors

ApplyTxError [PredicateFailure (EraRule "LEDGER" era)] 

Instances

Instances details
Show (PredicateFailure (EraRule "LEDGER" era)) => Show (ApplyTxError era) 
Instance details

Defined in Cardano.Ledger.Shelley.API.Mempool

(Era era, DecCBOR (PredicateFailure (EraRule "LEDGER" era))) => FromCBOR (ApplyTxError era) 
Instance details

Defined in Cardano.Ledger.Shelley.API.Mempool

Methods

fromCBOR :: Decoder s (ApplyTxError era)

label :: Proxy (ApplyTxError era) -> Text

(Era era, EncCBOR (PredicateFailure (EraRule "LEDGER" era))) => ToCBOR (ApplyTxError era) 
Instance details

Defined in Cardano.Ledger.Shelley.API.Mempool

Methods

toCBOR :: ApplyTxError era -> Encoding

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

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

(Era era, DecCBOR (PredicateFailure (EraRule "LEDGER" era))) => DecCBOR (ApplyTxError era) 
Instance details

Defined in Cardano.Ledger.Shelley.API.Mempool

Methods

decCBOR :: Decoder s (ApplyTxError era)

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

label :: Proxy (ApplyTxError era) -> Text

(Era era, EncCBOR (PredicateFailure (EraRule "LEDGER" era))) => EncCBOR (ApplyTxError era) 
Instance details

Defined in Cardano.Ledger.Shelley.API.Mempool

Methods

encCBOR :: ApplyTxError era -> Encoding

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

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

Eq (PredicateFailure (EraRule "LEDGER" era)) => Eq (ApplyTxError era) 
Instance details

Defined in Cardano.Ledger.Shelley.API.Mempool

Typeable era => ShowProxy (ApplyTxError era :: TYPE LiftedRep) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showProxy :: Proxy (ApplyTxError era) -> String

ShelleyBasedEra era => SerialiseNodeToClient (ShelleyBlock proto era) (ApplyTxError era)
ApplyTxErr '(ShelleyBlock era)'
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

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

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

class (EraSegWits era, EraGov era, ApplyTx era, ApplyBlock era, EraTransition era, GetLedgerView era, NoThunks (StashedAVVMAddresses era), EncCBOR (StashedAVVMAddresses era), DecCBOR (StashedAVVMAddresses era), Show (StashedAVVMAddresses era), Eq (StashedAVVMAddresses era), DecCBOR (PredicateFailure (EraRule "LEDGER" era)), EncCBOR (PredicateFailure (EraRule "LEDGER" era)), DecCBOR (PredicateFailure (EraRule "UTXOW" era)), EncCBOR (PredicateFailure (EraRule "UTXOW" era)), DSignable (EraCrypto era) (Hash (EraCrypto era) EraIndependentTxBody), NoThunks (PredicateFailure (EraRule "BBODY" era)), NoThunks (TranslationContext era)) => ShelleyBasedEra era Source #

Consensus often needs some more functionality than the ledger currently provides.

Either the functionality shouldn't or can't live in the ledger, in which case it can be part and remain part of ShelleyBasedEra. Or, the functionality should live in the ledger, but hasn't yet been added to the ledger, or it hasn't yet been propagated to this repository, in which case it can be added to this class until that is the case.

If this class becomes redundant, We can move it to ledger and re-export it from here.

TODO Currently we include some constraints on the update state which are needed to determine the hard fork point. In the future this should be replaced with an appropriate API - see https://github.com/input-output-hk/ouroboros-network/issues/2890

Instances

Instances details
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) => ShelleyBasedEra (AllegraEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName :: proxy (AllegraEra c) -> Text Source #

applyShelleyBasedTx :: Globals -> LedgerEnv (AllegraEra c) -> LedgerState (AllegraEra c) -> WhetherToIntervene -> Tx (AllegraEra c) -> Except (ApplyTxError (AllegraEra c)) (LedgerState (AllegraEra c), Validated (Tx (AllegraEra c))) Source #

getProposedProtocolVersion :: PParamsUpdate (AllegraEra c) -> Maybe ProtVer Source #

(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) => ShelleyBasedEra (AlonzoEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName :: proxy (AlonzoEra c) -> Text Source #

applyShelleyBasedTx :: Globals -> LedgerEnv (AlonzoEra c) -> LedgerState (AlonzoEra c) -> WhetherToIntervene -> Tx (AlonzoEra c) -> Except (ApplyTxError (AlonzoEra c)) (LedgerState (AlonzoEra c), Validated (Tx (AlonzoEra c))) Source #

getProposedProtocolVersion :: PParamsUpdate (AlonzoEra c) -> Maybe ProtVer Source #

PraosCrypto c => ShelleyBasedEra (BabbageEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName :: proxy (BabbageEra c) -> Text Source #

applyShelleyBasedTx :: Globals -> LedgerEnv (BabbageEra c) -> LedgerState (BabbageEra c) -> WhetherToIntervene -> Tx (BabbageEra c) -> Except (ApplyTxError (BabbageEra c)) (LedgerState (BabbageEra c), Validated (Tx (BabbageEra c))) Source #

getProposedProtocolVersion :: PParamsUpdate (BabbageEra c) -> Maybe ProtVer Source #

PraosCrypto c => ShelleyBasedEra (ConwayEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName :: proxy (ConwayEra c) -> Text Source #

applyShelleyBasedTx :: Globals -> LedgerEnv (ConwayEra c) -> LedgerState (ConwayEra c) -> WhetherToIntervene -> Tx (ConwayEra c) -> Except (ApplyTxError (ConwayEra c)) (LedgerState (ConwayEra c), Validated (Tx (ConwayEra c))) Source #

getProposedProtocolVersion :: PParamsUpdate (ConwayEra c) -> Maybe ProtVer Source #

(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) => ShelleyBasedEra (MaryEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName :: proxy (MaryEra c) -> Text Source #

applyShelleyBasedTx :: Globals -> LedgerEnv (MaryEra c) -> LedgerState (MaryEra c) -> WhetherToIntervene -> Tx (MaryEra c) -> Except (ApplyTxError (MaryEra c)) (LedgerState (MaryEra c), Validated (Tx (MaryEra c))) Source #

getProposedProtocolVersion :: PParamsUpdate (MaryEra c) -> Maybe ProtVer Source #

(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) => ShelleyBasedEra (ShelleyEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName :: proxy (ShelleyEra c) -> Text Source #

applyShelleyBasedTx :: Globals -> LedgerEnv (ShelleyEra c) -> LedgerState (ShelleyEra c) -> WhetherToIntervene -> Tx (ShelleyEra c) -> Except (ApplyTxError (ShelleyEra c)) (LedgerState (ShelleyEra c), Validated (Tx (ShelleyEra c))) Source #

getProposedProtocolVersion :: PParamsUpdate (ShelleyEra c) -> Maybe ProtVer Source #

verifyHeaderIntegrity Source #

Arguments

:: ProtocolHeaderSupportsKES proto 
=> Word64

Slots per KES period

-> ShelleyProtocolHeader proto 
-> Bool 

Verify that the signature on a header is correct and valid.

newtype ShelleyHash crypto Source #

Constructors

ShelleyHash 

Fields

Instances

Instances details
Generic (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Associated Types

type Rep (ShelleyHash crypto) :: Type -> Type Source #

Methods

from :: ShelleyHash crypto -> Rep (ShelleyHash crypto) x Source #

to :: Rep (ShelleyHash crypto) x -> ShelleyHash crypto Source #

Show (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

showsPrec :: Int -> ShelleyHash crypto -> ShowS Source #

show :: ShelleyHash crypto -> String Source #

showList :: [ShelleyHash crypto] -> ShowS Source #

Crypto crypto => FromCBOR (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

fromCBOR :: Decoder s (ShelleyHash crypto)

label :: Proxy (ShelleyHash crypto) -> Text

Crypto crypto => ToCBOR (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

toCBOR :: ShelleyHash crypto -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyHash crypto) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ShelleyHash crypto] -> Size

Eq (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

(==) :: ShelleyHash crypto -> ShelleyHash crypto -> Bool Source #

(/=) :: ShelleyHash crypto -> ShelleyHash crypto -> Bool Source #

Ord (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

compare :: ShelleyHash crypto -> ShelleyHash crypto -> Ordering Source #

(<) :: ShelleyHash crypto -> ShelleyHash crypto -> Bool Source #

(<=) :: ShelleyHash crypto -> ShelleyHash crypto -> Bool Source #

(>) :: ShelleyHash crypto -> ShelleyHash crypto -> Bool Source #

(>=) :: ShelleyHash crypto -> ShelleyHash crypto -> Bool Source #

max :: ShelleyHash crypto -> ShelleyHash crypto -> ShelleyHash crypto Source #

min :: ShelleyHash crypto -> ShelleyHash crypto -> ShelleyHash crypto Source #

NoThunks (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

noThunks :: Context -> ShelleyHash crypto -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> ShelleyHash crypto -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (ShelleyHash crypto) -> String

Condense (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

condense :: ShelleyHash crypto -> String

Crypto crypto => Serialise (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

encode :: ShelleyHash crypto -> Encoding

decode :: Decoder s (ShelleyHash crypto)

encodeList :: [ShelleyHash crypto] -> Encoding

decodeList :: Decoder s [ShelleyHash crypto]

type Rep (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

type Rep (ShelleyHash crypto) = D1 ('MetaData "ShelleyHash" "Ouroboros.Consensus.Shelley.Protocol.Abstract" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'True) (C1 ('MetaCons "ShelleyHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "unShelleyHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Hash crypto EraIndependentBlockHeader))))

data ShelleyBlock proto era Source #

Shelley-based block type.

This block is parametrised over both the (ledger) era and the protocol.

Constructors

ShelleyBlock 

Instances

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

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

(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

(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

(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

HasNestedContent f (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

unnest :: f (ShelleyBlock proto era) -> DepPair (NestedCtxt f (ShelleyBlock proto era))

nest :: DepPair (NestedCtxt f (ShelleyBlock proto era)) -> f (ShelleyBlock proto era)

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)

ShelleyCompatible proto era => StandardHash (ShelleyBlock proto era :: Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

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

(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)

(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)

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

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type TranslationError era (WrapValidatedGenTx :.: ShelleyBlock proto)

Methods

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

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 #

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 #

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 #

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 #

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

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 #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

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 #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

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 (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

ShelleyCompatible proto era => DecCBOR (Annotator (Header (ShelleyBlock proto era))) Source # 
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 => DecCBOR (Annotator (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

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

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

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

(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

ShelleyCompatible proto era => EncCBOR (Header (ShelleyBlock proto era)) Source # 
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

(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

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 #

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 #

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 #

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

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

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

ShelleyCompatible proto era => NoThunks (Header (ShelleyBlock proto era)) Source # 
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

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

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

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

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 (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

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

CardanoHardForkConstraints c => CanHardFork (CardanoEras c) 
Instance details

Defined in Ouroboros.Consensus.Cardano.CanHardFork

Methods

hardForkEraTranslation :: EraTranslation (CardanoEras c)

hardForkChainSel :: Tails AcrossEraSelection (CardanoEras c)

hardForkInjectTxs :: InPairs (RequiringBoth WrapLedgerConfig (Product2 InjectTx InjectValidatedTx)) (CardanoEras c)

CardanoHardForkConstraints c => CondenseConstraints (CardanoBlock c) 
Instance details

Defined in Ouroboros.Consensus.Cardano.Condense

CardanoHardForkConstraints c => SerialiseHFC (CardanoEras c)

Important: we need to maintain binary compatibility with Byron blocks, as they are already stored on disk.

We also want to be able to efficiently detect (without having to peek far ahead) whether we're dealing with a Byron or Shelley block, so that we can invoke the right decoder. We plan to have a few more hard forks after Shelley (Goguen, Basho, Voltaire), so we want a future-proof envelope for distinguishing the different block types, i.e., a byte indicating the era.

Byron does not provide such an envelope. However, a Byron block is a CBOR 2-tuple with the first element being a tag (Word: 0 = EBB; 1 = regular block) and the second being the payload. We can easily extend this encoding format with support for Shelley, Goguen, etc.

We encode a CardanoBlock as the same CBOR 2-tuple as a Byron block, but we use the tags after 1 for the hard forks after Byron:

  1. Byron EBB
  2. Byron regular block
  3. Shelley block
  4. Allegra block
  5. Mary block
  6. Goguen block
  7. etc.

For more details, see: https://github.com/input-output-hk/ouroboros-network/pull/1175#issuecomment-558147194

Instance details

Defined in Ouroboros.Consensus.Cardano.Node

Methods

encodeDiskHfcBlock :: CodecConfig (HardForkBlock (CardanoEras c)) -> HardForkBlock (CardanoEras c) -> Encoding

decodeDiskHfcBlock :: CodecConfig (HardForkBlock (CardanoEras c)) -> forall s. Decoder s (ByteString -> HardForkBlock (CardanoEras c))

reconstructHfcPrefixLen :: proxy (Header (HardForkBlock (CardanoEras c))) -> PrefixLen

reconstructHfcNestedCtxt :: proxy (Header (HardForkBlock (CardanoEras c))) -> ShortByteString -> SizeInBytes -> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c))

getHfcBinaryBlockInfo :: HardForkBlock (CardanoEras c) -> BinaryBlockInfo

estimateHfcBlockSize :: Header (HardForkBlock (CardanoEras c)) -> SizeInBytes

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 (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)))

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

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

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)

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

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

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)

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

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

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

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 => 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

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 #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

showsPrec :: Int -> ShelleyBlock proto era -> ShowS Source #

show :: ShelleyBlock proto era -> String Source #

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

encCBOR :: ShelleyBlock proto era -> Encoding

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

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

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 #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

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

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

toRawHash :: proxy (ShelleyBlock proto era) -> HeaderHash (ShelleyBlock proto era) -> ByteString

fromRawHash :: proxy (ShelleyBlock proto era) -> ByteString -> HeaderHash (ShelleyBlock proto era)

toShortRawHash :: proxy (ShelleyBlock proto era) -> HeaderHash (ShelleyBlock proto era) -> ShortByteString

fromShortRawHash :: proxy (ShelleyBlock proto era) -> ShortByteString -> HeaderHash (ShelleyBlock proto era)

hashSize :: proxy (ShelleyBlock proto era) -> Word32

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

getHeader :: ShelleyBlock proto era -> Header (ShelleyBlock proto era) #

blockMatchesHeader :: Header (ShelleyBlock proto era) -> ShelleyBlock proto era -> Bool #

headerIsEBB :: Header (ShelleyBlock proto era) -> Maybe EpochNo #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

headerPrevHash :: Header (ShelleyBlock proto era) -> ChainHash (ShelleyBlock proto era)

ShelleyCompatible proto era => BlockSupportsMetrics (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node

Methods

isSelfIssued :: BlockConfig (ShelleyBlock proto era) -> Header (ShelleyBlock proto era) -> WhetherSelfIssued

ShelleyCompatible proto era => BlockSupportsProtocol (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Protocol

Methods

validateView :: BlockConfig (ShelleyBlock proto era) -> Header (ShelleyBlock proto era) -> ValidateView (BlockProtocol (ShelleyBlock proto era))

selectView :: BlockConfig (ShelleyBlock proto era) -> Header (ShelleyBlock proto era) -> SelectView (BlockProtocol (ShelleyBlock proto era))

ConfigSupportsNode (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Common

Methods

getSystemStart :: BlockConfig (ShelleyBlock proto era) -> SystemStart

getNetworkMagic :: BlockConfig (ShelleyBlock proto era) -> NetworkMagic

HasHardForkHistory (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type HardForkIndices (ShelleyBlock proto era) :: [Type]

Methods

hardForkSummary :: LedgerConfig (ShelleyBlock proto era) -> LedgerState (ShelleyBlock proto era) -> Summary (HardForkIndices (ShelleyBlock proto era))

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era)) => NoHardForks (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Methods

getEraParams :: TopLevelConfig (ShelleyBlock proto era) -> EraParams

toPartialLedgerConfig :: proxy (ShelleyBlock proto era) -> LedgerConfig (ShelleyBlock proto era) -> PartialLedgerConfig (ShelleyBlock proto era)

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era)) => SingleEraBlock (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Methods

singleEraTransition :: PartialLedgerConfig (ShelleyBlock proto era) -> EraParams -> Bound -> LedgerState (ShelleyBlock proto era) -> Maybe EpochNo

singleEraInfo :: proxy (ShelleyBlock proto era) -> SingleEraInfo (ShelleyBlock proto era)

ShelleyCompatible proto era => CondenseConstraints (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Cardano.Condense

ShelleyCompatible proto era => HasPartialLedgerConfig (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type PartialLedgerConfig (ShelleyBlock proto era)

Methods

completeLedgerConfig :: proxy (ShelleyBlock proto era) -> EpochInfo (Except PastHorizonException) -> PartialLedgerConfig (ShelleyBlock proto era) -> LedgerConfig (ShelleyBlock proto era)

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era)) => SerialiseConstraintsHFC (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

ShelleyCompatible proto era => BasicEnvelopeValidation (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

expectedFirstBlockNo :: proxy (ShelleyBlock proto era) -> BlockNo

expectedNextBlockNo :: proxy (ShelleyBlock proto era) -> TipInfo (ShelleyBlock proto era) -> TipInfo (ShelleyBlock proto era) -> BlockNo -> BlockNo

minimumPossibleSlotNo :: Proxy (ShelleyBlock proto era) -> SlotNo

minimumNextSlotNo :: proxy (ShelleyBlock proto era) -> TipInfo (ShelleyBlock proto era) -> TipInfo (ShelleyBlock proto era) -> SlotNo -> SlotNo

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Associated Types

type TipInfo (ShelleyBlock proto era)

Methods

getTipInfo :: Header (ShelleyBlock proto era) -> TipInfo (ShelleyBlock proto era)

tipInfoHash :: proxy (ShelleyBlock proto era) -> TipInfo (ShelleyBlock proto era) -> HeaderHash (ShelleyBlock proto era)

ShelleyCompatible proto era => ValidateEnvelope (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type OtherHeaderEnvelopeError (ShelleyBlock proto era)

Methods

additionalEnvelopeChecks :: TopLevelConfig (ShelleyBlock proto era) -> LedgerView (BlockProtocol (ShelleyBlock proto era)) -> Header (ShelleyBlock proto era) -> Except (OtherHeaderEnvelopeError (ShelleyBlock proto era)) ()

ShelleyCompatible proto era => UpdateLedger (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

ShelleyCompatible proto era => CommonProtocolParams (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

ShelleyBasedEra era => InspectLedger (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Inspect

Associated Types

type LedgerWarning (ShelleyBlock proto era)

type LedgerUpdate (ShelleyBlock proto era)

Methods

inspectLedger :: TopLevelConfig (ShelleyBlock proto era) -> LedgerState (ShelleyBlock proto era) -> LedgerState (ShelleyBlock proto era) -> [LedgerEvent (ShelleyBlock proto era)]

(ShelleyCompatible proto era, ProtoCrypto proto ~ crypto) => QueryLedger (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

answerBlockQuery :: ExtLedgerCfg (ShelleyBlock proto era) -> BlockQuery (ShelleyBlock proto era) result -> ExtLedgerState (ShelleyBlock proto era) -> result

ShelleyBasedEra era => HasTxs (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

extractTxs :: ShelleyBlock proto era -> [GenTx (ShelleyBlock proto era)]

ShelleyCompatible proto era => LedgerSupportsMempool (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

txInvariant :: GenTx (ShelleyBlock proto era) -> Bool

applyTx :: LedgerConfig (ShelleyBlock proto era) -> WhetherToIntervene -> SlotNo -> GenTx (ShelleyBlock proto era) -> TickedLedgerState (ShelleyBlock proto era) -> Except (ApplyTxErr (ShelleyBlock proto era)) (TickedLedgerState (ShelleyBlock proto era), Validated (GenTx (ShelleyBlock proto era)))

reapplyTx :: LedgerConfig (ShelleyBlock proto era) -> SlotNo -> Validated (GenTx (ShelleyBlock proto era)) -> TickedLedgerState (ShelleyBlock proto era) -> Except (ApplyTxErr (ShelleyBlock proto era)) (TickedLedgerState (ShelleyBlock proto era))

txsMaxBytes :: TickedLedgerState (ShelleyBlock proto era) -> Word32

txInBlockSize :: GenTx (ShelleyBlock proto era) -> Word32

txForgetValidated :: Validated (GenTx (ShelleyBlock proto era)) -> GenTx (ShelleyBlock proto era)

c ~ EraCrypto era => LedgerSupportsPeerSelection (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.PeerSelection

Methods

getPeers :: LedgerState (ShelleyBlock proto era) -> [(PoolStake, NonEmpty StakePoolRelay)]

(ShelleyCompatible (Praos crypto) era, ShelleyCompatible (TPraos crypto) era, crypto ~ EraCrypto era, TranslateProto (TPraos crypto) (Praos crypto)) => LedgerSupportsProtocol (ShelleyBlock (Praos crypto) era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.SupportsProtocol

Methods

protocolLedgerView :: LedgerConfig (ShelleyBlock (Praos crypto) era) -> Ticked (LedgerState (ShelleyBlock (Praos crypto) era)) -> LedgerView (BlockProtocol (ShelleyBlock (Praos crypto) era))

ledgerViewForecastAt :: LedgerConfig (ShelleyBlock (Praos crypto) era) -> LedgerState (ShelleyBlock (Praos crypto) era) -> Forecast (LedgerView (BlockProtocol (ShelleyBlock (Praos crypto) era)))

(ShelleyCompatible (TPraos crypto) era, crypto ~ EraCrypto era) => LedgerSupportsProtocol (ShelleyBlock (TPraos crypto) era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.SupportsProtocol

Methods

protocolLedgerView :: LedgerConfig (ShelleyBlock (TPraos crypto) era) -> Ticked (LedgerState (ShelleyBlock (TPraos crypto) era)) -> LedgerView (BlockProtocol (ShelleyBlock (TPraos crypto) era))

ledgerViewForecastAt :: LedgerConfig (ShelleyBlock (TPraos crypto) era) -> LedgerState (ShelleyBlock (TPraos crypto) era) -> Forecast (LedgerView (BlockProtocol (ShelleyBlock (TPraos crypto) era)))

ShelleyCompatible p (AllegraEra c) => TxLimits (ShelleyBlock p (AllegraEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type TxMeasure (ShelleyBlock p (AllegraEra c))

ShelleyCompatible p (AlonzoEra c) => TxLimits (ShelleyBlock p (AlonzoEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type TxMeasure (ShelleyBlock p (AlonzoEra c))

ShelleyCompatible p (BabbageEra c) => TxLimits (ShelleyBlock p (BabbageEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type TxMeasure (ShelleyBlock p (BabbageEra c))

ShelleyCompatible p (ConwayEra c) => TxLimits (ShelleyBlock p (ConwayEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type TxMeasure (ShelleyBlock p (ConwayEra c))

ShelleyCompatible p (MaryEra c) => TxLimits (ShelleyBlock p (MaryEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type TxMeasure (ShelleyBlock p (MaryEra c))

ShelleyCompatible p (ShelleyEra c) => TxLimits (ShelleyBlock p (ShelleyEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type TxMeasure (ShelleyBlock p (ShelleyEra c))

ShelleyCompatible proto era => NodeInitStorage (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Common

Methods

nodeImmutableDbChunkInfo :: StorageConfig (ShelleyBlock proto era) -> ChunkInfo

nodeCheckIntegrity :: StorageConfig (ShelleyBlock proto era) -> ShelleyBlock proto era -> Bool

nodeInitChainDB :: IOLike m => StorageConfig (ShelleyBlock proto era) -> InitChainDB m (ShelleyBlock proto era) -> m ()

HasNetworkProtocolVersion (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion

Associated Types

type BlockNodeToNodeVersion (ShelleyBlock proto era)

type BlockNodeToClientVersion (ShelleyBlock proto era)

SupportedNetworkProtocolVersion (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion

Methods

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

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

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

(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)

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era)) => RunNode (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node

ShelleyCompatible proto era => SerialiseNodeToClientConstraints (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyCompatible proto era => SerialiseNodeToNodeConstraints (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

estimateBlockSize :: Header (ShelleyBlock proto era) -> SizeInBytes

ShelleyCompatible proto era => SerialiseDiskConstraints (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyCompatible proto era => HasBinaryBlockInfo (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

getBinaryBlockInfo :: ShelleyBlock proto era -> BinaryBlockInfo

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

condense :: ShelleyBlock proto era -> String

SameDepIndex (NestedCtxt_ (ShelleyBlock proto era) f) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

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

TrivialDependency (NestedCtxt_ (ShelleyBlock proto era) f) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Associated Types

type TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f)

Methods

hasSingleIndex :: NestedCtxt_ (ShelleyBlock proto era) f a -> NestedCtxt_ (ShelleyBlock proto era) f b -> a :~: b

indexIsTrivial :: NestedCtxt_ (ShelleyBlock proto era) f (TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f))

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

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

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

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

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

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

ShelleyBasedEra era => SerialiseNodeToClient (ShelleyBlock proto era) (ApplyTxError era)
ApplyTxErr '(ShelleyBlock era)'
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

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

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

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) (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 => 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))

SerialiseNodeToNode (ShelleyBlock proto era) (SerialisedHeader (ShelleyBlock proto era))

We use CBOR-in-CBOR

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

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

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

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

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

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDisk :: CodecConfig (ShelleyBlock proto era) -> forall s. Decoder s (AnnTip (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, EraCrypto era ~ c, PraosCrypto c) => DecodeDisk (ShelleyBlock proto era) (PraosState c)
ChainDepState (BlockProtocol (ShelleyBlock era))
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

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

(ShelleyCompatible proto era, EraCrypto era ~ c, PraosCrypto c) => DecodeDisk (ShelleyBlock proto era) (TPraosState c)
ChainDepState (BlockProtocol (ShelleyBlock era))
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

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

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 => EncodeDisk (ShelleyBlock proto era) (AnnTip (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

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

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

(ShelleyCompatible proto era, EraCrypto era ~ c, PraosCrypto c) => EncodeDisk (ShelleyBlock proto era) (PraosState c) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDisk :: CodecConfig (ShelleyBlock proto era) -> PraosState c -> Encoding

(ShelleyCompatible proto era, EraCrypto era ~ c, PraosCrypto c) => EncodeDisk (ShelleyBlock proto era) (TPraosState c)
ChainDepState (BlockProtocol (ShelleyBlock era))
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDisk :: CodecConfig (ShelleyBlock proto era) -> TPraosState c -> Encoding

(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))

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

CBOR-in-CBOR for the annotation. This also makes it compatible with the wrapped (Serialised) variant.

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

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

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

SerialiseNodeToClient (ShelleyBlock proto era) (Serialised (ShelleyBlock proto era))

Serialised uses CBOR-in-CBOR by default.

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

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

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

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

CBOR-in-CBOR for the annotation. This also makes it 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) -> ShelleyBlock proto era -> Encoding

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

SerialiseNodeToNode (ShelleyBlock proto era) (Serialised (ShelleyBlock proto era))

Serialised uses CBOR-in-CBOR by default.

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

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

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

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

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

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

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

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

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

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

Show (NestedCtxt_ (ShelleyBlock proto era) f a) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

showsPrec :: Int -> NestedCtxt_ (ShelleyBlock proto era) f a -> ShowS Source #

show :: NestedCtxt_ (ShelleyBlock proto era) f a -> String Source #

showList :: [NestedCtxt_ (ShelleyBlock proto era) f a] -> ShowS Source #

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era)) => SerialiseHFC '[ShelleyBlock proto era]

Use the default implementations. This means the serialisation of blocks includes an era wrapper. Each block should do this from the start to be prepared for future hard forks without having to do any bit twiddling.

Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Methods

encodeDiskHfcBlock :: CodecConfig (HardForkBlock '[ShelleyBlock proto era]) -> HardForkBlock '[ShelleyBlock proto era] -> Encoding

decodeDiskHfcBlock :: CodecConfig (HardForkBlock '[ShelleyBlock proto era]) -> forall s. Decoder s (ByteString -> HardForkBlock '[ShelleyBlock proto era])

reconstructHfcPrefixLen :: proxy (Header (HardForkBlock '[ShelleyBlock proto era])) -> PrefixLen

reconstructHfcNestedCtxt :: proxy (Header (HardForkBlock '[ShelleyBlock proto era])) -> ShortByteString -> SizeInBytes -> SomeSecond (NestedCtxt Header) (HardForkBlock '[ShelleyBlock proto era])

getHfcBinaryBlockInfo :: HardForkBlock '[ShelleyBlock proto era] -> BinaryBlockInfo

estimateHfcBlockSize :: Header (HardForkBlock '[ShelleyBlock proto era]) -> SizeInBytes

type HeaderHash (ShelleyBlock proto era :: Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

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

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type TranslationError era (LedgerState :.: ShelleyBlock proto) = Void
type TranslationError era (GenTx :.: ShelleyBlock proto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type TranslationError era (GenTx :.: ShelleyBlock proto) = TranslationError era WrapTx
type TranslationError era (WrapValidatedGenTx :.: ShelleyBlock proto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type TranslationError era (WrapValidatedGenTx :.: ShelleyBlock proto) = TranslationError era WrapTx
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)))))))
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))
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 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)))
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 (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 (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 (Ticked (LedgerState (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type LedgerErr (LedgerState (ShelleyBlock proto era)) = ShelleyLedgerError era
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 ProtocolParams (CardanoBlock c) Source #

Parameters needed to run Cardano.

Instance details

Defined in Ouroboros.Consensus.Cardano.Node

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 Ticked (LedgerState (ShelleyBlock proto era)) Source #

Ticking only affects the state itself

Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

data BlockConfig (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

data BlockConfig (ShelleyBlock proto era) = ShelleyConfig {}
type BlockProtocol (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Protocol

type BlockProtocol (ShelleyBlock proto era) = proto
data CodecConfig (ShelleyBlock proto era) Source #

No particular codec configuration is needed for Shelley

Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

data Header (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

data StorageConfig (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

type CannotForge (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Common

type CannotForge (ShelleyBlock proto era) = CannotForgeError proto
type ForgeStateInfo (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Common

type ForgeStateInfo (ShelleyBlock proto era) = KESInfo
type ForgeStateUpdateError (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Common

type ForgeStateUpdateError (ShelleyBlock proto era) = KESEvolutionError
data NestedCtxt_ (ShelleyBlock proto era) f a Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

data NestedCtxt_ (ShelleyBlock proto era) f a where
type HardForkIndices (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type HardForkIndices (ShelleyBlock proto era) = '[ShelleyBlock proto era]
type PartialLedgerConfig (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type PartialLedgerConfig (ShelleyBlock proto era) = ShelleyPartialLedgerConfig era
type OtherHeaderEnvelopeError (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type OtherHeaderEnvelopeError (ShelleyBlock proto era) = EnvelopeCheckError proto
type TipInfo (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

type TipInfo (ShelleyBlock proto era) = HeaderHash (ShelleyBlock proto era)
data LedgerState (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type LedgerUpdate (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Inspect

type LedgerUpdate (ShelleyBlock proto era) = ShelleyLedgerUpdate era
type LedgerWarning (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Inspect

type LedgerWarning (ShelleyBlock proto era) = Void
data BlockQuery (ShelleyBlock proto era) a Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

data BlockQuery (ShelleyBlock proto era) a where
type ApplyTxErr (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type ApplyTxErr (ShelleyBlock proto era) = ApplyTxError 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)
type TxMeasure (ShelleyBlock p (AllegraEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type TxMeasure (ShelleyBlock p (AllegraEra c)) = ByteSize
type TxMeasure (ShelleyBlock p (AlonzoEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type TxMeasure (ShelleyBlock p (AlonzoEra c)) = AlonzoMeasure
type TxMeasure (ShelleyBlock p (BabbageEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type TxMeasure (ShelleyBlock p (BabbageEra c)) = AlonzoMeasure
type TxMeasure (ShelleyBlock p (ConwayEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type TxMeasure (ShelleyBlock p (ConwayEra c)) = AlonzoMeasure
type TxMeasure (ShelleyBlock p (MaryEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type TxMeasure (ShelleyBlock p (MaryEra c)) = ByteSize
type TxMeasure (ShelleyBlock p (ShelleyEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type TxMeasure (ShelleyBlock p (ShelleyEra c)) = ByteSize
type BlockNodeToClientVersion (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion

type BlockNodeToClientVersion (ShelleyBlock proto era) = ShelleyNodeToClientVersion
type BlockNodeToNodeVersion (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion

type BlockNodeToNodeVersion (ShelleyBlock proto era) = ShelleyNodeToNodeVersion
data ProtocolParams (ShelleyBlock (Praos c) (BabbageEra c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Praos

data ProtocolParams (ShelleyBlock (Praos c) (ConwayEra c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Praos

data ProtocolParams (ShelleyBlock (TPraos c) (AllegraEra c)) Source #

Parameters needed to run Allegra

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.TPraos

data ProtocolParams (ShelleyBlock (TPraos c) (AlonzoEra c)) Source #

Parameters needed to run Alonzo

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.TPraos

data ProtocolParams (ShelleyBlock (TPraos c) (MaryEra c)) Source #

Parameters needed to run Mary

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.TPraos

data ProtocolParams (ShelleyBlock (TPraos c) (ShelleyEra c)) Source #

Parameters needed to run Shelley

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.TPraos

type TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

type TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f) = f (ShelleyBlock proto era)

class (ShelleyBasedEra era, ShelleyProtocol proto, Eq (ShelleyProtocolHeader proto), Show (ShelleyProtocolHeader proto), NoThunks (ShelleyProtocolHeader proto), EncCBOR (ShelleyProtocolHeader proto), DecCBOR (Annotator (ShelleyProtocolHeader proto)), Show (CannotForgeError proto), SelectView proto ~ PraosChainSelectView (EraCrypto era), SignedHeader (ShelleyProtocolHeader proto), DecodeDisk (ShelleyBlock proto era) (ChainDepState proto), EncodeDisk (ShelleyBlock proto era) (ChainDepState proto), EraCrypto era ~ ProtoCrypto proto, HasPartialConsensusConfig proto, DecCBOR (PState era), FromCBOR (LegacyPParams era), ToCBOR (LegacyPParams era)) => ShelleyCompatible proto era Source #

Instances

Instances details
PraosCrypto c => ShelleyCompatible (Praos c) (BabbageEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.HFEras

PraosCrypto c => ShelleyCompatible (Praos c) (ConwayEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.HFEras

(PraosCrypto c, Signable (DSIGN c) (Hash (HASH c) EraIndependentTxBody)) => ShelleyCompatible (TPraos c) (AllegraEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.HFEras

(PraosCrypto c, Signable (DSIGN c) (Hash (HASH c) EraIndependentTxBody)) => ShelleyCompatible (TPraos c) (AlonzoEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.HFEras

(PraosCrypto c, PraosCrypto c) => ShelleyCompatible (TPraos c) (BabbageEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.HFEras

(PraosCrypto c, PraosCrypto c) => ShelleyCompatible (TPraos c) (ConwayEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.HFEras

(PraosCrypto c, Signable (DSIGN c) (Hash (HASH c) EraIndependentTxBody)) => ShelleyCompatible (TPraos c) (MaryEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.HFEras

(PraosCrypto c, Signable (DSIGN c) (Hash (HASH c) EraIndependentTxBody)) => ShelleyCompatible (TPraos c) (ShelleyEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.HFEras

mkShelleyBlock :: ShelleyCompatible proto era => Block (ShelleyProtocolHeader proto) era -> ShelleyBlock proto era Source #

fromShelleyPrevHash :: EraCrypto era ~ ProtoCrypto proto => PrevHash (EraCrypto era) -> ChainHash (ShelleyBlock proto era) Source #

From cardano-ledger-specs to ouroboros-consensus

toShelleyPrevHash :: EraCrypto era ~ ProtoCrypto proto => ChainHash (Header (ShelleyBlock proto era)) -> PrevHash (EraCrypto era) Source #

From ouroboros-consensus to cardano-ledger-specs

encodeShelleyBlock :: forall proto era. ShelleyCompatible proto era => ShelleyBlock proto era -> Encoding Source #

decodeShelleyBlock :: forall proto era. ShelleyCompatible proto era => forall s. Decoder s (ByteString -> ShelleyBlock proto era) Source #

shelleyBinaryBlockInfo :: forall proto era. ShelleyCompatible proto era => ShelleyBlock proto era -> BinaryBlockInfo Source #

encodeShelleyHeader :: forall proto era. ShelleyCompatible proto era => Header (ShelleyBlock proto era) -> Encoding Source #

decodeShelleyHeader :: forall proto era. ShelleyCompatible proto era => forall s. Decoder s (ByteString -> Header (ShelleyBlock proto era)) Source #

data ShelleyNodeToClientVersion Source #

Constructors

ShelleyNodeToClientVersion1 
ShelleyNodeToClientVersion2

New queries introduced

ShelleyNodeToClientVersion3

New query introduced

ShelleyNodeToClientVersion4

New queries introduced

ShelleyNodeToClientVersion5

New queries introduced: GetRewardInfoPools

ShelleyNodeToClientVersion6

New queries introduced: GetPoolDistr, GetPoolState, GetStakeSnapshots

ShelleyNodeToClientVersion7

New queries introduced: GetStakeDelegDeposits

ShelleyNodeToClientVersion8

New queries introduced: GetConstitutionHash, GetFilteredVoteDelegatees

Instances

Instances details
Bounded ShelleyNodeToClientVersion Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion

Enum ShelleyNodeToClientVersion Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion

Show ShelleyNodeToClientVersion Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion

Eq ShelleyNodeToClientVersion Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion

Ord ShelleyNodeToClientVersion Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion

data ShelleyNodeToNodeVersion Source #

Instances

Instances details
Bounded ShelleyNodeToNodeVersion Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion

Enum ShelleyNodeToNodeVersion Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion

Show ShelleyNodeToNodeVersion Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion

Eq ShelleyNodeToNodeVersion Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion

Ord ShelleyNodeToNodeVersion Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion

verifyBlockIntegrity :: ShelleyCompatible proto era => Word64 -> ShelleyBlock proto era -> Bool Source #

Verifies whether the block is not corrupted by checking its signature and witnesses.

data CompactGenesis c Source #

Compact variant of ShelleyGenesis with some fields erased that are only used on start-up and that should not be kept in memory forever.

Concretely:

  • The sgInitialFunds field is erased. It is only used to set up the initial UTxO in tests and testnets.
  • The sgStaking field is erased. It is only used to register initial stake pools in tests and benchmarks.

Instances

Instances details
Generic (CompactGenesis c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Associated Types

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

Crypto c => Show (CompactGenesis c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Crypto c => FromCBOR (CompactGenesis c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Methods

fromCBOR :: Decoder s (CompactGenesis c)

label :: Proxy (CompactGenesis c) -> Text

Crypto c => ToCBOR (CompactGenesis c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Methods

toCBOR :: CompactGenesis c -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (CompactGenesis c) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [CompactGenesis c] -> Size

Crypto c => Eq (CompactGenesis c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Crypto c => NoThunks (CompactGenesis c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Methods

noThunks :: Context -> CompactGenesis c -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> CompactGenesis c -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (CompactGenesis c) -> String

type Rep (CompactGenesis c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

type Rep (CompactGenesis c) = D1 ('MetaData "CompactGenesis" "Ouroboros.Consensus.Shelley.Ledger.Config" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'True) (C1 ('MetaCons "CompactGenesis" 'PrefixI 'True) (S1 ('MetaSel ('Just "getCompactGenesis") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ShelleyGenesis c))))

mkShelleyBlockConfig :: ShelleyBasedEra era => ProtVer -> ShelleyGenesis (EraCrypto era) -> [VKey 'BlockIssuer (EraCrypto era)] -> BlockConfig (ShelleyBlock proto era) Source #

data ShelleyLedgerEvent era Source #

All events emitted by the Shelley ledger API

Constructors

ShelleyLedgerEventBBODY (Event (EraRule "BBODY" era))

An event emitted when (re)applying a block

ShelleyLedgerEventTICK (Event (EraRule "TICK" era))

An event emitted during the chain tick

newtype ShelleyTransition Source #

Information required to determine the hard fork point from Shelley to the next ledger

Constructors

ShelleyTransitionInfo 

Fields

  • shelleyAfterVoting :: Word32

    The number of blocks in this epoch past the voting deadline

    We record this to make sure that we can tell the HFC about hard forks if and only if we are certain:

    1. Blocks that came in within an epoch after the 4k/f voting deadline are not relevant (10kf - 2 * 3kf).
    2. Since there are slots between blocks, we are probably only sure that there will be no more relevant block when we have seen the first block after the deadline.
    3. If we count how many blocks we have seen post deadline, and we have reached k of them, we know that that last pre-deadline block won't be rolled back anymore.
    4. At this point we can look at the ledger state and see which proposals we accepted in the voting period, if any, and notify the HFC is one of them indicates a transition.

Instances

Instances details
Generic ShelleyTransition Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep ShelleyTransition :: Type -> Type Source #

Show ShelleyTransition Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Eq ShelleyTransition Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

NoThunks ShelleyTransition Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

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

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

showTypeOf :: Proxy ShelleyTransition -> String

type Rep ShelleyTransition Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep ShelleyTransition = D1 ('MetaData "ShelleyTransition" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'True) (C1 ('MetaCons "ShelleyTransitionInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "shelleyAfterVoting") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))

data ShelleyTip proto era Source #

Constructors

ShelleyTip 

Fields

Instances

Instances details
(ShelleyBasedEra era, ShelleyBasedEra (PreviousEra era), Era (PreviousEra era), EraCrypto (PreviousEra era) ~ EraCrypto era) => TranslateEra era (ShelleyTip proto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type TranslationError era (ShelleyTip proto)

Methods

translateEra :: TranslationContext era -> ShelleyTip proto (PreviousEra era) -> Except (TranslationError era (ShelleyTip proto)) (ShelleyTip proto era)

Generic (ShelleyTip proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

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

Methods

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

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

Show (ShelleyTip proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

showsPrec :: Int -> ShelleyTip proto era -> ShowS Source #

show :: ShelleyTip proto era -> String Source #

showList :: [ShelleyTip proto era] -> ShowS Source #

Eq (ShelleyTip proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

(==) :: ShelleyTip proto era -> ShelleyTip proto era -> Bool Source #

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

NoThunks (ShelleyTip proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

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

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

showTypeOf :: Proxy (ShelleyTip proto era) -> String

type TranslationError era (ShelleyTip proto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type TranslationError era (ShelleyTip proto) = Void
type Rep (ShelleyTip proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (ShelleyTip proto era) = D1 ('MetaData "ShelleyTip" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ShelleyTip" 'PrefixI 'True) (S1 ('MetaSel ('Just "shelleyTipSlotNo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo) :*: (S1 ('MetaSel ('Just "shelleyTipBlockNo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockNo) :*: S1 ('MetaSel ('Just "shelleyTipHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HeaderHash (ShelleyBlock proto era))))))

data ShelleyLedgerConfig era Source #

Constructors

ShelleyLedgerConfig 

Fields

Instances

Instances details
Generic (ShelleyLedgerConfig era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

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

(NoThunks (TranslationContext era), Era era) => NoThunks (ShelleyLedgerConfig era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

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

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

showTypeOf :: Proxy (ShelleyLedgerConfig era) -> String

type Rep (ShelleyLedgerConfig era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (ShelleyLedgerConfig era) = D1 ('MetaData "ShelleyLedgerConfig" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ShelleyLedgerConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "shelleyLedgerCompactGenesis") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (CompactGenesis (EraCrypto era))) :*: (S1 ('MetaSel ('Just "shelleyLedgerGlobals") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Globals) :*: S1 ('MetaSel ('Just "shelleyLedgerTranslationContext") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TranslationContext era)))))

newtype ShelleyLedgerError era Source #

Constructors

BBodyError (BlockTransitionError era) 

Instances

Instances details
Generic (ShelleyLedgerError era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

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

ShelleyBasedEra era => Show (ShelleyLedgerError era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

ShelleyBasedEra era => Eq (ShelleyLedgerError era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

ShelleyBasedEra era => NoThunks (ShelleyLedgerError era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

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

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

showTypeOf :: Proxy (ShelleyLedgerError era) -> String

type Rep (ShelleyLedgerError era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (ShelleyLedgerError era) = D1 ('MetaData "ShelleyLedgerError" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'True) (C1 ('MetaCons "BBodyError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (BlockTransitionError era))))

shelleyEraParamsNeverHardForks :: ShelleyGenesis c -> EraParams Source #

Separate variant of shelleyEraParams to be used for a Shelley-only chain.

mkShelleyLedgerConfig :: ShelleyGenesis (EraCrypto era) -> TranslationContext era -> EpochInfo (Except PastHorizonException) -> MaxMajorProtVer -> ShelleyLedgerConfig era Source #

shelleyTipToPoint :: WithOrigin (ShelleyTip proto era) -> Point (ShelleyBlock proto era) Source #

castShelleyTip :: HeaderHash (ShelleyBlock proto era) ~ HeaderHash (ShelleyBlock proto' era') => ShelleyTip proto era -> ShelleyTip proto' era' Source #

getPParams :: EraGov era => NewEpochState era -> PParams era Source #

encodeShelleyAnnTip :: ShelleyCompatible proto era => AnnTip (ShelleyBlock proto era) -> Encoding Source #

decodeShelleyAnnTip :: ShelleyCompatible proto era => Decoder s (AnnTip (ShelleyBlock proto era)) Source #

encodeShelleyHeaderState :: ShelleyCompatible proto era => HeaderState (ShelleyBlock proto era) -> Encoding Source #

decodeShelleyLedgerState :: forall era proto s. ShelleyCompatible proto era => Decoder s (LedgerState (ShelleyBlock proto era)) Source #

data StakeSnapshots crypto Source #

Constructors

StakeSnapshots 

Fields

Instances

Instances details
Generic (StakeSnapshots crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Associated Types

type Rep (StakeSnapshots crypto) :: Type -> Type Source #

Methods

from :: StakeSnapshots crypto -> Rep (StakeSnapshots crypto) x Source #

to :: Rep (StakeSnapshots crypto) x -> StakeSnapshots crypto Source #

Show (StakeSnapshots crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Crypto crypto => FromCBOR (StakeSnapshots crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

fromCBOR :: Decoder s (StakeSnapshots crypto)

label :: Proxy (StakeSnapshots crypto) -> Text

Crypto crypto => ToCBOR (StakeSnapshots crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

toCBOR :: StakeSnapshots crypto -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (StakeSnapshots crypto) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [StakeSnapshots crypto] -> Size

NFData (StakeSnapshots crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

rnf :: StakeSnapshots crypto -> () Source #

Eq (StakeSnapshots crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

(==) :: StakeSnapshots crypto -> StakeSnapshots crypto -> Bool Source #

(/=) :: StakeSnapshots crypto -> StakeSnapshots crypto -> Bool Source #

type Rep (StakeSnapshots crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

type Rep (StakeSnapshots crypto) = D1 ('MetaData "StakeSnapshots" "Ouroboros.Consensus.Shelley.Ledger.Query" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "StakeSnapshots" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ssStakeSnapshots") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (KeyHash 'StakePool crypto) (StakeSnapshot crypto))) :*: S1 ('MetaSel ('Just "ssMarkTotal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin)) :*: (S1 ('MetaSel ('Just "ssSetTotal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin) :*: S1 ('MetaSel ('Just "ssGoTotal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin))))

data StakeSnapshot crypto Source #

The stake snapshot returns information about the mark, set, go ledger snapshots for a pool, plus the total active stake for each snapshot that can be used in a sigma calculation.

Each snapshot is taken at the end of a different era. The go snapshot is the current one and was taken two epochs earlier, set was taken one epoch ago, and mark was taken immediately before the start of the current epoch.

Constructors

StakeSnapshot 

Fields

Instances

Instances details
Generic (StakeSnapshot crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Associated Types

type Rep (StakeSnapshot crypto) :: Type -> Type Source #

Methods

from :: StakeSnapshot crypto -> Rep (StakeSnapshot crypto) x Source #

to :: Rep (StakeSnapshot crypto) x -> StakeSnapshot crypto Source #

Show (StakeSnapshot crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Crypto crypto => FromCBOR (StakeSnapshot crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

fromCBOR :: Decoder s (StakeSnapshot crypto)

label :: Proxy (StakeSnapshot crypto) -> Text

Crypto crypto => ToCBOR (StakeSnapshot crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

toCBOR :: StakeSnapshot crypto -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (StakeSnapshot crypto) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [StakeSnapshot crypto] -> Size

NFData (StakeSnapshot crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

rnf :: StakeSnapshot crypto -> () Source #

Eq (StakeSnapshot crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

(==) :: StakeSnapshot crypto -> StakeSnapshot crypto -> Bool Source #

(/=) :: StakeSnapshot crypto -> StakeSnapshot crypto -> Bool Source #

type Rep (StakeSnapshot crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

type Rep (StakeSnapshot crypto) = D1 ('MetaData "StakeSnapshot" "Ouroboros.Consensus.Shelley.Ledger.Query" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "StakeSnapshot" 'PrefixI 'True) (S1 ('MetaSel ('Just "ssMarkPool") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin) :*: (S1 ('MetaSel ('Just "ssSetPool") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin) :*: S1 ('MetaSel ('Just "ssGoPool") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin))))

newtype NonMyopicMemberRewards c Source #

Constructors

NonMyopicMemberRewards 

Fields

Instances

Instances details
Show (NonMyopicMemberRewards c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Crypto c => FromCBOR (NonMyopicMemberRewards c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

fromCBOR :: Decoder s (NonMyopicMemberRewards c)

label :: Proxy (NonMyopicMemberRewards c) -> Text

Crypto c => ToCBOR (NonMyopicMemberRewards c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

toCBOR :: NonMyopicMemberRewards c -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (NonMyopicMemberRewards c) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [NonMyopicMemberRewards c] -> Size

Eq (NonMyopicMemberRewards c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

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

Is the given query supported by the given ShelleyNodeToClientVersion?

encodeShelleyQuery :: forall era proto result. ShelleyBasedEra era => BlockQuery (ShelleyBlock proto era) result -> Encoding Source #

decodeShelleyQuery :: forall era proto. ShelleyBasedEra era => forall s. Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era)) Source #

encodeShelleyResult :: forall proto era result. ShelleyCompatible proto era => ShelleyNodeToClientVersion -> BlockQuery (ShelleyBlock proto era) result -> result -> Encoding Source #

decodeShelleyResult :: forall proto era result. ShelleyCompatible proto era => ShelleyNodeToClientVersion -> BlockQuery (ShelleyBlock proto era) result -> forall s. Decoder s result Source #

data WithTop a Source #

Add a unique top element to a lattice.

TODO This should be relocated to `cardano-base:Data.Measure'.

Constructors

NotTop a 
Top 

Instances

Instances details
Generic (WithTop a) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type Rep (WithTop a) :: Type -> Type Source #

Methods

from :: WithTop a -> Rep (WithTop a) x Source #

to :: Rep (WithTop a) x -> WithTop a Source #

Show a => Show (WithTop a) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Eq a => Eq (WithTop a) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

(==) :: WithTop a -> WithTop a -> Bool Source #

(/=) :: WithTop a -> WithTop a -> Bool Source #

Ord a => Ord (WithTop a) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Measure a => BoundedMeasure (WithTop a) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

maxBound :: WithTop a

Measure a => Measure (WithTop a) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

zero :: WithTop a

plus :: WithTop a -> WithTop a -> WithTop a

min :: WithTop a -> WithTop a -> WithTop a

max :: WithTop a -> WithTop a -> WithTop a

type Rep (WithTop a) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type Rep (WithTop a) = D1 ('MetaData "WithTop" "Ouroboros.Consensus.Shelley.Ledger.Mempool" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "NotTop" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Top" 'PrefixI 'False) (U1 :: Type -> Type))

data AlonzoMeasure Source #

Constructors

AlonzoMeasure 

Fields

Instances

Instances details
Generic AlonzoMeasure Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type Rep AlonzoMeasure :: Type -> Type Source #

Show AlonzoMeasure Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Eq AlonzoMeasure Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

BoundedMeasure AlonzoMeasure Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Measure AlonzoMeasure Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type Rep AlonzoMeasure Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type Rep AlonzoMeasure = D1 ('MetaData "AlonzoMeasure" "Ouroboros.Consensus.Shelley.Ledger.Mempool" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "AlonzoMeasure" 'PrefixI 'True) (S1 ('MetaSel ('Just "byteSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByteSize) :*: S1 ('MetaSel ('Just "exUnits") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ExUnits' (WithTop Natural)))))

fixedBlockBodyOverhead :: Num a => a Source #

txInBlockSize is used to estimate how many transactions we can grab from the Mempool to put into the block we are going to forge without exceeding the maximum block body size according to the ledger. If we exceed that limit, we will have forged a block that is invalid according to the ledger. We ourselves won't even adopt it, causing us to lose our slot, something we must try to avoid.

For this reason it is better to overestimate the size of a transaction than to underestimate. The only downside is that we maybe could have put one (or more?) transactions extra in that block.

As the sum of the serialised transaction sizes is not equal to the size of the serialised block body (TxSeq) consisting of those transactions (see cardano-node#1545 for an example), we account for some extra overhead per transaction as a safety margin.

Also see perTxOverhead.

mkShelleyTx :: forall era proto. ShelleyBasedEra era => Tx era -> GenTx (ShelleyBlock proto era) Source #

mkShelleyValidatedTx :: forall era proto. ShelleyBasedEra era => Validated (Tx era) -> Validated (GenTx (ShelleyBlock proto era)) Source #

fromExUnits :: ExUnits -> ExUnits' (WithTop Natural) Source #

forgeShelleyBlock Source #

Arguments

:: forall m era proto. (ShelleyCompatible proto era, TxLimits (ShelleyBlock proto era), Monad m) 
=> HotKey (EraCrypto era) m 
-> CanBeLeader proto 
-> TopLevelConfig (ShelleyBlock proto era) 
-> TxOverrides (ShelleyBlock proto era)

How to override max tx capacity defined by ledger

-> BlockNo

Current block number

-> SlotNo

Current slot number

-> TickedLedgerState (ShelleyBlock proto era)

Current ledger

-> [Validated (GenTx (ShelleyBlock proto era))]

Txs to add in the block

-> IsLeader proto 
-> m (ShelleyBlock proto era)