Safe Haskell | None |
---|---|
Language | Haskell2010 |
Test.Util.TestBlock
Description
Minimal instantiation of the consensus layer to be able to run the ChainDB
Synopsis
- data family BlockConfig blk
- data family BlockQuery ∷ Type → QueryFootprint → Type → Type
- data family CodecConfig blk
- data family Header blk
- newtype LedgerTables (l ∷ LedgerStateKind) (mk ∷ MapKind) = LedgerTables {
- getLedgerTables ∷ mk (TxIn l) (TxOut l)
- data family StorageConfig blk
- data TestBlockError ptype
- = InvalidHash (ChainHash (TestBlockWith ptype)) (ChainHash (TestBlockWith ptype))
- | InvalidBlock
- | InvalidPayload (PayloadDependentError ptype)
- data TestBlockWith ptype
- data TestHash where
- data Validity
- firstBlockWithPayload ∷ Word64 → ptype → TestBlockWith ptype
- forkBlock ∷ TestBlock → TestBlock
- modifyFork ∷ (Word64 → Word64) → TestBlock → TestBlock
- successorBlockWithPayload ∷ TestHash → SlotNo → ptype → TestBlockWith ptype
- testHashFromList ∷ [Word64] → TestHash
- unTestHash ∷ TestHash → NonEmpty Word64
- type TestBlock = TestBlockWith ()
- firstBlock ∷ Word64 → TestBlock
- successorBlock ∷ TestBlock → TestBlock
- data family PayloadDependentState ptype (mk ∷ MapKind)
- class (Typeable ptype, Eq ptype, NoThunks ptype, ∀ (mk ∷ MapKind). EqMK mk ⇒ Eq (PayloadDependentState ptype mk), ∀ (mk ∷ MapKind). NoThunksMK mk ⇒ NoThunks (PayloadDependentState ptype mk), ∀ (mk ∷ MapKind). ShowMK mk ⇒ Show (PayloadDependentState ptype mk), ∀ (mk ∷ MapKind). Generic (PayloadDependentState ptype mk), Serialise (PayloadDependentState ptype EmptyMK), HasLedgerTables (LedgerState (TestBlockWith ptype)), HasLedgerTables (Ticked (LedgerState (TestBlockWith ptype))), CanStowLedgerTables (LedgerState (TestBlockWith ptype)), Eq (PayloadDependentError ptype), Show (PayloadDependentError ptype), Generic (PayloadDependentError ptype), ToExpr (PayloadDependentError ptype), Serialise (PayloadDependentError ptype), NoThunks (PayloadDependentError ptype), NoThunks (CodecConfig (TestBlockWith ptype)), NoThunks (StorageConfig (TestBlockWith ptype))) ⇒ PayloadSemantics ptype where
- data PayloadDependentState ptype (mk ∷ MapKind)
- type PayloadDependentError ptype
- applyPayload ∷ PayloadDependentState ptype ValuesMK → ptype → Either (PayloadDependentError ptype) (PayloadDependentState ptype TrackingMK)
- getPayloadKeySets ∷ ptype → LedgerTables (LedgerState (TestBlockWith ptype)) KeysMK
- applyDirectlyToPayloadDependentState ∷ PayloadSemantics ptype ⇒ Ticked (LedgerState (TestBlockWith ptype)) ValuesMK → ptype → Either (PayloadDependentError ptype) (Ticked (LedgerState (TestBlockWith ptype)) TrackingMK)
- data family LedgerState blk (mk ∷ MapKind)
- data family Ticked (st ∷ k) ∷ k
- getTickedTestLedger ∷ ∀ ptype (mk ∷ MapKind). Ticked (LedgerState (TestBlockWith ptype)) mk → LedgerState (TestBlockWith ptype) mk
- newtype BlockChain = BlockChain Word64
- blockChain ∷ BlockChain → Chain TestBlock
- chainToBlocks ∷ BlockChain → [TestBlock]
- newtype BlockTree = BlockTree (Tree ())
- blockTree ∷ BlockTree → Tree TestBlock
- treePreferredChain ∷ BlockTree → Chain TestBlock
- treeToBlocks ∷ BlockTree → [TestBlock]
- treeToChains ∷ BlockTree → [Chain TestBlock]
- singleNodeTestConfig ∷ TopLevelConfig TestBlock
- singleNodeTestConfigWith ∷ CodecConfig (TestBlockWith ptype) → StorageConfig (TestBlockWith ptype) → SecurityParam → GenesisWindow → TopLevelConfig (TestBlockWith ptype)
- singleNodeTestConfigWithK ∷ SecurityParam → TopLevelConfig TestBlock
- testInitExtLedger ∷ ExtLedgerState TestBlock ValuesMK
- testInitExtLedgerWithState ∷ ∀ ptype (mk ∷ MapKind). PayloadDependentState ptype mk → ExtLedgerState (TestBlockWith ptype) mk
- testInitLedger ∷ LedgerState TestBlock ValuesMK
- testInitLedgerWithState ∷ ∀ ptype (mk ∷ MapKind). PayloadDependentState ptype mk → LedgerState (TestBlockWith ptype) mk
- newtype Permutation = Permutation Int
- data TestBlockLedgerConfig = TestBlockLedgerConfig {}
- isAncestorOf ∷ TestBlock → TestBlock → Bool
- isDescendentOf ∷ TestBlock → TestBlock → Bool
- isStrictAncestorOf ∷ TestBlock → TestBlock → Bool
- isStrictDescendentOf ∷ TestBlock → TestBlock → Bool
- permute ∷ Permutation → [a] → [a]
- testBlockLedgerConfigFrom ∷ EraParams → TestBlockLedgerConfig
- unsafeTestBlockWithPayload ∷ TestHash → SlotNo → Validity → ptype → TestBlockWith ptype
- updateToNextNumeral ∷ RealPoint TestBlock → (Point TestBlock, NonEmpty TestBlock)
Blocks
data family BlockConfig blk Source #
Static configuration required to work with this type of blocks
Instances
data family BlockQuery ∷ Type → QueryFootprint → Type → Type Source #
Different queries supported by the ledger, indexed by the result type.
Instances
SameDepIndex2 (BlockQuery (DualBlock m a) ∷ QueryFootprint → Type → Type) | |
Defined in Ouroboros.Consensus.Ledger.Dual Methods sameDepIndex2 ∷ ∀ (x ∷ QueryFootprint) a0 (y ∷ QueryFootprint) b. BlockQuery (DualBlock m a) x a0 → BlockQuery (DualBlock m a) y b → Maybe ('(x, a0) :~: '(y, b)) Source # | |
SameDepIndex2 (BlockQuery TestBlock) Source # | |
Defined in Test.Util.TestBlock Methods sameDepIndex2 ∷ ∀ (x ∷ QueryFootprint) a (y ∷ QueryFootprint) b. BlockQuery TestBlock x a → BlockQuery TestBlock y b → Maybe ('(x, a) :~: '(y, b)) Source # | |
(∀ (footprint ∷ QueryFootprint) result. Show (BlockQuery blk footprint result)) ⇒ Show (SomeBlockQuery (BlockQuery blk)) | |
Defined in Ouroboros.Consensus.Ledger.Query Methods showsPrec ∷ Int → SomeBlockQuery (BlockQuery blk) → ShowS # show ∷ SomeBlockQuery (BlockQuery blk) → String # showList ∷ [SomeBlockQuery (BlockQuery blk)] → ShowS # | |
ShowQuery (BlockQuery (DualBlock m a) footprint) | |
Defined in Ouroboros.Consensus.Ledger.Dual Methods showResult ∷ BlockQuery (DualBlock m a) footprint result → result → String Source # | |
ShowQuery (BlockQuery TestBlock fp) Source # | |
Defined in Test.Util.TestBlock Methods showResult ∷ BlockQuery TestBlock fp result → result → String Source # | |
(Typeable m, Typeable a) ⇒ ShowProxy (BlockQuery (DualBlock m a) ∷ QueryFootprint → Type → Type) | |
Defined in Ouroboros.Consensus.Ledger.Dual | |
Show (BlockQuery (DualBlock m a) footprint result) | |
Defined in Ouroboros.Consensus.Ledger.Dual | |
Show (BlockQuery TestBlock fp result) Source # | |
Defined in Test.Util.TestBlock | |
Eq (BlockQuery TestBlock fp result) Source # | |
Defined in Test.Util.TestBlock Methods (==) ∷ BlockQuery TestBlock fp result → BlockQuery TestBlock fp result → Bool # (/=) ∷ BlockQuery TestBlock fp result → BlockQuery TestBlock fp result → Bool # | |
Inject (SomeBlockQuery :.: BlockQuery) | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Nary Methods inject ∷ ∀ x (xs ∷ [Type]). (CanHardFork xs, HasCanonicalTxIn xs, HasHardForkTxOut xs) ⇒ InjectionIndex xs x → (SomeBlockQuery :.: BlockQuery) x → (SomeBlockQuery :.: BlockQuery) (HardForkBlock xs) Source # | |
data BlockQuery TestBlock fp result Source # | |
Defined in Test.Util.TestBlock | |
data BlockQuery (HardForkBlock xs) footprint result | |
Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger.Query data BlockQuery (HardForkBlock xs) footprint result where
| |
data BlockQuery (DualBlock m a) footprint result | |
Defined in Ouroboros.Consensus.Ledger.Dual |
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.Util.TestBlock Associated Types
Methods from ∷ CodecConfig TestBlock → Rep (CodecConfig TestBlock) x # to ∷ Rep (CodecConfig TestBlock) x → CodecConfig TestBlock # | |||||
Show (CodecConfig TestBlock) Source # | |||||
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 # | |||||
data CodecConfig TestBlock Source # | 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.26.0.0-inplace" 'False) (C1 ('MetaCons "DualCodecConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "dualCodecConfigMain") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (CodecConfig m)) :*: S1 ('MetaSel ('Just "dualCodecConfigAux") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (CodecConfig a)))) | |||||
type Rep (CodecConfig TestBlock) Source # | |||||
newtype CodecConfig (HardForkBlock xs) | |||||
data CodecConfig (DualBlock m a) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual data CodecConfig (DualBlock m a) = DualCodecConfig {
|
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 (TestBlockWith ptype) Source # | |
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) Source # | |
Defined in Test.Util.TestBlock | |
HasNestedContent Header m ⇒ HasNestedContent Header (DualBlock m a) | |
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 ptype ⇒ Show (Header (TestBlockWith ptype)) Source # | |
Defined in Test.Util.TestBlock | |
Eq ptype ⇒ Eq (Header (TestBlockWith ptype)) Source # | |
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 ptype ⇒ NoThunks (Header (TestBlockWith ptype)) Source # | |
SignedHeader (Header (TestBlockWith ptype)) Source # | |
Defined in Test.Util.TestBlock Methods headerSigned ∷ Header (TestBlockWith ptype) → Signed (Header (TestBlockWith ptype)) Source # | |
(Typeable ptype, Eq ptype) ⇒ Condense (Header (TestBlockWith ptype)) Source # | |
Defined in Test.Util.TestBlock | |
Typeable ptype ⇒ HasHeader (Header (TestBlockWith ptype)) Source # | |
Defined in Test.Util.TestBlock Methods getHeaderFields ∷ Header (TestBlockWith ptype) → HeaderFields (Header (TestBlockWith ptype)) Source # | |
Serialise ptype ⇒ Serialise (Header (TestBlockWith ptype)) Source # | |
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 # | |
Serialise ptype ⇒ DecodeDiskDep (NestedCtxt Header) (TestBlockWith ptype) Source # | |
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)) Source # | |
Defined in Test.Util.TestBlock Methods encodeDisk ∷ CodecConfig (TestBlockWith ptype) → Header (TestBlockWith ptype) → Encoding Source # | |
Serialise ptype ⇒ EncodeDiskDep (NestedCtxt Header) (TestBlockWith ptype) Source # | |
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)) Source # | |
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 # | |
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) Source # | |
Defined in Test.Util.TestBlock | |
type Signed (Header (TestBlockWith ptype)) Source # | |
Defined in Test.Util.TestBlock | |
newtype Header (DualBlock m a) | |
Defined in Ouroboros.Consensus.Ledger.Dual |
newtype LedgerTables (l ∷ LedgerStateKind) (mk ∷ MapKind) Source #
The Ledger Tables represent the portion of the data on disk that has been pulled from disk and attached to the in-memory Ledger State or that will eventually be written to disk.
With UTxO-HD and the split of the Ledger ledger state into the in-memory
part and the on-disk part, this splitting was reflected in the new type
parameter added to the (Consensus)
LedgerState
, to which we refer as "the
MapKind" or mk
.
Every LedgerState
(or LedgerState
-like
type, such as the ExtLedgerState
) is
associated with a LedgerTables
and they both share the mk
. They both are
of kind LedgerStateKind
. LedgerTables
is just a way to refer only to a
partial view of the on-disk data without having the rest of the in-memory
LedgerState
in scope.
The mk
can be instantiated to anything that is map-like, i.e. that expects
two type parameters, the key and the value.
Constructors
LedgerTables | |
Fields
|
Instances
(Ord (TxIn l), Eq (TxOut l), Show (TxIn l), Show (TxOut l), NoThunks (TxIn l), NoThunks (TxOut l), MemPack (TxIn l), IndexedMemPack (MemPackIdx l EmptyMK) (TxOut l)) ⇒ HasLedgerTables (LedgerTables l) | |||||
Defined in Ouroboros.Consensus.Ledger.Tables Methods projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerTables l mk → LedgerTables (LedgerTables l) mk Source # withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerTables l any → LedgerTables (LedgerTables l) mk → LedgerTables l mk Source # | |||||
Generic (LedgerTables l mk) | |||||
Defined in Ouroboros.Consensus.Ledger.Tables.Basics Associated Types
Methods from ∷ LedgerTables l mk → Rep (LedgerTables l mk) x # to ∷ Rep (LedgerTables l mk) x → LedgerTables l mk # | |||||
Show (mk (TxIn l) (TxOut l)) ⇒ Show (LedgerTables l mk) | |||||
Defined in Ouroboros.Consensus.Ledger.Tables.Basics Methods showsPrec ∷ Int → LedgerTables l mk → ShowS # show ∷ LedgerTables l mk → String # showList ∷ [LedgerTables l mk] → ShowS # | |||||
Eq (mk (TxIn l) (TxOut l)) ⇒ Eq (LedgerTables l mk) | |||||
Defined in Ouroboros.Consensus.Ledger.Tables.Basics Methods (==) ∷ LedgerTables l mk → LedgerTables l mk → Bool # (/=) ∷ LedgerTables l mk → LedgerTables l mk → Bool # | |||||
NoThunks (mk (TxIn l) (TxOut l)) ⇒ NoThunks (LedgerTables l mk) | |||||
Defined in Ouroboros.Consensus.Ledger.Tables.Basics | |||||
type TxIn (LedgerTables l) | |||||
Defined in Ouroboros.Consensus.Ledger.Tables.Basics | |||||
type TxOut (LedgerTables l) | |||||
Defined in Ouroboros.Consensus.Ledger.Tables.Basics | |||||
type Rep (LedgerTables l mk) | |||||
Defined in Ouroboros.Consensus.Ledger.Tables.Basics type Rep (LedgerTables l mk) = D1 ('MetaData "LedgerTables" "Ouroboros.Consensus.Ledger.Tables.Basics" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "LedgerTables" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLedgerTables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (mk (TxIn l) (TxOut l))))) | |||||
type SerializeTablesHint (LedgerTables l ValuesMK) | |||||
Defined in Ouroboros.Consensus.Ledger.Tables | |||||
type InitHint (LedgerTables l ValuesMK) | |||||
type ReadHint (LedgerTables l ValuesMK) | |||||
type WriteHint (LedgerTables l DiffMK) | |||||
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.Util.TestBlock Associated Types
Methods from ∷ StorageConfig TestBlock → Rep (StorageConfig TestBlock) x # to ∷ Rep (StorageConfig TestBlock) x → StorageConfig TestBlock # | |||||
Show (StorageConfig TestBlock) Source # | |||||
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 # | |||||
data StorageConfig TestBlock Source # | 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.26.0.0-inplace" 'False) (C1 ('MetaCons "DualStorageConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "dualStorageConfigMain") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StorageConfig m)) :*: S1 ('MetaSel ('Just "dualStorageConfigAux") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StorageConfig a)))) | |||||
type Rep (StorageConfig TestBlock) Source # | |||||
newtype StorageConfig (HardForkBlock xs) | |||||
data StorageConfig (DualBlock m a) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual |
data TestBlockError ptype Source #
Constructors
InvalidHash | The hashes don't line up |
Fields
| |
InvalidBlock | The block itself is invalid |
InvalidPayload (PayloadDependentError ptype) |
Instances
Generic (TestBlockError ptype) Source # | |||||
Defined in Test.Util.TestBlock Associated Types
Methods from ∷ TestBlockError ptype → Rep (TestBlockError ptype) x # to ∷ Rep (TestBlockError ptype) x → TestBlockError ptype # | |||||
Show (PayloadDependentError ptype) ⇒ Show (TestBlockError ptype) Source # | |||||
Defined in Test.Util.TestBlock Methods showsPrec ∷ Int → TestBlockError ptype → ShowS # show ∷ TestBlockError ptype → String # showList ∷ [TestBlockError ptype] → ShowS # | |||||
Eq (PayloadDependentError ptype) ⇒ Eq (TestBlockError ptype) Source # | |||||
Defined in Test.Util.TestBlock Methods (==) ∷ TestBlockError ptype → TestBlockError ptype → Bool # (/=) ∷ TestBlockError ptype → TestBlockError ptype → Bool # | |||||
(Typeable ptype, Generic (PayloadDependentError ptype), NoThunks (PayloadDependentError ptype)) ⇒ NoThunks (TestBlockError ptype) Source # | |||||
Defined in Test.Util.TestBlock | |||||
type Rep (TestBlockError ptype) Source # | |||||
Defined in Test.Util.TestBlock type Rep (TestBlockError ptype) = D1 ('MetaData "TestBlockError" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "InvalidHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ChainHash (TestBlockWith ptype))) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ChainHash (TestBlockWith ptype)))) :+: (C1 ('MetaCons "InvalidBlock" 'PrefixI 'False) (U1 ∷ Type → Type) :+: C1 ('MetaCons "InvalidPayload" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PayloadDependentError ptype))))) |
data TestBlockWith ptype Source #
Test block parametrized on the payload type
For blocks without payload see the TestBlock
type alias.
By defining a PayloadSemantics
it is possible to obtain an ApplyBlock
instance. See the former class for more details.
Instances
HasHardForkHistory TestBlock Source # | |||||||||
Defined in Test.Util.TestBlock Associated Types
Methods hardForkSummary ∷ ∀ (mk ∷ MapKind). LedgerConfig TestBlock → LedgerState TestBlock mk → Summary (HardForkIndices TestBlock) Source # | |||||||||
BlockSupportsLedgerQuery TestBlock Source # | |||||||||
Defined in Test.Util.TestBlock Methods answerPureBlockQuery ∷ ExtLedgerCfg TestBlock → BlockQuery TestBlock 'QFNoTables result → ExtLedgerState TestBlock EmptyMK → result Source # answerBlockQueryLookup ∷ MonadSTM m ⇒ ExtLedgerCfg TestBlock → BlockQuery TestBlock 'QFLookupTables result → ReadOnlyForker' m TestBlock → m result Source # answerBlockQueryTraverse ∷ MonadSTM m ⇒ ExtLedgerCfg TestBlock → BlockQuery TestBlock 'QFTraverseTables result → ReadOnlyForker' m TestBlock → m result Source # blockQueryIsSupportedOnVersion ∷ ∀ (fp ∷ QueryFootprint) result. BlockQuery TestBlock fp result → BlockNodeToClientVersion TestBlock → Bool Source # | |||||||||
ShowProxy TestBlock Source # | |||||||||
SameDepIndex2 (BlockQuery TestBlock) Source # | |||||||||
Defined in Test.Util.TestBlock Methods sameDepIndex2 ∷ ∀ (x ∷ QueryFootprint) a (y ∷ QueryFootprint) b. BlockQuery TestBlock x a → BlockQuery TestBlock y b → Maybe ('(x, a) :~: '(y, b)) Source # | |||||||||
HasNestedContent f (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Methods unnest ∷ f (TestBlockWith ptype) → DepPair (NestedCtxt f (TestBlockWith ptype)) Source # nest ∷ DepPair (NestedCtxt f (TestBlockWith ptype)) → f (TestBlockWith ptype) Source # | |||||||||
ReconstructNestedCtxt Header (TestBlockWith ptype) Source # | |||||||||
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 (TestBlockWith ptype ∷ Type) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
Typeable ptype ⇒ ShowProxy (Header (TestBlockWith ptype) ∷ Type) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
SameDepIndex (NestedCtxt_ (TestBlockWith ptype) f ∷ Type → Type) Source # | |||||||||
Defined in Test.Util.TestBlock Methods sameDepIndex ∷ NestedCtxt_ (TestBlockWith ptype) f a → NestedCtxt_ (TestBlockWith ptype) f b → Maybe (a :~: b) Source # | |||||||||
TrivialDependency (NestedCtxt_ (TestBlockWith ptype) f ∷ Type → Type) Source # | |||||||||
Defined in Test.Util.TestBlock Methods hasSingleIndex ∷ NestedCtxt_ (TestBlockWith ptype) f a → NestedCtxt_ (TestBlockWith ptype) f b → a :~: b Source # indexIsTrivial ∷ NestedCtxt_ (TestBlockWith ptype) f (TrivialIndex (NestedCtxt_ (TestBlockWith ptype) f) ∷ Type) Source # | |||||||||
Generic (BlockConfig (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock Associated Types
Methods from ∷ BlockConfig (TestBlockWith ptype) → Rep (BlockConfig (TestBlockWith ptype)) x # to ∷ Rep (BlockConfig (TestBlockWith ptype)) x → BlockConfig (TestBlockWith ptype) # | |||||||||
Generic (CodecConfig TestBlock) Source # | |||||||||
Defined in Test.Util.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.Util.TestBlock Associated Types
Methods from ∷ StorageConfig TestBlock → Rep (StorageConfig TestBlock) x # to ∷ Rep (StorageConfig TestBlock) x → StorageConfig TestBlock # | |||||||||
Generic (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Associated Types
Methods from ∷ TestBlockWith ptype → Rep (TestBlockWith ptype) x # to ∷ Rep (TestBlockWith ptype) x → TestBlockWith ptype # | |||||||||
Show (BlockConfig (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock Methods showsPrec ∷ Int → BlockConfig (TestBlockWith ptype) → ShowS # show ∷ BlockConfig (TestBlockWith ptype) → String # showList ∷ [BlockConfig (TestBlockWith ptype)] → ShowS # | |||||||||
Show (CodecConfig TestBlock) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
Show ptype ⇒ Show (Header (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
Show (StorageConfig TestBlock) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
Show ptype ⇒ Show (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Methods showsPrec ∷ Int → TestBlockWith ptype → ShowS # show ∷ TestBlockWith ptype → String # showList ∷ [TestBlockWith ptype] → ShowS # | |||||||||
Eq ptype ⇒ Eq (Header (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock Methods (==) ∷ Header (TestBlockWith ptype) → Header (TestBlockWith ptype) → Bool # (/=) ∷ Header (TestBlockWith ptype) → Header (TestBlockWith ptype) → Bool # | |||||||||
Eq ptype ⇒ Eq (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Methods (==) ∷ TestBlockWith ptype → TestBlockWith ptype → Bool # (/=) ∷ TestBlockWith ptype → TestBlockWith ptype → Bool # | |||||||||
Ord ptype ⇒ Ord (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Methods compare ∷ TestBlockWith ptype → TestBlockWith ptype → Ordering # (<) ∷ TestBlockWith ptype → TestBlockWith ptype → Bool # (<=) ∷ TestBlockWith ptype → TestBlockWith ptype → Bool # (>) ∷ TestBlockWith ptype → TestBlockWith ptype → Bool # (>=) ∷ TestBlockWith ptype → TestBlockWith ptype → Bool # max ∷ TestBlockWith ptype → TestBlockWith ptype → TestBlockWith ptype # min ∷ TestBlockWith ptype → TestBlockWith ptype → TestBlockWith ptype # | |||||||||
NoThunks (BlockConfig (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock Methods noThunks ∷ Context → BlockConfig (TestBlockWith ptype) → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → BlockConfig (TestBlockWith ptype) → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (BlockConfig (TestBlockWith ptype)) → String Source # | |||||||||
NoThunks (CodecConfig TestBlock) Source # | |||||||||
NoThunks ptype ⇒ NoThunks (Header (TestBlockWith ptype)) Source # | |||||||||
NoThunks (StorageConfig TestBlock) Source # | |||||||||
NoThunks ptype ⇒ NoThunks (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
ConvertRawHash (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Methods toRawHash ∷ proxy (TestBlockWith ptype) → HeaderHash (TestBlockWith ptype) → ByteString Source # fromRawHash ∷ proxy (TestBlockWith ptype) → ByteString → HeaderHash (TestBlockWith ptype) Source # toShortRawHash ∷ proxy (TestBlockWith ptype) → HeaderHash (TestBlockWith ptype) → ShortByteString Source # fromShortRawHash ∷ proxy (TestBlockWith ptype) → ShortByteString → HeaderHash (TestBlockWith ptype) Source # hashSize ∷ proxy (TestBlockWith ptype) → Word32 Source # | |||||||||
(Typeable ptype, Eq ptype) ⇒ GetHeader (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Methods getHeader ∷ TestBlockWith ptype → Header (TestBlockWith ptype) Source # blockMatchesHeader ∷ Header (TestBlockWith ptype) → TestBlockWith ptype → Bool Source # headerIsEBB ∷ Header (TestBlockWith ptype) → Maybe EpochNo Source # | |||||||||
(Typeable ptype, Eq ptype) ⇒ GetPrevHash (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Methods headerPrevHash ∷ Header (TestBlockWith ptype) → ChainHash (TestBlockWith ptype) Source # | |||||||||
BlockSupportsProtocol (TestBlockWith ptype) ⇒ BlockSupportsDiffusionPipelining (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Associated Types
Methods initialTentativeHeaderState ∷ Proxy (TestBlockWith ptype) → TentativeHeaderState (TestBlockWith ptype) Source # tentativeHeaderView ∷ BlockConfig (TestBlockWith ptype) → Header (TestBlockWith ptype) → TentativeHeaderView (TestBlockWith ptype) Source # applyTentativeHeaderView ∷ Proxy (TestBlockWith ptype) → TentativeHeaderView (TestBlockWith ptype) → TentativeHeaderState (TestBlockWith ptype) → Maybe (TentativeHeaderState (TestBlockWith ptype)) Source # | |||||||||
(Typeable ptype, Eq ptype, NoThunks ptype, NoThunks (CodecConfig (TestBlockWith ptype)), NoThunks (StorageConfig (TestBlockWith ptype))) ⇒ BlockSupportsProtocol (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Methods validateView ∷ BlockConfig (TestBlockWith ptype) → Header (TestBlockWith ptype) → ValidateView (BlockProtocol (TestBlockWith ptype)) Source # selectView ∷ BlockConfig (TestBlockWith ptype) → Header (TestBlockWith ptype) → SelectView (BlockProtocol (TestBlockWith ptype)) Source # projectChainOrderConfig ∷ BlockConfig (TestBlockWith ptype) → ChainOrderConfig (SelectView (BlockProtocol (TestBlockWith ptype))) Source # | |||||||||
ConfigSupportsNode (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Methods getSystemStart ∷ BlockConfig (TestBlockWith ptype) → SystemStart Source # getNetworkMagic ∷ BlockConfig (TestBlockWith ptype) → NetworkMagic Source # | |||||||||
ImmutableEraParams (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Methods immutableEraParams ∷ TopLevelConfig (TestBlockWith ptype) → EraParams Source # | |||||||||
PayloadSemantics ptype ⇒ BasicEnvelopeValidation (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Methods expectedFirstBlockNo ∷ proxy (TestBlockWith ptype) → BlockNo Source # expectedNextBlockNo ∷ proxy (TestBlockWith ptype) → TipInfo (TestBlockWith ptype) → TipInfo (TestBlockWith ptype) → BlockNo → BlockNo Source # minimumPossibleSlotNo ∷ Proxy (TestBlockWith ptype) → SlotNo Source # minimumNextSlotNo ∷ proxy (TestBlockWith ptype) → TipInfo (TestBlockWith ptype) → TipInfo (TestBlockWith ptype) → SlotNo → SlotNo Source # | |||||||||
PayloadSemantics ptype ⇒ HasAnnTip (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Associated Types
Methods getTipInfo ∷ Header (TestBlockWith ptype) → TipInfo (TestBlockWith ptype) Source # tipInfoHash ∷ proxy (TestBlockWith ptype) → TipInfo (TestBlockWith ptype) → HeaderHash (TestBlockWith ptype) Source # | |||||||||
PayloadSemantics ptype ⇒ ValidateEnvelope (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Associated Types
Methods additionalEnvelopeChecks ∷ TopLevelConfig (TestBlockWith ptype) → LedgerView (BlockProtocol (TestBlockWith ptype)) → Header (TestBlockWith ptype) → Except (OtherHeaderEnvelopeError (TestBlockWith ptype)) () Source # | |||||||||
PayloadSemantics ptype ⇒ UpdateLedger (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
GetTip (LedgerState (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock Methods getTip ∷ ∀ (mk ∷ MapKind). LedgerState (TestBlockWith ptype) mk → Point (LedgerState (TestBlockWith ptype)) Source # | |||||||||
PayloadSemantics ptype ⇒ IsLedger (LedgerState (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock Associated Types
Methods applyChainTickLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (LedgerState (TestBlockWith ptype)) → SlotNo → LedgerState (TestBlockWith ptype) EmptyMK → LedgerResult (LedgerState (TestBlockWith ptype)) (Ticked (LedgerState (TestBlockWith ptype)) DiffMK) Source # | |||||||||
InspectLedger (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Associated Types
Methods inspectLedger ∷ ∀ (mk1 ∷ MapKind) (mk2 ∷ MapKind). TopLevelConfig (TestBlockWith ptype) → LedgerState (TestBlockWith ptype) mk1 → LedgerState (TestBlockWith ptype) mk2 → [LedgerEvent (TestBlockWith ptype)] Source # | |||||||||
PayloadSemantics ptype ⇒ LedgerSupportsProtocol (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Methods protocolLedgerView ∷ ∀ (mk ∷ MapKind). LedgerConfig (TestBlockWith ptype) → Ticked (LedgerState (TestBlockWith ptype)) mk → LedgerView (BlockProtocol (TestBlockWith ptype)) Source # ledgerViewForecastAt ∷ ∀ (mk ∷ MapKind). HasCallStack ⇒ LedgerConfig (TestBlockWith ptype) → LedgerState (TestBlockWith ptype) mk → Forecast (LedgerView (BlockProtocol (TestBlockWith ptype))) Source # | |||||||||
CanStowLedgerTables (LedgerState TestBlock) Source # | |||||||||
HasLedgerTables (LedgerState TestBlock) Source # | |||||||||
Defined in Test.Util.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.Util.TestBlock Methods convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). LedgerState TestBlock mk → LedgerState TestBlock mk' Source # | |||||||||
SerializeTablesWithHint (LedgerState TestBlock) Source # | |||||||||
Defined in Test.Util.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 # | |||||||||
HasNetworkProtocolVersion (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Associated Types
| |||||||||
SignedHeader (Header (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock Methods headerSigned ∷ Header (TestBlockWith ptype) → Signed (Header (TestBlockWith ptype)) Source # | |||||||||
(Serialise ptype, PayloadSemantics ptype, IndexedMemPack (LedgerState (TestBlockWith ptype) EmptyMK) (TxOut (LedgerState (TestBlockWith ptype))), SerializeTablesWithHint (LedgerState (TestBlockWith ptype))) ⇒ SerialiseDiskConstraints (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
CanUpgradeLedgerTables (LedgerState TestBlock) Source # | |||||||||
Defined in Test.Util.TestBlock Methods upgradeTables ∷ ∀ (mk1 ∷ MapKind) (mk2 ∷ MapKind). LedgerState TestBlock mk1 → LedgerState TestBlock mk2 → LedgerTables (LedgerState TestBlock) ValuesMK → LedgerTables (LedgerState TestBlock) ValuesMK Source # | |||||||||
Serialise ptype ⇒ HasBinaryBlockInfo (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Methods getBinaryBlockInfo ∷ TestBlockWith ptype → BinaryBlockInfo Source # | |||||||||
(Typeable ptype, Eq ptype) ⇒ Condense (Header (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
(Typeable ptype, Eq ptype) ⇒ Condense (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Methods condense ∷ TestBlockWith ptype → String Source # | |||||||||
Typeable ptype ⇒ HasHeader (Header (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock Methods getHeaderFields ∷ Header (TestBlockWith ptype) → HeaderFields (Header (TestBlockWith ptype)) Source # | |||||||||
(Typeable ptype, Eq ptype) ⇒ HasHeader (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Methods getHeaderFields ∷ TestBlockWith ptype → HeaderFields (TestBlockWith ptype) Source # | |||||||||
Serialise ptype ⇒ Serialise (Header (TestBlockWith ptype)) Source # | |||||||||
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 # | |||||||||
Serialise (RealPoint (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock Methods encode ∷ RealPoint (TestBlockWith ptype) → Encoding Source # decode ∷ Decoder s (RealPoint (TestBlockWith ptype)) Source # encodeList ∷ [RealPoint (TestBlockWith ptype)] → Encoding Source # decodeList ∷ Decoder s [RealPoint (TestBlockWith ptype)] Source # | |||||||||
Serialise (AnnTip (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock Methods encode ∷ AnnTip (TestBlockWith ptype) → Encoding Source # decode ∷ Decoder s (AnnTip (TestBlockWith ptype)) Source # encodeList ∷ [AnnTip (TestBlockWith ptype)] → Encoding Source # decodeList ∷ Decoder s [AnnTip (TestBlockWith ptype)] Source # | |||||||||
Serialise ptype ⇒ Serialise (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Methods encode ∷ TestBlockWith ptype → Encoding Source # decode ∷ Decoder s (TestBlockWith ptype) Source # encodeList ∷ [TestBlockWith ptype] → Encoding Source # decodeList ∷ Decoder s [TestBlockWith ptype] Source # | |||||||||
ToExpr ptype ⇒ ToExpr (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Methods toExpr ∷ TestBlockWith ptype → Expr Source # listToExpr ∷ [TestBlockWith ptype] → Expr Source # | |||||||||
DecodeDisk (TestBlockWith ptype) () Source # | |||||||||
Defined in Test.Util.TestBlock Methods decodeDisk ∷ CodecConfig (TestBlockWith ptype) → ∀ s. Decoder s () Source # | |||||||||
EncodeDisk (TestBlockWith ptype) () Source # | |||||||||
Defined in Test.Util.TestBlock Methods encodeDisk ∷ CodecConfig (TestBlockWith ptype) → () → Encoding Source # | |||||||||
PayloadSemantics ptype ⇒ ApplyBlock (LedgerState (TestBlockWith ptype)) (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Methods applyBlockLedgerResultWithValidation ∷ ValidationPolicy → ComputeLedgerEvents → LedgerCfg (LedgerState (TestBlockWith ptype)) → TestBlockWith ptype → Ticked (LedgerState (TestBlockWith ptype)) ValuesMK → Except (LedgerErr (LedgerState (TestBlockWith ptype))) (LedgerResult (LedgerState (TestBlockWith ptype)) (LedgerState (TestBlockWith ptype) DiffMK)) Source # applyBlockLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (LedgerState (TestBlockWith ptype)) → TestBlockWith ptype → Ticked (LedgerState (TestBlockWith ptype)) ValuesMK → Except (LedgerErr (LedgerState (TestBlockWith ptype))) (LedgerResult (LedgerState (TestBlockWith ptype)) (LedgerState (TestBlockWith ptype) DiffMK)) Source # reapplyBlockLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (LedgerState (TestBlockWith ptype)) → TestBlockWith ptype → Ticked (LedgerState (TestBlockWith ptype)) ValuesMK → LedgerResult (LedgerState (TestBlockWith ptype)) (LedgerState (TestBlockWith ptype) DiffMK) Source # getBlockKeySets ∷ TestBlockWith ptype → LedgerTables (LedgerState (TestBlockWith ptype)) KeysMK Source # | |||||||||
DecodeDisk (TestBlockWith ptype) (AnnTip (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock Methods decodeDisk ∷ CodecConfig (TestBlockWith ptype) → ∀ s. Decoder s (AnnTip (TestBlockWith ptype)) Source # | |||||||||
Serialise ptype ⇒ DecodeDiskDep (NestedCtxt Header) (TestBlockWith ptype) Source # | |||||||||
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)) Source # | |||||||||
Defined in Test.Util.TestBlock Methods encodeDisk ∷ CodecConfig (TestBlockWith ptype) → Header (TestBlockWith ptype) → Encoding Source # | |||||||||
EncodeDisk (TestBlockWith ptype) (AnnTip (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock Methods encodeDisk ∷ CodecConfig (TestBlockWith ptype) → AnnTip (TestBlockWith ptype) → Encoding Source # | |||||||||
Serialise ptype ⇒ EncodeDisk (TestBlockWith ptype) (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Methods encodeDisk ∷ CodecConfig (TestBlockWith ptype) → TestBlockWith ptype → Encoding Source # | |||||||||
Serialise ptype ⇒ EncodeDiskDep (NestedCtxt Header) (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Methods encodeDiskDep ∷ CodecConfig (TestBlockWith ptype) → NestedCtxt Header (TestBlockWith ptype) a → a → Encoding Source # | |||||||||
PayloadSemantics ptype ⇒ DecodeDisk (TestBlockWith ptype) (LedgerState (TestBlockWith ptype) EmptyMK) Source # | |||||||||
Defined in Test.Util.TestBlock Methods decodeDisk ∷ CodecConfig (TestBlockWith ptype) → ∀ s. Decoder s (LedgerState (TestBlockWith ptype) EmptyMK) Source # | |||||||||
Serialise ptype ⇒ DecodeDisk (TestBlockWith ptype) (ByteString → Header (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock Methods decodeDisk ∷ CodecConfig (TestBlockWith ptype) → ∀ s. Decoder s (ByteString → Header (TestBlockWith ptype)) Source # | |||||||||
Serialise ptype ⇒ DecodeDisk (TestBlockWith ptype) (ByteString → TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Methods decodeDisk ∷ CodecConfig (TestBlockWith ptype) → ∀ s. Decoder s (ByteString → TestBlockWith ptype) Source # | |||||||||
PayloadSemantics ptype ⇒ EncodeDisk (TestBlockWith ptype) (LedgerState (TestBlockWith ptype) EmptyMK) Source # | |||||||||
Defined in Test.Util.TestBlock Methods encodeDisk ∷ CodecConfig (TestBlockWith ptype) → LedgerState (TestBlockWith ptype) EmptyMK → Encoding Source # | |||||||||
Generic (LedgerState (TestBlockWith ptype) mk) Source # | |||||||||
Defined in Test.Util.TestBlock Associated Types
Methods from ∷ LedgerState (TestBlockWith ptype) mk → Rep (LedgerState (TestBlockWith ptype) mk) x # to ∷ Rep (LedgerState (TestBlockWith ptype) mk) x → LedgerState (TestBlockWith ptype) mk # | |||||||||
(ShowMK mk, PayloadSemantics ptype) ⇒ Show (LedgerState (TestBlockWith ptype) mk) Source # | |||||||||
Defined in Test.Util.TestBlock Methods showsPrec ∷ Int → LedgerState (TestBlockWith ptype) mk → ShowS # show ∷ LedgerState (TestBlockWith ptype) mk → String # showList ∷ [LedgerState (TestBlockWith ptype) mk] → ShowS # | |||||||||
Eq (PayloadDependentState ptype mk) ⇒ Eq (LedgerState (TestBlockWith ptype) mk) Source # | |||||||||
Defined in Test.Util.TestBlock Methods (==) ∷ LedgerState (TestBlockWith ptype) mk → LedgerState (TestBlockWith ptype) mk → Bool # (/=) ∷ LedgerState (TestBlockWith ptype) mk → LedgerState (TestBlockWith ptype) mk → Bool # | |||||||||
NoThunks (PayloadDependentState ptype mk) ⇒ NoThunks (LedgerState (TestBlockWith ptype) mk) Source # | |||||||||
Defined in Test.Util.TestBlock Methods noThunks ∷ Context → LedgerState (TestBlockWith ptype) mk → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → LedgerState (TestBlockWith ptype) mk → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (LedgerState (TestBlockWith ptype) mk) → String Source # | |||||||||
GetTip (Ticked (LedgerState (TestBlockWith ptype))) Source # | |||||||||
Defined in Test.Util.TestBlock Methods getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (TestBlockWith ptype)) mk → Point (Ticked (LedgerState (TestBlockWith ptype))) Source # | |||||||||
HasLedgerTables (Ticked (LedgerState TestBlock)) Source # | |||||||||
Defined in Test.Util.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.Util.TestBlock Methods convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). Ticked (LedgerState TestBlock) mk → Ticked (LedgerState TestBlock) mk' Source # | |||||||||
Condense (ChainHash (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
ShowQuery (BlockQuery TestBlock fp) Source # | |||||||||
Defined in Test.Util.TestBlock Methods showResult ∷ BlockQuery TestBlock fp result → result → String Source # | |||||||||
PayloadSemantics ptype ⇒ Serialise (LedgerState (TestBlockWith ptype) EmptyMK) Source # | |||||||||
Defined in Test.Util.TestBlock Methods encode ∷ LedgerState (TestBlockWith ptype) EmptyMK → Encoding Source # decode ∷ Decoder s (LedgerState (TestBlockWith ptype) EmptyMK) Source # encodeList ∷ [LedgerState (TestBlockWith ptype) EmptyMK] → Encoding Source # decodeList ∷ Decoder s [LedgerState (TestBlockWith ptype) EmptyMK] Source # | |||||||||
PayloadSemantics ptype ⇒ Serialise (ExtLedgerState (TestBlockWith ptype) EmptyMK) Source # | |||||||||
Defined in Test.Util.TestBlock Methods encode ∷ ExtLedgerState (TestBlockWith ptype) EmptyMK → Encoding Source # decode ∷ Decoder s (ExtLedgerState (TestBlockWith ptype) EmptyMK) Source # encodeList ∷ [ExtLedgerState (TestBlockWith ptype) EmptyMK] → Encoding Source # decodeList ∷ Decoder s [ExtLedgerState (TestBlockWith ptype) EmptyMK] Source # | |||||||||
IndexedMemPack (LedgerState TestBlock EmptyMK) Void Source # | |||||||||
Defined in Test.Util.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 # | |||||||||
Generic (Ticked (LedgerState (TestBlockWith ptype)) mk) Source # | |||||||||
Defined in Test.Util.TestBlock Associated Types
Methods from ∷ Ticked (LedgerState (TestBlockWith ptype)) mk → Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) x # to ∷ Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) x → Ticked (LedgerState (TestBlockWith ptype)) mk # | |||||||||
Show (NestedCtxt_ (TestBlockWith ptype) f a) Source # | |||||||||
Defined in Test.Util.TestBlock Methods showsPrec ∷ Int → NestedCtxt_ (TestBlockWith ptype) f a → ShowS # show ∷ NestedCtxt_ (TestBlockWith ptype) f a → String # showList ∷ [NestedCtxt_ (TestBlockWith ptype) f a] → ShowS # | |||||||||
Show (BlockQuery TestBlock fp result) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
Eq (BlockQuery TestBlock fp result) Source # | |||||||||
Defined in Test.Util.TestBlock Methods (==) ∷ BlockQuery TestBlock fp result → BlockQuery TestBlock fp result → Bool # (/=) ∷ BlockQuery TestBlock fp result → BlockQuery TestBlock fp result → Bool # | |||||||||
(NoThunksMK mk, NoThunks (PayloadDependentState ptype mk)) ⇒ NoThunks (Ticked (LedgerState (TestBlockWith ptype)) mk) Source # | |||||||||
Defined in Test.Util.TestBlock Methods noThunks ∷ Context → Ticked (LedgerState (TestBlockWith ptype)) mk → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → Ticked (LedgerState (TestBlockWith ptype)) mk → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (Ticked (LedgerState (TestBlockWith ptype)) mk) → String Source # | |||||||||
data CodecConfig TestBlock Source # | The | ||||||||
Defined in Test.Util.TestBlock | |||||||||
data StorageConfig TestBlock Source # | The | ||||||||
Defined in Test.Util.TestBlock | |||||||||
type HardForkIndices TestBlock Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
data BlockQuery TestBlock fp result Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
type TrivialIndex (NestedCtxt_ (TestBlockWith ptype) f ∷ Type → Type) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
type HeaderHash (TestBlockWith ptype ∷ Type) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
type Rep (BlockConfig (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock type Rep (BlockConfig (TestBlockWith ptype)) = D1 ('MetaData "BlockConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "testBlockNumCoreNodes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NumCoreNodes))) | |||||||||
type Rep (CodecConfig TestBlock) Source # | |||||||||
type Rep (StorageConfig TestBlock) Source # | |||||||||
type Rep (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock type Rep (TestBlockWith ptype) = D1 ('MetaData "TestBlockWith" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockWith" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tbHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TestHash) :*: S1 ('MetaSel ('Just "tbSlot") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo)) :*: (S1 ('MetaSel ('Just "tbValid") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Validity) :*: S1 ('MetaSel ('Just "tbPayload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ptype)))) | |||||||||
data BlockConfig (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
type BlockProtocol (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
newtype Header (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
data NestedCtxt_ (TestBlockWith ptype) f a Source # | |||||||||
Defined in Test.Util.TestBlock data NestedCtxt_ (TestBlockWith ptype) f a where
| |||||||||
type TentativeHeaderState (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock type TentativeHeaderState (TestBlockWith ptype) = TentativeHeaderState (SelectViewDiffusionPipelining (TestBlockWith ptype)) | |||||||||
type TentativeHeaderView (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock type TentativeHeaderView (TestBlockWith ptype) = TentativeHeaderView (SelectViewDiffusionPipelining (TestBlockWith ptype)) | |||||||||
type OtherHeaderEnvelopeError (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
type TipInfo (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
type AuxLedgerEvent (LedgerState (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock type AuxLedgerEvent (LedgerState (TestBlockWith ptype)) = VoidLedgerEvent (LedgerState (TestBlockWith ptype)) | |||||||||
type LedgerCfg (LedgerState (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
type LedgerErr (LedgerState (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
data LedgerState (TestBlockWith ptype) mk Source # | |||||||||
Defined in Test.Util.TestBlock data LedgerState (TestBlockWith ptype) mk = TestLedger {
| |||||||||
type LedgerUpdate (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
type LedgerWarning (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
type TxIn (LedgerState TestBlock) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
type TxOut (LedgerState TestBlock) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
type BlockNodeToClientVersion (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
type BlockNodeToNodeVersion (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
type Signed (Header (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
type Rep (LedgerState (TestBlockWith ptype) mk) Source # | |||||||||
Defined in Test.Util.TestBlock type Rep (LedgerState (TestBlockWith ptype) mk) = D1 ('MetaData "LedgerState" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "lastAppliedPoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Point (TestBlockWith ptype))) :*: S1 ('MetaSel ('Just "payloadDependentState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PayloadDependentState ptype mk)))) | |||||||||
newtype Ticked (LedgerState (TestBlockWith ptype) ∷ MapKind → Type) (mk ∷ MapKind) Source # | |||||||||
Defined in Test.Util.TestBlock newtype Ticked (LedgerState (TestBlockWith ptype) ∷ MapKind → Type) (mk ∷ MapKind) = TickedTestLedger {
| |||||||||
type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) Source # | |||||||||
Defined in Test.Util.TestBlock type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) = D1 ('MetaData "Ticked" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'True) (C1 ('MetaCons "TickedTestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTickedTestLedger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerState (TestBlockWith ptype) mk)))) |
Instances
Generic TestHash Source # | |||||
Defined in Test.Util.TestBlock Associated Types
| |||||
Show TestHash Source # | |||||
Eq TestHash Source # | |||||
Ord TestHash Source # | |||||
NoThunks TestHash Source # | |||||
Condense TestHash Source # | |||||
Serialise TestHash Source # | |||||
ToExpr TestHash Source # | |||||
type Rep TestHash Source # | |||||
Defined in Test.Util.TestBlock type Rep TestHash = D1 ('MetaData "TestHash" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'True) (C1 ('MetaCons "UnsafeTestHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTestHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Word64)))) |
Instances
Bounded Validity Source # | |
Enum Validity Source # | |
Generic Validity Source # | |
Defined in Test.Util.TestBlock | |
Show Validity Source # | |
Eq Validity Source # | |
Ord Validity Source # | |
NoThunks Validity Source # | |
Serialise Validity Source # | |
ToExpr Validity Source # | |
type Rep Validity Source # | |
firstBlockWithPayload ∷ Word64 → ptype → TestBlockWith ptype Source #
Create the first block in the given fork, [fork]
, with the given payload.
The SlotNo
will be 1.
successorBlockWithPayload ∷ TestHash → SlotNo → ptype → TestBlockWith ptype Source #
Create the successor of the given block without forking: b -> b ++ [0]
(in
the printed representation) The SlotNo
is increased by 1.
In Zipper parlance, this corresponds to going down in a tree.
testHashFromList ∷ [Word64] → TestHash Source #
Test block without payload
type TestBlock = TestBlockWith () Source #
Block without payload
Payload semantics
data family PayloadDependentState ptype (mk ∷ MapKind) Source #
Instances
Generic (PayloadDependentState () mk) Source # | |||||
Defined in Test.Util.TestBlock Associated Types
Methods from ∷ PayloadDependentState () mk → Rep (PayloadDependentState () mk) x # to ∷ Rep (PayloadDependentState () mk) x → PayloadDependentState () mk # | |||||
Show (PayloadDependentState () mk) Source # | |||||
Defined in Test.Util.TestBlock Methods showsPrec ∷ Int → PayloadDependentState () mk → ShowS # show ∷ PayloadDependentState () mk → String # showList ∷ [PayloadDependentState () mk] → ShowS # | |||||
Eq (PayloadDependentState () mk) Source # | |||||
Defined in Test.Util.TestBlock Methods (==) ∷ PayloadDependentState () mk → PayloadDependentState () mk → Bool # (/=) ∷ PayloadDependentState () mk → PayloadDependentState () mk → Bool # | |||||
NoThunks (PayloadDependentState () mk) Source # | |||||
Defined in Test.Util.TestBlock | |||||
Serialise (PayloadDependentState () mk) Source # | |||||
Defined in Test.Util.TestBlock Methods encode ∷ PayloadDependentState () mk → Encoding Source # decode ∷ Decoder s (PayloadDependentState () mk) Source # encodeList ∷ [PayloadDependentState () mk] → Encoding Source # decodeList ∷ Decoder s [PayloadDependentState () mk] Source # | |||||
data PayloadDependentState () mk Source # | |||||
Defined in Test.Util.TestBlock | |||||
type Rep (PayloadDependentState () mk) Source # | |||||
class (Typeable ptype, Eq ptype, NoThunks ptype, ∀ (mk ∷ MapKind). EqMK mk ⇒ Eq (PayloadDependentState ptype mk), ∀ (mk ∷ MapKind). NoThunksMK mk ⇒ NoThunks (PayloadDependentState ptype mk), ∀ (mk ∷ MapKind). ShowMK mk ⇒ Show (PayloadDependentState ptype mk), ∀ (mk ∷ MapKind). Generic (PayloadDependentState ptype mk), Serialise (PayloadDependentState ptype EmptyMK), HasLedgerTables (LedgerState (TestBlockWith ptype)), HasLedgerTables (Ticked (LedgerState (TestBlockWith ptype))), CanStowLedgerTables (LedgerState (TestBlockWith ptype)), Eq (PayloadDependentError ptype), Show (PayloadDependentError ptype), Generic (PayloadDependentError ptype), ToExpr (PayloadDependentError ptype), Serialise (PayloadDependentError ptype), NoThunks (PayloadDependentError ptype), NoThunks (CodecConfig (TestBlockWith ptype)), NoThunks (StorageConfig (TestBlockWith ptype))) ⇒ PayloadSemantics ptype where Source #
Associated Types
data PayloadDependentState ptype (mk ∷ MapKind) Source #
type PayloadDependentError ptype Source #
Methods
applyPayload ∷ PayloadDependentState ptype ValuesMK → ptype → Either (PayloadDependentError ptype) (PayloadDependentState ptype TrackingMK) Source #
getPayloadKeySets ∷ ptype → LedgerTables (LedgerState (TestBlockWith ptype)) KeysMK Source #
This function is used to implement the getBlockKeySets
function of the
ApplyBlock
class. Thus we assume that the payload contains all the
information needed to determine which keys should be retrieved from the
backing store to apply a TestBlockWith
.
Instances
PayloadSemantics () Source # | |||||||||
Defined in Test.Util.TestBlock Associated Types
Methods applyPayload ∷ PayloadDependentState () ValuesMK → () → Either (PayloadDependentError ()) (PayloadDependentState () TrackingMK) Source # getPayloadKeySets ∷ () → LedgerTables (LedgerState (TestBlockWith ())) KeysMK Source # |
applyDirectlyToPayloadDependentState ∷ PayloadSemantics ptype ⇒ Ticked (LedgerState (TestBlockWith ptype)) ValuesMK → ptype → Either (PayloadDependentError ptype) (Ticked (LedgerState (TestBlockWith ptype)) TrackingMK) Source #
Apply the payload directly to the payload dependent state portion of a ticked state, leaving the rest of the input ticked state unaltered.
LedgerState
data family LedgerState blk (mk ∷ MapKind) Source #
Ledger state associated with a block
This is the Consensus notion of a Ledger ledger state. Each block type is
associated with one of the Ledger types for the ledger state. Virtually
every concept in this codebase revolves around this type, or the referenced
blk
. Whenever we use the type variable l
we intend to signal that the
expected instantiation is either a LedgerState
or some wrapper over it
(like the ExtLedgerState
).
This type is parametrized over mk ::
to express the
MapKind
LedgerTables
contained in such a LedgerState
. See LedgerTables
for a
more thorough description.
The main operations we can do with a LedgerState
are ticking (defined in
IsLedger
), and applying a block (defined in
ApplyBlock
).
Instances
Bridge m a ⇒ GetTip (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods getTip ∷ ∀ (mk ∷ MapKind). LedgerState (DualBlock m a) mk → Point (LedgerState (DualBlock m a)) Source # | |||||||||
GetTip (LedgerState (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock Methods getTip ∷ ∀ (mk ∷ MapKind). LedgerState (TestBlockWith ptype) mk → Point (LedgerState (TestBlockWith ptype)) Source # | |||||||||
Bridge m a ⇒ IsLedger (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Associated Types
Methods applyChainTickLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (LedgerState (DualBlock m a)) → SlotNo → LedgerState (DualBlock m a) EmptyMK → LedgerResult (LedgerState (DualBlock m a)) (Ticked (LedgerState (DualBlock m a)) DiffMK) Source # | |||||||||
PayloadSemantics ptype ⇒ IsLedger (LedgerState (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock Associated Types
Methods applyChainTickLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (LedgerState (TestBlockWith ptype)) → SlotNo → LedgerState (TestBlockWith ptype) EmptyMK → LedgerResult (LedgerState (TestBlockWith ptype)) (Ticked (LedgerState (TestBlockWith ptype)) DiffMK) Source # | |||||||||
CanStowLedgerTables (LedgerState m) ⇒ CanStowLedgerTables (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods stowLedgerTables ∷ LedgerState (DualBlock m a) ValuesMK → LedgerState (DualBlock m a) EmptyMK Source # unstowLedgerTables ∷ LedgerState (DualBlock m a) EmptyMK → LedgerState (DualBlock m a) ValuesMK Source # | |||||||||
CanStowLedgerTables (LedgerState TestBlock) Source # | |||||||||
(Bridge m a, NoThunks (TxOut (LedgerState m)), NoThunks (TxIn (LedgerState m)), Show (TxOut (LedgerState m)), Show (TxIn (LedgerState m)), Eq (TxOut (LedgerState m)), Ord (TxIn (LedgerState m)), MemPack (TxIn (LedgerState m))) ⇒ HasLedgerTables (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerState (DualBlock m a) mk → LedgerTables (LedgerState (DualBlock m a)) mk Source # withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerState (DualBlock m a) any → LedgerTables (LedgerState (DualBlock m a)) mk → LedgerState (DualBlock m a) mk Source # | |||||||||
HasLedgerTables (LedgerState TestBlock) Source # | |||||||||
Defined in Test.Util.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.Util.TestBlock Methods convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). LedgerState TestBlock mk → LedgerState TestBlock mk' Source # | |||||||||
(Ord (TxIn (LedgerState m)), MemPack (TxIn (LedgerState m)), MemPack (TxOut (LedgerState m))) ⇒ SerializeTablesWithHint (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods encodeTablesWithHint ∷ SerializeTablesHint (LedgerTables (LedgerState (DualBlock m a)) ValuesMK) → LedgerTables (LedgerState (DualBlock m a)) ValuesMK → Encoding Source # decodeTablesWithHint ∷ SerializeTablesHint (LedgerTables (LedgerState (DualBlock m a)) ValuesMK) → Decoder s (LedgerTables (LedgerState (DualBlock m a)) ValuesMK) Source # | |||||||||
SerializeTablesWithHint (LedgerState TestBlock) Source # | |||||||||
Defined in Test.Util.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 # | |||||||||
CanUpgradeLedgerTables (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods upgradeTables ∷ ∀ (mk1 ∷ MapKind) (mk2 ∷ MapKind). LedgerState (DualBlock m a) mk1 → LedgerState (DualBlock m a) mk2 → LedgerTables (LedgerState (DualBlock m a)) ValuesMK → LedgerTables (LedgerState (DualBlock m a)) ValuesMK Source # | |||||||||
CanUpgradeLedgerTables (LedgerState TestBlock) Source # | |||||||||
Defined in Test.Util.TestBlock Methods upgradeTables ∷ ∀ (mk1 ∷ MapKind) (mk2 ∷ MapKind). LedgerState TestBlock mk1 → LedgerState TestBlock mk2 → LedgerTables (LedgerState TestBlock) ValuesMK → LedgerTables (LedgerState TestBlock) ValuesMK Source # | |||||||||
PayloadSemantics ptype ⇒ ApplyBlock (LedgerState (TestBlockWith ptype)) (TestBlockWith ptype) Source # | |||||||||
Defined in Test.Util.TestBlock Methods applyBlockLedgerResultWithValidation ∷ ValidationPolicy → ComputeLedgerEvents → LedgerCfg (LedgerState (TestBlockWith ptype)) → TestBlockWith ptype → Ticked (LedgerState (TestBlockWith ptype)) ValuesMK → Except (LedgerErr (LedgerState (TestBlockWith ptype))) (LedgerResult (LedgerState (TestBlockWith ptype)) (LedgerState (TestBlockWith ptype) DiffMK)) Source # applyBlockLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (LedgerState (TestBlockWith ptype)) → TestBlockWith ptype → Ticked (LedgerState (TestBlockWith ptype)) ValuesMK → Except (LedgerErr (LedgerState (TestBlockWith ptype))) (LedgerResult (LedgerState (TestBlockWith ptype)) (LedgerState (TestBlockWith ptype) DiffMK)) Source # reapplyBlockLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (LedgerState (TestBlockWith ptype)) → TestBlockWith ptype → Ticked (LedgerState (TestBlockWith ptype)) ValuesMK → LedgerResult (LedgerState (TestBlockWith ptype)) (LedgerState (TestBlockWith ptype) DiffMK) Source # getBlockKeySets ∷ TestBlockWith ptype → LedgerTables (LedgerState (TestBlockWith ptype)) KeysMK Source # | |||||||||
Bridge m a ⇒ ApplyBlock (LedgerState (DualBlock m a)) (DualBlock m a) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods applyBlockLedgerResultWithValidation ∷ ValidationPolicy → ComputeLedgerEvents → LedgerCfg (LedgerState (DualBlock m a)) → DualBlock m a → Ticked (LedgerState (DualBlock m a)) ValuesMK → Except (LedgerErr (LedgerState (DualBlock m a))) (LedgerResult (LedgerState (DualBlock m a)) (LedgerState (DualBlock m a) DiffMK)) Source # applyBlockLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (LedgerState (DualBlock m a)) → DualBlock m a → Ticked (LedgerState (DualBlock m a)) ValuesMK → Except (LedgerErr (LedgerState (DualBlock m a))) (LedgerResult (LedgerState (DualBlock m a)) (LedgerState (DualBlock m a) DiffMK)) Source # reapplyBlockLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (LedgerState (DualBlock m a)) → DualBlock m a → Ticked (LedgerState (DualBlock m a)) ValuesMK → LedgerResult (LedgerState (DualBlock m a)) (LedgerState (DualBlock m a) DiffMK) Source # getBlockKeySets ∷ DualBlock m a → LedgerTables (LedgerState (DualBlock m a)) KeysMK Source # | |||||||||
PayloadSemantics ptype ⇒ DecodeDisk (TestBlockWith ptype) (LedgerState (TestBlockWith ptype) EmptyMK) Source # | |||||||||
Defined in Test.Util.TestBlock Methods decodeDisk ∷ CodecConfig (TestBlockWith ptype) → ∀ s. Decoder s (LedgerState (TestBlockWith ptype) EmptyMK) Source # | |||||||||
PayloadSemantics ptype ⇒ EncodeDisk (TestBlockWith ptype) (LedgerState (TestBlockWith ptype) EmptyMK) Source # | |||||||||
Defined in Test.Util.TestBlock Methods encodeDisk ∷ CodecConfig (TestBlockWith ptype) → LedgerState (TestBlockWith ptype) EmptyMK → Encoding Source # | |||||||||
(IsNonEmpty xs, SListI xs, All (Compose Arbitrary (Flip LedgerState mk)) xs) ⇒ Arbitrary (LedgerState (HardForkBlock xs) mk) Source # | |||||||||
Defined in Test.Util.Orphans.Arbitrary Methods arbitrary ∷ Gen (LedgerState (HardForkBlock xs) mk) Source # shrink ∷ LedgerState (HardForkBlock xs) mk → [LedgerState (HardForkBlock xs) mk] Source # | |||||||||
Generic (LedgerState (TestBlockWith ptype) mk) Source # | |||||||||
Defined in Test.Util.TestBlock Associated Types
Methods from ∷ LedgerState (TestBlockWith ptype) mk → Rep (LedgerState (TestBlockWith ptype) mk) x # to ∷ Rep (LedgerState (TestBlockWith ptype) mk) x → LedgerState (TestBlockWith ptype) mk # | |||||||||
(ShowMK mk, CanHardFork xs) ⇒ Show (LedgerState (HardForkBlock xs) mk) | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Methods showsPrec ∷ Int → LedgerState (HardForkBlock xs) mk → ShowS # show ∷ LedgerState (HardForkBlock xs) mk → String # showList ∷ [LedgerState (HardForkBlock xs) mk] → ShowS # | |||||||||
(Bridge m a, ShowMK mk) ⇒ Show (LedgerState (DualBlock m a) mk) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
(ShowMK mk, PayloadSemantics ptype) ⇒ Show (LedgerState (TestBlockWith ptype) mk) Source # | |||||||||
Defined in Test.Util.TestBlock Methods showsPrec ∷ Int → LedgerState (TestBlockWith ptype) mk → ShowS # show ∷ LedgerState (TestBlockWith ptype) mk → String # showList ∷ [LedgerState (TestBlockWith ptype) mk] → ShowS # | |||||||||
(EqMK mk, CanHardFork xs) ⇒ Eq (LedgerState (HardForkBlock xs) mk) | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Methods (==) ∷ LedgerState (HardForkBlock xs) mk → LedgerState (HardForkBlock xs) mk → Bool # (/=) ∷ LedgerState (HardForkBlock xs) mk → LedgerState (HardForkBlock xs) mk → Bool # | |||||||||
(Bridge m a, EqMK mk) ⇒ Eq (LedgerState (DualBlock m a) mk) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods (==) ∷ LedgerState (DualBlock m a) mk → LedgerState (DualBlock m a) mk → Bool # (/=) ∷ LedgerState (DualBlock m a) mk → LedgerState (DualBlock m a) mk → Bool # | |||||||||
Eq (PayloadDependentState ptype mk) ⇒ Eq (LedgerState (TestBlockWith ptype) mk) Source # | |||||||||
Defined in Test.Util.TestBlock Methods (==) ∷ LedgerState (TestBlockWith ptype) mk → LedgerState (TestBlockWith ptype) mk → Bool # (/=) ∷ LedgerState (TestBlockWith ptype) mk → LedgerState (TestBlockWith ptype) mk → Bool # | |||||||||
(NoThunksMK mk, CanHardFork xs) ⇒ NoThunks (LedgerState (HardForkBlock xs) mk) | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Methods noThunks ∷ Context → LedgerState (HardForkBlock xs) mk → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → LedgerState (HardForkBlock xs) mk → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (LedgerState (HardForkBlock xs) mk) → String Source # | |||||||||
NoThunks (LedgerState (DualBlock m a) mk) | |||||||||
NoThunks (PayloadDependentState ptype mk) ⇒ NoThunks (LedgerState (TestBlockWith ptype) mk) Source # | |||||||||
Defined in Test.Util.TestBlock Methods noThunks ∷ Context → LedgerState (TestBlockWith ptype) mk → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → LedgerState (TestBlockWith ptype) mk → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (LedgerState (TestBlockWith ptype) mk) → String Source # | |||||||||
Bridge m a ⇒ GetTip (Ticked (LedgerState (DualBlock m a))) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
GetTip (Ticked (LedgerState (TestBlockWith ptype))) Source # | |||||||||
Defined in Test.Util.TestBlock Methods getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (TestBlockWith ptype)) mk → Point (Ticked (LedgerState (TestBlockWith ptype))) Source # | |||||||||
(Ord k, Eq v, MemPack k, MemPack v) ⇒ CanStowLedgerTables (OTLedgerState k v) Source # | |||||||||
Defined in Test.Util.LedgerStateOnlyTables Methods stowLedgerTables ∷ OTLedgerState k v ValuesMK → OTLedgerState k v EmptyMK Source # unstowLedgerTables ∷ OTLedgerState k v EmptyMK → OTLedgerState k v ValuesMK Source # | |||||||||
(Bridge m a, NoThunks (TxOut (LedgerState m)), NoThunks (TxIn (LedgerState m)), Show (TxOut (LedgerState m)), Show (TxIn (LedgerState m)), Eq (TxOut (LedgerState m)), Ord (TxIn (LedgerState m)), MemPack (TxIn (LedgerState m))) ⇒ HasLedgerTables (Ticked (LedgerState (DualBlock m a))) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (DualBlock m a)) mk → LedgerTables (Ticked (LedgerState (DualBlock m a))) mk Source # withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (DualBlock m a)) any → LedgerTables (Ticked (LedgerState (DualBlock m a))) mk → Ticked (LedgerState (DualBlock m a)) mk Source # | |||||||||
HasLedgerTables (Ticked (LedgerState TestBlock)) Source # | |||||||||
Defined in Test.Util.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 # | |||||||||
(Ord k, Eq v, Show k, Show v, MemPack k, MemPack v, NoThunks k, NoThunks v) ⇒ HasLedgerTables (OTLedgerState k v) Source # | |||||||||
Defined in Test.Util.LedgerStateOnlyTables Methods projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ OTLedgerState k v mk → LedgerTables (OTLedgerState k v) mk Source # withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ OTLedgerState k v any → LedgerTables (OTLedgerState k v) mk → OTLedgerState k v mk Source # | |||||||||
LedgerTablesAreTrivial (Ticked (LedgerState TestBlock)) Source # | |||||||||
Defined in Test.Util.TestBlock Methods convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). Ticked (LedgerState TestBlock) mk → Ticked (LedgerState TestBlock) mk' Source # | |||||||||
PayloadSemantics ptype ⇒ Serialise (LedgerState (TestBlockWith ptype) EmptyMK) Source # | |||||||||
Defined in Test.Util.TestBlock Methods encode ∷ LedgerState (TestBlockWith ptype) EmptyMK → Encoding Source # decode ∷ Decoder s (LedgerState (TestBlockWith ptype) EmptyMK) Source # encodeList ∷ [LedgerState (TestBlockWith ptype) EmptyMK] → Encoding Source # decodeList ∷ Decoder s [LedgerState (TestBlockWith ptype) EmptyMK] Source # | |||||||||
(txout ~ TxOut (LedgerState m), IndexedMemPack (LedgerState m EmptyMK) txout) ⇒ IndexedMemPack (LedgerState (DualBlock m a) EmptyMK) txout | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods indexedPackedByteCount ∷ LedgerState (DualBlock m a) EmptyMK → txout → Int Source # indexedPackM ∷ LedgerState (DualBlock m a) EmptyMK → txout → Pack s () Source # indexedUnpackM ∷ Buffer b ⇒ LedgerState (DualBlock m a) EmptyMK → Unpack b txout Source # indexedTypeName ∷ LedgerState (DualBlock m a) EmptyMK → String Source # | |||||||||
IndexedMemPack (LedgerState TestBlock EmptyMK) Void Source # | |||||||||
Defined in Test.Util.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 # | |||||||||
StandardHash blk ⇒ StandardHash (LedgerState blk ∷ MapKind → Type) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Basics | |||||||||
Generic (Ticked (LedgerState (TestBlockWith ptype)) mk) Source # | |||||||||
Defined in Test.Util.TestBlock Associated Types
Methods from ∷ Ticked (LedgerState (TestBlockWith ptype)) mk → Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) x # to ∷ Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) x → Ticked (LedgerState (TestBlockWith ptype)) mk # | |||||||||
(Show k, Show v, Show (mk k v)) ⇒ Show (OTLedgerState k v mk) Source # | |||||||||
Defined in Test.Util.LedgerStateOnlyTables Methods showsPrec ∷ Int → OTLedgerState k v mk → ShowS # show ∷ OTLedgerState k v mk → String # showList ∷ [OTLedgerState k v mk] → ShowS # | |||||||||
(Ord k, Eq v, Eq (mk k v)) ⇒ Eq (OTLedgerState k v mk) Source # | |||||||||
Defined in Test.Util.LedgerStateOnlyTables Methods (==) ∷ OTLedgerState k v mk → OTLedgerState k v mk → Bool # (/=) ∷ OTLedgerState k v mk → OTLedgerState k v mk → Bool # | |||||||||
NoThunks (Ticked (LedgerState (DualBlock m a)) mk) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
(NoThunksMK mk, NoThunks (PayloadDependentState ptype mk)) ⇒ NoThunks (Ticked (LedgerState (TestBlockWith ptype)) mk) Source # | |||||||||
Defined in Test.Util.TestBlock Methods noThunks ∷ Context → Ticked (LedgerState (TestBlockWith ptype)) mk → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → Ticked (LedgerState (TestBlockWith ptype)) mk → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (Ticked (LedgerState (TestBlockWith ptype)) mk) → String Source # | |||||||||
(NoThunks k, NoThunks v, NoThunks (mk k v)) ⇒ NoThunks (OTLedgerState k v mk) Source # | |||||||||
Defined in Test.Util.LedgerStateOnlyTables | |||||||||
Inject (Flip LedgerState mk) | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Nary Methods inject ∷ ∀ x (xs ∷ [Type]). (CanHardFork xs, HasCanonicalTxIn xs, HasHardForkTxOut xs) ⇒ InjectionIndex xs x → Flip LedgerState mk x → Flip LedgerState mk (HardForkBlock xs) Source # | |||||||||
Isomorphic (Flip LedgerState mk) | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary Methods project ∷ NoHardForks blk ⇒ Flip LedgerState mk (HardForkBlock '[blk]) → Flip LedgerState mk blk Source # inject ∷ NoHardForks blk ⇒ Flip LedgerState mk blk → Flip LedgerState mk (HardForkBlock '[blk]) Source # | |||||||||
type AuxLedgerEvent (LedgerState (HardForkBlock xs)) | |||||||||
type AuxLedgerEvent (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
type AuxLedgerEvent (LedgerState (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock type AuxLedgerEvent (LedgerState (TestBlockWith ptype)) = VoidLedgerEvent (LedgerState (TestBlockWith ptype)) | |||||||||
type LedgerCfg (LedgerState (HardForkBlock xs)) | |||||||||
type LedgerCfg (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
type LedgerCfg (LedgerState (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
type LedgerErr (LedgerState (HardForkBlock xs)) | |||||||||
type LedgerErr (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
type LedgerErr (LedgerState (TestBlockWith ptype)) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
newtype LedgerState (HardForkBlock xs) mk | |||||||||
data LedgerState (TestBlockWith ptype) mk Source # | |||||||||
Defined in Test.Util.TestBlock data LedgerState (TestBlockWith ptype) mk = TestLedger {
| |||||||||
type TxIn (LedgerState (HardForkBlock xs)) | Must be the | ||||||||
type TxIn (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
type TxIn (LedgerState TestBlock) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
type TxOut (LedgerState (HardForkBlock xs)) | Must be the | ||||||||
type TxOut (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
type TxOut (LedgerState TestBlock) Source # | |||||||||
Defined in Test.Util.TestBlock | |||||||||
type Rep (LedgerState (TestBlockWith ptype) mk) Source # | |||||||||
Defined in Test.Util.TestBlock type Rep (LedgerState (TestBlockWith ptype) mk) = D1 ('MetaData "LedgerState" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "lastAppliedPoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Point (TestBlockWith ptype))) :*: S1 ('MetaSel ('Just "payloadDependentState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PayloadDependentState ptype mk)))) | |||||||||
data LedgerState (DualBlock m a) mk | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
type TxIn (OTLedgerState k v) Source # | |||||||||
Defined in Test.Util.LedgerStateOnlyTables | |||||||||
type TxOut (OTLedgerState k v) Source # | |||||||||
Defined in Test.Util.LedgerStateOnlyTables | |||||||||
data Ticked (LedgerState (HardForkBlock xs) ∷ MapKind → Type) (mk ∷ MapKind) | |||||||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger data Ticked (LedgerState (HardForkBlock xs) ∷ MapKind → Type) (mk ∷ MapKind) = TickedHardForkLedgerState {} | |||||||||
data Ticked (LedgerState (DualBlock m a) ∷ MapKind → Type) (mk ∷ MapKind) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual data Ticked (LedgerState (DualBlock m a) ∷ MapKind → Type) (mk ∷ MapKind) = TickedDualLedgerState {} | |||||||||
newtype Ticked (LedgerState (TestBlockWith ptype) ∷ MapKind → Type) (mk ∷ MapKind) Source # | |||||||||
Defined in Test.Util.TestBlock newtype Ticked (LedgerState (TestBlockWith ptype) ∷ MapKind → Type) (mk ∷ MapKind) = TickedTestLedger {
| |||||||||
type HeaderHash (LedgerState blk ∷ MapKind → Type) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Basics | |||||||||
type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) Source # | |||||||||
Defined in Test.Util.TestBlock type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) = D1 ('MetaData "Ticked" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'True) (C1 ('MetaCons "TickedTestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTickedTestLedger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerState (TestBlockWith ptype) mk)))) |
data family Ticked (st ∷ k) ∷ k Source #
" Ticked " piece of state, either LedgerState
or ChainDepState
Ticking refers to the passage of time (the ticking of the clock). When a
piece of state is marked as ticked, it means that time-related changes have
been applied to the state. There are exactly two methods in the interface
that do that: tickChainDepState
and
applyChainTickLedgerResult
.
Also note that a successful forecast
must equal
forecastFor
(ledgerViewForecastAt
cfg st)
slot
. Thus a
protocolLedgerView
cfg
(applyChainTick
cfg slot st)LedgerView
can only be projected
from a Ticked
state, but cannot itself be ticked.
Some examples of time related changes:
- Scheduled delegations might have been applied in Byron
- New leader schedule computed for Shelley
- Transition from Byron to Shelley activated in the hard fork combinator.
- Nonces switched out at the start of a new epoch.
Instances
Show (Ticked ()) | |||||
Bridge m a ⇒ GetTip (Ticked (LedgerState (DualBlock m a))) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||
GetTip (Ticked (LedgerState (TestBlockWith ptype))) Source # | |||||
Defined in Test.Util.TestBlock Methods getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (TestBlockWith ptype)) mk → Point (Ticked (LedgerState (TestBlockWith ptype))) Source # | |||||
IsLedger (LedgerState blk) ⇒ GetTip (Ticked (ExtLedgerState blk)) | |||||
Defined in Ouroboros.Consensus.Ledger.Extended Methods getTip ∷ ∀ (mk ∷ MapKind). Ticked (ExtLedgerState blk) mk → Point (Ticked (ExtLedgerState blk)) Source # | |||||
(Bridge m a, NoThunks (TxOut (LedgerState m)), NoThunks (TxIn (LedgerState m)), Show (TxOut (LedgerState m)), Show (TxIn (LedgerState m)), Eq (TxOut (LedgerState m)), Ord (TxIn (LedgerState m)), MemPack (TxIn (LedgerState m))) ⇒ HasLedgerTables (Ticked (LedgerState (DualBlock m a))) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (DualBlock m a)) mk → LedgerTables (Ticked (LedgerState (DualBlock m a))) mk Source # withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (DualBlock m a)) any → LedgerTables (Ticked (LedgerState (DualBlock m a))) mk → Ticked (LedgerState (DualBlock m a)) mk Source # | |||||
HasLedgerTables (Ticked (LedgerState TestBlock)) Source # | |||||
Defined in Test.Util.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 # | |||||
(HasLedgerTables (Ticked (LedgerState blk)), NoThunks (TxOut (LedgerState blk)), NoThunks (TxIn (LedgerState blk)), Show (TxOut (LedgerState blk)), Show (TxIn (LedgerState blk)), Eq (TxOut (LedgerState blk)), Ord (TxIn (LedgerState blk)), MemPack (TxIn (LedgerState blk))) ⇒ HasLedgerTables (Ticked (ExtLedgerState blk)) | |||||
Defined in Ouroboros.Consensus.Ledger.Extended Methods projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (ExtLedgerState blk) mk → LedgerTables (Ticked (ExtLedgerState blk)) mk Source # withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (ExtLedgerState blk) any → LedgerTables (Ticked (ExtLedgerState blk)) mk → Ticked (ExtLedgerState blk) mk Source # | |||||
LedgerTablesAreTrivial (Ticked (LedgerState TestBlock)) Source # | |||||
Defined in Test.Util.TestBlock Methods convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). Ticked (LedgerState TestBlock) mk → Ticked (LedgerState TestBlock) mk' Source # | |||||
LedgerTablesAreTrivial (Ticked (LedgerState blk)) ⇒ LedgerTablesAreTrivial (Ticked (ExtLedgerState blk)) | |||||
Defined in Ouroboros.Consensus.Ledger.Extended Methods convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). Ticked (ExtLedgerState blk) mk → Ticked (ExtLedgerState blk) mk' Source # | |||||
Generic (Ticked (LedgerState (TestBlockWith ptype)) mk) Source # | |||||
Defined in Test.Util.TestBlock Associated Types
Methods from ∷ Ticked (LedgerState (TestBlockWith ptype)) mk → Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) x # to ∷ Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) x → Ticked (LedgerState (TestBlockWith ptype)) mk # | |||||
NoThunks (Ticked (LedgerState (DualBlock m a)) mk) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||
(NoThunksMK mk, NoThunks (PayloadDependentState ptype mk)) ⇒ NoThunks (Ticked (LedgerState (TestBlockWith ptype)) mk) Source # | |||||
Defined in Test.Util.TestBlock Methods noThunks ∷ Context → Ticked (LedgerState (TestBlockWith ptype)) mk → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → Ticked (LedgerState (TestBlockWith ptype)) mk → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (Ticked (LedgerState (TestBlockWith ptype)) mk) → String Source # | |||||
Show (Ticked (f a)) ⇒ Show (((Ticked ∷ Type → Type) :.: f) a) | |||||
NoThunks (Ticked (f a)) ⇒ NoThunks (((Ticked ∷ Type → Type) :.: f) a) | |||||
data Ticked () | |||||
Defined in Ouroboros.Consensus.Ticked | |||||
data Ticked (HardForkChainDepState xs ∷ Type) | |||||
data Ticked (HeaderState blk ∷ Type) | |||||
Defined in Ouroboros.Consensus.HeaderValidation | |||||
data Ticked (PBftState c ∷ Type) | |||||
Defined in Ouroboros.Consensus.Protocol.PBFT | |||||
newtype Ticked (WrapChainDepState blk ∷ Type) | |||||
Defined in Ouroboros.Consensus.TypeFamilyWrappers | |||||
type HeaderHash (Ticked l ∷ k) | |||||
Defined in Ouroboros.Consensus.Ticked | |||||
type TxIn (Ticked l) | |||||
Defined in Ouroboros.Consensus.Ledger.Tables.Basics | |||||
type TxOut (Ticked l) | |||||
Defined in Ouroboros.Consensus.Ledger.Tables.Basics | |||||
data Ticked (LedgerState (HardForkBlock xs) ∷ MapKind → Type) (mk ∷ MapKind) | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger data Ticked (LedgerState (HardForkBlock xs) ∷ MapKind → Type) (mk ∷ MapKind) = TickedHardForkLedgerState {} | |||||
data Ticked (LedgerState (DualBlock m a) ∷ MapKind → Type) (mk ∷ MapKind) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual data Ticked (LedgerState (DualBlock m a) ∷ MapKind → Type) (mk ∷ MapKind) = TickedDualLedgerState {} | |||||
newtype Ticked (LedgerState (TestBlockWith ptype) ∷ MapKind → Type) (mk ∷ MapKind) Source # | |||||
Defined in Test.Util.TestBlock newtype Ticked (LedgerState (TestBlockWith ptype) ∷ MapKind → Type) (mk ∷ MapKind) = TickedTestLedger {
| |||||
data Ticked (ExtLedgerState blk ∷ MapKind → Type) (mk ∷ MapKind) | |||||
Defined in Ouroboros.Consensus.Ledger.Extended data Ticked (ExtLedgerState blk ∷ MapKind → Type) (mk ∷ MapKind) = TickedExtLedgerState {
| |||||
type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) Source # | |||||
Defined in Test.Util.TestBlock type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) = D1 ('MetaData "Ticked" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'True) (C1 ('MetaCons "TickedTestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTickedTestLedger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerState (TestBlockWith ptype) mk)))) |
getTickedTestLedger ∷ ∀ ptype (mk ∷ MapKind). Ticked (LedgerState (TestBlockWith ptype)) mk → LedgerState (TestBlockWith ptype) mk Source #
Chain
newtype BlockChain Source #
Constructors
BlockChain Word64 |
Instances
Arbitrary BlockChain Source # | |
Defined in Test.Util.TestBlock | |
Show BlockChain Source # | |
Defined in Test.Util.TestBlock Methods showsPrec ∷ Int → BlockChain → ShowS # show ∷ BlockChain → String # showList ∷ [BlockChain] → ShowS # |
chainToBlocks ∷ BlockChain → [TestBlock] Source #
Tree
treeToBlocks ∷ BlockTree → [TestBlock] Source #
Ledger infrastructure
singleNodeTestConfig ∷ TopLevelConfig TestBlock Source #
Trivial test configuration with a single core node
singleNodeTestConfigWith ∷ CodecConfig (TestBlockWith ptype) → StorageConfig (TestBlockWith ptype) → SecurityParam → GenesisWindow → TopLevelConfig (TestBlockWith ptype) Source #
testInitExtLedgerWithState ∷ ∀ ptype (mk ∷ MapKind). PayloadDependentState ptype mk → ExtLedgerState (TestBlockWith ptype) mk Source #
testInitLedgerWithState ∷ ∀ ptype (mk ∷ MapKind). PayloadDependentState ptype mk → LedgerState (TestBlockWith ptype) mk Source #
Support for tests
newtype Permutation Source #
Constructors
Permutation Int |
Instances
Arbitrary Permutation Source # | |
Defined in Test.Util.TestBlock | |
Show Permutation Source # | |
Defined in Test.Util.TestBlock Methods showsPrec ∷ Int → Permutation → ShowS # show ∷ Permutation → String # showList ∷ [Permutation] → ShowS # |
data TestBlockLedgerConfig Source #
Constructors
TestBlockLedgerConfig | |
Fields |
Instances
Generic TestBlockLedgerConfig Source # | |||||
Defined in Test.Util.TestBlock Associated Types
Methods from ∷ TestBlockLedgerConfig → Rep TestBlockLedgerConfig x # | |||||
Show TestBlockLedgerConfig Source # | |||||
Defined in Test.Util.TestBlock Methods showsPrec ∷ Int → TestBlockLedgerConfig → ShowS # show ∷ TestBlockLedgerConfig → String # showList ∷ [TestBlockLedgerConfig] → ShowS # | |||||
Eq TestBlockLedgerConfig Source # | |||||
Defined in Test.Util.TestBlock Methods (==) ∷ TestBlockLedgerConfig → TestBlockLedgerConfig → Bool # (/=) ∷ TestBlockLedgerConfig → TestBlockLedgerConfig → Bool # | |||||
NoThunks TestBlockLedgerConfig Source # | |||||
Defined in Test.Util.TestBlock | |||||
type Rep TestBlockLedgerConfig Source # | |||||
Defined in Test.Util.TestBlock type Rep TestBlockLedgerConfig = D1 ('MetaData "TestBlockLedgerConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockLedgerConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "tblcHardForkParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EraParams) :*: S1 ('MetaSel ('Just "tblcForecastRange") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StrictMaybe SlotNo)))) |
isAncestorOf ∷ TestBlock → TestBlock → Bool Source #
A block b1
is the ancestor of another block b2
if there exists a chain
of blocks from b1
to b2
. For test blocks in particular, this can be seen
in the hash: the hash of b1
should be a prefix of the hash of b2
.
Note that this is a partial comparison function. In particular, it does hold
that for all b1
and b2
, b1
but it does not hold that for all isDescendentOf
b2 === b2 isAncestorOf
b1b1
and b2
, b1
.isDescendentOf
b2 ===
not (b1 isAncestorOf
b2) || b1 == b2
isDescendentOf ∷ TestBlock → TestBlock → Bool Source #
A block b1
is the descendent of another block b2
if there exists a
chain of blocks from b2
to b1
. For test blocks in particular, this can be
seen in the hash: the hash of b2
should be a prefix of the hash of b1
.
Note that this is a partial comparison function. In particular, it does hold
that for all b1
and b2
, b1
but it does not hold that for all isDescendentOf
b2 === b2 isAncestorOf
b1b1
and b2
, b1
.isDescendentOf
b2 ===
not (b1 isAncestorOf
b2) || b1 == b2
isStrictAncestorOf ∷ TestBlock → TestBlock → Bool Source #
Variant of isAncestorOf
that returns False
when the two blocks are
equal.
isStrictDescendentOf ∷ TestBlock → TestBlock → Bool Source #
Variant of isDescendentOf
that returns False
when the two blocks are
equal.
permute ∷ Permutation → [a] → [a] Source #
unsafeTestBlockWithPayload ∷ TestHash → SlotNo → Validity → ptype → TestBlockWith ptype Source #
Create a block directly with the given parameters. This allows creating
inconsistent blocks; prefer firstBlockWithPayload
or successorBlockWithPayload
.
updateToNextNumeral ∷ RealPoint TestBlock → (Point TestBlock, NonEmpty TestBlock) Source #
Given a point to a chain of length L, generates a SwitchFork
that
switches to the "next" block of length L, where "next" is determined by
interpreting the "forks" in the TestHash
as binary digits (except the
deepest, which is a simple counter).
For example, the following are input and outputs for a chains of length 3,
where the TestHash
es and Point
s are denoted by numerals (the SlotNo
is
merely the number of digits).
000 :-> [RollBack 00, AddBlock 001] 001 :-> [RollBack 0 , AddBlock 01 , AddBlock 010] 010 :-> [RollBack 01, AddBlock 011] 011 :-> [RollBack G , AddBlock 1 , AddBlock 10 , AddBlock 100] 100 :-> [RollBack 10, AddBlock 101] 101 :-> [RollBack 1 , AddBlock 11 , AddBlock 110] 110 :-> [RollBack 11, AddBlock 111] 111 :-> [RollBack G , AddBlock 2 , AddBlock 20 , AddBlock 200] 200 :-> [RollBack 20, AddBlock 201] 201 :-> [RollBack 2 , AddBlock 21 , AddBlock 210] 210 :-> [RollBack 21, AddBlock 211] 211 :-> [RollBack G , AddBlock 3 , AddBlock 30 , AddBlock 300] etc