ouroboros-consensus-0.18.0.0: Consensus layer for the Ouroboros blockchain protocol
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ouroboros.Consensus.Block.Abstract

Synopsis

Protocol

type family BlockProtocol blk ∷ Type Source #

Map block to consensus protocol

Instances

Instances details
type BlockProtocol (Header blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

type BlockProtocol (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type BlockProtocol (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Configuration

data family BlockConfig blk ∷ Type Source #

Static configuration required to work with this type of blocks

Instances

Instances details
Isomorphic BlockConfig Source # 
Instance details

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

CanHardFork xs ⇒ NoThunks (BlockConfig (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

NoThunks (BlockConfig (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

newtype BlockConfig (DisableDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype BlockConfig (SelectViewDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype BlockConfig (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data BlockConfig (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data family CodecConfig blk ∷ Type Source #

Static configuration required for serialisation and deserialisation of types pertaining to this type of block.

Data family instead of type family to get better type inference.

Instances

Instances details
Isomorphic CodecConfig Source # 
Instance details

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

Generic (CodecConfig (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Associated Types

type Rep (CodecConfig (DualBlock m a)) ∷ TypeType #

Methods

fromCodecConfig (DualBlock m a) → Rep (CodecConfig (DualBlock m a)) x #

toRep (CodecConfig (DualBlock m a)) x → CodecConfig (DualBlock m a) #

CanHardFork xs ⇒ NoThunks (CodecConfig (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

(NoThunks (CodecConfig m), NoThunks (CodecConfig a)) ⇒ NoThunks (CodecConfig (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type Rep (CodecConfig (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type Rep (CodecConfig (DualBlock m a)) = D1 ('MetaData "CodecConfig" "Ouroboros.Consensus.Ledger.Dual" "ouroboros-consensus-0.18.0.0-inplace" 'False) (C1 ('MetaCons "DualCodecConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "dualCodecConfigMain") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (CodecConfig m)) :*: S1 ('MetaSel ('Just "dualCodecConfigAux") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (CodecConfig a))))
newtype CodecConfig (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data CodecConfig (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data family StorageConfig blk ∷ Type Source #

Config needed for the NodeInitStorage class. Defined here to avoid circular dependencies.

Instances

Instances details
Isomorphic StorageConfig Source # 
Instance details

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

Generic (StorageConfig (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Associated Types

type Rep (StorageConfig (DualBlock m a)) ∷ TypeType #

CanHardFork xs ⇒ NoThunks (StorageConfig (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

(NoThunks (StorageConfig m), NoThunks (StorageConfig a)) ⇒ NoThunks (StorageConfig (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type Rep (StorageConfig (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type Rep (StorageConfig (DualBlock m a)) = D1 ('MetaData "StorageConfig" "Ouroboros.Consensus.Ledger.Dual" "ouroboros-consensus-0.18.0.0-inplace" 'False) (C1 ('MetaCons "DualStorageConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "dualStorageConfigMain") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StorageConfig m)) :*: S1 ('MetaSel ('Just "dualStorageConfigAux") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StorageConfig a))))
newtype StorageConfig (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data StorageConfig (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Previous hash

class (HasHeader blk, GetHeader blk) ⇒ GetPrevHash blk where Source #

Methods

headerPrevHashHeader blk → ChainHash blk Source #

Get the hash of the predecessor of this block

Instances

Instances details
CanHardFork xs ⇒ GetPrevHash (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

Bridge m a ⇒ GetPrevHash (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

blockPrevHashGetPrevHash blk ⇒ blk → ChainHash blk Source #

Working with headers

class HasHeader (Header blk) ⇒ GetHeader blk where Source #

Methods

getHeader ∷ blk → Header blk Source #

blockMatchesHeaderHeader blk → blk → Bool Source #

Check whether the header is the header of the block.

For example, by checking whether the hash of the body stored in the header matches that of the block.

headerIsEBBHeader blk → Maybe EpochNo Source #

When the given header is the header of an Epoch Boundary Block, returns its epoch number.

data family Header blk ∷ Type Source #

Instances

Instances details
Inject Header Source # 
Instance details

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

Methods

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

Isomorphic Header Source # 
Instance details

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

Methods

projectNoHardForks blk ⇒ Header (HardForkBlock '[blk]) → Header blk Source #

injectNoHardForks blk ⇒ Header blk → Header (HardForkBlock '[blk]) Source #

CanHardFork xs ⇒ HasNestedContent Header (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

SerialiseHFC xs ⇒ ReconstructNestedCtxt Header (HardForkBlock xs) Source # 
Instance details

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

HasHeader blk ⇒ StandardHash (Header blk ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

Typeable xs ⇒ ShowProxy (Header (HardForkBlock xs) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

HasNestedContent Header m ⇒ HasNestedContent Header (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

ReconstructNestedCtxt Header m ⇒ ReconstructNestedCtxt Header (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

(Typeable m, Typeable a) ⇒ ShowProxy (DualHeader m a ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showProxyProxy (DualHeader m a) → String Source #

CanHardFork xs ⇒ Show (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

All (Compose Eq Header) xs ⇒ Eq (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

Methods

(==)Header (HardForkBlock xs) → Header (HardForkBlock xs) → Bool #

(/=)Header (HardForkBlock xs) → Header (HardForkBlock xs) → Bool #

CanHardFork xs ⇒ NoThunks (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

NoThunks (Header (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

All CondenseConstraints xs ⇒ Condense (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Condense

CanHardFork xs ⇒ HasHeader (Header (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

SerialiseHFC xs ⇒ SerialiseNodeToNode (HardForkBlock xs) (Header (HardForkBlock xs)) Source # 
Instance details

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

SerialiseHFC xs ⇒ DecodeDiskDep (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

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

SerialiseHFC xs ⇒ DecodeDiskDepIx (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

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

SerialiseHFC xs ⇒ EncodeDiskDep (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

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

SerialiseHFC xs ⇒ EncodeDiskDepIx (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

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

EncodeDiskDep (NestedCtxt Header) m ⇒ EncodeDiskDep (NestedCtxt Header) (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

encodeDiskDepCodecConfig (DualBlock m a) → NestedCtxt Header (DualBlock m a) a0 → a0 → Encoding Source #

EncodeDiskDepIx (NestedCtxt Header) m ⇒ EncodeDiskDepIx (NestedCtxt Header) (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Show (Header m) ⇒ Show (DualHeader m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntDualHeader m a → ShowS #

showDualHeader m a → String #

showList ∷ [DualHeader m a] → ShowS #

CanHardFork xs ⇒ SameDepIndex (NestedCtxt_ (HardForkBlock xs) Header) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

Bridge m a ⇒ HasHeader (DualHeader m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

All SingleEraBlock xs ⇒ Show (NestedCtxt_ (HardForkBlock xs) Header a) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

type HeaderHash (Header blk ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

type HeaderHash (Header blk ∷ Type) = HeaderHash blk
type BlockProtocol (Header blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

newtype Header (DisableDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype Header (SelectViewDiffusionPipelining blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype Header (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

newtype Header (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

blockToIsEBBGetHeader blk ⇒ blk → IsEBB Source #

getBlockHeaderFieldsGetHeader blk ⇒ blk → HeaderFields blk Source #

Get the HeaderFields of a block, without requiring 'HasHeader blk'

This is primarily useful as a a simple definition of HasHeader for block types:

instance HasHeader SomeBlock where
  getHeaderFields = getBlockHeaderFields

provided that there is a HasHeader instance for the header.

Unfortunately we cannot give a HasHeader instance once and for all; if we mapped from a header to a block instead we could do

instance HasHeader hdr => HasHeader (Block hdr) where
 ..

but we can't do that when we do things this way around.

headerHashHasHeader (Header blk) ⇒ Header blk → HeaderHash blk Source #

headerPointHasHeader (Header blk) ⇒ Header blk → Point blk Source #

Raw hash

class ConvertRawHash blk where Source #

Convert a hash from/to raw bytes

Variants of toRawHash and fromRawHash for ShortByteString are included. Override the default implementations to avoid an extra step in case the HeaderHash is a ShortByteString under the hood.

Minimal complete definition

hashSize, (toRawHash | toShortRawHash), (fromRawHash | fromShortRawHash)

Methods

toRawHash ∷ proxy blk → HeaderHash blk → ByteString Source #

Get the raw bytes from a hash

fromRawHash ∷ proxy blk → ByteStringHeaderHash blk Source #

Construct the hash from a raw hash

PRECONDITION: the bytestring's size must match hashSize

toShortRawHash ∷ proxy blk → HeaderHash blk → ShortByteString Source #

Variant of toRawHash for ShortByteString

fromShortRawHash ∷ proxy blk → ShortByteStringHeaderHash blk Source #

hashSize ∷ proxy blk → Word32 Source #

The size of the hash in number of bytes

decodeRawHashConvertRawHash blk ⇒ proxy blk → ∀ s. Decoder s (HeaderHash blk) Source #

encodeRawHashConvertRawHash blk ⇒ proxy blk → HeaderHash blk → Encoding Source #

Utilities for working with WithOrigin

succWithOrigin ∷ (Bounded t, Enum t) ⇒ WithOrigin t → t Source #

Return the successor of a WithOrigin value. Useful in combination with SlotNo and BlockNo.

Ouroboros Genesis window

newtype GenesisWindow Source #

Constructors

GenesisWindow 

Instances

Instances details
Num GenesisWindow Source # 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

Show GenesisWindow Source # 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

Eq GenesisWindow Source # 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

Ord GenesisWindow Source # 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

NoThunks GenesisWindow Source # 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

Re-export basic definitions from ouroboros-network

data ChainHash (b ∷ k) Source #

Constructors

GenesisHash 
BlockHash !(HeaderHash b) 

Instances

Instances details
Isomorphic (ChainHashTypeType) Source # 
Instance details

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

Methods

projectNoHardForks blk ⇒ ChainHash (HardForkBlock '[blk]) → ChainHash blk Source #

injectNoHardForks blk ⇒ ChainHash blk → ChainHash (HardForkBlock '[blk]) Source #

Generic (ChainHash b) 
Instance details

Defined in Ouroboros.Network.Block

Associated Types

type Rep (ChainHash b) ∷ TypeType #

Methods

fromChainHash b → Rep (ChainHash b) x #

toRep (ChainHash b) x → ChainHash b #

StandardHash block ⇒ Show (ChainHash block) 
Instance details

Defined in Ouroboros.Network.Block

Methods

showsPrecIntChainHash block → ShowS #

showChainHash block → String #

showList ∷ [ChainHash block] → ShowS #

StandardHash block ⇒ Eq (ChainHash block) 
Instance details

Defined in Ouroboros.Network.Block

Methods

(==)ChainHash block → ChainHash block → Bool #

(/=)ChainHash block → ChainHash block → Bool #

StandardHash block ⇒ Ord (ChainHash block) 
Instance details

Defined in Ouroboros.Network.Block

Methods

compareChainHash block → ChainHash block → Ordering #

(<)ChainHash block → ChainHash block → Bool #

(<=)ChainHash block → ChainHash block → Bool #

(>)ChainHash block → ChainHash block → Bool #

(>=)ChainHash block → ChainHash block → Bool #

maxChainHash block → ChainHash block → ChainHash block #

minChainHash block → ChainHash block → ChainHash block #

(StandardHash block, Typeable block) ⇒ NoThunks (ChainHash block) 
Instance details

Defined in Ouroboros.Network.Block

Condense (HeaderHash b) ⇒ Condense (ChainHash b) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.Condense

Methods

condenseChainHash b → String Source #

Serialise (HeaderHash b) ⇒ Serialise (ChainHash b) 
Instance details

Defined in Ouroboros.Network.Block

type Rep (ChainHash b) 
Instance details

Defined in Ouroboros.Network.Block

type Rep (ChainHash b) = D1 ('MetaData "ChainHash" "Ouroboros.Network.Block" "ouroboros-network-api-0.7.2.0-0bea7b823cbda00590f7ea5f9786d7648393f2aa10b0aef7b53ea3ea0094c568" 'False) (C1 ('MetaCons "GenesisHash" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "BlockHash" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HeaderHash b))))

class (StandardHash b, Typeable b) ⇒ HasHeader b where Source #

Abstract over the shape of blocks (or indeed just block headers)

data HeaderFields (b ∷ k) Source #

Header fields we expect to be present in a block

These fields are lazy because they are extracted from a block or block header; this type is not intended for storage.

Constructors

HeaderFields 

Fields

Instances

Instances details
StandardHash b ⇒ StandardHash (HeaderFields b ∷ Type) 
Instance details

Defined in Ouroboros.Network.Block

Generic (HeaderFields b) 
Instance details

Defined in Ouroboros.Network.Block

Associated Types

type Rep (HeaderFields b) ∷ TypeType #

Methods

fromHeaderFields b → Rep (HeaderFields b) x #

toRep (HeaderFields b) x → HeaderFields b #

StandardHash b ⇒ Show (HeaderFields b) 
Instance details

Defined in Ouroboros.Network.Block

Methods

showsPrecIntHeaderFields b → ShowS #

showHeaderFields b → String #

showList ∷ [HeaderFields b] → ShowS #

StandardHash b ⇒ Eq (HeaderFields b) 
Instance details

Defined in Ouroboros.Network.Block

Methods

(==)HeaderFields b → HeaderFields b → Bool #

(/=)HeaderFields b → HeaderFields b → Bool #

StandardHash b ⇒ Ord (HeaderFields b) 
Instance details

Defined in Ouroboros.Network.Block

(StandardHash b, Typeable b, Typeable k) ⇒ HasHeader (HeaderFields b) 
Instance details

Defined in Ouroboros.Network.Block

Serialise (HeaderHash b) ⇒ Serialise (HeaderFields b) 
Instance details

Defined in Ouroboros.Network.Block

type HeaderHash (HeaderFields b ∷ Type) 
Instance details

Defined in Ouroboros.Network.Block

type Rep (HeaderFields b) 
Instance details

Defined in Ouroboros.Network.Block

type Rep (HeaderFields b) = D1 ('MetaData "HeaderFields" "Ouroboros.Network.Block" "ouroboros-network-api-0.7.2.0-0bea7b823cbda00590f7ea5f9786d7648393f2aa10b0aef7b53ea3ea0094c568" 'False) (C1 ('MetaCons "HeaderFields" 'PrefixI 'True) (S1 ('MetaSel ('Just "headerFieldSlot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SlotNo) :*: (S1 ('MetaSel ('Just "headerFieldBlockNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockNo) :*: S1 ('MetaSel ('Just "headerFieldHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HeaderHash b)))))

type family HeaderHash (b ∷ k) Source #

Header hash

Instances

Instances details
type HeaderHash (Header blk ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

type HeaderHash (Header blk ∷ Type) = HeaderHash blk
type HeaderHash (HardForkBlock xs ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type HeaderHash (LedgerState blk ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

type HeaderHash (LedgerState blk ∷ Type) = HeaderHash blk
type HeaderHash (ExtLedgerState blk ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type HeaderHash (LedgerDB l ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.LedgerDB

type HeaderHash (SerialisedHeader blk ∷ Type) Source #

Only needed for the ChainSyncServer

Instance details

Defined in Ouroboros.Consensus.Storage.Serialisation

type HeaderHash (Ticked l ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

type HeaderHash (Ticked l ∷ Type) = HeaderHash l
type HeaderHash (DualBlock m a ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type HeaderHash (DualBlock m a ∷ Type) = HeaderHash m
type HeaderHash (WithPoint blk b ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.API

type HeaderHash (WithPoint blk b ∷ Type) = HeaderHash blk
type HeaderHash (HeaderFields b ∷ Type) 
Instance details

Defined in Ouroboros.Network.Block

type HeaderHash (Serialised block ∷ Type) 
Instance details

Defined in Ouroboros.Network.Block

type HeaderHash (Serialised block ∷ Type) = HeaderHash block

data Point (block ∷ k) where Source #

A point on the chain is identified by its Slot and HeaderHash.

The Slot tells us where to look and the HeaderHash either simply serves as a check, or in some contexts it disambiguates blocks from different forks that were in the same slot.

It's a newtype rather than a type synonym, because using a type synonym would lead to ambiguity, since HeaderHash is a non-injective type family.

Bundled Patterns

pattern GenesisPointPoint block 
pattern BlockPointSlotNoHeaderHash block → Point block 

Instances

Instances details
ShowProxy block ⇒ ShowProxy (Point block ∷ Type) 
Instance details

Defined in Ouroboros.Network.Block

Methods

showProxyProxy (Point block) → String Source #

Generic (Point block) 
Instance details

Defined in Ouroboros.Network.Block

Associated Types

type Rep (Point block) ∷ TypeType #

Methods

fromPoint block → Rep (Point block) x #

toRep (Point block) x → Point block #

StandardHash block ⇒ Show (Point block) 
Instance details

Defined in Ouroboros.Network.Block

Methods

showsPrecIntPoint block → ShowS #

showPoint block → String #

showList ∷ [Point block] → ShowS #

StandardHash block ⇒ Eq (Point block) 
Instance details

Defined in Ouroboros.Network.Block

Methods

(==)Point block → Point block → Bool #

(/=)Point block → Point block → Bool #

StandardHash block ⇒ Ord (Point block) 
Instance details

Defined in Ouroboros.Network.Block

Methods

comparePoint block → Point block → Ordering #

(<)Point block → Point block → Bool #

(<=)Point block → Point block → Bool #

(>)Point block → Point block → Bool #

(>=)Point block → Point block → Bool #

maxPoint block → Point block → Point block #

minPoint block → Point block → Point block #

StandardHash block ⇒ NoThunks (Point block) 
Instance details

Defined in Ouroboros.Network.Block

Methods

noThunksContextPoint block → IO (Maybe ThunkInfo) Source #

wNoThunksContextPoint block → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (Point block) → String Source #

Condense (HeaderHash block) ⇒ Condense (Point block) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.Condense

Methods

condensePoint block → String Source #

Serialise (HeaderHash block) ⇒ Serialise (Point block) 
Instance details

Defined in Ouroboros.Network.Block

Methods

encodePoint block → Encoding Source #

decodeDecoder s (Point block) Source #

encodeList ∷ [Point block] → Encoding Source #

decodeListDecoder s [Point block] Source #

type Rep (Point block) 
Instance details

Defined in Ouroboros.Network.Block

type Rep (Point block) = D1 ('MetaData "Point" "Ouroboros.Network.Block" "ouroboros-network-api-0.7.2.0-0bea7b823cbda00590f7ea5f9786d7648393f2aa10b0aef7b53ea3ea0094c568" 'True) (C1 ('MetaCons "Point" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (WithOrigin (Block SlotNo (HeaderHash block))))))

class (Eq (HeaderHash b), Ord (HeaderHash b), Show (HeaderHash b), Typeable (HeaderHash b), NoThunks (HeaderHash b)) ⇒ StandardHash (b ∷ k) Source #

StandardHash summarises the constraints we want header hashes to have

Without this class we would need to write

deriving instance Eq (HeaderHash block) => Eq (ChainHash block)

That requires UndecidableInstances; not a problem by itself, but it also means that we can then not use deriving Eq anywhere else for datatypes that reference Hash, which is very frustrating; see

https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/exts/deriving_inferred.html

Introducing the StandardHash class avoids this problem.

Having these constraints directly as part of the HasHeader class is possible but libraries that use the networking layer may wish to be able to talk about StandardHash independently of HasHeader since the latter may impose yet further constraints.

Instances

Instances details
HasHeader blk ⇒ StandardHash (Header blk ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

CanHardFork xs ⇒ StandardHash (HardForkBlock xs ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

StandardHash blk ⇒ StandardHash (SerialisedHeader blk ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.Serialisation

StandardHash m ⇒ StandardHash (DualBlock m a ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

StandardHash blk ⇒ StandardHash (WithPoint blk b ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.API

StandardHash b ⇒ StandardHash (HeaderFields b ∷ Type) 
Instance details

Defined in Ouroboros.Network.Block

StandardHash block ⇒ StandardHash (Serialised block ∷ Type) 
Instance details

Defined in Ouroboros.Network.Block

blockNoHasHeader b ⇒ b → BlockNo Source #

blockPointHasHeader block ⇒ block → Point block Source #

castHash ∷ ∀ {k1} {k2} (b ∷ k1) (b' ∷ k2). Coercible (HeaderHash b) (HeaderHash b') ⇒ ChainHash b → ChainHash b' Source #

castHeaderFields ∷ ∀ {k1} {k2} (b ∷ k1) (b' ∷ k2). HeaderHash b ~ HeaderHash b' ⇒ HeaderFields b → HeaderFields b' Source #

castPoint ∷ ∀ {k1} {k2} (b ∷ k1) (b' ∷ k2). Coercible (HeaderHash b) (HeaderHash b') ⇒ Point b → Point b' Source #

pointHash ∷ ∀ {k} (block ∷ k). Point block → ChainHash block Source #

pointSlot ∷ ∀ {k} (block ∷ k). Point block → WithOrigin SlotNo Source #

Re-export basic definitions from cardano-base

newtype BlockNo Source #

The 0-based index of the block in the blockchain. BlockNo is <= SlotNo and is only equal at slot N if there is a block for every slot where N <= SlotNo.

Constructors

BlockNo 

Fields

Instances

Instances details
FromJSON BlockNo 
Instance details

Defined in Cardano.Slotting.Block

ToJSON BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Bounded BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Enum BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Generic BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Associated Types

type Rep BlockNoTypeType #

Methods

fromBlockNoRep BlockNo x #

toRep BlockNo x → BlockNo #

Num BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Show BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Methods

showsPrecIntBlockNoShowS #

showBlockNoString #

showList ∷ [BlockNo] → ShowS #

FromCBOR BlockNo 
Instance details

Defined in Cardano.Slotting.Block

ToCBOR BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Methods

toCBORBlockNoEncoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy BlockNoSize Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [BlockNo] → Size Source #

NFData BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Methods

rnfBlockNo → () #

Eq BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Methods

(==)BlockNoBlockNoBool #

(/=)BlockNoBlockNoBool #

Ord BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Methods

compareBlockNoBlockNoOrdering #

(<)BlockNoBlockNoBool #

(<=)BlockNoBlockNoBool #

(>)BlockNoBlockNoBool #

(>=)BlockNoBlockNoBool #

maxBlockNoBlockNoBlockNo #

minBlockNoBlockNoBlockNo #

NoThunks BlockNo 
Instance details

Defined in Cardano.Slotting.Block

ChainOrder BlockNo Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Abstract

Associated Types

type ChainOrderConfig BlockNo Source #

Condense BlockNo Source # 
Instance details

Defined in Ouroboros.Consensus.Util.Condense

Methods

condenseBlockNoString Source #

Serialise BlockNo 
Instance details

Defined in Cardano.Slotting.Block

type Rep BlockNo 
Instance details

Defined in Cardano.Slotting.Block

type Rep BlockNo = D1 ('MetaData "BlockNo" "Cardano.Slotting.Block" "cardano-slotting-0.2.0.0-efb016fbe9e168c0ff2b2dc78099f0dcce58de3212bf5f1627b43e6c92636bbb" 'True) (C1 ('MetaCons "BlockNo" 'PrefixI 'True) (S1 ('MetaSel ('Just "unBlockNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))
type ChainOrderConfig BlockNo Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.Abstract

newtype EpochNo Source #

An epoch, i.e. the number of the epoch.

Constructors

EpochNo 

Fields

Instances

Instances details
FromJSON EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

ToJSON EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Enum EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Generic EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Associated Types

type Rep EpochNoTypeType #

Methods

fromEpochNoRep EpochNo x #

toRep EpochNo x → EpochNo #

Show EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

showsPrecIntEpochNoShowS #

showEpochNoString #

showList ∷ [EpochNo] → ShowS #

FromCBOR EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

ToCBOR EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toCBOREpochNoEncoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy EpochNoSize Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [EpochNo] → Size Source #

NFData EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

rnfEpochNo → () #

Eq EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

(==)EpochNoEpochNoBool #

(/=)EpochNoEpochNoBool #

Ord EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

compareEpochNoEpochNoOrdering #

(<)EpochNoEpochNoBool #

(<=)EpochNoEpochNoBool #

(>)EpochNoEpochNoBool #

(>=)EpochNoEpochNoBool #

maxEpochNoEpochNoEpochNo #

minEpochNoEpochNoEpochNo #

NoThunks EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Condense EpochNo Source # 
Instance details

Defined in Ouroboros.Consensus.Util.Condense

Methods

condenseEpochNoString Source #

Serialise EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

type Rep EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

type Rep EpochNo = D1 ('MetaData "EpochNo" "Cardano.Slotting.Slot" "cardano-slotting-0.2.0.0-efb016fbe9e168c0ff2b2dc78099f0dcce58de3212bf5f1627b43e6c92636bbb" 'True) (C1 ('MetaCons "EpochNo" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEpochNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

newtype EpochSize Source #

Constructors

EpochSize 

Fields

Instances

Instances details
FromJSON EpochSize 
Instance details

Defined in Cardano.Slotting.Slot

ToJSON EpochSize 
Instance details

Defined in Cardano.Slotting.Slot

Enum EpochSize 
Instance details

Defined in Cardano.Slotting.Slot

Generic EpochSize 
Instance details

Defined in Cardano.Slotting.Slot

Associated Types

type Rep EpochSizeTypeType #

Methods

fromEpochSizeRep EpochSize x #

toRep EpochSize x → EpochSize #

Show EpochSize 
Instance details

Defined in Cardano.Slotting.Slot

Methods

showsPrecIntEpochSizeShowS #

showEpochSizeString #

showList ∷ [EpochSize] → ShowS #

FromCBOR EpochSize 
Instance details

Defined in Cardano.Slotting.Slot

ToCBOR EpochSize 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toCBOREpochSizeEncoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy EpochSizeSize Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [EpochSize] → Size Source #

NFData EpochSize 
Instance details

Defined in Cardano.Slotting.Slot

Methods

rnfEpochSize → () #

Eq EpochSize 
Instance details

Defined in Cardano.Slotting.Slot

Methods

(==)EpochSizeEpochSizeBool #

(/=)EpochSizeEpochSizeBool #

Ord EpochSize 
Instance details

Defined in Cardano.Slotting.Slot

NoThunks EpochSize 
Instance details

Defined in Cardano.Slotting.Slot

type Rep EpochSize 
Instance details

Defined in Cardano.Slotting.Slot

type Rep EpochSize = D1 ('MetaData "EpochSize" "Cardano.Slotting.Slot" "cardano-slotting-0.2.0.0-efb016fbe9e168c0ff2b2dc78099f0dcce58de3212bf5f1627b43e6c92636bbb" 'True) (C1 ('MetaCons "EpochSize" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEpochSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

newtype SlotNo Source #

The 0-based index for the Ourboros time slot.

Constructors

SlotNo 

Fields

Instances

Instances details
FromJSON SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

ToJSON SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Bounded SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Enum SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Generic SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Associated Types

type Rep SlotNoTypeType #

Methods

fromSlotNoRep SlotNo x #

toRep SlotNo x → SlotNo #

Num SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

(+)SlotNoSlotNoSlotNo #

(-)SlotNoSlotNoSlotNo #

(*)SlotNoSlotNoSlotNo #

negateSlotNoSlotNo #

absSlotNoSlotNo #

signumSlotNoSlotNo #

fromIntegerIntegerSlotNo #

Show SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

showsPrecIntSlotNoShowS #

showSlotNoString #

showList ∷ [SlotNo] → ShowS #

FromCBOR SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

ToCBOR SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toCBORSlotNoEncoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy SlotNoSize Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [SlotNo] → Size Source #

NFData SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

rnfSlotNo → () #

Eq SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

(==)SlotNoSlotNoBool #

(/=)SlotNoSlotNoBool #

Ord SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

compareSlotNoSlotNoOrdering #

(<)SlotNoSlotNoBool #

(<=)SlotNoSlotNoBool #

(>)SlotNoSlotNoBool #

(>=)SlotNoSlotNoBool #

maxSlotNoSlotNoSlotNo #

minSlotNoSlotNoSlotNo #

NoThunks SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Condense SlotNo Source # 
Instance details

Defined in Ouroboros.Consensus.Util.Condense

Methods

condenseSlotNoString Source #

Serialise SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

ShowProxy SlotNo 
Instance details

Defined in Ouroboros.Network.Util.ShowProxy

(Condense block, HasHeader block, Condense (HeaderHash block)) ⇒ Condense (AnchoredFragment block) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.Condense

Methods

condenseAnchoredFragment block → String Source #

SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) SlotNo Source # 
Instance details

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

HasHeader block ⇒ Anchorable (WithOrigin SlotNo) (Anchor block) block 
Instance details

Defined in Ouroboros.Network.AnchoredFragment

Methods

asAnchor ∷ block → Anchor block Source #

getAnchorMeasureProxy block → Anchor block → WithOrigin SlotNo Source #

Anchorable (WithOrigin SlotNo) (HeaderState blk) (HeaderState blk) Source #

Used by HeaderStateHistory but defined here, where it is not an orphan.

Instance details

Defined in Ouroboros.Consensus.HeaderValidation

GetTip l ⇒ Anchorable (WithOrigin SlotNo) (Checkpoint l) (Checkpoint l) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.LedgerDB

type Rep SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

type Rep SlotNo = D1 ('MetaData "SlotNo" "Cardano.Slotting.Slot" "cardano-slotting-0.2.0.0-efb016fbe9e168c0ff2b2dc78099f0dcce58de3212bf5f1627b43e6c92636bbb" 'True) (C1 ('MetaCons "SlotNo" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSlotNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

data WithOrigin t Source #

Constructors

Origin 

Bundled Patterns

pattern NotOrigin ∷ t → WithOrigin t

Custom pattern for WithOrigin

This avoids clashing with our (extensive) use of At for testing.

Instances

Instances details
Foldable WithOrigin 
Instance details

Defined in Cardano.Slotting.Slot

Methods

foldMonoid m ⇒ WithOrigin m → m #

foldMapMonoid m ⇒ (a → m) → WithOrigin a → m #

foldMap'Monoid m ⇒ (a → m) → WithOrigin a → m #

foldr ∷ (a → b → b) → b → WithOrigin a → b #

foldr' ∷ (a → b → b) → b → WithOrigin a → b #

foldl ∷ (b → a → b) → b → WithOrigin a → b #

foldl' ∷ (b → a → b) → b → WithOrigin a → b #

foldr1 ∷ (a → a → a) → WithOrigin a → a #

foldl1 ∷ (a → a → a) → WithOrigin a → a #

toListWithOrigin a → [a] #

nullWithOrigin a → Bool #

lengthWithOrigin a → Int #

elemEq a ⇒ a → WithOrigin a → Bool #

maximumOrd a ⇒ WithOrigin a → a #

minimumOrd a ⇒ WithOrigin a → a #

sumNum a ⇒ WithOrigin a → a #

productNum a ⇒ WithOrigin a → a #

Traversable WithOrigin 
Instance details

Defined in Cardano.Slotting.Slot

Methods

traverseApplicative f ⇒ (a → f b) → WithOrigin a → f (WithOrigin b) #

sequenceAApplicative f ⇒ WithOrigin (f a) → f (WithOrigin a) #

mapMMonad m ⇒ (a → m b) → WithOrigin a → m (WithOrigin b) #

sequenceMonad m ⇒ WithOrigin (m a) → m (WithOrigin a) #

Functor WithOrigin 
Instance details

Defined in Cardano.Slotting.Slot

Methods

fmap ∷ (a → b) → WithOrigin a → WithOrigin b #

(<$) ∷ a → WithOrigin b → WithOrigin a #

FromJSON a ⇒ FromJSON (WithOrigin a) 
Instance details

Defined in Cardano.Slotting.Slot

ToJSON a ⇒ ToJSON (WithOrigin a) 
Instance details

Defined in Cardano.Slotting.Slot

Bounded t ⇒ Bounded (WithOrigin t) 
Instance details

Defined in Cardano.Slotting.Slot

Generic (WithOrigin t) 
Instance details

Defined in Cardano.Slotting.Slot

Associated Types

type Rep (WithOrigin t) ∷ TypeType #

Methods

fromWithOrigin t → Rep (WithOrigin t) x #

toRep (WithOrigin t) x → WithOrigin t #

Show t ⇒ Show (WithOrigin t) 
Instance details

Defined in Cardano.Slotting.Slot

Methods

showsPrecIntWithOrigin t → ShowS #

showWithOrigin t → String #

showList ∷ [WithOrigin t] → ShowS #

(Serialise t, Typeable t) ⇒ FromCBOR (WithOrigin t) 
Instance details

Defined in Cardano.Slotting.Slot

(Serialise t, Typeable t) ⇒ ToCBOR (WithOrigin t) 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toCBORWithOrigin t → Encoding Source #

encodedSizeExpr ∷ (∀ t0. ToCBOR t0 ⇒ Proxy t0 → Size) → Proxy (WithOrigin t) → Size Source #

encodedListSizeExpr ∷ (∀ t0. ToCBOR t0 ⇒ Proxy t0 → Size) → Proxy [WithOrigin t] → Size Source #

NFData a ⇒ NFData (WithOrigin a) 
Instance details

Defined in Cardano.Slotting.Slot

Methods

rnfWithOrigin a → () #

Eq t ⇒ Eq (WithOrigin t) 
Instance details

Defined in Cardano.Slotting.Slot

Methods

(==)WithOrigin t → WithOrigin t → Bool #

(/=)WithOrigin t → WithOrigin t → Bool #

Ord t ⇒ Ord (WithOrigin t) 
Instance details

Defined in Cardano.Slotting.Slot

Methods

compareWithOrigin t → WithOrigin t → Ordering #

(<)WithOrigin t → WithOrigin t → Bool #

(<=)WithOrigin t → WithOrigin t → Bool #

(>)WithOrigin t → WithOrigin t → Bool #

(>=)WithOrigin t → WithOrigin t → Bool #

maxWithOrigin t → WithOrigin t → WithOrigin t #

minWithOrigin t → WithOrigin t → WithOrigin t #

NoThunks t ⇒ NoThunks (WithOrigin t) 
Instance details

Defined in Cardano.Slotting.Slot

Condense a ⇒ Condense (WithOrigin a) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.Condense

Methods

condenseWithOrigin a → String Source #

(Condense block, HasHeader block, Condense (HeaderHash block)) ⇒ Condense (AnchoredFragment block) Source # 
Instance details

Defined in Ouroboros.Consensus.Util.Condense

Methods

condenseAnchoredFragment block → String Source #

Serialise t ⇒ Serialise (WithOrigin t) 
Instance details

Defined in Cardano.Slotting.Slot

HasHeader block ⇒ Anchorable (WithOrigin SlotNo) (Anchor block) block 
Instance details

Defined in Ouroboros.Network.AnchoredFragment

Methods

asAnchor ∷ block → Anchor block Source #

getAnchorMeasureProxy block → Anchor block → WithOrigin SlotNo Source #

Anchorable (WithOrigin SlotNo) (HeaderState blk) (HeaderState blk) Source #

Used by HeaderStateHistory but defined here, where it is not an orphan.

Instance details

Defined in Ouroboros.Consensus.HeaderValidation

GetTip l ⇒ Anchorable (WithOrigin SlotNo) (Checkpoint l) (Checkpoint l) Source # 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.LedgerDB

type Rep (WithOrigin t) 
Instance details

Defined in Cardano.Slotting.Slot

type Rep (WithOrigin t) = D1 ('MetaData "WithOrigin" "Cardano.Slotting.Slot" "cardano-slotting-0.2.0.0-efb016fbe9e168c0ff2b2dc78099f0dcce58de3212bf5f1627b43e6c92636bbb" 'False) (C1 ('MetaCons "Origin" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "At" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 t)))

fromWithOrigin ∷ t → WithOrigin t → t Source #

withOrigin ∷ b → (t → b) → WithOrigin t → b Source #