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

Test.Util.TestBlock

Description

Minimal instantiation of the consensus layer to be able to run the ChainDB

Synopsis

Blocks

data family BlockConfig blk Source #

Static configuration required to work with this type of blocks

Instances

Instances details
Isomorphic BlockConfig 
Instance details

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

Generic (BlockConfig (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (BlockConfig (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

type Rep (BlockConfig (TestBlockWith ptype)) = D1 ('MetaData "BlockConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "testBlockNumCoreNodes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NumCoreNodes)))

Methods

fromBlockConfig (TestBlockWith ptype) → Rep (BlockConfig (TestBlockWith ptype)) x #

toRep (BlockConfig (TestBlockWith ptype)) x → BlockConfig (TestBlockWith ptype) #

Show (BlockConfig (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

NoThunks (BlockConfig (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

NoThunks (BlockConfig (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (BlockConfig (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (BlockConfig (TestBlockWith ptype)) = D1 ('MetaData "BlockConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "testBlockNumCoreNodes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NumCoreNodes)))
newtype BlockConfig (DisableDiffusionPipelining blk) 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype BlockConfig (SelectViewDiffusionPipelining blk) 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype BlockConfig (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data BlockConfig (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

data BlockConfig (DualBlock m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data family BlockQueryTypeQueryFootprintTypeType Source #

Different queries supported by the ledger, indexed by the result type.

Instances

Instances details
SameDepIndex2 (BlockQuery (DualBlock m a) ∷ QueryFootprintTypeType) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

sameDepIndex2 ∷ ∀ (x ∷ QueryFootprint) a0 (y ∷ QueryFootprint) b. BlockQuery (DualBlock m a) x a0 → BlockQuery (DualBlock m a) y b → Maybe ('(x, a0) :~: '(y, b)) Source #

SameDepIndex2 (BlockQuery TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

sameDepIndex2 ∷ ∀ (x ∷ QueryFootprint) a (y ∷ QueryFootprint) b. BlockQuery TestBlock x a → BlockQuery TestBlock y b → Maybe ('(x, a) :~: '(y, b)) Source #

(∀ (footprint ∷ QueryFootprint) result. Show (BlockQuery blk footprint result)) ⇒ Show (SomeBlockQuery (BlockQuery blk)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Query

ShowQuery (BlockQuery (DualBlock m a) footprint) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showResultBlockQuery (DualBlock m a) footprint result → result → String Source #

ShowQuery (BlockQuery TestBlock fp) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showResultBlockQuery TestBlock fp result → result → String Source #

(Typeable m, Typeable a) ⇒ ShowProxy (BlockQuery (DualBlock m a) ∷ QueryFootprintTypeType) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Show (BlockQuery (DualBlock m a) footprint result) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntBlockQuery (DualBlock m a) footprint result → ShowS #

showBlockQuery (DualBlock m a) footprint result → String #

showList ∷ [BlockQuery (DualBlock m a) footprint result] → ShowS #

Show (BlockQuery TestBlock fp result) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showsPrecIntBlockQuery TestBlock fp result → ShowS #

showBlockQuery TestBlock fp result → String #

showList ∷ [BlockQuery TestBlock fp result] → ShowS #

Eq (BlockQuery TestBlock fp result) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

(==)BlockQuery TestBlock fp result → BlockQuery TestBlock fp result → Bool #

(/=)BlockQuery TestBlock fp result → BlockQuery TestBlock fp result → Bool #

Inject (SomeBlockQuery :.: BlockQuery) 
Instance details

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

data BlockQuery TestBlock fp result Source # 
Instance details

Defined in Test.Util.TestBlock

data BlockQuery (HardForkBlock xs) footprint result 
Instance details

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

data BlockQuery (HardForkBlock xs) footprint result where
data BlockQuery (DualBlock m a) footprint result 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data BlockQuery (DualBlock m a) footprint result

data family CodecConfig blk 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 
Instance details

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

Generic (CodecConfig (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Associated Types

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

Defined in Ouroboros.Consensus.Ledger.Dual

type Rep (CodecConfig (DualBlock m a)) = D1 ('MetaData "CodecConfig" "Ouroboros.Consensus.Ledger.Dual" "ouroboros-consensus-0.26.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))))

Methods

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

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

Generic (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (CodecConfig TestBlock) 
Instance details

Defined in Test.Util.TestBlock

type Rep (CodecConfig TestBlock) = D1 ('MetaData "CodecConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockCodecConfig" 'PrefixI 'False) (U1TypeType))
Show (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

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

Defined in Ouroboros.Consensus.Ledger.Dual

NoThunks (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

data CodecConfig TestBlock Source #

The TestBlock does not need any codec config

Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Ledger.Dual

type Rep (CodecConfig (DualBlock m a)) = D1 ('MetaData "CodecConfig" "Ouroboros.Consensus.Ledger.Dual" "ouroboros-consensus-0.26.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))))
type Rep (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (CodecConfig TestBlock) = D1 ('MetaData "CodecConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockCodecConfig" 'PrefixI 'False) (U1TypeType))
newtype CodecConfig (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data CodecConfig (DualBlock m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data family Header blk Source #

Instances

Instances details
GetHeader1 Header 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

Methods

getHeader1Header blk → Header blk Source #

Inject Header 
Instance details

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

Methods

inject ∷ ∀ x (xs ∷ [Type]). (CanHardFork xs, HasCanonicalTxIn xs, HasHardForkTxOut xs) ⇒ InjectionIndex xs x → Header x → Header (HardForkBlock xs) Source #

Isomorphic Header 
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 #

ReconstructNestedCtxt Header (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

StandardHash blk ⇒ StandardHash (Header blk ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

Typeable ptype ⇒ ShowProxy (Header (TestBlockWith ptype) ∷ Type) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showProxyProxy (Header (TestBlockWith ptype)) → String Source #

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showProxyProxy (DualHeader m a) → String Source #

Show ptype ⇒ Show (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showsPrecIntHeader (TestBlockWith ptype) → ShowS #

showHeader (TestBlockWith ptype) → String #

showList ∷ [Header (TestBlockWith ptype)] → ShowS #

Eq ptype ⇒ Eq (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

(==)Header (TestBlockWith ptype) → Header (TestBlockWith ptype) → Bool #

(/=)Header (TestBlockWith ptype) → Header (TestBlockWith ptype) → Bool #

NoThunks (Header (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

NoThunks ptype ⇒ NoThunks (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

SignedHeader (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

(Typeable ptype, Eq ptype) ⇒ Condense (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

condenseHeader (TestBlockWith ptype) → String Source #

Typeable ptype ⇒ HasHeader (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Serialise ptype ⇒ Serialise (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Serialise ptype ⇒ DecodeDiskDep (NestedCtxt Header) (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

decodeDiskDepCodecConfig (TestBlockWith ptype) → NestedCtxt Header (TestBlockWith ptype) a → ∀ s. Decoder s (ByteString → a) Source #

Serialise ptype ⇒ EncodeDisk (TestBlockWith ptype) (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Serialise ptype ⇒ EncodeDiskDep (NestedCtxt Header) (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Serialise ptype ⇒ DecodeDisk (TestBlockWith ptype) (ByteStringHeader (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

decodeDiskCodecConfig (TestBlockWith ptype) → ∀ s. Decoder s (ByteStringHeader (TestBlockWith ptype)) Source #

EncodeDiskDep (NestedCtxt Header) m ⇒ EncodeDiskDep (NestedCtxt Header) (DualBlock m a) 
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) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntDualHeader m a → ShowS #

showDualHeader m a → String #

showList ∷ [DualHeader m a] → ShowS #

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

Defined in Ouroboros.Consensus.Ledger.Dual

type HeaderHash (Header blk ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

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

Defined in Ouroboros.Consensus.Block.Abstract

newtype Header (DisableDiffusionPipelining blk) 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype Header (SelectViewDiffusionPipelining blk) 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype Header (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

newtype Header (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type Signed (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

type Signed (Header (TestBlockWith ptype)) = ()
newtype Header (DualBlock m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

newtype LedgerTables (l ∷ LedgerStateKind) (mk ∷ MapKind) Source #

The Ledger Tables represent the portion of the data on disk that has been pulled from disk and attached to the in-memory Ledger State or that will eventually be written to disk.

With UTxO-HD and the split of the Ledger ledger state into the in-memory part and the on-disk part, this splitting was reflected in the new type parameter added to the (Consensus) LedgerState, to which we refer as "the MapKind" or mk.

Every LedgerState (or LedgerState-like type, such as the ExtLedgerState) is associated with a LedgerTables and they both share the mk. They both are of kind LedgerStateKind. LedgerTables is just a way to refer only to a partial view of the on-disk data without having the rest of the in-memory LedgerState in scope.

The mk can be instantiated to anything that is map-like, i.e. that expects two type parameters, the key and the value.

Constructors

LedgerTables 

Fields

Instances

Instances details
(Ord (TxIn l), Eq (TxOut l), Show (TxIn l), Show (TxOut l), NoThunks (TxIn l), NoThunks (TxOut l), MemPack (TxIn l), IndexedMemPack (MemPackIdx l EmptyMK) (TxOut l)) ⇒ HasLedgerTables (LedgerTables l) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables

Methods

projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerTables l mk → LedgerTables (LedgerTables l) mk Source #

withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerTables l any → LedgerTables (LedgerTables l) mk → LedgerTables l mk Source #

Generic (LedgerTables l mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

Associated Types

type Rep (LedgerTables l mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type Rep (LedgerTables l mk) = D1 ('MetaData "LedgerTables" "Ouroboros.Consensus.Ledger.Tables.Basics" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "LedgerTables" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLedgerTables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (mk (TxIn l) (TxOut l)))))

Methods

fromLedgerTables l mk → Rep (LedgerTables l mk) x #

toRep (LedgerTables l mk) x → LedgerTables l mk #

Show (mk (TxIn l) (TxOut l)) ⇒ Show (LedgerTables l mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

Methods

showsPrecIntLedgerTables l mk → ShowS #

showLedgerTables l mk → String #

showList ∷ [LedgerTables l mk] → ShowS #

Eq (mk (TxIn l) (TxOut l)) ⇒ Eq (LedgerTables l mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

Methods

(==)LedgerTables l mk → LedgerTables l mk → Bool #

(/=)LedgerTables l mk → LedgerTables l mk → Bool #

NoThunks (mk (TxIn l) (TxOut l)) ⇒ NoThunks (LedgerTables l mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type TxIn (LedgerTables l) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type TxIn (LedgerTables l) = TxIn l
type TxOut (LedgerTables l) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type TxOut (LedgerTables l) = TxOut l
type Rep (LedgerTables l mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type Rep (LedgerTables l mk) = D1 ('MetaData "LedgerTables" "Ouroboros.Consensus.Ledger.Tables.Basics" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "LedgerTables" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLedgerTables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (mk (TxIn l) (TxOut l)))))
type SerializeTablesHint (LedgerTables l ValuesMK) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables

type InitHint (LedgerTables l ValuesMK) 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.V1.BackingStore.API

type ReadHint (LedgerTables l ValuesMK) 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.V1.BackingStore.API

type WriteHint (LedgerTables l DiffMK) 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.V1.BackingStore.API

data family StorageConfig blk Source #

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

Instances

Instances details
Isomorphic StorageConfig 
Instance details

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

Generic (StorageConfig (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Associated Types

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

Defined in Ouroboros.Consensus.Ledger.Dual

type Rep (StorageConfig (DualBlock m a)) = D1 ('MetaData "StorageConfig" "Ouroboros.Consensus.Ledger.Dual" "ouroboros-consensus-0.26.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))))
Generic (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (StorageConfig TestBlock) 
Instance details

Defined in Test.Util.TestBlock

type Rep (StorageConfig TestBlock) = D1 ('MetaData "StorageConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockStorageConfig" 'PrefixI 'False) (U1TypeType))
Show (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

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

Defined in Ouroboros.Consensus.Ledger.Dual

NoThunks (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

data StorageConfig TestBlock Source #

The TestBlock does not need any storage config

Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Ledger.Dual

type Rep (StorageConfig (DualBlock m a)) = D1 ('MetaData "StorageConfig" "Ouroboros.Consensus.Ledger.Dual" "ouroboros-consensus-0.26.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))))
type Rep (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (StorageConfig TestBlock) = D1 ('MetaData "StorageConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockStorageConfig" 'PrefixI 'False) (U1TypeType))
newtype StorageConfig (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data StorageConfig (DualBlock m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data TestBlockError ptype Source #

Constructors

InvalidHash

The hashes don't line up

Fields

InvalidBlock

The block itself is invalid

InvalidPayload (PayloadDependentError ptype) 

Instances

Instances details
Generic (TestBlockError ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (TestBlockError ptype) 
Instance details

Defined in Test.Util.TestBlock

type Rep (TestBlockError ptype) = D1 ('MetaData "TestBlockError" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "InvalidHash" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ChainHash (TestBlockWith ptype))) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ChainHash (TestBlockWith ptype)))) :+: (C1 ('MetaCons "InvalidBlock" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "InvalidPayload" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PayloadDependentError ptype)))))

Methods

fromTestBlockError ptype → Rep (TestBlockError ptype) x #

toRep (TestBlockError ptype) x → TestBlockError ptype #

Show (PayloadDependentError ptype) ⇒ Show (TestBlockError ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showsPrecIntTestBlockError ptype → ShowS #

showTestBlockError ptype → String #

showList ∷ [TestBlockError ptype] → ShowS #

Eq (PayloadDependentError ptype) ⇒ Eq (TestBlockError ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

(==)TestBlockError ptype → TestBlockError ptype → Bool #

(/=)TestBlockError ptype → TestBlockError ptype → Bool #

(Typeable ptype, Generic (PayloadDependentError ptype), NoThunks (PayloadDependentError ptype)) ⇒ NoThunks (TestBlockError ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (TestBlockError ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (TestBlockError ptype) = D1 ('MetaData "TestBlockError" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "InvalidHash" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ChainHash (TestBlockWith ptype))) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ChainHash (TestBlockWith ptype)))) :+: (C1 ('MetaCons "InvalidBlock" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "InvalidPayload" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PayloadDependentError ptype)))))

data TestBlockWith ptype Source #

Test block parametrized on the payload type

For blocks without payload see the TestBlock type alias.

By defining a PayloadSemantics it is possible to obtain an ApplyBlock instance. See the former class for more details.

Instances

Instances details
HasHardForkHistory TestBlock Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type HardForkIndices TestBlock 
Instance details

Defined in Test.Util.TestBlock

BlockSupportsLedgerQuery TestBlock Source # 
Instance details

Defined in Test.Util.TestBlock

ShowProxy TestBlock Source # 
Instance details

Defined in Test.Util.TestBlock

SameDepIndex2 (BlockQuery TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

sameDepIndex2 ∷ ∀ (x ∷ QueryFootprint) a (y ∷ QueryFootprint) b. BlockQuery TestBlock x a → BlockQuery TestBlock y b → Maybe ('(x, a) :~: '(y, b)) Source #

HasNestedContent f (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

unnest ∷ f (TestBlockWith ptype) → DepPair (NestedCtxt f (TestBlockWith ptype)) Source #

nestDepPair (NestedCtxt f (TestBlockWith ptype)) → f (TestBlockWith ptype) Source #

ReconstructNestedCtxt Header (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

StandardHash (TestBlockWith ptype ∷ Type) Source # 
Instance details

Defined in Test.Util.TestBlock

Typeable ptype ⇒ ShowProxy (Header (TestBlockWith ptype) ∷ Type) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showProxyProxy (Header (TestBlockWith ptype)) → String Source #

SameDepIndex (NestedCtxt_ (TestBlockWith ptype) f ∷ TypeType) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

sameDepIndexNestedCtxt_ (TestBlockWith ptype) f a → NestedCtxt_ (TestBlockWith ptype) f b → Maybe (a :~: b) Source #

TrivialDependency (NestedCtxt_ (TestBlockWith ptype) f ∷ TypeType) Source # 
Instance details

Defined in Test.Util.TestBlock

Generic (BlockConfig (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (BlockConfig (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

type Rep (BlockConfig (TestBlockWith ptype)) = D1 ('MetaData "BlockConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "testBlockNumCoreNodes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NumCoreNodes)))

Methods

fromBlockConfig (TestBlockWith ptype) → Rep (BlockConfig (TestBlockWith ptype)) x #

toRep (BlockConfig (TestBlockWith ptype)) x → BlockConfig (TestBlockWith ptype) #

Generic (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (CodecConfig TestBlock) 
Instance details

Defined in Test.Util.TestBlock

type Rep (CodecConfig TestBlock) = D1 ('MetaData "CodecConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockCodecConfig" 'PrefixI 'False) (U1TypeType))
Generic (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (StorageConfig TestBlock) 
Instance details

Defined in Test.Util.TestBlock

type Rep (StorageConfig TestBlock) = D1 ('MetaData "StorageConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockStorageConfig" 'PrefixI 'False) (U1TypeType))
Generic (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (TestBlockWith ptype) 
Instance details

Defined in Test.Util.TestBlock

type Rep (TestBlockWith ptype) = D1 ('MetaData "TestBlockWith" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockWith" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tbHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TestHash) :*: S1 ('MetaSel ('Just "tbSlot") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo)) :*: (S1 ('MetaSel ('Just "tbValid") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Validity) :*: S1 ('MetaSel ('Just "tbPayload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ptype))))

Methods

fromTestBlockWith ptype → Rep (TestBlockWith ptype) x #

toRep (TestBlockWith ptype) x → TestBlockWith ptype #

Show (BlockConfig (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Show (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Show ptype ⇒ Show (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showsPrecIntHeader (TestBlockWith ptype) → ShowS #

showHeader (TestBlockWith ptype) → String #

showList ∷ [Header (TestBlockWith ptype)] → ShowS #

Show (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Show ptype ⇒ Show (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showsPrecIntTestBlockWith ptype → ShowS #

showTestBlockWith ptype → String #

showList ∷ [TestBlockWith ptype] → ShowS #

Eq ptype ⇒ Eq (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

(==)Header (TestBlockWith ptype) → Header (TestBlockWith ptype) → Bool #

(/=)Header (TestBlockWith ptype) → Header (TestBlockWith ptype) → Bool #

Eq ptype ⇒ Eq (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

(==)TestBlockWith ptype → TestBlockWith ptype → Bool #

(/=)TestBlockWith ptype → TestBlockWith ptype → Bool #

Ord ptype ⇒ Ord (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

compareTestBlockWith ptype → TestBlockWith ptype → Ordering #

(<)TestBlockWith ptype → TestBlockWith ptype → Bool #

(<=)TestBlockWith ptype → TestBlockWith ptype → Bool #

(>)TestBlockWith ptype → TestBlockWith ptype → Bool #

(>=)TestBlockWith ptype → TestBlockWith ptype → Bool #

maxTestBlockWith ptype → TestBlockWith ptype → TestBlockWith ptype #

minTestBlockWith ptype → TestBlockWith ptype → TestBlockWith ptype #

NoThunks (BlockConfig (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

NoThunks (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

NoThunks ptype ⇒ NoThunks (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

NoThunks (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

NoThunks ptype ⇒ NoThunks (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

ConvertRawHash (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

(Typeable ptype, Eq ptype) ⇒ GetHeader (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

(Typeable ptype, Eq ptype) ⇒ GetPrevHash (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

BlockSupportsProtocol (TestBlockWith ptype) ⇒ BlockSupportsDiffusionPipelining (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

(Typeable ptype, Eq ptype, NoThunks ptype, NoThunks (CodecConfig (TestBlockWith ptype)), NoThunks (StorageConfig (TestBlockWith ptype))) ⇒ BlockSupportsProtocol (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

ConfigSupportsNode (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

ImmutableEraParams (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ BasicEnvelopeValidation (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ HasAnnTip (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type TipInfo (TestBlockWith ptype) 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ ValidateEnvelope (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type OtherHeaderEnvelopeError (TestBlockWith ptype) 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ UpdateLedger (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

GetTip (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

getTip ∷ ∀ (mk ∷ MapKind). LedgerState (TestBlockWith ptype) mk → Point (LedgerState (TestBlockWith ptype)) Source #

PayloadSemantics ptype ⇒ IsLedger (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type LedgerErr (LedgerState (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

type AuxLedgerEvent (LedgerState (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

InspectLedger (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type LedgerWarning (TestBlockWith ptype) 
Instance details

Defined in Test.Util.TestBlock

type LedgerUpdate (TestBlockWith ptype) 
Instance details

Defined in Test.Util.TestBlock

Methods

inspectLedger ∷ ∀ (mk1 ∷ MapKind) (mk2 ∷ MapKind). TopLevelConfig (TestBlockWith ptype) → LedgerState (TestBlockWith ptype) mk1 → LedgerState (TestBlockWith ptype) mk2 → [LedgerEvent (TestBlockWith ptype)] Source #

PayloadSemantics ptype ⇒ LedgerSupportsProtocol (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

CanStowLedgerTables (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

HasLedgerTables (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

LedgerTablesAreTrivial (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). LedgerState TestBlock mk → LedgerState TestBlock mk' Source #

SerializeTablesWithHint (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

HasNetworkProtocolVersion (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type BlockNodeToNodeVersion (TestBlockWith ptype) 
Instance details

Defined in Test.Util.TestBlock

type BlockNodeToClientVersion (TestBlockWith ptype) 
Instance details

Defined in Test.Util.TestBlock

SignedHeader (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

(Serialise ptype, PayloadSemantics ptype, IndexedMemPack (LedgerState (TestBlockWith ptype) EmptyMK) (TxOut (LedgerState (TestBlockWith ptype))), SerializeTablesWithHint (LedgerState (TestBlockWith ptype))) ⇒ SerialiseDiskConstraints (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

CanUpgradeLedgerTables (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Serialise ptype ⇒ HasBinaryBlockInfo (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

(Typeable ptype, Eq ptype) ⇒ Condense (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

condenseHeader (TestBlockWith ptype) → String Source #

(Typeable ptype, Eq ptype) ⇒ Condense (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

condenseTestBlockWith ptype → String Source #

Typeable ptype ⇒ HasHeader (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

(Typeable ptype, Eq ptype) ⇒ HasHeader (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Serialise ptype ⇒ Serialise (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Serialise (RealPoint (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Serialise (AnnTip (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Serialise ptype ⇒ Serialise (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

ToExpr ptype ⇒ ToExpr (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

toExprTestBlockWith ptype → Expr Source #

listToExpr ∷ [TestBlockWith ptype] → Expr Source #

DecodeDisk (TestBlockWith ptype) () Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

decodeDiskCodecConfig (TestBlockWith ptype) → ∀ s. Decoder s () Source #

EncodeDisk (TestBlockWith ptype) () Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

encodeDiskCodecConfig (TestBlockWith ptype) → () → Encoding Source #

PayloadSemantics ptype ⇒ ApplyBlock (LedgerState (TestBlockWith ptype)) (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

DecodeDisk (TestBlockWith ptype) (AnnTip (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

decodeDiskCodecConfig (TestBlockWith ptype) → ∀ s. Decoder s (AnnTip (TestBlockWith ptype)) Source #

Serialise ptype ⇒ DecodeDiskDep (NestedCtxt Header) (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

decodeDiskDepCodecConfig (TestBlockWith ptype) → NestedCtxt Header (TestBlockWith ptype) a → ∀ s. Decoder s (ByteString → a) Source #

Serialise ptype ⇒ EncodeDisk (TestBlockWith ptype) (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

EncodeDisk (TestBlockWith ptype) (AnnTip (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Serialise ptype ⇒ EncodeDisk (TestBlockWith ptype) (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Serialise ptype ⇒ EncodeDiskDep (NestedCtxt Header) (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ DecodeDisk (TestBlockWith ptype) (LedgerState (TestBlockWith ptype) EmptyMK) Source # 
Instance details

Defined in Test.Util.TestBlock

Serialise ptype ⇒ DecodeDisk (TestBlockWith ptype) (ByteStringHeader (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

decodeDiskCodecConfig (TestBlockWith ptype) → ∀ s. Decoder s (ByteStringHeader (TestBlockWith ptype)) Source #

Serialise ptype ⇒ DecodeDisk (TestBlockWith ptype) (ByteStringTestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

decodeDiskCodecConfig (TestBlockWith ptype) → ∀ s. Decoder s (ByteStringTestBlockWith ptype) Source #

PayloadSemantics ptype ⇒ EncodeDisk (TestBlockWith ptype) (LedgerState (TestBlockWith ptype) EmptyMK) Source # 
Instance details

Defined in Test.Util.TestBlock

Generic (LedgerState (TestBlockWith ptype) mk) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (LedgerState (TestBlockWith ptype) mk) 
Instance details

Defined in Test.Util.TestBlock

type Rep (LedgerState (TestBlockWith ptype) mk) = D1 ('MetaData "LedgerState" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "lastAppliedPoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Point (TestBlockWith ptype))) :*: S1 ('MetaSel ('Just "payloadDependentState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PayloadDependentState ptype mk))))

Methods

fromLedgerState (TestBlockWith ptype) mk → Rep (LedgerState (TestBlockWith ptype) mk) x #

toRep (LedgerState (TestBlockWith ptype) mk) x → LedgerState (TestBlockWith ptype) mk #

(ShowMK mk, PayloadSemantics ptype) ⇒ Show (LedgerState (TestBlockWith ptype) mk) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showsPrecIntLedgerState (TestBlockWith ptype) mk → ShowS #

showLedgerState (TestBlockWith ptype) mk → String #

showList ∷ [LedgerState (TestBlockWith ptype) mk] → ShowS #

Eq (PayloadDependentState ptype mk) ⇒ Eq (LedgerState (TestBlockWith ptype) mk) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

(==)LedgerState (TestBlockWith ptype) mk → LedgerState (TestBlockWith ptype) mk → Bool #

(/=)LedgerState (TestBlockWith ptype) mk → LedgerState (TestBlockWith ptype) mk → Bool #

NoThunks (PayloadDependentState ptype mk) ⇒ NoThunks (LedgerState (TestBlockWith ptype) mk) Source # 
Instance details

Defined in Test.Util.TestBlock

GetTip (Ticked (LedgerState (TestBlockWith ptype))) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (TestBlockWith ptype)) mk → Point (Ticked (LedgerState (TestBlockWith ptype))) Source #

HasLedgerTables (Ticked (LedgerState TestBlock)) Source # 
Instance details

Defined in Test.Util.TestBlock

LedgerTablesAreTrivial (Ticked (LedgerState TestBlock)) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). Ticked (LedgerState TestBlock) mk → Ticked (LedgerState TestBlock) mk' Source #

Condense (ChainHash (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

ShowQuery (BlockQuery TestBlock fp) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showResultBlockQuery TestBlock fp result → result → String Source #

PayloadSemantics ptype ⇒ Serialise (LedgerState (TestBlockWith ptype) EmptyMK) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ Serialise (ExtLedgerState (TestBlockWith ptype) EmptyMK) Source # 
Instance details

Defined in Test.Util.TestBlock

IndexedMemPack (LedgerState TestBlock EmptyMK) Void Source # 
Instance details

Defined in Test.Util.TestBlock

Generic (Ticked (LedgerState (TestBlockWith ptype)) mk) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) 
Instance details

Defined in Test.Util.TestBlock

type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) = D1 ('MetaData "Ticked" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'True) (C1 ('MetaCons "TickedTestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTickedTestLedger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerState (TestBlockWith ptype) mk))))

Methods

fromTicked (LedgerState (TestBlockWith ptype)) mk → Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) x #

toRep (Ticked (LedgerState (TestBlockWith ptype)) mk) x → Ticked (LedgerState (TestBlockWith ptype)) mk #

Show (NestedCtxt_ (TestBlockWith ptype) f a) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showsPrecIntNestedCtxt_ (TestBlockWith ptype) f a → ShowS #

showNestedCtxt_ (TestBlockWith ptype) f a → String #

showList ∷ [NestedCtxt_ (TestBlockWith ptype) f a] → ShowS #

Show (BlockQuery TestBlock fp result) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showsPrecIntBlockQuery TestBlock fp result → ShowS #

showBlockQuery TestBlock fp result → String #

showList ∷ [BlockQuery TestBlock fp result] → ShowS #

Eq (BlockQuery TestBlock fp result) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

(==)BlockQuery TestBlock fp result → BlockQuery TestBlock fp result → Bool #

(/=)BlockQuery TestBlock fp result → BlockQuery TestBlock fp result → Bool #

(NoThunksMK mk, NoThunks (PayloadDependentState ptype mk)) ⇒ NoThunks (Ticked (LedgerState (TestBlockWith ptype)) mk) Source # 
Instance details

Defined in Test.Util.TestBlock

data CodecConfig TestBlock Source #

The TestBlock does not need any codec config

Instance details

Defined in Test.Util.TestBlock

data StorageConfig TestBlock Source #

The TestBlock does not need any storage config

Instance details

Defined in Test.Util.TestBlock

type HardForkIndices TestBlock Source # 
Instance details

Defined in Test.Util.TestBlock

data BlockQuery TestBlock fp result Source # 
Instance details

Defined in Test.Util.TestBlock

type TrivialIndex (NestedCtxt_ (TestBlockWith ptype) f ∷ TypeType) Source # 
Instance details

Defined in Test.Util.TestBlock

type TrivialIndex (NestedCtxt_ (TestBlockWith ptype) f ∷ TypeType) = f (TestBlockWith ptype)
type HeaderHash (TestBlockWith ptype ∷ Type) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (BlockConfig (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (BlockConfig (TestBlockWith ptype)) = D1 ('MetaData "BlockConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "testBlockNumCoreNodes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NumCoreNodes)))
type Rep (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (CodecConfig TestBlock) = D1 ('MetaData "CodecConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockCodecConfig" 'PrefixI 'False) (U1TypeType))
type Rep (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (StorageConfig TestBlock) = D1 ('MetaData "StorageConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockStorageConfig" 'PrefixI 'False) (U1TypeType))
type Rep (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (TestBlockWith ptype) = D1 ('MetaData "TestBlockWith" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockWith" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tbHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TestHash) :*: S1 ('MetaSel ('Just "tbSlot") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo)) :*: (S1 ('MetaSel ('Just "tbValid") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Validity) :*: S1 ('MetaSel ('Just "tbPayload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ptype))))
data BlockConfig (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type BlockProtocol (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

newtype Header (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

data NestedCtxt_ (TestBlockWith ptype) f a Source # 
Instance details

Defined in Test.Util.TestBlock

data NestedCtxt_ (TestBlockWith ptype) f a where
type TentativeHeaderState (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type TentativeHeaderView (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type OtherHeaderEnvelopeError (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type TipInfo (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type AuxLedgerEvent (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

type LedgerCfg (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

type LedgerErr (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

data LedgerState (TestBlockWith ptype) mk Source # 
Instance details

Defined in Test.Util.TestBlock

type LedgerUpdate (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type LedgerWarning (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type TxIn (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

type TxOut (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

type BlockNodeToClientVersion (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type BlockNodeToNodeVersion (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type Signed (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

type Signed (Header (TestBlockWith ptype)) = ()
type Rep (LedgerState (TestBlockWith ptype) mk) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (LedgerState (TestBlockWith ptype) mk) = D1 ('MetaData "LedgerState" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "lastAppliedPoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Point (TestBlockWith ptype))) :*: S1 ('MetaSel ('Just "payloadDependentState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PayloadDependentState ptype mk))))
newtype Ticked (LedgerState (TestBlockWith ptype) ∷ MapKindType) (mk ∷ MapKind) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) = D1 ('MetaData "Ticked" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'True) (C1 ('MetaCons "TickedTestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTickedTestLedger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerState (TestBlockWith ptype) mk))))

data TestHash where Source #

Bundled Patterns

pattern TestHashNonEmpty Word64TestHash 

Instances

Instances details
Generic TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep TestHash 
Instance details

Defined in Test.Util.TestBlock

type Rep TestHash = D1 ('MetaData "TestHash" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'True) (C1 ('MetaCons "UnsafeTestHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTestHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Word64))))

Methods

fromTestHashRep TestHash x #

toRep TestHash x → TestHash #

Show TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showsPrecIntTestHashShowS #

showTestHashString #

showList ∷ [TestHash] → ShowS #

Eq TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

(==)TestHashTestHashBool #

(/=)TestHashTestHashBool #

Ord TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

NoThunks TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

Condense TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

Serialise TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

ToExpr TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep TestHash = D1 ('MetaData "TestHash" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'True) (C1 ('MetaCons "UnsafeTestHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTestHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Word64))))

data Validity Source #

Constructors

Valid 
Invalid 

Instances

Instances details
Bounded Validity Source # 
Instance details

Defined in Test.Util.TestBlock

Enum Validity Source # 
Instance details

Defined in Test.Util.TestBlock

Generic Validity Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep Validity 
Instance details

Defined in Test.Util.TestBlock

type Rep Validity = D1 ('MetaData "Validity" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "Valid" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "Invalid" 'PrefixI 'False) (U1TypeType))

Methods

fromValidityRep Validity x #

toRep Validity x → Validity #

Show Validity Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showsPrecIntValidityShowS #

showValidityString #

showList ∷ [Validity] → ShowS #

Eq Validity Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

(==)ValidityValidityBool #

(/=)ValidityValidityBool #

Ord Validity Source # 
Instance details

Defined in Test.Util.TestBlock

NoThunks Validity Source # 
Instance details

Defined in Test.Util.TestBlock

Serialise Validity Source # 
Instance details

Defined in Test.Util.TestBlock

ToExpr Validity Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep Validity Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep Validity = D1 ('MetaData "Validity" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "Valid" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "Invalid" 'PrefixI 'False) (U1TypeType))

firstBlockWithPayloadWord64 → ptype → TestBlockWith ptype Source #

Create the first block in the given fork, [fork], with the given payload. The SlotNo will be 1.

successorBlockWithPayloadTestHashSlotNo → ptype → TestBlockWith ptype Source #

Create the successor of the given block without forking: b -> b ++ [0] (in the printed representation) The SlotNo is increased by 1.

In Zipper parlance, this corresponds to going down in a tree.

Test block without payload

type TestBlock = TestBlockWith () Source #

Block without payload

Payload semantics

data family PayloadDependentState ptype (mk ∷ MapKind) Source #

Instances

Instances details
Generic (PayloadDependentState () mk) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (PayloadDependentState () mk) 
Instance details

Defined in Test.Util.TestBlock

type Rep (PayloadDependentState () mk) = D1 ('MetaData "PayloadDependentState" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "EmptyPLDS" 'PrefixI 'False) (U1TypeType))
Show (PayloadDependentState () mk) Source # 
Instance details

Defined in Test.Util.TestBlock

Eq (PayloadDependentState () mk) Source # 
Instance details

Defined in Test.Util.TestBlock

NoThunks (PayloadDependentState () mk) Source # 
Instance details

Defined in Test.Util.TestBlock

Serialise (PayloadDependentState () mk) Source # 
Instance details

Defined in Test.Util.TestBlock

data PayloadDependentState () mk Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (PayloadDependentState () mk) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (PayloadDependentState () mk) = D1 ('MetaData "PayloadDependentState" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "EmptyPLDS" 'PrefixI 'False) (U1TypeType))

class (Typeable ptype, Eq ptype, NoThunks ptype, ∀ (mk ∷ MapKind). EqMK mk ⇒ Eq (PayloadDependentState ptype mk), ∀ (mk ∷ MapKind). NoThunksMK mk ⇒ NoThunks (PayloadDependentState ptype mk), ∀ (mk ∷ MapKind). ShowMK mk ⇒ Show (PayloadDependentState ptype mk), ∀ (mk ∷ MapKind). Generic (PayloadDependentState ptype mk), Serialise (PayloadDependentState ptype EmptyMK), HasLedgerTables (LedgerState (TestBlockWith ptype)), HasLedgerTables (Ticked (LedgerState (TestBlockWith ptype))), CanStowLedgerTables (LedgerState (TestBlockWith ptype)), Eq (PayloadDependentError ptype), Show (PayloadDependentError ptype), Generic (PayloadDependentError ptype), ToExpr (PayloadDependentError ptype), Serialise (PayloadDependentError ptype), NoThunks (PayloadDependentError ptype), NoThunks (CodecConfig (TestBlockWith ptype)), NoThunks (StorageConfig (TestBlockWith ptype))) ⇒ PayloadSemantics ptype where Source #

Associated Types

data PayloadDependentState ptype (mk ∷ MapKind) Source #

type PayloadDependentError ptype Source #

Methods

applyPayloadPayloadDependentState ptype ValuesMK → ptype → Either (PayloadDependentError ptype) (PayloadDependentState ptype TrackingMK) Source #

getPayloadKeySets ∷ ptype → LedgerTables (LedgerState (TestBlockWith ptype)) KeysMK Source #

This function is used to implement the getBlockKeySets function of the ApplyBlock class. Thus we assume that the payload contains all the information needed to determine which keys should be retrieved from the backing store to apply a TestBlockWith.

Instances

Instances details
PayloadSemantics () Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

data PayloadDependentState () mk 
Instance details

Defined in Test.Util.TestBlock

type PayloadDependentError () 
Instance details

Defined in Test.Util.TestBlock

applyDirectlyToPayloadDependentStatePayloadSemantics ptype ⇒ Ticked (LedgerState (TestBlockWith ptype)) ValuesMK → ptype → Either (PayloadDependentError ptype) (Ticked (LedgerState (TestBlockWith ptype)) TrackingMK) Source #

Apply the payload directly to the payload dependent state portion of a ticked state, leaving the rest of the input ticked state unaltered.

LedgerState

data family LedgerState blk (mk ∷ MapKind) Source #

Ledger state associated with a block

This is the Consensus notion of a Ledger ledger state. Each block type is associated with one of the Ledger types for the ledger state. Virtually every concept in this codebase revolves around this type, or the referenced blk. Whenever we use the type variable l we intend to signal that the expected instantiation is either a LedgerState or some wrapper over it (like the ExtLedgerState).

This type is parametrized over mk :: MapKind to express the LedgerTables contained in such a LedgerState. See LedgerTables for a more thorough description.

The main operations we can do with a LedgerState are ticking (defined in IsLedger), and applying a block (defined in ApplyBlock).

Instances

Instances details
Bridge m a ⇒ GetTip (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

getTip ∷ ∀ (mk ∷ MapKind). LedgerState (DualBlock m a) mk → Point (LedgerState (DualBlock m a)) Source #

GetTip (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

getTip ∷ ∀ (mk ∷ MapKind). LedgerState (TestBlockWith ptype) mk → Point (LedgerState (TestBlockWith ptype)) Source #

Bridge m a ⇒ IsLedger (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Associated Types

type LedgerErr (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type AuxLedgerEvent (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

PayloadSemantics ptype ⇒ IsLedger (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type LedgerErr (LedgerState (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

type AuxLedgerEvent (LedgerState (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

CanStowLedgerTables (LedgerState m) ⇒ CanStowLedgerTables (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanStowLedgerTables (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

(Bridge m a, NoThunks (TxOut (LedgerState m)), NoThunks (TxIn (LedgerState m)), Show (TxOut (LedgerState m)), Show (TxIn (LedgerState m)), Eq (TxOut (LedgerState m)), Ord (TxIn (LedgerState m)), MemPack (TxIn (LedgerState m))) ⇒ HasLedgerTables (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerState (DualBlock m a) mk → LedgerTables (LedgerState (DualBlock m a)) mk Source #

withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerState (DualBlock m a) any → LedgerTables (LedgerState (DualBlock m a)) mk → LedgerState (DualBlock m a) mk Source #

HasLedgerTables (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

LedgerTablesAreTrivial (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). LedgerState TestBlock mk → LedgerState TestBlock mk' Source #

(Ord (TxIn (LedgerState m)), MemPack (TxIn (LedgerState m)), MemPack (TxOut (LedgerState m))) ⇒ SerializeTablesWithHint (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

SerializeTablesWithHint (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

CanUpgradeLedgerTables (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanUpgradeLedgerTables (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ ApplyBlock (LedgerState (TestBlockWith ptype)) (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Bridge m a ⇒ ApplyBlock (LedgerState (DualBlock m a)) (DualBlock m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

PayloadSemantics ptype ⇒ DecodeDisk (TestBlockWith ptype) (LedgerState (TestBlockWith ptype) EmptyMK) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ EncodeDisk (TestBlockWith ptype) (LedgerState (TestBlockWith ptype) EmptyMK) Source # 
Instance details

Defined in Test.Util.TestBlock

(IsNonEmpty xs, SListI xs, All (Compose Arbitrary (Flip LedgerState mk)) xs) ⇒ Arbitrary (LedgerState (HardForkBlock xs) mk) Source # 
Instance details

Defined in Test.Util.Orphans.Arbitrary

Generic (LedgerState (TestBlockWith ptype) mk) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (LedgerState (TestBlockWith ptype) mk) 
Instance details

Defined in Test.Util.TestBlock

type Rep (LedgerState (TestBlockWith ptype) mk) = D1 ('MetaData "LedgerState" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "lastAppliedPoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Point (TestBlockWith ptype))) :*: S1 ('MetaSel ('Just "payloadDependentState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PayloadDependentState ptype mk))))

Methods

fromLedgerState (TestBlockWith ptype) mk → Rep (LedgerState (TestBlockWith ptype) mk) x #

toRep (LedgerState (TestBlockWith ptype) mk) x → LedgerState (TestBlockWith ptype) mk #

(ShowMK mk, CanHardFork xs) ⇒ Show (LedgerState (HardForkBlock xs) mk) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

(Bridge m a, ShowMK mk) ⇒ Show (LedgerState (DualBlock m a) mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntLedgerState (DualBlock m a) mk → ShowS #

showLedgerState (DualBlock m a) mk → String #

showList ∷ [LedgerState (DualBlock m a) mk] → ShowS #

(ShowMK mk, PayloadSemantics ptype) ⇒ Show (LedgerState (TestBlockWith ptype) mk) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showsPrecIntLedgerState (TestBlockWith ptype) mk → ShowS #

showLedgerState (TestBlockWith ptype) mk → String #

showList ∷ [LedgerState (TestBlockWith ptype) mk] → ShowS #

(EqMK mk, CanHardFork xs) ⇒ Eq (LedgerState (HardForkBlock xs) mk) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

(Bridge m a, EqMK mk) ⇒ Eq (LedgerState (DualBlock m a) mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

(==)LedgerState (DualBlock m a) mk → LedgerState (DualBlock m a) mk → Bool #

(/=)LedgerState (DualBlock m a) mk → LedgerState (DualBlock m a) mk → Bool #

Eq (PayloadDependentState ptype mk) ⇒ Eq (LedgerState (TestBlockWith ptype) mk) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

(==)LedgerState (TestBlockWith ptype) mk → LedgerState (TestBlockWith ptype) mk → Bool #

(/=)LedgerState (TestBlockWith ptype) mk → LedgerState (TestBlockWith ptype) mk → Bool #

(NoThunksMK mk, CanHardFork xs) ⇒ NoThunks (LedgerState (HardForkBlock xs) mk) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

NoThunks (LedgerState (DualBlock m a) mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

NoThunks (PayloadDependentState ptype mk) ⇒ NoThunks (LedgerState (TestBlockWith ptype) mk) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (DualBlock m a)) mk → Point (Ticked (LedgerState (DualBlock m a))) Source #

GetTip (Ticked (LedgerState (TestBlockWith ptype))) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (TestBlockWith ptype)) mk → Point (Ticked (LedgerState (TestBlockWith ptype))) Source #

(Ord k, Eq v, MemPack k, MemPack v) ⇒ CanStowLedgerTables (OTLedgerState k v) Source # 
Instance details

Defined in Test.Util.LedgerStateOnlyTables

(Bridge m a, NoThunks (TxOut (LedgerState m)), NoThunks (TxIn (LedgerState m)), Show (TxOut (LedgerState m)), Show (TxIn (LedgerState m)), Eq (TxOut (LedgerState m)), Ord (TxIn (LedgerState m)), MemPack (TxIn (LedgerState m))) ⇒ HasLedgerTables (Ticked (LedgerState (DualBlock m a))) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

HasLedgerTables (Ticked (LedgerState TestBlock)) Source # 
Instance details

Defined in Test.Util.TestBlock

(Ord k, Eq v, Show k, Show v, MemPack k, MemPack v, NoThunks k, NoThunks v) ⇒ HasLedgerTables (OTLedgerState k v) Source # 
Instance details

Defined in Test.Util.LedgerStateOnlyTables

Methods

projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ OTLedgerState k v mk → LedgerTables (OTLedgerState k v) mk Source #

withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ OTLedgerState k v any → LedgerTables (OTLedgerState k v) mk → OTLedgerState k v mk Source #

LedgerTablesAreTrivial (Ticked (LedgerState TestBlock)) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). Ticked (LedgerState TestBlock) mk → Ticked (LedgerState TestBlock) mk' Source #

PayloadSemantics ptype ⇒ Serialise (LedgerState (TestBlockWith ptype) EmptyMK) Source # 
Instance details

Defined in Test.Util.TestBlock

(txout ~ TxOut (LedgerState m), IndexedMemPack (LedgerState m EmptyMK) txout) ⇒ IndexedMemPack (LedgerState (DualBlock m a) EmptyMK) txout 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

IndexedMemPack (LedgerState TestBlock EmptyMK) Void Source # 
Instance details

Defined in Test.Util.TestBlock

StandardHash blk ⇒ StandardHash (LedgerState blk ∷ MapKindType) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

Generic (Ticked (LedgerState (TestBlockWith ptype)) mk) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) 
Instance details

Defined in Test.Util.TestBlock

type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) = D1 ('MetaData "Ticked" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'True) (C1 ('MetaCons "TickedTestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTickedTestLedger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerState (TestBlockWith ptype) mk))))

Methods

fromTicked (LedgerState (TestBlockWith ptype)) mk → Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) x #

toRep (Ticked (LedgerState (TestBlockWith ptype)) mk) x → Ticked (LedgerState (TestBlockWith ptype)) mk #

(Show k, Show v, Show (mk k v)) ⇒ Show (OTLedgerState k v mk) Source # 
Instance details

Defined in Test.Util.LedgerStateOnlyTables

Methods

showsPrecIntOTLedgerState k v mk → ShowS #

showOTLedgerState k v mk → String #

showList ∷ [OTLedgerState k v mk] → ShowS #

(Ord k, Eq v, Eq (mk k v)) ⇒ Eq (OTLedgerState k v mk) Source # 
Instance details

Defined in Test.Util.LedgerStateOnlyTables

Methods

(==)OTLedgerState k v mk → OTLedgerState k v mk → Bool #

(/=)OTLedgerState k v mk → OTLedgerState k v mk → Bool #

NoThunks (Ticked (LedgerState (DualBlock m a)) mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

(NoThunksMK mk, NoThunks (PayloadDependentState ptype mk)) ⇒ NoThunks (Ticked (LedgerState (TestBlockWith ptype)) mk) Source # 
Instance details

Defined in Test.Util.TestBlock

(NoThunks k, NoThunks v, NoThunks (mk k v)) ⇒ NoThunks (OTLedgerState k v mk) Source # 
Instance details

Defined in Test.Util.LedgerStateOnlyTables

Inject (Flip LedgerState mk) 
Instance details

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

Methods

inject ∷ ∀ x (xs ∷ [Type]). (CanHardFork xs, HasCanonicalTxIn xs, HasHardForkTxOut xs) ⇒ InjectionIndex xs x → Flip LedgerState mk x → Flip LedgerState mk (HardForkBlock xs) Source #

Isomorphic (Flip LedgerState mk) 
Instance details

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

Methods

projectNoHardForks blk ⇒ Flip LedgerState mk (HardForkBlock '[blk]) → Flip LedgerState mk blk Source #

injectNoHardForks blk ⇒ Flip LedgerState mk blk → Flip LedgerState mk (HardForkBlock '[blk]) Source #

type AuxLedgerEvent (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type AuxLedgerEvent (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type AuxLedgerEvent (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

type LedgerCfg (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type LedgerCfg (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type LedgerCfg (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

type LedgerErr (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type LedgerErr (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type LedgerErr (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

newtype LedgerState (HardForkBlock xs) mk 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data LedgerState (TestBlockWith ptype) mk Source # 
Instance details

Defined in Test.Util.TestBlock

type TxIn (LedgerState (HardForkBlock xs))

Must be the CannonicalTxIn type, but this will probably change in the future to NS WrapTxIn xs. See HasCanonicalTxIn.

Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type TxIn (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type TxIn (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

type TxOut (LedgerState (HardForkBlock xs))

Must be the HardForkTxOut type

Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type TxOut (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type TxOut (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (LedgerState (TestBlockWith ptype) mk) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (LedgerState (TestBlockWith ptype) mk) = D1 ('MetaData "LedgerState" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "lastAppliedPoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Point (TestBlockWith ptype))) :*: S1 ('MetaSel ('Just "payloadDependentState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PayloadDependentState ptype mk))))
data LedgerState (DualBlock m a) mk 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type TxIn (OTLedgerState k v) Source # 
Instance details

Defined in Test.Util.LedgerStateOnlyTables

type TxIn (OTLedgerState k v) = k
type TxOut (OTLedgerState k v) Source # 
Instance details

Defined in Test.Util.LedgerStateOnlyTables

type TxOut (OTLedgerState k v) = v
data Ticked (LedgerState (HardForkBlock xs) ∷ MapKindType) (mk ∷ MapKind) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

data Ticked (LedgerState (DualBlock m a) ∷ MapKindType) (mk ∷ MapKind) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

newtype Ticked (LedgerState (TestBlockWith ptype) ∷ MapKindType) (mk ∷ MapKind) Source # 
Instance details

Defined in Test.Util.TestBlock

type HeaderHash (LedgerState blk ∷ MapKindType) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

type HeaderHash (LedgerState blk ∷ MapKindType) = HeaderHash blk
type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) = D1 ('MetaData "Ticked" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'True) (C1 ('MetaCons "TickedTestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTickedTestLedger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerState (TestBlockWith ptype) mk))))

data family Ticked (st ∷ k) ∷ k Source #

" Ticked " piece of state, either LedgerState or ChainDepState

Ticking refers to the passage of time (the ticking of the clock). When a piece of state is marked as ticked, it means that time-related changes have been applied to the state. There are exactly two methods in the interface that do that: tickChainDepState and applyChainTickLedgerResult.

Also note that a successful forecast forecastFor (ledgerViewForecastAt cfg st) slot must equal protocolLedgerView cfg (applyChainTick cfg slot st). Thus a LedgerView can only be projected from a Ticked state, but cannot itself be ticked.

Some examples of time related changes:

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

Instances

Instances details
Show (Ticked ()) 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecIntTicked () → ShowS #

showTicked () → String #

showList ∷ [Ticked ()] → ShowS #

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (DualBlock m a)) mk → Point (Ticked (LedgerState (DualBlock m a))) Source #

GetTip (Ticked (LedgerState (TestBlockWith ptype))) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (TestBlockWith ptype)) mk → Point (Ticked (LedgerState (TestBlockWith ptype))) Source #

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

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (ExtLedgerState blk) mk → Point (Ticked (ExtLedgerState blk)) Source #

(Bridge m a, NoThunks (TxOut (LedgerState m)), NoThunks (TxIn (LedgerState m)), Show (TxOut (LedgerState m)), Show (TxIn (LedgerState m)), Eq (TxOut (LedgerState m)), Ord (TxIn (LedgerState m)), MemPack (TxIn (LedgerState m))) ⇒ HasLedgerTables (Ticked (LedgerState (DualBlock m a))) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

HasLedgerTables (Ticked (LedgerState TestBlock)) Source # 
Instance details

Defined in Test.Util.TestBlock

(HasLedgerTables (Ticked (LedgerState blk)), NoThunks (TxOut (LedgerState blk)), NoThunks (TxIn (LedgerState blk)), Show (TxOut (LedgerState blk)), Show (TxIn (LedgerState blk)), Eq (TxOut (LedgerState blk)), Ord (TxIn (LedgerState blk)), MemPack (TxIn (LedgerState blk))) ⇒ HasLedgerTables (Ticked (ExtLedgerState blk)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (ExtLedgerState blk) mk → LedgerTables (Ticked (ExtLedgerState blk)) mk Source #

withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (ExtLedgerState blk) any → LedgerTables (Ticked (ExtLedgerState blk)) mk → Ticked (ExtLedgerState blk) mk Source #

LedgerTablesAreTrivial (Ticked (LedgerState TestBlock)) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). Ticked (LedgerState TestBlock) mk → Ticked (LedgerState TestBlock) mk' Source #

LedgerTablesAreTrivial (Ticked (LedgerState blk)) ⇒ LedgerTablesAreTrivial (Ticked (ExtLedgerState blk)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). Ticked (ExtLedgerState blk) mk → Ticked (ExtLedgerState blk) mk' Source #

Generic (Ticked (LedgerState (TestBlockWith ptype)) mk) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) 
Instance details

Defined in Test.Util.TestBlock

type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) = D1 ('MetaData "Ticked" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'True) (C1 ('MetaCons "TickedTestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTickedTestLedger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerState (TestBlockWith ptype) mk))))

Methods

fromTicked (LedgerState (TestBlockWith ptype)) mk → Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) x #

toRep (Ticked (LedgerState (TestBlockWith ptype)) mk) x → Ticked (LedgerState (TestBlockWith ptype)) mk #

NoThunks (Ticked (LedgerState (DualBlock m a)) mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

(NoThunksMK mk, NoThunks (PayloadDependentState ptype mk)) ⇒ NoThunks (Ticked (LedgerState (TestBlockWith ptype)) mk) Source # 
Instance details

Defined in Test.Util.TestBlock

Show (Ticked (f a)) ⇒ Show (((TickedTypeType) :.: f) a) 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecInt → ((TickedTypeType) :.: f) a → ShowS #

show ∷ ((TickedTypeType) :.: f) a → String #

showList ∷ [((TickedTypeType) :.: f) a] → ShowS #

NoThunks (Ticked (f a)) ⇒ NoThunks (((TickedTypeType) :.: f) a) 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

noThunksContext → ((TickedTypeType) :.: f) a → IO (Maybe ThunkInfo) Source #

wNoThunksContext → ((TickedTypeType) :.: f) a → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (((TickedTypeType) :.: f) a) → String Source #

data Ticked () 
Instance details

Defined in Ouroboros.Consensus.Ticked

data Ticked (HardForkChainDepState xs ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

data Ticked (HeaderState blk ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

data Ticked (PBftState c ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

newtype Ticked (WrapChainDepState blk ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

type HeaderHash (Ticked l ∷ k) 
Instance details

Defined in Ouroboros.Consensus.Ticked

type HeaderHash (Ticked l ∷ k) = HeaderHash l
type TxIn (Ticked l) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type TxIn (Ticked l) = TxIn l
type TxOut (Ticked l) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type TxOut (Ticked l) = TxOut l
data Ticked (LedgerState (HardForkBlock xs) ∷ MapKindType) (mk ∷ MapKind) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

data Ticked (LedgerState (DualBlock m a) ∷ MapKindType) (mk ∷ MapKind) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

newtype Ticked (LedgerState (TestBlockWith ptype) ∷ MapKindType) (mk ∷ MapKind) Source # 
Instance details

Defined in Test.Util.TestBlock

data Ticked (ExtLedgerState blk ∷ MapKindType) (mk ∷ MapKind) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) = D1 ('MetaData "Ticked" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'True) (C1 ('MetaCons "TickedTestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTickedTestLedger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerState (TestBlockWith ptype) mk))))

getTickedTestLedger ∷ ∀ ptype (mk ∷ MapKind). Ticked (LedgerState (TestBlockWith ptype)) mk → LedgerState (TestBlockWith ptype) mk Source #

Chain

newtype BlockChain Source #

Constructors

BlockChain Word64 

Instances

Instances details
Arbitrary BlockChain Source # 
Instance details

Defined in Test.Util.TestBlock

Show BlockChain Source # 
Instance details

Defined in Test.Util.TestBlock

Tree

newtype BlockTree Source #

Constructors

BlockTree (Tree ()) 

Instances

Instances details
Arbitrary BlockTree Source # 
Instance details

Defined in Test.Util.TestBlock

Show BlockTree Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showsPrecIntBlockTreeShowS #

showBlockTreeString #

showList ∷ [BlockTree] → ShowS #

Ledger infrastructure

singleNodeTestConfigTopLevelConfig TestBlock Source #

Trivial test configuration with a single core node

Support for tests

newtype Permutation Source #

Constructors

Permutation Int 

Instances

Instances details
Arbitrary Permutation Source # 
Instance details

Defined in Test.Util.TestBlock

Show Permutation Source # 
Instance details

Defined in Test.Util.TestBlock

data TestBlockLedgerConfig Source #

Constructors

TestBlockLedgerConfig 

Fields

Instances

Instances details
Generic TestBlockLedgerConfig Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep TestBlockLedgerConfig 
Instance details

Defined in Test.Util.TestBlock

type Rep TestBlockLedgerConfig = D1 ('MetaData "TestBlockLedgerConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockLedgerConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "tblcHardForkParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EraParams) :*: S1 ('MetaSel ('Just "tblcForecastRange") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe SlotNo))))
Show TestBlockLedgerConfig Source # 
Instance details

Defined in Test.Util.TestBlock

Eq TestBlockLedgerConfig Source # 
Instance details

Defined in Test.Util.TestBlock

NoThunks TestBlockLedgerConfig Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep TestBlockLedgerConfig Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep TestBlockLedgerConfig = D1 ('MetaData "TestBlockLedgerConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockLedgerConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "tblcHardForkParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EraParams) :*: S1 ('MetaSel ('Just "tblcForecastRange") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe SlotNo))))

isAncestorOfTestBlockTestBlockBool Source #

A block b1 is the ancestor of another block b2 if there exists a chain of blocks from b1 to b2. For test blocks in particular, this can be seen in the hash: the hash of b1 should be a prefix of the hash of b2.

Note that this is a partial comparison function. In particular, it does hold that for all b1 and b2, b1 isDescendentOf b2 === b2 isAncestorOf b1 but it does not hold that for all b1 and b2, b1 isDescendentOf b2 === not (b1 isAncestorOf b2) || b1 == b2.

isDescendentOfTestBlockTestBlockBool Source #

A block b1 is the descendent of another block b2 if there exists a chain of blocks from b2 to b1. For test blocks in particular, this can be seen in the hash: the hash of b2 should be a prefix of the hash of b1.

Note that this is a partial comparison function. In particular, it does hold that for all b1 and b2, b1 isDescendentOf b2 === b2 isAncestorOf b1 but it does not hold that for all b1 and b2, b1 isDescendentOf b2 === not (b1 isAncestorOf b2) || b1 == b2.

isStrictAncestorOfTestBlockTestBlockBool Source #

Variant of isAncestorOf that returns False when the two blocks are equal.

isStrictDescendentOfTestBlockTestBlockBool Source #

Variant of isDescendentOf that returns False when the two blocks are equal.

permutePermutation → [a] → [a] Source #

unsafeTestBlockWithPayloadTestHashSlotNoValidity → ptype → TestBlockWith ptype Source #

Create a block directly with the given parameters. This allows creating inconsistent blocks; prefer firstBlockWithPayload or successorBlockWithPayload.

updateToNextNumeralRealPoint TestBlock → (Point TestBlock, NonEmpty TestBlock) Source #

Given a point to a chain of length L, generates a SwitchFork that switches to the "next" block of length L, where "next" is determined by interpreting the "forks" in the TestHash as binary digits (except the deepest, which is a simple counter).

For example, the following are input and outputs for a chains of length 3, where the TestHashes and Points are denoted by numerals (the SlotNo is merely the number of digits).

000 :-> [RollBack 00, AddBlock 001]
001 :-> [RollBack 0 , AddBlock 01 , AddBlock 010]
010 :-> [RollBack 01, AddBlock 011]
011 :-> [RollBack G , AddBlock 1  , AddBlock 10 , AddBlock 100]

100 :-> [RollBack 10, AddBlock 101]
101 :-> [RollBack 1 , AddBlock 11 , AddBlock 110]
110 :-> [RollBack 11, AddBlock 111]
111 :-> [RollBack G , AddBlock 2  , AddBlock 20 , AddBlock 200]

200 :-> [RollBack 20, AddBlock 201]
201 :-> [RollBack 2 , AddBlock 21 , AddBlock 210]
210 :-> [RollBack 21, AddBlock 211]
211 :-> [RollBack G , AddBlock 3  , AddBlock 30 , AddBlock 300]

etc