ouroboros-consensus-0.1.0.1: Consensus layer for the Ouroboros blockchain protocol
Safe Haskell None
Language Haskell2010

Ouroboros.Consensus.Block.Abstract

Synopsis

Protocol

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

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

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

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

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.1.0.1-DT4Cvwf63DZKctsEvaJqCU" ' 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

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

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.1.0.1-DT4Cvwf63DZKctsEvaJqCU" ' 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

Working with headers

data family Header blk :: Type Source #

Instances

Instances details
Isomorphic Header Source #
Instance details

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

Inject Header Source #
Instance details

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

Typeable xs => ShowProxy ( Header ( HardForkBlock xs) :: Type ) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

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

( Typeable m, Typeable a) => ShowProxy ( DualHeader m a :: Type ) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

CanHardFork xs => Show ( 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

CanHardFork xs => NoThunks ( Header ( HardForkBlock xs)) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

CanHardFork xs => HasHeader ( Header ( HardForkBlock xs)) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

HasHeader blk => StandardHash ( Header blk) Source #
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Condense

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

SerialiseHFC xs => SerialiseNodeToNode ( HardForkBlock xs) ( Header ( HardForkBlock xs)) Source #
Instance details

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

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Bridge m a => HasHeader ( DualHeader m a) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

type HeaderHash ( Header blk) Source #
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

newtype Header ( HardForkBlock xs) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

type BlockProtocol ( Header blk) Source #
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

newtype Header ( DualBlock m a) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

getBlockHeaderFields :: GetHeader 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.

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.

Methods

toRawHash :: proxy blk -> HeaderHash blk -> ByteString Source #

Get the raw bytes from a hash

fromRawHash :: proxy blk -> ByteString -> HeaderHash blk Source #

Construct the hash from a raw hash

PRECONDITION: the bytestring's size must match hashSize

toShortRawHash :: proxy blk -> HeaderHash blk -> ShortByteString Source #

fromShortRawHash :: proxy blk -> ShortByteString -> HeaderHash blk Source #

hashSize :: proxy blk -> Word32 Source #

The size of the hash in number of bytes

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 .

Re-export basic definitions from ouroboros-network

data ChainHash b Source #

Instances

Instances details
Isomorphic ChainHash Source #
Instance details

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

StandardHash block => Eq ( ChainHash block)
Instance details

Defined in Ouroboros.Network.Block

StandardHash block => Ord ( ChainHash block)
Instance details

Defined in Ouroboros.Network.Block

StandardHash block => Show ( ChainHash block)
Instance details

Defined in Ouroboros.Network.Block

Generic ( ChainHash b)
Instance details

Defined in Ouroboros.Network.Block

Associated Types

type Rep ( ChainHash b) :: Type -> Type Source #

( StandardHash block, Typeable block) => NoThunks ( ChainHash block)
Instance details

Defined in Ouroboros.Network.Block

Serialise ( HeaderHash b) => Serialise ( ChainHash b)
Instance details

Defined in Ouroboros.Network.Block

Condense ( HeaderHash b) => Condense ( ChainHash b) Source #
Instance details

Defined in Ouroboros.Consensus.Util.Condense

type Rep ( ChainHash b)
Instance details

Defined in Ouroboros.Network.Block

type Rep ( ChainHash b) = D1 (' MetaData "ChainHash" "Ouroboros.Network.Block" "ouroboros-network-0.1.0.1-2UgqzRSdBh49QYumtriFSI" ' False ) ( C1 (' MetaCons "GenesisHash" ' PrefixI ' False ) ( U1 :: Type -> Type ) :+: C1 (' MetaCons "BlockHash" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 ( HeaderHash b))))

data HeaderFields b 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 => Eq ( HeaderFields b)
Instance details

Defined in Ouroboros.Network.Block

StandardHash b => Ord ( HeaderFields b)
Instance details

Defined in Ouroboros.Network.Block

StandardHash b => Show ( HeaderFields b)
Instance details

Defined in Ouroboros.Network.Block

Generic ( HeaderFields b)
Instance details

Defined in Ouroboros.Network.Block

Associated Types

type Rep ( HeaderFields b) :: Type -> Type Source #

( StandardHash b, Typeable b) => HasHeader ( HeaderFields b)
Instance details

Defined in Ouroboros.Network.Block

StandardHash b => StandardHash ( HeaderFields b)
Instance details

Defined in Ouroboros.Network.Block

Serialise ( HeaderHash b) => Serialise ( HeaderFields b)
Instance details

Defined in Ouroboros.Network.Block

type Rep ( HeaderFields b)
Instance details

Defined in Ouroboros.Network.Block

type HeaderHash ( HeaderFields b)
Instance details

Defined in Ouroboros.Network.Block

type family HeaderHash b Source #

Header hash

Instances

Instances details
type HeaderHash ( HeaderFields b)
Instance details

Defined in Ouroboros.Network.Block

type HeaderHash ( Serialised block)
Instance details

Defined in Ouroboros.Network.Block

type HeaderHash ( Ticked l) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

