Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Minimal instantiation of the consensus layer to be able to run the ChainDB
Synopsis
- data family BlockConfig blk
- data family BlockQuery blk ∷ Type → Type
- data family CodecConfig blk
- data family Header blk
- 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
- class (Typeable ptype, Eq ptype, NoThunks ptype, Eq (PayloadDependentState ptype), Show (PayloadDependentState ptype), Generic (PayloadDependentState ptype), ToExpr (PayloadDependentState ptype), Serialise (PayloadDependentState ptype), NoThunks (PayloadDependentState 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
- type PayloadDependentState ptype ∷ Type
- type PayloadDependentError ptype ∷ Type
- applyPayload ∷ PayloadDependentState ptype → ptype → Either (PayloadDependentError ptype) (PayloadDependentState ptype)
- applyDirectlyToPayloadDependentState ∷ PayloadSemantics ptype ⇒ Ticked (LedgerState (TestBlockWith ptype)) → ptype → Either (PayloadDependentError ptype) (Ticked (LedgerState (TestBlockWith ptype)))
- data family LedgerState blk
- data family Ticked st
- lastAppliedPoint ∷ LedgerState (TestBlockWith ptype) → Point (TestBlockWith ptype)
- payloadDependentState ∷ LedgerState (TestBlockWith ptype) → PayloadDependentState ptype
- 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
- testInitExtLedgerWithState ∷ PayloadDependentState ptype → ExtLedgerState (TestBlockWith ptype)
- testInitLedger ∷ LedgerState TestBlock
- testInitLedgerWithState ∷ PayloadDependentState ptype → LedgerState (TestBlockWith ptype)
- 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 blk ∷ Type → Type Source #
Different queries supported by the ledger, indexed by the result type.
Instances
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
Generic (CodecConfig TestBlock) Source # | |
Defined in Test.Util.TestBlock 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 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 TestBlock) Source # | |
data CodecConfig TestBlock Source # | The |
Defined in Test.Util.TestBlock | |
type Rep (CodecConfig TestBlock) Source # | |
newtype CodecConfig (HardForkBlock xs) | |
data family Header blk Source #
Instances
data family StorageConfig blk Source #
Config needed for the
NodeInitStorage
class. Defined here to
avoid circular dependencies.
Instances
Generic (StorageConfig TestBlock) Source # | |
Defined in Test.Util.TestBlock 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 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 TestBlock) Source # | |
data StorageConfig TestBlock Source # | The |
Defined in Test.Util.TestBlock | |
type Rep (StorageConfig TestBlock) Source # | |
newtype StorageConfig (HardForkBlock xs) | |
data TestBlockError ptype Source #
InvalidHash | The hashes don't line up |
| |
InvalidBlock | The block itself is invalid |
InvalidPayload (PayloadDependentError ptype) |
Instances
data TestBlockWith ptype Source #
Test block parametrized on the payload type
For blocks without payload see the TestBlock
type alias.
By defining a PayloadSemantics
it is possible to obtain an ApplyBlock
instance. See the former class for more details.
Instances
Instances
Generic TestHash Source # | |
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.21.0.0-inplace-unstable-consensus-testlib" 'True) (C1 ('MetaCons "UnsafeTestHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTestHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Word64)))) |
Instances
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
class (Typeable ptype, Eq ptype, NoThunks ptype, Eq (PayloadDependentState ptype), Show (PayloadDependentState ptype), Generic (PayloadDependentState ptype), ToExpr (PayloadDependentState ptype), Serialise (PayloadDependentState ptype), NoThunks (PayloadDependentState 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 #
type PayloadDependentState ptype ∷ Type Source #
type PayloadDependentError ptype ∷ Type Source #
applyPayload ∷ PayloadDependentState ptype → ptype → Either (PayloadDependentError ptype) (PayloadDependentState ptype) Source #
Instances
PayloadSemantics () Source # | |
Defined in Test.Util.TestBlock type PayloadDependentState () Source # type PayloadDependentError () Source # applyPayload ∷ PayloadDependentState () → () → Either (PayloadDependentError ()) (PayloadDependentState ()) Source # |
applyDirectlyToPayloadDependentState ∷ PayloadSemantics ptype ⇒ Ticked (LedgerState (TestBlockWith ptype)) → ptype → Either (PayloadDependentError ptype) (Ticked (LedgerState (TestBlockWith ptype))) 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 Source #
Ledger state associated with a block
This is the Consensus notion of a 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 denote that the
expected instantiation is either a LedgerState
or some wrapper over it
(like the ExtLedgerState
).
The main operations we can do with a LedgerState
are ticking (defined in
IsLedger
), and applying a block (defined in
ApplyBlock
).
Instances
data family Ticked st 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
lastAppliedPoint ∷ LedgerState (TestBlockWith ptype) → Point (TestBlockWith ptype) Source #
payloadDependentState ∷ LedgerState (TestBlockWith ptype) → PayloadDependentState ptype Source #
Chain
newtype BlockChain Source #
Instances
Arbitrary BlockChain Source # | |
Defined in Test.Util.TestBlock arbitrary ∷ Gen BlockChain Source # shrink ∷ BlockChain → [BlockChain] Source # | |
Show BlockChain Source # | |
Defined in Test.Util.TestBlock |
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 ∷ PayloadDependentState ptype → ExtLedgerState (TestBlockWith ptype) Source #
testInitLedgerWithState ∷ PayloadDependentState ptype → LedgerState (TestBlockWith ptype) Source #
Support for tests
newtype Permutation Source #
Instances
Arbitrary Permutation Source # | |
Defined in Test.Util.TestBlock | |
Show Permutation Source # | |
Defined in Test.Util.TestBlock showsPrec ∷ Int → Permutation → ShowS # show ∷ Permutation → String # showList ∷ [Permutation] → ShowS # |
data TestBlockLedgerConfig Source #
Instances
Generic TestBlockLedgerConfig Source # | |
Defined in Test.Util.TestBlock type Rep TestBlockLedgerConfig ∷ Type → Type # | |
Show TestBlockLedgerConfig Source # | |
Defined in Test.Util.TestBlock | |
Eq TestBlockLedgerConfig Source # | |
Defined in Test.Util.TestBlock | |
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.21.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