storage-test
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.Ouroboros.Storage.TestBlock

Synopsis

Test block

data family BlockConfig blk Source #

Static configuration required to work with this type of blocks

Instances

Instances details
Generic (BlockConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Associated Types

type Rep (BlockConfig TestBlock) ∷ TypeType #

Generic (BlockConfig (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (BlockConfig (TestBlockWith ptype)) ∷ TypeType #

Methods

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

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

Show (BlockConfig (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

NoThunks (BlockConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

NoThunks (BlockConfig (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

data BlockConfig TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep (BlockConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep (BlockConfig TestBlock) = D1 ('MetaData "BlockConfig" "Test.Ouroboros.Storage.TestBlock" "main" 'False) (C1 ('MetaCons "TestBlockConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "testBlockEBBsAllowed") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "testBlockNumCoreNodes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NumCoreNodes)))
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.18.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) 
Instance details

Defined in Test.Util.TestBlock

newtype ChainLength Source #

In chain selection, we use BlockNo as a proxy for the block length. This is entirely correct, except for those dreadful EBBs, which share their block number with their predecessor. So it is possible that two chains with the same BlockNo at the tip have a different length because the longer chain contains more EBBs than the shorter.

For example:

.. :> EBB (100, slotNo 10, blockNo 1) :> (400, slotNo 10, blockNo 2)
.. :> (999, slotNo 10, blockNo 2)

The chain selection for this TestBlock looks at the hashes in case of a BlockNo tie (after prefering the chain ending with an EBB) and will pick the block with the highest hash. This is to have a more deterministic chain selection (less implementation specific) which will keep the model better in sync with the implementation.

In the example above, that would mean picking the second chain, /even though it is shorter/! The implementation does not support switching to a shorter chain.

Note that this is not a problem for Byron, because we don't look at the hashes or anything else in case of a tie (we just prefer a chain ending with an EBB, which must be longer).

Note that is not a problem for Shelley either, where we do look at the certificate number and VRF hash in case of a tie, because there are no EBBs.

This is only an issue when: * There can be EBBs in the chain * In case of equal blockNos, we still prefer one over the other because of some additional condition.

Which is the case for this TestBlock.

To solve this, we store the real chain length inside the block. The only difference with the BlockNo is that ChainLength takes EBBs into account.

When there is BlockNo tie as in the example above and we would look at the hashes, we will first look at the ChainLength (and prefer the longest one). Only if that is equal do we actually look at the hashes. This guarantees that we never prefer a chain that is shorter.

NOTE: we start counting from 1 (unlike BlockNo, which starts from 0), because it corresponds to the length.

Constructors

ChainLength Int 

Instances

Instances details
Enum ChainLength Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Generic ChainLength Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Associated Types

type Rep ChainLengthTypeType #

Show ChainLength Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Eq ChainLength Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Ord ChainLength Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Hashable ChainLength Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

NoThunks ChainLength Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Serialise ChainLength Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

ToExpr ChainLength Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep ChainLength Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep ChainLength = D1 ('MetaData "ChainLength" "Test.Ouroboros.Storage.TestBlock" "main" 'True) (C1 ('MetaCons "ChainLength" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

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
Generic (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Associated Types

type Rep (CodecConfig TestBlock) ∷ TypeType #

Generic (CodecConfig TestBlock) 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (CodecConfig TestBlock) ∷ TypeType #

Show (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Show (CodecConfig TestBlock) 
Instance details

Defined in Test.Util.TestBlock

NoThunks (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

NoThunks (CodecConfig TestBlock) 
Instance details

Defined in Test.Util.TestBlock

ToExpr (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

data CodecConfig TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

data CodecConfig TestBlock

The TestBlock does not need any codec config

Instance details

Defined in Test.Util.TestBlock

type Rep (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep (CodecConfig TestBlock) = D1 ('MetaData "CodecConfig" "Test.Ouroboros.Storage.TestBlock" "main" 'False) (C1 ('MetaCons "TestBlockCodecConfig" 'PrefixI 'False) (U1TypeType))
type Rep (CodecConfig TestBlock) 
Instance details

Defined in Test.Util.TestBlock

type Rep (CodecConfig TestBlock) = D1 ('MetaData "CodecConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.18.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 EBB Source #

Strict variant of Maybe EpochNo

Constructors

EBB !EpochNo 
RegularBlock 

Instances

Instances details
Generic EBB Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Associated Types

type Rep EBBTypeType #

Methods

fromEBBRep EBB x #

toRep EBB x → EBB #

Show EBB Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Methods

showsPrecIntEBBShowS #

showEBBString #

showList ∷ [EBB] → ShowS #

Eq EBB Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Methods

(==)EBBEBBBool #

(/=)EBBEBBBool #

Hashable EBB Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Methods

hashWithSaltIntEBBInt Source #

hashEBBInt Source #

NoThunks EBB Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Serialise EBB Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

ToExpr EBB Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Methods

toExprEBBExpr Source #

listToExpr ∷ [EBB] → Expr Source #

type Rep EBB Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep EBB = D1 ('MetaData "EBB" "Test.Ouroboros.Storage.TestBlock" "main" 'False) (C1 ('MetaCons "EBB" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EpochNo)) :+: C1 ('MetaCons "RegularBlock" 'PrefixI 'False) (U1TypeType))

data family Header blk Source #

Instances

Instances details
ReconstructNestedCtxt Header TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

EncodeDisk TestBlock (Header TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

ReconstructNestedCtxt Header (TestBlockWith ptype) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Block.Abstract

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

Defined in Test.Util.TestBlock

Methods

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

DecodeDisk TestBlock (ByteStringHeader TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Show (Header TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

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

Defined in Test.Util.TestBlock

Methods

showsPrecIntHeader (TestBlockWith ptype) → ShowS #

showHeader (TestBlockWith ptype) → String #

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

Eq (Header TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

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

Defined in Test.Util.TestBlock

Methods

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

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

NoThunks (Header TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

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

Defined in Test.Util.TestBlock

SignedHeader (Header TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

SignedHeader (Header (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

Methods

condenseHeader (TestBlockWith ptype) → String Source #

HasHeader (Header TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

(Typeable ptype, Eq ptype) ⇒ HasHeader (Header (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

Serialise (Header TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

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

Defined in Test.Util.TestBlock

DecodeDiskDep (NestedCtxt Header) TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

DecodeDiskDepIx (NestedCtxt Header) TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

EncodeDiskDep (NestedCtxt Header) TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

EncodeDiskDepIx (NestedCtxt Header) TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Serialise ptype ⇒ DecodeDiskDep (NestedCtxt Header) (TestBlockWith ptype) 
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)) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

Methods

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

newtype Header TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

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

Defined in Test.Util.TestBlock

type Signed (Header TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Signed (Header TestBlock) = ()
type Signed (Header (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

type Signed (Header (TestBlockWith ptype)) = ()

data family StorageConfig blk Source #

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

Instances

Instances details
Generic (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Associated Types

type Rep (StorageConfig TestBlock) ∷ TypeType #

Generic (StorageConfig TestBlock) 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (StorageConfig TestBlock) ∷ TypeType #

Show (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Show (StorageConfig TestBlock) 
Instance details

Defined in Test.Util.TestBlock

NoThunks (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

NoThunks (StorageConfig TestBlock) 
Instance details

Defined in Test.Util.TestBlock

data StorageConfig TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

data StorageConfig TestBlock

The TestBlock does not need any storage config

Instance details

Defined in Test.Util.TestBlock

type Rep (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep (StorageConfig TestBlock) = D1 ('MetaData "StorageConfig" "Test.Ouroboros.Storage.TestBlock" "main" 'False) (C1 ('MetaCons "TestBlockStorageConfig" 'PrefixI 'False) (U1TypeType))
type Rep (StorageConfig TestBlock) 
Instance details

Defined in Test.Util.TestBlock

type Rep (StorageConfig TestBlock) = D1 ('MetaData "StorageConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.18.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 TestBlock Source #

Constructors

TestBlock 

Instances

Instances details
Generic TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Associated Types

type Rep TestBlockTypeType #

Methods

fromTestBlockRep TestBlock x #

toRep TestBlock x → TestBlock #

Show TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Methods

showsPrecIntTestBlockShowS #

showTestBlockString #

showList ∷ [TestBlock] → ShowS #

Eq TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Methods

(==)TestBlockTestBlockBool #

(/=)TestBlockTestBlockBool #

ModelSupportsBlock TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

NoThunks TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

ConvertRawHash TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

GetHeader TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

GetPrevHash TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

BlockSupportsDiffusionPipelining TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

BlockSupportsProtocol TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

HasHardForkHistory TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Associated Types

type HardForkIndices TestBlock ∷ [Type] Source #

BasicEnvelopeValidation TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

HasAnnTip TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Associated Types

type TipInfo TestBlock Source #

ValidateEnvelope TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

UpdateLedger TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

InspectLedger TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

LedgerSupportsProtocol TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

SerialiseDiskConstraints TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

HasBinaryBlockInfo TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Condense TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

HasHeader TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Serialise TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

ToExpr TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

HasNestedContent f TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

DecodeDisk TestBlock () Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Methods

decodeDiskCodecConfig TestBlock → ∀ s. Decoder s () Source #

EncodeDisk TestBlock TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

EncodeDisk TestBlock () Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

ReconstructNestedCtxt Header TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

StandardHash TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

DecodeDisk TestBlock (AnnTip TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

DecodeDisk TestBlock (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

EncodeDisk TestBlock (Header TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

EncodeDisk TestBlock (AnnTip TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

EncodeDisk TestBlock (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

DecodeDisk TestBlock (ByteStringTestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

DecodeDisk TestBlock (ByteStringHeader TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Generic (BlockConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Associated Types

type Rep (BlockConfig TestBlock) ∷ TypeType #

Generic (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Associated Types

type Rep (CodecConfig TestBlock) ∷ TypeType #

Generic (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Associated Types

type Rep (StorageConfig TestBlock) ∷ TypeType #

Generic (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Associated Types

type Rep (LedgerState TestBlock) ∷ TypeType #

Show (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Show (Header TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Show (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Show (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Eq (Header TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Eq (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

NoThunks (BlockConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

NoThunks (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

NoThunks (Header TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

NoThunks (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

NoThunks (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

GetTip (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

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

Defined in Test.Ouroboros.Storage.TestBlock

IsLedger (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

SignedHeader (Header TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

HasHeader (Header TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Serialise (Header TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Serialise (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

ToExpr (DBModel TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.ImmutableDB.Model

ToExpr (InSlot TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.ImmutableDB.Model

ToExpr (IteratorModel TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.ImmutableDB.Model

ToExpr (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

ToExpr (HeaderEnvelopeError TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

ToExpr (HeaderError TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

ToExpr (TipInfoIsEBB TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

ToExpr (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

ToExpr (ExtValidationError TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

ToExpr (Tip TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

ApplyBlock (LedgerState TestBlock) TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

DecodeDiskDep (NestedCtxt Header) TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

DecodeDiskDepIx (NestedCtxt Header) TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

EncodeDiskDep (NestedCtxt Header) TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

EncodeDiskDepIx (NestedCtxt Header) TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

SameDepIndex (NestedCtxt_ TestBlock f) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

TrivialDependency (NestedCtxt_ TestBlock f) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Associated Types

type TrivialIndex (NestedCtxt_ TestBlock f) Source #

Show (NestedCtxt_ TestBlock f a) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep TestBlock = D1 ('MetaData "TestBlock" "Test.Ouroboros.Storage.TestBlock" "main" 'False) (C1 ('MetaCons "TestBlock" 'PrefixI 'True) (S1 ('MetaSel ('Just "testHeader") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TestHeader) :*: S1 ('MetaSel ('Just "testBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TestBody)))
data BlockConfig TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type BlockProtocol TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

data CodecConfig TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

newtype Header TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

data StorageConfig TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

data NestedCtxt_ TestBlock f a Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

data NestedCtxt_ TestBlock f a where
type TentativeHeaderState TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type TentativeHeaderView TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type HardForkIndices TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type OtherHeaderEnvelopeError TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type TipInfo TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

data LedgerState TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type LedgerUpdate TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type LedgerWarning TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type HeaderHash TestBlock Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep (BlockConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep (BlockConfig TestBlock) = D1 ('MetaData "BlockConfig" "Test.Ouroboros.Storage.TestBlock" "main" 'False) (C1 ('MetaCons "TestBlockConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "testBlockEBBsAllowed") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "testBlockNumCoreNodes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NumCoreNodes)))
type Rep (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep (CodecConfig TestBlock) = D1 ('MetaData "CodecConfig" "Test.Ouroboros.Storage.TestBlock" "main" 'False) (C1 ('MetaCons "TestBlockCodecConfig" 'PrefixI 'False) (U1TypeType))
type Rep (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep (StorageConfig TestBlock) = D1 ('MetaData "StorageConfig" "Test.Ouroboros.Storage.TestBlock" "main" 'False) (C1 ('MetaCons "TestBlockStorageConfig" 'PrefixI 'False) (U1TypeType))
type Rep (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep (LedgerState TestBlock) = D1 ('MetaData "LedgerState" "Test.Ouroboros.Storage.TestBlock" "main" 'False) (C1 ('MetaCons "TestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "lastAppliedPoint") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Point TestBlock)) :*: S1 ('MetaSel ('Just "lastAppliedHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ChainHash TestBlock))))
type AuxLedgerEvent (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type LedgerCfg (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type LedgerErr (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Signed (Header TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Signed (Header TestBlock) = ()
newtype Ticked (LedgerState TestBlock) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type TrivialIndex (NestedCtxt_ TestBlock f) Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

data TestBody Source #

Constructors

TestBody 

Fields

  • tbForkNo ∷ !Word

    If we don't have something that can vary per block, we're not generating forks, except when skipping slots. For example, when we want to have multiple different valid successor blocks created in the same slot, all fields in the header and body will be the same. Consequently, the hashes will also be the same, so we don't have different blocks after all. By using a different tbForkNo for each block, we have different bodies, and thus different hashes.

    Note that this is a local number, it is specific to this block, other blocks need not be aware of it.

  • tbIsValid ∷ !Bool
     

Instances

Instances details
Generic TestBody Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Associated Types

type Rep TestBodyTypeType #

Methods

fromTestBodyRep TestBody x #

toRep TestBody x → TestBody #

Show TestBody Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Methods

showsPrecIntTestBodyShowS #

showTestBodyString #

showList ∷ [TestBody] → ShowS #

Eq TestBody Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Methods

(==)TestBodyTestBodyBool #

(/=)TestBodyTestBodyBool #

Hashable TestBody Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

NoThunks TestBody Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Serialise TestBody Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

ToExpr TestBody Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep TestBody Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep TestBody = D1 ('MetaData "TestBody" "Test.Ouroboros.Storage.TestBlock" "main" 'False) (C1 ('MetaCons "TestBody" 'PrefixI 'True) (S1 ('MetaSel ('Just "tbForkNo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word) :*: S1 ('MetaSel ('Just "tbIsValid") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)))

newtype TestBodyHash Source #

Hash of a TestBody

Constructors

TestBodyHash Int 

Instances

Instances details
Generic TestBodyHash Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Associated Types

type Rep TestBodyHashTypeType #

Show TestBodyHash Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Eq TestBodyHash Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Ord TestBodyHash Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Hashable TestBodyHash Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

NoThunks TestBodyHash Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Condense TestBodyHash Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Serialise TestBodyHash Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

ToExpr TestBodyHash Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep TestBodyHash Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep TestBodyHash = D1 ('MetaData "TestBodyHash" "Test.Ouroboros.Storage.TestBlock" "main" 'True) (C1 ('MetaCons "TestBodyHash" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

data TestHeader Source #

Constructors

TestHeader 

Fields

Instances

Instances details
Generic TestHeader Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Associated Types

type Rep TestHeaderTypeType #

Show TestHeader Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Eq TestHeader Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Methods

(==)TestHeaderTestHeaderBool #

(/=)TestHeaderTestHeaderBool #

NoThunks TestHeader Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Condense TestHeader Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Serialise TestHeader Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

ToExpr TestHeader Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

StandardHash TestHeader Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep TestHeader Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type HeaderHash TestHeader Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

newtype TestHeaderHash Source #

Hash of a TestHeader

Constructors

TestHeaderHash Int 

Instances

Instances details
Generic TestHeaderHash Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Associated Types

type Rep TestHeaderHashTypeType #

Show TestHeaderHash Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Binary TestHeaderHash Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Eq TestHeaderHash Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Ord TestHeaderHash Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Hashable TestHeaderHash Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

NoThunks TestHeaderHash Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Condense TestHeaderHash Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Serialise TestHeaderHash Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

ToExpr TestHeaderHash Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep TestHeaderHash Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep TestHeaderHash = D1 ('MetaData "TestHeaderHash" "Test.Ouroboros.Storage.TestBlock" "main" 'True) (C1 ('MetaCons "TestHeaderHash" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))

Construction

firstBlockSlotNoTestBodyTestBlock Source #

Note the first block need not be an EBB, see firstEBB.

mkBlock Source #

Arguments

HasCallStack 
⇒ (SlotNoBool)

Is this slot allowed contain an EBB?

This argument is used primarily to detect the generation of invalid blocks with different kind of ChunkInfo.

TestBody 
ChainHash TestHeader

Hash of previous header

SlotNo 
BlockNo 
ChainLength 
Maybe EpochNo 
TestBlock 

mkNextBlock Source #

Arguments

TestBlock

Previous block

SlotNo 
TestBody 
TestBlock 

Variant of mkNextBlock that takes the entire previous block.

mkNextBlock' Source #

Arguments

∷ (HeaderFields TestBlock, ChainLength)

Information about the previous block

SlotNo 
TestBody 
TestBlock 

mkNextEBB Source #

Arguments

∷ (SlotNoBool) 
TestBlock

Previous block

SlotNo 
EpochNo 
TestBody 
TestBlock 

Variant of mkNextEBB that takes the entire previous block.

mkNextEBB' Source #

Arguments

∷ (SlotNoBool) 
→ (HeaderFields TestBlock, ChainLength)

Information about the previous block

SlotNo 
EpochNo 
TestBody 
TestBlock 

Note that in various places, e.g., the ImmutableDB, we rely on the fact that the slotNo should correspond to the first slot number of the epoch, as is the case for real EBBs.

Query

testBlockIsValidTestBlockBool Source #

Check whether the header matches its hash and whether the body matches its hash.

Serialisation

Ledger

data TestBlockError Source #

Constructors

InvalidHash

The hashes don't line up

Fields

InvalidBlock

The block itself is invalid

Instances

Instances details
Generic TestBlockError Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Associated Types

type Rep TestBlockErrorTypeType #

Show TestBlockError Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Eq TestBlockError Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

NoThunks TestBlockError Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

ToExpr TestBlockError Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep TestBlockError Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep TestBlockError = D1 ('MetaData "TestBlockError" "Test.Ouroboros.Storage.TestBlock" "main" 'False) (C1 ('MetaCons "InvalidHash" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ChainHash TestBlock)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ChainHash TestBlock))) :+: C1 ('MetaCons "InvalidBlock" 'PrefixI 'False) (U1TypeType))

data TestBlockOtherHeaderEnvelopeError Source #

Instances

Instances details
Generic TestBlockOtherHeaderEnvelopeError Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Associated Types

type Rep TestBlockOtherHeaderEnvelopeErrorTypeType #

Show TestBlockOtherHeaderEnvelopeError Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

Eq TestBlockOtherHeaderEnvelopeError Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

NoThunks TestBlockOtherHeaderEnvelopeError Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

ToExpr TestBlockOtherHeaderEnvelopeError Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep TestBlockOtherHeaderEnvelopeError Source # 
Instance details

Defined in Test.Ouroboros.Storage.TestBlock

type Rep TestBlockOtherHeaderEnvelopeError = D1 ('MetaData "TestBlockOtherHeaderEnvelopeError" "Test.Ouroboros.Storage.TestBlock" "main" 'False) (C1 ('MetaCons "UnexpectedEBBInSlot" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo)))

Corruptions

type Corruptions = NonEmpty (FileCorruption, FsPath) Source #

Multiple corruptions

data FileCorruption Source #

Constructors

DeleteFile 
DropLastBytes Word64

Drop the last n bytes of a file.

Corrupt Word64

Corrupt the file by adding 1 to the byte at the given location (modulo the file size).

corruptFileMonadThrow m ⇒ HasFS m h → FileCorruptionFsPath → m Bool Source #

Returns True when something was actually corrupted. For example, when drop the last bytes of an empty file, we don't actually corrupt it.

corruptionFilesCorruptions → [FsPath] Source #

Return a list of all files that will be corrupted

generateCorruptionsNonEmpty FsPathGen Corruptions Source #

The same file will not occur twice.

Orphan instances

Hashable BlockNo Source # 
Instance details

Methods

hashWithSaltIntBlockNoInt Source #

hashBlockNoInt Source #

Hashable SlotNo Source # 
Instance details

Methods

hashWithSaltIntSlotNoInt Source #

hashSlotNoInt Source #

Hashable IsEBB Source # 
Instance details

Methods

hashWithSaltIntIsEBBInt Source #

hashIsEBBInt Source #

ToExpr FsPath Source # 
Instance details

ToExpr IsEBB Source # 
Instance details

Methods

toExprIsEBBExpr Source #

listToExpr ∷ [IsEBB] → Expr Source #

ToExpr BftValidationErr Source # 
Instance details

ToExpr BinaryBlockInfo Source # 
Instance details

ToExpr BlocksPerFile Source # 
Instance details

(StandardHash b, Hashable (HeaderHash b)) ⇒ Hashable (ChainHash b) Source # 
Instance details

Methods

hashWithSaltIntChainHash b → Int Source #

hashChainHash b → Int Source #