type HeaderHash ( Header blk) Source #
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

type HeaderHash ( LedgerState blk) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

type HeaderHash ( SerialisedHeader blk) Source #

Only needed for the ChainSyncServer

Instance details

Defined in Ouroboros.Consensus.Storage.Serialisation

type HeaderHash ( ExtLedgerState blk) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type HeaderHash ( LedgerDB l) Source #
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.InMemory

type HeaderHash ( HardForkBlock xs) Source #
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type HeaderHash ( DualBlock m a) Source #
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type HeaderHash ( WithPoint blk b) Source #
Instance details

Defined in Ouroboros.Consensus.Storage.ChainDB.API

data Point block 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 GenesisPoint :: Point block
pattern BlockPoint :: SlotNo -> HeaderHash block -> Point block

Instances

Instances details
StandardHash block => Eq ( Point block)
Instance details

Defined in Ouroboros.Network.Block

StandardHash block => Ord ( Point block)
Instance details

Defined in Ouroboros.Network.Block

StandardHash block => Show ( Point block)
Instance details

Defined in Ouroboros.Network.Block

Generic ( Point block)
Instance details

Defined in Ouroboros.Network.Block

Associated Types

type Rep ( Point block) :: Type -> Type Source #

StandardHash block => NoThunks ( Point block)
Instance details

Defined in Ouroboros.Network.Block

Serialise ( HeaderHash block) => Serialise ( Point block)
Instance details

Defined in Ouroboros.Network.Block

Condense ( HeaderHash block) => Condense ( Point block) Source #
Instance details

Defined in Ouroboros.Consensus.Util.Orphans

ShowProxy block => ShowProxy ( Point block :: Type )
Instance details

Defined in Ouroboros.Network.Block

type Rep ( Point block)
Instance details

Defined in Ouroboros.Network.Block

