Safe Haskell | None |
---|---|
Language | Haskell2010 |
Test.Ouroboros.Storage.TestBlock
Synopsis
- data family BlockConfig blk
- newtype ChainLength = ChainLength Int
- data family CodecConfig blk
- data EBB
- = EBB !EpochNo
- | RegularBlock
- data family Header blk
- data family StorageConfig blk
- data TestBlock = TestBlock {}
- data TestBody = TestBody {}
- newtype TestBodyHash = TestBodyHash Int
- data TestHeader = TestHeader {}
- newtype TestHeaderHash = TestHeaderHash Int
- firstBlock ∷ SlotNo → TestBody → TestBlock
- firstEBB ∷ (SlotNo → Bool) → TestBody → TestBlock
- mkBlock ∷ HasCallStack ⇒ (SlotNo → Bool) → TestBody → ChainHash TestHeader → SlotNo → BlockNo → ChainLength → Maybe EpochNo → TestBlock
- mkNextBlock ∷ TestBlock → SlotNo → TestBody → TestBlock
- mkNextBlock' ∷ (HeaderFields TestBlock, ChainLength) → SlotNo → TestBody → TestBlock
- mkNextEBB ∷ (SlotNo → Bool) → TestBlock → SlotNo → EpochNo → TestBody → TestBlock
- mkNextEBB' ∷ (SlotNo → Bool) → (HeaderFields TestBlock, ChainLength) → SlotNo → EpochNo → TestBody → TestBlock
- testBlockChainLength ∷ TestBlock → ChainLength
- testBlockIsEBB ∷ TestBlock → IsEBB
- testBlockIsValid ∷ TestBlock → Bool
- testBlockFromLazyByteString ∷ HasCallStack ⇒ ByteString → TestBlock
- testBlockToBuilder ∷ TestBlock → Builder
- testBlockToLazyByteString ∷ TestBlock → ByteString
- data TestBlockError
- data TestBlockOtherHeaderEnvelopeError = UnexpectedEBBInSlot !SlotNo
- mkTestConfig ∷ SecurityParam → ChunkSize → TopLevelConfig TestBlock
- testInitExtLedger ∷ ExtLedgerState TestBlock EmptyMK
- type Corruptions = NonEmpty (FileCorruption, FsPath)
- data FileCorruption
- corruptFile ∷ MonadThrow m ⇒ HasFS m h → FileCorruption → FsPath → m Bool
- corruptionFiles ∷ Corruptions → [FsPath]
- generateCorruptions ∷ NonEmpty FsPath → Gen Corruptions
- shrinkCorruptions ∷ Corruptions → [Corruptions]
Test block
data family BlockConfig blk Source #
Static configuration required to work with this type of blocks
Instances
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 blockNo
s, 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
Enum ChainLength Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Methods succ ∷ ChainLength → ChainLength # pred ∷ ChainLength → ChainLength # toEnum ∷ Int → ChainLength # fromEnum ∷ ChainLength → Int # enumFrom ∷ ChainLength → [ChainLength] # enumFromThen ∷ ChainLength → ChainLength → [ChainLength] # enumFromTo ∷ ChainLength → ChainLength → [ChainLength] # enumFromThenTo ∷ ChainLength → ChainLength → ChainLength → [ChainLength] # | |||||
Generic ChainLength Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Associated Types
| |||||
Show ChainLength Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Methods showsPrec ∷ Int → ChainLength → ShowS # show ∷ ChainLength → String # showList ∷ [ChainLength] → ShowS # | |||||
Eq ChainLength Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
Ord ChainLength Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Methods compare ∷ ChainLength → ChainLength → Ordering # (<) ∷ ChainLength → ChainLength → Bool # (<=) ∷ ChainLength → ChainLength → Bool # (>) ∷ ChainLength → ChainLength → Bool # (>=) ∷ ChainLength → ChainLength → Bool # max ∷ ChainLength → ChainLength → ChainLength # min ∷ ChainLength → ChainLength → ChainLength # | |||||
Hashable ChainLength Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
NoThunks ChainLength Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
Serialise ChainLength Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Methods encode ∷ ChainLength → Encoding Source # decode ∷ Decoder s ChainLength Source # encodeList ∷ [ChainLength] → Encoding Source # decodeList ∷ Decoder s [ChainLength] Source # | |||||
ToExpr ChainLength Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
type Rep ChainLength Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock type Rep ChainLength = D1 ('MetaData "ChainLength" "Test.Ouroboros.Storage.TestBlock" "ouroboros-consensus-0.27.0.0-inplace-storage-test" 'True) (C1 ('MetaCons "ChainLength" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe 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
Isomorphic CodecConfig | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary Methods project ∷ NoHardForks blk ⇒ CodecConfig (HardForkBlock '[blk]) → CodecConfig blk Source # inject ∷ NoHardForks blk ⇒ CodecConfig blk → CodecConfig (HardForkBlock '[blk]) Source # | |||||
Generic (CodecConfig (DualBlock m a)) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual Associated Types
Methods from ∷ CodecConfig (DualBlock m a) → Rep (CodecConfig (DualBlock m a)) x # to ∷ Rep (CodecConfig (DualBlock m a)) x → CodecConfig (DualBlock m a) # | |||||
Generic (CodecConfig TestBlock) Source # | |||||
Defined in Test.Ouroboros.Storage.LedgerDB.StateMachine.TestBlock Associated Types
Methods from ∷ CodecConfig TestBlock → Rep (CodecConfig TestBlock) x # to ∷ Rep (CodecConfig TestBlock) x → CodecConfig TestBlock # | |||||
Generic (CodecConfig TestBlock) Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Associated Types
Methods from ∷ CodecConfig TestBlock → Rep (CodecConfig TestBlock) x # to ∷ Rep (CodecConfig TestBlock) x → CodecConfig TestBlock # | |||||
Generic (CodecConfig TestBlock) | |||||
Defined in Test.Util.TestBlock Associated Types
Methods from ∷ CodecConfig TestBlock → Rep (CodecConfig TestBlock) x # to ∷ Rep (CodecConfig TestBlock) x → CodecConfig TestBlock # | |||||
Show (CodecConfig TestBlock) Source # | |||||
Show (CodecConfig TestBlock) Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
Show (CodecConfig TestBlock) | |||||
Defined in Test.Util.TestBlock | |||||
CanHardFork xs ⇒ NoThunks (CodecConfig (HardForkBlock xs)) | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Methods noThunks ∷ Context → CodecConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → CodecConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (CodecConfig (HardForkBlock xs)) → String Source # | |||||
(NoThunks (CodecConfig m), NoThunks (CodecConfig a)) ⇒ NoThunks (CodecConfig (DualBlock m a)) | |||||
NoThunks (CodecConfig TestBlock) Source # | |||||
NoThunks (CodecConfig TestBlock) Source # | |||||
NoThunks (CodecConfig TestBlock) | |||||
ToExpr (CodecConfig TestBlock) Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Methods toExpr ∷ CodecConfig TestBlock → Expr Source # listToExpr ∷ [CodecConfig TestBlock] → Expr Source # | |||||
data CodecConfig TestBlock Source # | TODO: for the time being | ||||
data CodecConfig TestBlock Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
data CodecConfig TestBlock | The | ||||
Defined in Test.Util.TestBlock | |||||
type Rep (CodecConfig (DualBlock m a)) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual type Rep (CodecConfig (DualBlock m a)) = D1 ('MetaData "CodecConfig" "Ouroboros.Consensus.Ledger.Dual" "ouroboros-consensus-0.27.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 # | |||||
type Rep (CodecConfig TestBlock) Source # | |||||
type Rep (CodecConfig TestBlock) | |||||
newtype CodecConfig (HardForkBlock xs) | |||||
data CodecConfig (DualBlock m a) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual data CodecConfig (DualBlock m a) = DualCodecConfig {
|
Strict variant of Maybe EpochNo
Constructors
EBB !EpochNo | |
RegularBlock |
Instances
Generic EBB Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Associated Types
| |||||
Show EBB Source # | |||||
Eq EBB Source # | |||||
Hashable EBB Source # | |||||
NoThunks EBB Source # | |||||
Serialise EBB Source # | |||||
ToExpr EBB Source # | |||||
type Rep EBB Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock type Rep EBB = D1 ('MetaData "EBB" "Test.Ouroboros.Storage.TestBlock" "ouroboros-consensus-0.27.0.0-inplace-storage-test" 'False) (C1 ('MetaCons "EBB" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EpochNo)) :+: C1 ('MetaCons "RegularBlock" 'PrefixI 'False) (U1 ∷ Type → Type)) |
data family Header blk Source #
Instances
GetHeader1 Header | |
Defined in Ouroboros.Consensus.Block.Abstract Methods getHeader1 ∷ Header blk → Header blk Source # | |
Inject Header | |
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 | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary Methods project ∷ NoHardForks blk ⇒ Header (HardForkBlock '[blk]) → Header blk Source # inject ∷ NoHardForks blk ⇒ Header blk → Header (HardForkBlock '[blk]) Source # | |
ReconstructNestedCtxt Header TestBlock Source # | |
Defined in Test.Ouroboros.Storage.TestBlock Methods reconstructPrefixLen ∷ proxy (Header TestBlock) → PrefixLen Source # reconstructNestedCtxt ∷ proxy (Header TestBlock) → ShortByteString → SizeInBytes → SomeSecond (NestedCtxt Header) TestBlock Source # | |
EncodeDisk TestBlock (Header TestBlock) Source # | |
Defined in Test.Ouroboros.Storage.TestBlock Methods encodeDisk ∷ CodecConfig TestBlock → Header TestBlock → Encoding Source # | |
ReconstructNestedCtxt Header (TestBlockWith ptype) | |
Defined in Test.Util.TestBlock Methods reconstructPrefixLen ∷ proxy (Header (TestBlockWith ptype)) → PrefixLen Source # reconstructNestedCtxt ∷ proxy (Header (TestBlockWith ptype)) → ShortByteString → SizeInBytes → SomeSecond (NestedCtxt Header) (TestBlockWith ptype) Source # | |
StandardHash blk ⇒ StandardHash (Header blk ∷ Type) | |
Defined in Ouroboros.Consensus.Block.Abstract | |
Typeable ptype ⇒ ShowProxy (Header (TestBlockWith ptype) ∷ Type) | |
Defined in Test.Util.TestBlock | |
HasNestedContent Header m ⇒ HasNestedContent Header (DualBlock m a) | |
DecodeDisk TestBlock (ByteString → Header TestBlock) Source # | |
Defined in Test.Ouroboros.Storage.TestBlock Methods decodeDisk ∷ CodecConfig TestBlock → ∀ s. Decoder s (ByteString → Header TestBlock) Source # | |
ReconstructNestedCtxt Header m ⇒ ReconstructNestedCtxt Header (DualBlock m a) | |
Defined in Ouroboros.Consensus.Ledger.Dual Methods reconstructPrefixLen ∷ proxy (Header (DualBlock m a)) → PrefixLen Source # reconstructNestedCtxt ∷ proxy (Header (DualBlock m a)) → ShortByteString → SizeInBytes → SomeSecond (NestedCtxt Header) (DualBlock m a) Source # | |
(Typeable m, Typeable a) ⇒ ShowProxy (DualHeader m a ∷ Type) | |
Defined in Ouroboros.Consensus.Ledger.Dual | |
Show (Header TestBlock) Source # | |
Show ptype ⇒ Show (Header (TestBlockWith ptype)) | |
Defined in Test.Util.TestBlock | |
Eq (Header TestBlock) Source # | |
Eq ptype ⇒ Eq (Header (TestBlockWith ptype)) | |
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)) | |
NoThunks (Header TestBlock) Source # | |
NoThunks ptype ⇒ NoThunks (Header (TestBlockWith ptype)) | |
SignedHeader (Header TestBlock) Source # | |
Defined in Test.Ouroboros.Storage.TestBlock | |
SignedHeader (Header (TestBlockWith ptype)) | |
Defined in Test.Util.TestBlock Methods headerSigned ∷ Header (TestBlockWith ptype) → Signed (Header (TestBlockWith ptype)) Source # | |
(Typeable ptype, Eq ptype) ⇒ Condense (Header (TestBlockWith ptype)) | |
Defined in Test.Util.TestBlock | |
HasHeader (Header TestBlock) Source # | |
Defined in Test.Ouroboros.Storage.TestBlock Methods getHeaderFields ∷ Header TestBlock → HeaderFields (Header TestBlock) Source # | |
Typeable ptype ⇒ HasHeader (Header (TestBlockWith ptype)) | |
Defined in Test.Util.TestBlock Methods getHeaderFields ∷ Header (TestBlockWith ptype) → HeaderFields (Header (TestBlockWith ptype)) Source # | |
Serialise (Header TestBlock) Source # | |
Serialise ptype ⇒ Serialise (Header (TestBlockWith ptype)) | |
Defined in Test.Util.TestBlock Methods encode ∷ Header (TestBlockWith ptype) → Encoding Source # decode ∷ Decoder s (Header (TestBlockWith ptype)) Source # encodeList ∷ [Header (TestBlockWith ptype)] → Encoding Source # decodeList ∷ Decoder s [Header (TestBlockWith ptype)] Source # | |
DecodeDiskDep (NestedCtxt Header) TestBlock Source # | |
Defined in Test.Ouroboros.Storage.TestBlock Methods decodeDiskDep ∷ CodecConfig TestBlock → NestedCtxt Header TestBlock a → ∀ s. Decoder s (ByteString → a) Source # | |
DecodeDiskDepIx (NestedCtxt Header) TestBlock Source # | |
Defined in Test.Ouroboros.Storage.TestBlock Methods decodeDiskDepIx ∷ CodecConfig TestBlock → Decoder s (SomeSecond (NestedCtxt Header) TestBlock) Source # | |
EncodeDiskDep (NestedCtxt Header) TestBlock Source # | |
Defined in Test.Ouroboros.Storage.TestBlock Methods encodeDiskDep ∷ CodecConfig TestBlock → NestedCtxt Header TestBlock a → a → Encoding Source # | |
EncodeDiskDepIx (NestedCtxt Header) TestBlock Source # | |
Defined in Test.Ouroboros.Storage.TestBlock Methods encodeDiskDepIx ∷ CodecConfig TestBlock → SomeSecond (NestedCtxt Header) TestBlock → Encoding Source # | |
Serialise ptype ⇒ DecodeDiskDep (NestedCtxt Header) (TestBlockWith ptype) | |
Defined in Test.Util.TestBlock Methods decodeDiskDep ∷ CodecConfig (TestBlockWith ptype) → NestedCtxt Header (TestBlockWith ptype) a → ∀ s. Decoder s (ByteString → a) Source # | |
Serialise ptype ⇒ EncodeDisk (TestBlockWith ptype) (Header (TestBlockWith ptype)) | |
Defined in Test.Util.TestBlock Methods encodeDisk ∷ CodecConfig (TestBlockWith ptype) → Header (TestBlockWith ptype) → Encoding Source # | |
Serialise ptype ⇒ EncodeDiskDep (NestedCtxt Header) (TestBlockWith ptype) | |
Defined in Test.Util.TestBlock Methods encodeDiskDep ∷ CodecConfig (TestBlockWith ptype) → NestedCtxt Header (TestBlockWith ptype) a → a → Encoding Source # | |
Serialise ptype ⇒ DecodeDisk (TestBlockWith ptype) (ByteString → Header (TestBlockWith ptype)) | |
Defined in Test.Util.TestBlock Methods decodeDisk ∷ CodecConfig (TestBlockWith ptype) → ∀ s. Decoder s (ByteString → Header (TestBlockWith ptype)) Source # | |
EncodeDiskDep (NestedCtxt Header) m ⇒ EncodeDiskDep (NestedCtxt Header) (DualBlock m a) | |
Defined in Ouroboros.Consensus.Ledger.Dual Methods encodeDiskDep ∷ CodecConfig (DualBlock m a) → NestedCtxt Header (DualBlock m a) a0 → a0 → Encoding Source # | |
EncodeDiskDepIx (NestedCtxt Header) m ⇒ EncodeDiskDepIx (NestedCtxt Header) (DualBlock m a) | |
Defined in Ouroboros.Consensus.Ledger.Dual Methods encodeDiskDepIx ∷ CodecConfig (DualBlock m a) → SomeSecond (NestedCtxt Header) (DualBlock m a) → Encoding Source # | |
Show (Header m) ⇒ Show (DualHeader m a) | |
Defined in Ouroboros.Consensus.Ledger.Dual Methods showsPrec ∷ Int → DualHeader m a → ShowS # show ∷ DualHeader m a → String # showList ∷ [DualHeader m a] → ShowS # | |
Bridge m a ⇒ HasHeader (DualHeader m a) | |
Defined in Ouroboros.Consensus.Ledger.Dual Methods getHeaderFields ∷ DualHeader m a → HeaderFields (DualHeader m a) Source # | |
newtype Header TestBlock Source # | |
Defined in Test.Ouroboros.Storage.TestBlock | |
type HeaderHash (Header blk ∷ Type) | |
Defined in Ouroboros.Consensus.Block.Abstract | |
type BlockProtocol (Header blk) | |
Defined in Ouroboros.Consensus.Block.Abstract | |
newtype Header (DisableDiffusionPipelining blk) | |
newtype Header (SelectViewDiffusionPipelining blk) | |
Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining newtype Header (SelectViewDiffusionPipelining blk) = SelectViewDiffusionPipeliningHeader (Header blk) | |
newtype Header (HardForkBlock xs) | |
newtype Header (TestBlockWith ptype) | |
Defined in Test.Util.TestBlock | |
type Signed (Header TestBlock) Source # | |
Defined in Test.Ouroboros.Storage.TestBlock | |
type Signed (Header (TestBlockWith ptype)) | |
Defined in Test.Util.TestBlock | |
newtype Header (DualBlock m a) | |
Defined in Ouroboros.Consensus.Ledger.Dual |
data family StorageConfig blk Source #
Config needed for the
NodeInitStorage
class. Defined here to
avoid circular dependencies.
Instances
Isomorphic StorageConfig | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary Methods project ∷ NoHardForks blk ⇒ StorageConfig (HardForkBlock '[blk]) → StorageConfig blk Source # inject ∷ NoHardForks blk ⇒ StorageConfig blk → StorageConfig (HardForkBlock '[blk]) Source # | |||||
Generic (StorageConfig (DualBlock m a)) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual Associated Types
Methods from ∷ StorageConfig (DualBlock m a) → Rep (StorageConfig (DualBlock m a)) x # to ∷ Rep (StorageConfig (DualBlock m a)) x → StorageConfig (DualBlock m a) # | |||||
Generic (StorageConfig TestBlock) Source # | |||||
Defined in Test.Ouroboros.Storage.LedgerDB.StateMachine.TestBlock Associated Types
Methods from ∷ StorageConfig TestBlock → Rep (StorageConfig TestBlock) x # to ∷ Rep (StorageConfig TestBlock) x → StorageConfig TestBlock # | |||||
Generic (StorageConfig TestBlock) Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Associated Types
Methods from ∷ StorageConfig TestBlock → Rep (StorageConfig TestBlock) x # to ∷ Rep (StorageConfig TestBlock) x → StorageConfig TestBlock # | |||||
Generic (StorageConfig TestBlock) | |||||
Defined in Test.Util.TestBlock Associated Types
Methods from ∷ StorageConfig TestBlock → Rep (StorageConfig TestBlock) x # to ∷ Rep (StorageConfig TestBlock) x → StorageConfig TestBlock # | |||||
Show (StorageConfig TestBlock) Source # | |||||
Show (StorageConfig TestBlock) Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
Show (StorageConfig TestBlock) | |||||
Defined in Test.Util.TestBlock | |||||
CanHardFork xs ⇒ NoThunks (StorageConfig (HardForkBlock xs)) | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Methods noThunks ∷ Context → StorageConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → StorageConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (StorageConfig (HardForkBlock xs)) → String Source # | |||||
(NoThunks (StorageConfig m), NoThunks (StorageConfig a)) ⇒ NoThunks (StorageConfig (DualBlock m a)) | |||||
NoThunks (StorageConfig TestBlock) Source # | |||||
NoThunks (StorageConfig TestBlock) Source # | |||||
NoThunks (StorageConfig TestBlock) | |||||
data StorageConfig TestBlock Source # | TODO: for the time being | ||||
data StorageConfig TestBlock Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
data StorageConfig TestBlock | The | ||||
Defined in Test.Util.TestBlock | |||||
type Rep (StorageConfig (DualBlock m a)) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual type Rep (StorageConfig (DualBlock m a)) = D1 ('MetaData "StorageConfig" "Ouroboros.Consensus.Ledger.Dual" "ouroboros-consensus-0.27.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 # | |||||
type Rep (StorageConfig TestBlock) Source # | |||||
type Rep (StorageConfig TestBlock) | |||||
newtype StorageConfig (HardForkBlock xs) | |||||
data StorageConfig (DualBlock m a) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual |
Constructors
TestBlock | |
Fields
|
Instances
Generic TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Associated Types
| |||||||||
Show TestBlock Source # | |||||||||
Eq TestBlock Source # | |||||||||
NoThunks TestBlock Source # | |||||||||
ConvertRawHash TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods toRawHash ∷ proxy TestBlock → HeaderHash TestBlock → ByteString Source # fromRawHash ∷ proxy TestBlock → ByteString → HeaderHash TestBlock Source # toShortRawHash ∷ proxy TestBlock → HeaderHash TestBlock → ShortByteString Source # fromShortRawHash ∷ proxy TestBlock → ShortByteString → HeaderHash TestBlock Source # | |||||||||
GetHeader TestBlock Source # | |||||||||
GetPrevHash TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
BlockSupportsDiffusionPipelining TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Associated Types
Methods initialTentativeHeaderState ∷ Proxy TestBlock → TentativeHeaderState TestBlock Source # tentativeHeaderView ∷ BlockConfig TestBlock → Header TestBlock → TentativeHeaderView TestBlock Source # applyTentativeHeaderView ∷ Proxy TestBlock → TentativeHeaderView TestBlock → TentativeHeaderState TestBlock → Maybe (TentativeHeaderState TestBlock) Source # | |||||||||
BlockSupportsProtocol TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods validateView ∷ BlockConfig TestBlock → Header TestBlock → ValidateView (BlockProtocol TestBlock) Source # selectView ∷ BlockConfig TestBlock → Header TestBlock → SelectView (BlockProtocol TestBlock) Source # projectChainOrderConfig ∷ BlockConfig TestBlock → ChainOrderConfig (SelectView (BlockProtocol TestBlock)) Source # | |||||||||
HasHardForkHistory TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Associated Types
Methods hardForkSummary ∷ ∀ (mk ∷ MapKind). LedgerConfig TestBlock → LedgerState TestBlock mk → Summary (HardForkIndices TestBlock) Source # | |||||||||
ImmutableEraParams TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods immutableEraParams ∷ TopLevelConfig TestBlock → EraParams Source # | |||||||||
BasicEnvelopeValidation TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods expectedFirstBlockNo ∷ proxy TestBlock → BlockNo Source # expectedNextBlockNo ∷ proxy TestBlock → TipInfo TestBlock → TipInfo TestBlock → BlockNo → BlockNo Source # minimumPossibleSlotNo ∷ Proxy TestBlock → SlotNo Source # minimumNextSlotNo ∷ proxy TestBlock → TipInfo TestBlock → TipInfo TestBlock → SlotNo → SlotNo Source # | |||||||||
HasAnnTip TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Associated Types
Methods getTipInfo ∷ Header TestBlock → TipInfo TestBlock Source # tipInfoHash ∷ proxy TestBlock → TipInfo TestBlock → HeaderHash TestBlock Source # | |||||||||
ValidateEnvelope TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Associated Types
| |||||||||
UpdateLedger TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
InspectLedger TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Associated Types
Methods inspectLedger ∷ ∀ (mk1 ∷ MapKind) (mk2 ∷ MapKind). TopLevelConfig TestBlock → LedgerState TestBlock mk1 → LedgerState TestBlock mk2 → [LedgerEvent TestBlock] Source # | |||||||||
LedgerSupportsProtocol TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods protocolLedgerView ∷ ∀ (mk ∷ MapKind). LedgerConfig TestBlock → Ticked (LedgerState TestBlock) mk → LedgerView (BlockProtocol TestBlock) Source # ledgerViewForecastAt ∷ ∀ (mk ∷ MapKind). HasCallStack ⇒ LedgerConfig TestBlock → LedgerState TestBlock mk → Forecast (LedgerView (BlockProtocol TestBlock)) Source # | |||||||||
SerialiseDiskConstraints TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
HasBinaryBlockInfo TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods | |||||||||
Condense TestBlock Source # | |||||||||
ModelSupportsBlock TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
HasHeader TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods getHeaderFields ∷ TestBlock → HeaderFields TestBlock Source # | |||||||||
Serialise TestBlock Source # | |||||||||
ToExpr TestBlock Source # | |||||||||
HasNestedContent f TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
DecodeDisk TestBlock () Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods decodeDisk ∷ CodecConfig TestBlock → ∀ s. Decoder s () Source # | |||||||||
EncodeDisk TestBlock TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods encodeDisk ∷ CodecConfig TestBlock → TestBlock → Encoding Source # | |||||||||
EncodeDisk TestBlock () Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods encodeDisk ∷ CodecConfig TestBlock → () → Encoding Source # | |||||||||
ReconstructNestedCtxt Header TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods reconstructPrefixLen ∷ proxy (Header TestBlock) → PrefixLen Source # reconstructNestedCtxt ∷ proxy (Header TestBlock) → ShortByteString → SizeInBytes → SomeSecond (NestedCtxt Header) TestBlock Source # | |||||||||
StandardHash TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
DecodeDisk TestBlock (AnnTip TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods decodeDisk ∷ CodecConfig TestBlock → ∀ s. Decoder s (AnnTip TestBlock) Source # | |||||||||
EncodeDisk TestBlock (Header TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods encodeDisk ∷ CodecConfig TestBlock → Header TestBlock → Encoding Source # | |||||||||
EncodeDisk TestBlock (AnnTip TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods encodeDisk ∷ CodecConfig TestBlock → AnnTip TestBlock → Encoding Source # | |||||||||
DecodeDisk TestBlock (LedgerState TestBlock EmptyMK) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods decodeDisk ∷ CodecConfig TestBlock → ∀ s. Decoder s (LedgerState TestBlock EmptyMK) Source # | |||||||||
DecodeDisk TestBlock (ByteString → Header TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods decodeDisk ∷ CodecConfig TestBlock → ∀ s. Decoder s (ByteString → Header TestBlock) Source # | |||||||||
DecodeDisk TestBlock (ByteString → TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods decodeDisk ∷ CodecConfig TestBlock → ∀ s. Decoder s (ByteString → TestBlock) Source # | |||||||||
EncodeDisk TestBlock (LedgerState TestBlock EmptyMK) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods encodeDisk ∷ CodecConfig TestBlock → LedgerState TestBlock EmptyMK → Encoding Source # | |||||||||
SameDepIndex (NestedCtxt_ TestBlock f ∷ Type → Type) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods sameDepIndex ∷ NestedCtxt_ TestBlock f a → NestedCtxt_ TestBlock f b → Maybe (a :~: b) Source # | |||||||||
TrivialDependency (NestedCtxt_ TestBlock f ∷ Type → Type) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods hasSingleIndex ∷ NestedCtxt_ TestBlock f a → NestedCtxt_ TestBlock f b → a :~: b Source # indexIsTrivial ∷ NestedCtxt_ TestBlock f (TrivialIndex (NestedCtxt_ TestBlock f) ∷ Type) Source # | |||||||||
Generic (BlockConfig TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Associated Types
Methods from ∷ BlockConfig TestBlock → Rep (BlockConfig TestBlock) x # to ∷ Rep (BlockConfig TestBlock) x → BlockConfig TestBlock # | |||||||||
Generic (CodecConfig TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Associated Types
Methods from ∷ CodecConfig TestBlock → Rep (CodecConfig TestBlock) x # to ∷ Rep (CodecConfig TestBlock) x → CodecConfig TestBlock # | |||||||||
Generic (StorageConfig TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Associated Types
Methods from ∷ StorageConfig TestBlock → Rep (StorageConfig TestBlock) x # to ∷ Rep (StorageConfig TestBlock) x → StorageConfig TestBlock # | |||||||||
Show (CodecConfig TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
Show (Header TestBlock) Source # | |||||||||
Show (StorageConfig TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
Eq (Header TestBlock) Source # | |||||||||
NoThunks (BlockConfig TestBlock) Source # | |||||||||
NoThunks (CodecConfig TestBlock) Source # | |||||||||
NoThunks (Header TestBlock) Source # | |||||||||
NoThunks (StorageConfig TestBlock) Source # | |||||||||
GetTip (LedgerState TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods getTip ∷ ∀ (mk ∷ MapKind). LedgerState TestBlock mk → Point (LedgerState TestBlock) Source # | |||||||||
IsLedger (LedgerState TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Associated Types
| |||||||||
CanStowLedgerTables (LedgerState TestBlock) Source # | |||||||||
HasLedgerTables (LedgerState TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerState TestBlock mk → LedgerTables (LedgerState TestBlock) mk Source # withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerState TestBlock any → LedgerTables (LedgerState TestBlock) mk → LedgerState TestBlock mk Source # | |||||||||
LedgerTablesAreTrivial (LedgerState TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). LedgerState TestBlock mk → LedgerState TestBlock mk' Source # | |||||||||
SerializeTablesWithHint (LedgerState TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods encodeTablesWithHint ∷ SerializeTablesHint (LedgerTables (LedgerState TestBlock) ValuesMK) → LedgerTables (LedgerState TestBlock) ValuesMK → Encoding Source # decodeTablesWithHint ∷ SerializeTablesHint (LedgerTables (LedgerState TestBlock) ValuesMK) → Decoder s (LedgerTables (LedgerState TestBlock) ValuesMK) Source # | |||||||||
SignedHeader (Header TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
CanUpgradeLedgerTables (LedgerState TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods upgradeTables ∷ ∀ (mk1 ∷ MapKind) (mk2 ∷ MapKind). LedgerState TestBlock mk1 → LedgerState TestBlock mk2 → LedgerTables (LedgerState TestBlock) ValuesMK → LedgerTables (LedgerState TestBlock) ValuesMK Source # | |||||||||
HasHeader (Header TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods getHeaderFields ∷ Header TestBlock → HeaderFields (Header TestBlock) Source # | |||||||||
Serialise (Header TestBlock) Source # | |||||||||
ToExpr (CodecConfig TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods toExpr ∷ CodecConfig TestBlock → Expr Source # listToExpr ∷ [CodecConfig TestBlock] → Expr Source # | |||||||||
ToExpr (HeaderEnvelopeError TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods toExpr ∷ HeaderEnvelopeError TestBlock → Expr Source # listToExpr ∷ [HeaderEnvelopeError TestBlock] → Expr Source # | |||||||||
ToExpr (HeaderError TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods toExpr ∷ HeaderError TestBlock → Expr Source # listToExpr ∷ [HeaderError TestBlock] → Expr Source # | |||||||||
ToExpr (TipInfoIsEBB TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods toExpr ∷ TipInfoIsEBB TestBlock → Expr Source # listToExpr ∷ [TipInfoIsEBB TestBlock] → Expr Source # | |||||||||
ToExpr (ExtValidationError TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
ToExpr (Tip TestBlock) Source # | |||||||||
ToExpr (DBModel TestBlock) Source # | |||||||||
ToExpr (InSlot TestBlock) Source # | |||||||||
ToExpr (IteratorModel TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.ImmutableDB.Model Methods toExpr ∷ IteratorModel TestBlock → Expr Source # listToExpr ∷ [IteratorModel TestBlock] → Expr Source # | |||||||||
ApplyBlock (LedgerState TestBlock) TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods applyBlockLedgerResultWithValidation ∷ ValidationPolicy → ComputeLedgerEvents → LedgerCfg (LedgerState TestBlock) → TestBlock → Ticked (LedgerState TestBlock) ValuesMK → Except (LedgerErr (LedgerState TestBlock)) (LedgerResult (LedgerState TestBlock) (LedgerState TestBlock DiffMK)) Source # applyBlockLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (LedgerState TestBlock) → TestBlock → Ticked (LedgerState TestBlock) ValuesMK → Except (LedgerErr (LedgerState TestBlock)) (LedgerResult (LedgerState TestBlock) (LedgerState TestBlock DiffMK)) Source # reapplyBlockLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (LedgerState TestBlock) → TestBlock → Ticked (LedgerState TestBlock) ValuesMK → LedgerResult (LedgerState TestBlock) (LedgerState TestBlock DiffMK) Source # getBlockKeySets ∷ TestBlock → LedgerTables (LedgerState TestBlock) KeysMK Source # | |||||||||
DecodeDiskDep (NestedCtxt Header) TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods decodeDiskDep ∷ CodecConfig TestBlock → NestedCtxt Header TestBlock a → ∀ s. Decoder s (ByteString → a) Source # | |||||||||
DecodeDiskDepIx (NestedCtxt Header) TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods decodeDiskDepIx ∷ CodecConfig TestBlock → Decoder s (SomeSecond (NestedCtxt Header) TestBlock) Source # | |||||||||
EncodeDiskDep (NestedCtxt Header) TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods encodeDiskDep ∷ CodecConfig TestBlock → NestedCtxt Header TestBlock a → a → Encoding Source # | |||||||||
EncodeDiskDepIx (NestedCtxt Header) TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods encodeDiskDepIx ∷ CodecConfig TestBlock → SomeSecond (NestedCtxt Header) TestBlock → Encoding Source # | |||||||||
Generic (LedgerState TestBlock mk) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Associated Types
Methods from ∷ LedgerState TestBlock mk → Rep (LedgerState TestBlock mk) x # to ∷ Rep (LedgerState TestBlock mk) x → LedgerState TestBlock mk # | |||||||||
Show (LedgerState TestBlock mk) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
Eq (LedgerState TestBlock mk) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods (==) ∷ LedgerState TestBlock mk → LedgerState TestBlock mk → Bool # (/=) ∷ LedgerState TestBlock mk → LedgerState TestBlock mk → Bool # | |||||||||
NoThunks (LedgerState TestBlock mk) Source # | |||||||||
GetTip (Ticked (LedgerState TestBlock)) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
HasLedgerTables (Ticked (LedgerState TestBlock)) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState TestBlock) mk → LedgerTables (Ticked (LedgerState TestBlock)) mk Source # withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState TestBlock) any → LedgerTables (Ticked (LedgerState TestBlock)) mk → Ticked (LedgerState TestBlock) mk Source # | |||||||||
LedgerTablesAreTrivial (Ticked (LedgerState TestBlock)) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). Ticked (LedgerState TestBlock) mk → Ticked (LedgerState TestBlock) mk' Source # | |||||||||
Serialise (LedgerState TestBlock mk) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods encode ∷ LedgerState TestBlock mk → Encoding Source # decode ∷ Decoder s (LedgerState TestBlock mk) Source # encodeList ∷ [LedgerState TestBlock mk] → Encoding Source # decodeList ∷ Decoder s [LedgerState TestBlock mk] Source # | |||||||||
ToExpr (LedgerState TestBlock EmptyMK) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods toExpr ∷ LedgerState TestBlock EmptyMK → Expr Source # listToExpr ∷ [LedgerState TestBlock EmptyMK] → Expr Source # | |||||||||
IndexedMemPack (LedgerState TestBlock EmptyMK) Void Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock Methods indexedPackedByteCount ∷ LedgerState TestBlock EmptyMK → Void → Int Source # indexedPackM ∷ LedgerState TestBlock EmptyMK → Void → Pack s () Source # indexedUnpackM ∷ Buffer b ⇒ LedgerState TestBlock EmptyMK → Unpack b Void Source # indexedTypeName ∷ LedgerState TestBlock EmptyMK → String Source # | |||||||||
Show (NestedCtxt_ TestBlock f a) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
type Rep TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock type Rep TestBlock = D1 ('MetaData "TestBlock" "Test.Ouroboros.Storage.TestBlock" "ouroboros-consensus-0.27.0.0-inplace-storage-test" '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 # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
type BlockProtocol TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
data CodecConfig TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
newtype Header TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
data StorageConfig TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
data NestedCtxt_ TestBlock f a Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock data NestedCtxt_ TestBlock f a where
| |||||||||
type TentativeHeaderState TestBlock Source # | |||||||||
type TentativeHeaderView TestBlock Source # | |||||||||
type HardForkIndices TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
type OtherHeaderEnvelopeError TestBlock Source # | |||||||||
type TipInfo TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
data LedgerState TestBlock mk Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
type LedgerUpdate TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
type LedgerWarning TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
type HeaderHash TestBlock Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
type TrivialIndex (NestedCtxt_ TestBlock f ∷ Type → Type) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
type Rep (BlockConfig TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock type Rep (BlockConfig TestBlock) = D1 ('MetaData "BlockConfig" "Test.Ouroboros.Storage.TestBlock" "ouroboros-consensus-0.27.0.0-inplace-storage-test" '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 # | |||||||||
type Rep (StorageConfig TestBlock) Source # | |||||||||
type AuxLedgerEvent (LedgerState TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
type LedgerCfg (LedgerState TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
type LedgerErr (LedgerState TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
type TxIn (LedgerState TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
type TxOut (LedgerState TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
type Signed (Header TestBlock) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||||||
type Rep (LedgerState TestBlock mk) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock type Rep (LedgerState TestBlock mk) = D1 ('MetaData "LedgerState" "Test.Ouroboros.Storage.TestBlock" "ouroboros-consensus-0.27.0.0-inplace-storage-test" '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)))) | |||||||||
newtype Ticked (LedgerState TestBlock) (mk ∷ MapKind) Source # | |||||||||
Defined in Test.Ouroboros.Storage.TestBlock |
Constructors
TestBody | |
Fields
|
Instances
Generic TestBody Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Associated Types
| |||||
Show TestBody Source # | |||||
Eq TestBody Source # | |||||
Hashable TestBody Source # | |||||
NoThunks TestBody Source # | |||||
Serialise TestBody Source # | |||||
ToExpr TestBody Source # | |||||
type Rep TestBody Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock type Rep TestBody = D1 ('MetaData "TestBody" "Test.Ouroboros.Storage.TestBlock" "ouroboros-consensus-0.27.0.0-inplace-storage-test" '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
Generic TestBodyHash Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Associated Types
| |||||
Show TestBodyHash Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Methods showsPrec ∷ Int → TestBodyHash → ShowS # show ∷ TestBodyHash → String # showList ∷ [TestBodyHash] → ShowS # | |||||
Eq TestBodyHash Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
Ord TestBodyHash Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Methods compare ∷ TestBodyHash → TestBodyHash → Ordering # (<) ∷ TestBodyHash → TestBodyHash → Bool # (<=) ∷ TestBodyHash → TestBodyHash → Bool # (>) ∷ TestBodyHash → TestBodyHash → Bool # (>=) ∷ TestBodyHash → TestBodyHash → Bool # max ∷ TestBodyHash → TestBodyHash → TestBodyHash # min ∷ TestBodyHash → TestBodyHash → TestBodyHash # | |||||
Hashable TestBodyHash Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
NoThunks TestBodyHash Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
Condense TestBodyHash Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Methods | |||||
Serialise TestBodyHash Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Methods encode ∷ TestBodyHash → Encoding Source # decode ∷ Decoder s TestBodyHash Source # encodeList ∷ [TestBodyHash] → Encoding Source # decodeList ∷ Decoder s [TestBodyHash] Source # | |||||
ToExpr TestBodyHash Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
type Rep TestBodyHash Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock type Rep TestBodyHash = D1 ('MetaData "TestBodyHash" "Test.Ouroboros.Storage.TestBlock" "ouroboros-consensus-0.27.0.0-inplace-storage-test" 'True) (C1 ('MetaCons "TestBodyHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) |
data TestHeader Source #
Constructors
TestHeader | |
Fields
|
Instances
Generic TestHeader Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Associated Types
| |||||
Show TestHeader Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Methods showsPrec ∷ Int → TestHeader → ShowS # show ∷ TestHeader → String # showList ∷ [TestHeader] → ShowS # | |||||
Eq TestHeader Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
NoThunks TestHeader Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
Condense TestHeader Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Methods condense ∷ TestHeader → String Source # | |||||
Serialise TestHeader Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Methods encode ∷ TestHeader → Encoding Source # decode ∷ Decoder s TestHeader Source # encodeList ∷ [TestHeader] → Encoding Source # decodeList ∷ Decoder s [TestHeader] Source # | |||||
ToExpr TestHeader Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
StandardHash TestHeader Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
type Rep TestHeader Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock type Rep TestHeader = D1 ('MetaData "TestHeader" "Test.Ouroboros.Storage.TestBlock" "ouroboros-consensus-0.27.0.0-inplace-storage-test" 'False) (C1 ('MetaCons "TestHeader" 'PrefixI 'True) ((S1 ('MetaSel ('Just "thHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HeaderHash TestHeader)) :*: (S1 ('MetaSel ('Just "thPrevHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ChainHash TestHeader)) :*: S1 ('MetaSel ('Just "thBodyHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TestBodyHash))) :*: ((S1 ('MetaSel ('Just "thSlotNo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo) :*: S1 ('MetaSel ('Just "thBlockNo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockNo)) :*: (S1 ('MetaSel ('Just "thChainLength") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ChainLength) :*: S1 ('MetaSel ('Just "thIsEBB") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EBB))))) | |||||
type HeaderHash TestHeader Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock |
newtype TestHeaderHash Source #
Hash of a TestHeader
Constructors
TestHeaderHash Int |
Instances
Binary TestHeaderHash Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
Generic TestHeaderHash Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Associated Types
| |||||
Show TestHeaderHash Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Methods showsPrec ∷ Int → TestHeaderHash → ShowS # show ∷ TestHeaderHash → String # showList ∷ [TestHeaderHash] → ShowS # | |||||
Eq TestHeaderHash Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Methods (==) ∷ TestHeaderHash → TestHeaderHash → Bool # (/=) ∷ TestHeaderHash → TestHeaderHash → Bool # | |||||
Ord TestHeaderHash Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Methods compare ∷ TestHeaderHash → TestHeaderHash → Ordering # (<) ∷ TestHeaderHash → TestHeaderHash → Bool # (<=) ∷ TestHeaderHash → TestHeaderHash → Bool # (>) ∷ TestHeaderHash → TestHeaderHash → Bool # (>=) ∷ TestHeaderHash → TestHeaderHash → Bool # | |||||
Hashable TestHeaderHash Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
NoThunks TestHeaderHash Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
Condense TestHeaderHash Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Methods | |||||
Serialise TestHeaderHash Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Methods encode ∷ TestHeaderHash → Encoding Source # decode ∷ Decoder s TestHeaderHash Source # encodeList ∷ [TestHeaderHash] → Encoding Source # decodeList ∷ Decoder s [TestHeaderHash] Source # | |||||
ToExpr TestHeaderHash Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
type Rep TestHeaderHash Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock type Rep TestHeaderHash = D1 ('MetaData "TestHeaderHash" "Test.Ouroboros.Storage.TestBlock" "ouroboros-consensus-0.27.0.0-inplace-storage-test" 'True) (C1 ('MetaCons "TestHeaderHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) |
Construction
firstBlock ∷ SlotNo → TestBody → TestBlock Source #
Note the first block need not be an EBB, see firstEBB
.
Arguments
∷ HasCallStack | |
⇒ (SlotNo → Bool) | Is this slot allowed contain an EBB? This argument is used primarily to detect the generation of invalid blocks
with different kind of |
→ TestBody | |
→ ChainHash TestHeader | Hash of previous header |
→ SlotNo | |
→ BlockNo | |
→ ChainLength | |
→ Maybe EpochNo | |
→ TestBlock |
Variant of mkNextBlock
that takes the entire previous block.
Arguments
∷ (HeaderFields TestBlock, ChainLength) | Information about the previous block |
→ SlotNo | |
→ TestBody | |
→ TestBlock |
Variant of mkNextEBB
that takes the entire previous block.
Arguments
∷ (SlotNo → Bool) | |
→ (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
testBlockIsValid ∷ TestBlock → Bool 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 |
InvalidBlock | The block itself is invalid |
Instances
Generic TestBlockError Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Associated Types
| |||||
Show TestBlockError Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Methods showsPrec ∷ Int → TestBlockError → ShowS # show ∷ TestBlockError → String # showList ∷ [TestBlockError] → ShowS # | |||||
Eq TestBlockError Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Methods (==) ∷ TestBlockError → TestBlockError → Bool # (/=) ∷ TestBlockError → TestBlockError → Bool # | |||||
NoThunks TestBlockError Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
ToExpr TestBlockError Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
type Rep TestBlockError Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock type Rep TestBlockError = D1 ('MetaData "TestBlockError" "Test.Ouroboros.Storage.TestBlock" "ouroboros-consensus-0.27.0.0-inplace-storage-test" 'False) (C1 ('MetaCons "InvalidHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ChainHash TestBlock)) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ChainHash TestBlock))) :+: C1 ('MetaCons "InvalidBlock" 'PrefixI 'False) (U1 ∷ Type → Type)) |
data TestBlockOtherHeaderEnvelopeError Source #
Constructors
UnexpectedEBBInSlot !SlotNo |
Instances
Generic TestBlockOtherHeaderEnvelopeError Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock Associated Types
| |||||
Show TestBlockOtherHeaderEnvelopeError Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
Eq TestBlockOtherHeaderEnvelopeError Source # | |||||
NoThunks TestBlockOtherHeaderEnvelopeError Source # | |||||
ToExpr TestBlockOtherHeaderEnvelopeError Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock | |||||
type Rep TestBlockOtherHeaderEnvelopeError Source # | |||||
Defined in Test.Ouroboros.Storage.TestBlock type Rep TestBlockOtherHeaderEnvelopeError = D1 ('MetaData "TestBlockOtherHeaderEnvelopeError" "Test.Ouroboros.Storage.TestBlock" "ouroboros-consensus-0.27.0.0-inplace-storage-test" 'False) (C1 ('MetaCons "UnexpectedEBBInSlot" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe 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 |
Corrupt Word64 | Corrupt the file by adding 1 to the byte at the given location (modulo the file size). |
Instances
Arbitrary FileCorruption Source # | |
Defined in Test.Ouroboros.Storage.TestBlock | |
Show FileCorruption Source # | |
Defined in Test.Ouroboros.Storage.TestBlock Methods showsPrec ∷ Int → FileCorruption → ShowS # show ∷ FileCorruption → String # showList ∷ [FileCorruption] → ShowS # | |
Eq FileCorruption Source # | |
Defined in Test.Ouroboros.Storage.TestBlock Methods (==) ∷ FileCorruption → FileCorruption → Bool # (/=) ∷ FileCorruption → FileCorruption → Bool # |
corruptFile ∷ MonadThrow m ⇒ HasFS m h → FileCorruption → FsPath → 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.
corruptionFiles ∷ Corruptions → [FsPath] Source #
Return a list of all files that will be corrupted
generateCorruptions ∷ NonEmpty FsPath → Gen Corruptions Source #
The same file will not occur twice.