type Rep ( Point block) = D1 (' MetaData "Point" "Ouroboros.Network.Block" "ouroboros-network-0.1.0.1-2UgqzRSdBh49QYumtriFSI" ' 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 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/glasgow_exts.html#inferred-context-for-deriving-clauses

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.

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

Instances

Instances details
Bounded BlockNo
Instance details

Defined in Cardano.Slotting.Block

Enum BlockNo
Instance details

Defined in Cardano.Slotting.Block

Eq BlockNo
Instance details

Defined in Cardano.Slotting.Block

Num BlockNo
Instance details

Defined in Cardano.Slotting.Block

Ord BlockNo
Instance details

Defined in Cardano.Slotting.Block

Show BlockNo
Instance details

Defined in Cardano.Slotting.Block

Generic BlockNo
Instance details

Defined in Cardano.Slotting.Block

ToCBOR BlockNo
Instance details

Defined in Cardano.Slotting.Block

FromCBOR BlockNo
Instance details

Defined in Cardano.Slotting.Block

NFData BlockNo
Instance details

Defined in Cardano.Slotting.Block

NoThunks BlockNo
Instance details

Defined in Cardano.Slotting.Block

Serialise BlockNo
Instance details

Defined in Cardano.Slotting.Block

Condense BlockNo Source #
Instance details

Defined in Ouroboros.Consensus.Util.Condense

type Rep BlockNo
Instance details

Defined in Cardano.Slotting.Block

type Rep BlockNo = D1 (' MetaData "BlockNo" "Cardano.Slotting.Block" "cardano-slotting-0.1.0.2-j5NuF73p5IFfcfvmth6tS" ' True ) ( C1 (' MetaCons "BlockNo" ' PrefixI ' True ) ( S1 (' MetaSel (' Just "unBlockNo") ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 Word64 )))

newtype EpochNo Source #

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

Constructors

EpochNo

Instances

Instances details
Enum EpochNo
Instance details

Defined in Cardano.Slotting.Slot

Eq EpochNo
Instance details

Defined in Cardano.Slotting.Slot

Num EpochNo
Instance details

Defined in Cardano.Slotting.Slot

Ord EpochNo
Instance details

Defined in Cardano.Slotting.Slot

Show EpochNo
Instance details

Defined in Cardano.Slotting.Slot

Generic EpochNo
Instance details

Defined in Cardano.Slotting.Slot

ToJSON EpochNo
Instance details

Defined in Cardano.Slotting.Slot

FromJSON EpochNo
Instance details

Defined in Cardano.Slotting.Slot

ToCBOR EpochNo
Instance details

Defined in Cardano.Slotting.Slot

FromCBOR EpochNo
Instance details

Defined in Cardano.Slotting.Slot

NFData EpochNo
Instance details

Defined in Cardano.Slotting.Slot

NoThunks EpochNo
Instance details

Defined in Cardano.Slotting.Slot

Serialise EpochNo
Instance details

Defined in Cardano.Slotting.Slot

Condense EpochNo Source #
Instance details

Defined in Ouroboros.Consensus.Util.Condense

type Rep EpochNo
Instance details

Defined in Cardano.Slotting.Slot

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

newtype EpochSize Source #

Instances

Instances details
Enum EpochSize
Instance details

Defined in Cardano.Slotting.Slot

Eq EpochSize
Instance details

Defined in Cardano.Slotting.Slot

Integral EpochSize
Instance details

Defined in Cardano.Slotting.Slot

Num EpochSize
Instance details

Defined in Cardano.Slotting.Slot

Ord EpochSize
Instance details

Defined in Cardano.Slotting.Slot

Real EpochSize
Instance details

Defined in Cardano.Slotting.Slot

Show EpochSize
Instance details

Defined in Cardano.Slotting.Slot

Generic EpochSize
Instance details

Defined in Cardano.Slotting.Slot

ToJSON EpochSize
Instance details

Defined in Cardano.Slotting.Slot

FromJSON EpochSize
Instance details

Defined in Cardano.Slotting.Slot

ToCBOR EpochSize
Instance details

Defined in Cardano.Slotting.Slot

FromCBOR EpochSize
Instance details

Defined in Cardano.Slotting.Slot

NFData 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.1.0.2-j5NuF73p5IFfcfvmth6tS" ' 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

Instances

Instances details
Bounded SlotNo
Instance details

Defined in Cardano.Slotting.Slot

Enum SlotNo
Instance details

Defined in Cardano.Slotting.Slot

Eq SlotNo
Instance details

Defined in Cardano.Slotting.Slot

Num SlotNo
Instance details

Defined in Cardano.Slotting.Slot

Ord SlotNo
Instance details

Defined in Cardano.Slotting.Slot

Show SlotNo
Instance details

Defined in Cardano.Slotting.Slot

Generic SlotNo
Instance details

Defined in Cardano.Slotting.Slot

ToJSON SlotNo
Instance details

Defined in Cardano.Slotting.Slot

FromJSON SlotNo
Instance details

Defined in Cardano.Slotting.Slot

ToCBOR SlotNo
Instance details

Defined in Cardano.Slotting.Slot

FromCBOR SlotNo
Instance details

Defined in Cardano.Slotting.Slot

NFData SlotNo
Instance details

Defined in Cardano.Slotting.Slot

NoThunks SlotNo
Instance details

Defined in Cardano.Slotting.Slot

Serialise SlotNo
Instance details

Defined in Cardano.Slotting.Slot

Condense SlotNo Source #
Instance details

Defined in Ouroboros.Consensus.Util.Condense

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

Defined in Ouroboros.Consensus.Util.Orphans

ShowProxy SlotNo Source #
Instance details

Defined in Ouroboros.Consensus.Util.Orphans

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

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

type Rep SlotNo
Instance details

Defined in Cardano.Slotting.Slot

type Rep SlotNo = D1 (' MetaData "SlotNo" "Cardano.Slotting.Slot" "cardano-slotting-0.1.0.2-j5NuF73p5IFfcfvmth6tS" ' 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
Functor WithOrigin
Instance details

Defined in Cardano.Slotting.Slot

Foldable WithOrigin
Instance details

Defined in Cardano.Slotting.Slot

Traversable WithOrigin
Instance details

Defined in Cardano.Slotting.Slot

Bounded t => Bounded ( WithOrigin t)
Instance details

Defined in Cardano.Slotting.Slot

Eq t => Eq ( WithOrigin t)
Instance details

Defined in Cardano.Slotting.Slot

Ord t => Ord ( WithOrigin t)
Instance details

Defined in Cardano.Slotting.Slot

Show t => Show ( 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) :: Type -> Type Source #

( Serialise t, Typeable t) => ToCBOR ( WithOrigin t)
Instance details

Defined in Cardano.Slotting.Slot

( Serialise t, Typeable t) => FromCBOR ( WithOrigin t)
Instance details

Defined in Cardano.Slotting.Slot

NFData a => NFData ( WithOrigin a)
Instance details

Defined in Cardano.Slotting.Slot

NoThunks t => NoThunks ( WithOrigin t)
Instance details

Defined in Cardano.Slotting.Slot

Serialise t => Serialise ( WithOrigin t)
Instance details

Defined in Cardano.Slotting.Slot

Condense a => Condense ( WithOrigin a) Source #
Instance details

Defined in Ouroboros.Consensus.Util.Condense

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

Defined in Ouroboros.Consensus.Util.Orphans

HasHeader block => Anchorable ( WithOrigin SlotNo ) ( Anchor block) block
Instance details

Defined in Ouroboros.Network.AnchoredFragment

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

type Rep ( WithOrigin t)
Instance details

Defined in Cardano.Slotting.Slot

type Rep ( WithOrigin t) = D1 (' MetaData "WithOrigin" "Cardano.Slotting.Slot" "cardano-slotting-0.1.0.2-j5NuF73p5IFfcfvmth6tS" ' False ) ( C1 (' MetaCons "Origin" ' PrefixI ' False ) ( U1 :: Type -> Type ) :+: C1 (' MetaCons "At" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 t)))

withOrigin :: b -> (t -> b) -> WithOrigin t -> b Source #