Safe Haskell | None |
---|---|
Language | Haskell2010 |
Ouroboros.Consensus.Mock.Ledger.Block
Description
Simple block to go with the mock ledger
None of the definitions in this module depend on, or even refer to, any specific consensus protocols.
Synopsis
- data family BlockQuery ∷ Type → QueryFootprint → Type → Type
- data family Header blk
- type SimpleBlock c ext = SimpleBlock' c ext ext
- data SimpleBlock' c ext ext' = SimpleBlock {
- simpleHeader ∷ Header (SimpleBlock' c ext ext')
- simpleBody ∷ SimpleBody
- data SimpleBody = SimpleBody {}
- type family SimpleHash c
- type SimpleHeader c ext = Header (SimpleBlock c ext)
- data SimpleStdHeader c ext = SimpleStdHeader {}
- countSimpleGenTxs ∷ SimpleBlock c ext → Word64
- matchesSimpleHeader ∷ SimpleCrypto c ⇒ Header (SimpleBlock' c ext ext') → SimpleBlock' c ext ext'' → Bool
- mkSimpleHeader ∷ SimpleCrypto c ⇒ (ext' → Encoding) → SimpleStdHeader c ext → ext' → Header (SimpleBlock' c ext ext')
- data family BlockConfig blk
- data family CodecConfig blk
- data SimpleLedgerConfig c ext = SimpleLedgerConfig {}
- data family StorageConfig blk
- class (SimpleCrypto c, Typeable ext, Show (MockLedgerConfig c ext), NoThunks (MockLedgerConfig c ext), Serialise (MockLedgerConfig c ext)) ⇒ MockProtocolSpecific c ext where
- type MockLedgerConfig c ext
- data family LedgerState blk (mk ∷ MapKind)
- newtype LedgerTables (l ∷ LedgerStateKind) (mk ∷ MapKind) = LedgerTables {
- getLedgerTables ∷ mk (TxIn l) (TxOut l)
- data family Ticked (st ∷ k) ∷ k
- genesisSimpleLedgerState ∷ AddrDist → LedgerState (SimpleBlock c ext) ValuesMK
- updateSimpleLedgerState ∷ ∀ c ext (mk1 ∷ MapKind). (SimpleCrypto c, Typeable ext) ⇒ LedgerConfig (SimpleBlock c ext) → SimpleBlock c ext → TickedLedgerState (SimpleBlock c ext) mk1 → Except (MockError (SimpleBlock c ext)) (LedgerState (SimpleBlock c ext) mk1)
- data family GenTx blk
- data family TxId blk
- data family Validated x
- genTxSize ∷ GenTx (SimpleBlock c ext) → ByteSize32
- mkSimpleGenTx ∷ Tx → GenTx (SimpleBlock c ext)
- class (KnownNat (SizeHash (SimpleHash c)), HashAlgorithm (SimpleHash c), Typeable c) ⇒ SimpleCrypto c
- data SimpleMockCrypto
- data SimpleStandardCrypto
- decodeSimpleHeader ∷ SimpleCrypto c ⇒ (ext' → Encoding) → (∀ s. Decoder s ext') → ∀ s. Decoder s (Header (SimpleBlock' c ext ext'))
- encodeSimpleHeader ∷ KnownNat (SizeHash (SimpleHash c)) ⇒ (ext' → Encoding) → Header (SimpleBlock' c ext ext') → Encoding
- simpleBlockBinaryBlockInfo ∷ (SimpleCrypto c, Serialise ext', Typeable ext, Typeable ext') ⇒ SimpleBlock' c ext ext' → BinaryBlockInfo
- simpleBlockCapacity ∷ ByteSize32
Documentation
data family BlockQuery ∷ Type → QueryFootprint → Type → Type Source #
Different queries supported by the ledger, indexed by the result type.
Instances
data family Header blk Source #
Instances
type SimpleBlock c ext = SimpleBlock' c ext ext Source #
data SimpleBlock' c ext ext' Source #
Constructors
SimpleBlock | |
Fields
|
Instances
SameDepIndex2 (BlockQuery (SimpleBlock c ext) ∷ QueryFootprint → Type → Type) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods sameDepIndex2 ∷ ∀ (x ∷ QueryFootprint) a (y ∷ QueryFootprint) b. BlockQuery (SimpleBlock c ext) x a → BlockQuery (SimpleBlock c ext) y b → Maybe ('(x, a) :~: '(y, b)) Source # | |||||||||
Serialise ext ⇒ ReconstructNestedCtxt Header (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods reconstructPrefixLen ∷ proxy (Header (MockBlock ext)) → PrefixLen Source # reconstructNestedCtxt ∷ proxy (Header (MockBlock ext)) → ShortByteString → SizeInBytes → SomeSecond (NestedCtxt Header) (MockBlock ext) Source # | |||||||||
(Typeable c, Typeable ext, Typeable ext') ⇒ ShowProxy (Header (SimpleBlock' c ext ext') ∷ Type) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
(Typeable c, Typeable ext) ⇒ ShowProxy (GenTx (SimpleBlock c ext) ∷ Type) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
(Typeable c, Typeable ext) ⇒ ShowProxy (TxId (GenTx (SimpleBlock c ext)) ∷ Type) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
SerialiseBlockQueryResult (MockBlock ext) BlockQuery Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeBlockQueryResult ∷ ∀ (fp ∷ QueryFootprint) result. CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → BlockQuery (MockBlock ext) fp result → result → Encoding Source # decodeBlockQueryResult ∷ ∀ (fp ∷ QueryFootprint) result. CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → BlockQuery (MockBlock ext) fp result → ∀ s. Decoder s result Source # | |||||||||
HasNestedContent f (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods unnest ∷ f (SimpleBlock c ext) → DepPair (NestedCtxt f (SimpleBlock c ext)) Source # nest ∷ DepPair (NestedCtxt f (SimpleBlock c ext)) → f (SimpleBlock c ext) Source # | |||||||||
SameDepIndex (NestedCtxt_ (SimpleBlock c ext) f ∷ Type → Type) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods sameDepIndex ∷ NestedCtxt_ (SimpleBlock c ext) f a → NestedCtxt_ (SimpleBlock c ext) f b → Maybe (a :~: b) Source # | |||||||||
TrivialDependency (NestedCtxt_ (SimpleBlock c ext) f ∷ Type → Type) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods hasSingleIndex ∷ NestedCtxt_ (SimpleBlock c ext) f a → NestedCtxt_ (SimpleBlock c ext) f b → a :~: b Source # indexIsTrivial ∷ NestedCtxt_ (SimpleBlock c ext) f (TrivialIndex (NestedCtxt_ (SimpleBlock c ext) f) ∷ Type) Source # | |||||||||
(SimpleCrypto c, Typeable ext, Typeable ext') ⇒ StandardHash (SimpleBlock' c ext ext' ∷ Type) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
(Typeable c, Typeable ext, Typeable ext') ⇒ ShowProxy (SimpleBlock' c ext ext' ∷ Type) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
Generic (BlockConfig (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods from ∷ BlockConfig (SimpleBlock c ext) → Rep (BlockConfig (SimpleBlock c ext)) x # to ∷ Rep (BlockConfig (SimpleBlock c ext)) x → BlockConfig (SimpleBlock c ext) # | |||||||||
Generic (CodecConfig (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods from ∷ CodecConfig (SimpleBlock c ext) → Rep (CodecConfig (SimpleBlock c ext)) x # to ∷ Rep (CodecConfig (SimpleBlock c ext)) x → CodecConfig (SimpleBlock c ext) # | |||||||||
Generic (Header (SimpleBlock' c ext ext')) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods from ∷ Header (SimpleBlock' c ext ext') → Rep (Header (SimpleBlock' c ext ext')) x # to ∷ Rep (Header (SimpleBlock' c ext ext')) x → Header (SimpleBlock' c ext ext') # | |||||||||
Generic (StorageConfig (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods from ∷ StorageConfig (SimpleBlock c ext) → Rep (StorageConfig (SimpleBlock c ext)) x # to ∷ Rep (StorageConfig (SimpleBlock c ext)) x → StorageConfig (SimpleBlock c ext) # | |||||||||
Generic (Validated (GenTx (SimpleBlock c ext))) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods from ∷ Validated (GenTx (SimpleBlock c ext)) → Rep (Validated (GenTx (SimpleBlock c ext))) x # to ∷ Rep (Validated (GenTx (SimpleBlock c ext))) x → Validated (GenTx (SimpleBlock c ext)) # | |||||||||
Generic (GenTx (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods from ∷ GenTx (SimpleBlock c ext) → Rep (GenTx (SimpleBlock c ext)) x # to ∷ Rep (GenTx (SimpleBlock c ext)) x → GenTx (SimpleBlock c ext) # | |||||||||
Generic (TxId (GenTx (SimpleBlock c ext))) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods from ∷ TxId (GenTx (SimpleBlock c ext)) → Rep (TxId (GenTx (SimpleBlock c ext))) x # to ∷ Rep (TxId (GenTx (SimpleBlock c ext))) x → TxId (GenTx (SimpleBlock c ext)) # | |||||||||
(SimpleCrypto c, Show ext', Typeable ext) ⇒ Show (Header (SimpleBlock' c ext ext')) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
Show (Validated (GenTx (SimpleBlock p c))) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
Show (GenTx (SimpleBlock p c)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
Show (TxId (GenTx (SimpleBlock c ext))) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
(SimpleCrypto c, Eq ext', Typeable ext) ⇒ Eq (Header (SimpleBlock' c ext ext')) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods (==) ∷ Header (SimpleBlock' c ext ext') → Header (SimpleBlock' c ext ext') → Bool # (/=) ∷ Header (SimpleBlock' c ext ext') → Header (SimpleBlock' c ext ext') → Bool # | |||||||||
Eq (Validated (GenTx (SimpleBlock c ext))) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods (==) ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Bool # (/=) ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Bool # | |||||||||
Eq (GenTx (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods (==) ∷ GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) → Bool # (/=) ∷ GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) → Bool # | |||||||||
Eq (TxId (GenTx (SimpleBlock c ext))) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods (==) ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → Bool # (/=) ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → Bool # | |||||||||
Ord (Validated (GenTx (SimpleBlock c ext))) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods compare ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Ordering # (<) ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Bool # (<=) ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Bool # (>) ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Bool # (>=) ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Bool # max ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) # min ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) # | |||||||||
Ord (GenTx (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods compare ∷ GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) → Ordering # (<) ∷ GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) → Bool # (<=) ∷ GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) → Bool # (>) ∷ GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) → Bool # (>=) ∷ GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) → Bool # max ∷ GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) # min ∷ GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) # | |||||||||
Ord (TxId (GenTx (SimpleBlock c ext))) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods compare ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → Ordering # (<) ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → Bool # (<=) ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → Bool # (>) ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → Bool # (>=) ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → Bool # max ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) # min ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) # | |||||||||
NoThunks (BlockConfig (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods noThunks ∷ Context → BlockConfig (SimpleBlock c ext) → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → BlockConfig (SimpleBlock c ext) → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (BlockConfig (SimpleBlock c ext)) → String Source # | |||||||||
NoThunks (CodecConfig (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods noThunks ∷ Context → CodecConfig (SimpleBlock c ext) → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → CodecConfig (SimpleBlock c ext) → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (CodecConfig (SimpleBlock c ext)) → String Source # | |||||||||
(SimpleCrypto c, NoThunks ext', Typeable ext) ⇒ NoThunks (Header (SimpleBlock' c ext ext')) Source # | |||||||||
NoThunks (StorageConfig (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods noThunks ∷ Context → StorageConfig (SimpleBlock c ext) → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → StorageConfig (SimpleBlock c ext) → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (StorageConfig (SimpleBlock c ext)) → String Source # | |||||||||
(Typeable p, Typeable c) ⇒ NoThunks (Validated (GenTx (SimpleBlock p c))) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
(Typeable p, Typeable c) ⇒ NoThunks (GenTx (SimpleBlock p c)) Source # | |||||||||
NoThunks (TxId (GenTx (SimpleBlock c ext))) Source # | |||||||||
GetTip (LedgerState (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods getTip ∷ ∀ (mk ∷ MapKind). LedgerState (SimpleBlock c ext) mk → Point (LedgerState (SimpleBlock c ext)) Source # | |||||||||
MockProtocolSpecific c ext ⇒ IsLedger (LedgerState (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods applyChainTickLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (LedgerState (SimpleBlock c ext)) → SlotNo → LedgerState (SimpleBlock c ext) EmptyMK → LedgerResult (LedgerState (SimpleBlock c ext)) (Ticked (LedgerState (SimpleBlock c ext)) DiffMK) Source # | |||||||||
HasTxId (GenTx (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods txId ∷ GenTx (SimpleBlock c ext) → TxId (GenTx (SimpleBlock c ext)) Source # | |||||||||
SimpleCrypto c ⇒ LedgerSupportsProtocol (SimplePraosRuleBlock c) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule Methods protocolLedgerView ∷ ∀ (mk ∷ MapKind). LedgerConfig (SimplePraosRuleBlock c) → Ticked (LedgerState (SimplePraosRuleBlock c)) mk → LedgerView (BlockProtocol (SimplePraosRuleBlock c)) Source # ledgerViewForecastAt ∷ ∀ (mk ∷ MapKind). HasCallStack ⇒ LedgerConfig (SimplePraosRuleBlock c) → LedgerState (SimplePraosRuleBlock c) mk → Forecast (LedgerView (BlockProtocol (SimplePraosRuleBlock c))) Source # | |||||||||
CanStowLedgerTables (LedgerState (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods stowLedgerTables ∷ LedgerState (SimpleBlock c ext) ValuesMK → LedgerState (SimpleBlock c ext) EmptyMK Source # unstowLedgerTables ∷ LedgerState (SimpleBlock c ext) EmptyMK → LedgerState (SimpleBlock c ext) ValuesMK Source # | |||||||||
HasLedgerTables (LedgerState (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerState (SimpleBlock c ext) mk → LedgerTables (LedgerState (SimpleBlock c ext)) mk Source # withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerState (SimpleBlock c ext) any → LedgerTables (LedgerState (SimpleBlock c ext)) mk → LedgerState (SimpleBlock c ext) mk Source # | |||||||||
SerializeTablesWithHint (LedgerState (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods encodeTablesWithHint ∷ SerializeTablesHint (LedgerTables (LedgerState (SimpleBlock c ext)) ValuesMK) → LedgerTables (LedgerState (SimpleBlock c ext)) ValuesMK → Encoding Source # decodeTablesWithHint ∷ SerializeTablesHint (LedgerTables (LedgerState (SimpleBlock c ext)) ValuesMK) → Decoder s (LedgerTables (LedgerState (SimpleBlock c ext)) ValuesMK) Source # | |||||||||
HasNetworkProtocolVersion (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Associated Types
| |||||||||
(Serialise ext, Typeable ext, Serialise (MockLedgerConfig SimpleMockCrypto ext), MockProtocolSpecific SimpleMockCrypto ext) ⇒ SerialiseNodeToClientConstraints (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation | |||||||||
Serialise ext ⇒ SerialiseNodeToNodeConstraints (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods estimateBlockSize ∷ Header (MockBlock ext) → SizeInBytes Source # | |||||||||
(Serialise ext, RunMockBlock SimpleMockCrypto ext) ⇒ SerialiseDiskConstraints (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation | |||||||||
CanUpgradeLedgerTables (LedgerState (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods upgradeTables ∷ ∀ (mk1 ∷ MapKind) (mk2 ∷ MapKind). LedgerState (SimpleBlock c ext) mk1 → LedgerState (SimpleBlock c ext) mk2 → LedgerTables (LedgerState (SimpleBlock c ext)) ValuesMK → LedgerTables (LedgerState (SimpleBlock c ext)) ValuesMK Source # | |||||||||
(Serialise ext, Typeable ext) ⇒ HasBinaryBlockInfo (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods getBinaryBlockInfo ∷ MockBlock ext → BinaryBlockInfo Source # | |||||||||
Condense ext' ⇒ Condense (Header (SimpleBlock' c ext ext')) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
Condense (GenTx (SimpleBlock p c)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
Condense (GenTxId (SimpleBlock p c)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
HasMockTxs (GenTx (SimpleBlock p c)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods getMockTxs ∷ GenTx (SimpleBlock p c) → [Tx] Source # | |||||||||
(SimpleCrypto c, Typeable ext, Typeable ext') ⇒ HasHeader (Header (SimpleBlock' c ext ext')) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods getHeaderFields ∷ Header (SimpleBlock' c ext ext') → HeaderFields (Header (SimpleBlock' c ext ext')) Source # | |||||||||
(SimpleCrypto c, Serialise ext') ⇒ Serialise (Header (SimpleBlock' c ext ext')) Source # | Custom | ||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods encode ∷ Header (SimpleBlock' c ext ext') → Encoding Source # decode ∷ Decoder s (Header (SimpleBlock' c ext ext')) Source # encodeList ∷ [Header (SimpleBlock' c ext ext')] → Encoding Source # decodeList ∷ Decoder s [Header (SimpleBlock' c ext ext')] Source # | |||||||||
Serialise (GenTx (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods encode ∷ GenTx (SimpleBlock c ext) → Encoding Source # decode ∷ Decoder s (GenTx (SimpleBlock c ext)) Source # encodeList ∷ [GenTx (SimpleBlock c ext)] → Encoding Source # decodeList ∷ Decoder s [GenTx (SimpleBlock c ext)] Source # | |||||||||
Serialise (TxId (GenTx (SimpleBlock c ext))) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods encode ∷ TxId (GenTx (SimpleBlock c ext)) → Encoding Source # decode ∷ Decoder s (TxId (GenTx (SimpleBlock c ext))) Source # encodeList ∷ [TxId (GenTx (SimpleBlock c ext))] → Encoding Source # decodeList ∷ Decoder s [TxId (GenTx (SimpleBlock c ext))] Source # | |||||||||
SerialiseNodeToClient (MockBlock ext) SlotNo Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → SlotNo → Encoding Source # decodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → ∀ s. Decoder s SlotNo Source # | |||||||||
DecodeDisk (SimplePraosRuleBlock c) () Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule Methods decodeDisk ∷ CodecConfig (SimplePraosRuleBlock c) → ∀ s. Decoder s () Source # | |||||||||
EncodeDisk (SimplePraosRuleBlock c) () Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule Methods encodeDisk ∷ CodecConfig (SimplePraosRuleBlock c) → () → Encoding Source # | |||||||||
SerialiseNodeToClient (MockBlock ext) (SomeBlockQuery (BlockQuery (MockBlock ext))) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → SomeBlockQuery (BlockQuery (MockBlock ext)) → Encoding Source # decodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → ∀ s. Decoder s (SomeBlockQuery (BlockQuery (MockBlock ext))) Source # | |||||||||
SerialiseNodeToClient (MockBlock ext) (GenTx (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → GenTx (MockBlock ext) → Encoding Source # decodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → ∀ s. Decoder s (GenTx (MockBlock ext)) Source # | |||||||||
SerialiseNodeToClient (MockBlock ext) (GenTxId (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → GenTxId (MockBlock ext) → Encoding Source # decodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → ∀ s. Decoder s (GenTxId (MockBlock ext)) Source # | |||||||||
SerialiseNodeToClient (MockBlock ext) (MockError (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → MockError (MockBlock ext) → Encoding Source # decodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → ∀ s. Decoder s (MockError (MockBlock ext)) Source # | |||||||||
Serialise ext ⇒ SerialiseNodeToClient (MockBlock ext) (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → MockBlock ext → Encoding Source # decodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → ∀ s. Decoder s (MockBlock ext) Source # | |||||||||
Serialise ext ⇒ SerialiseNodeToNode (MockBlock ext) (Header (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → Header (MockBlock ext) → Encoding Source # decodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → ∀ s. Decoder s (Header (MockBlock ext)) Source # | |||||||||
SerialiseNodeToNode (MockBlock ext) (GenTx (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → GenTx (MockBlock ext) → Encoding Source # decodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → ∀ s. Decoder s (GenTx (MockBlock ext)) Source # | |||||||||
SerialiseNodeToNode (MockBlock ext) (GenTxId (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → GenTxId (MockBlock ext) → Encoding Source # decodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → ∀ s. Decoder s (GenTxId (MockBlock ext)) Source # | |||||||||
Serialise ext ⇒ SerialiseNodeToNode (MockBlock ext) (SerialisedHeader (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → SerialisedHeader (MockBlock ext) → Encoding Source # decodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → ∀ s. Decoder s (SerialisedHeader (MockBlock ext)) Source # | |||||||||
Serialise ext ⇒ SerialiseNodeToNode (MockBlock ext) (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → MockBlock ext → Encoding Source # decodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → ∀ s. Decoder s (MockBlock ext) Source # | |||||||||
DecodeDisk (MockBlock ext) (AnnTip (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods decodeDisk ∷ CodecConfig (MockBlock ext) → ∀ s. Decoder s (AnnTip (MockBlock ext)) Source # | |||||||||
Serialise ext ⇒ DecodeDiskDep (NestedCtxt Header) (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods decodeDiskDep ∷ CodecConfig (MockBlock ext) → NestedCtxt Header (MockBlock ext) a → ∀ s. Decoder s (ByteString → a) Source # | |||||||||
Serialise ext ⇒ DecodeDiskDepIx (NestedCtxt Header) (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods decodeDiskDepIx ∷ CodecConfig (MockBlock ext) → Decoder s (SomeSecond (NestedCtxt Header) (MockBlock ext)) Source # | |||||||||
Serialise ext ⇒ EncodeDisk (MockBlock ext) (Header (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeDisk ∷ CodecConfig (MockBlock ext) → Header (MockBlock ext) → Encoding Source # | |||||||||
EncodeDisk (MockBlock ext) (AnnTip (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeDisk ∷ CodecConfig (MockBlock ext) → AnnTip (MockBlock ext) → Encoding Source # | |||||||||
Serialise ext ⇒ EncodeDisk (MockBlock ext) (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeDisk ∷ CodecConfig (MockBlock ext) → MockBlock ext → Encoding Source # | |||||||||
Serialise ext ⇒ EncodeDiskDep (NestedCtxt Header) (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeDiskDep ∷ CodecConfig (MockBlock ext) → NestedCtxt Header (MockBlock ext) a → a → Encoding Source # | |||||||||
Serialise ext ⇒ EncodeDiskDepIx (NestedCtxt Header) (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeDiskDepIx ∷ CodecConfig (MockBlock ext) → SomeSecond (NestedCtxt Header) (MockBlock ext) → Encoding Source # | |||||||||
MockProtocolSpecific c ext ⇒ ApplyBlock (LedgerState (SimpleBlock c ext)) (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods applyBlockLedgerResultWithValidation ∷ ValidationPolicy → ComputeLedgerEvents → LedgerCfg (LedgerState (SimpleBlock c ext)) → SimpleBlock c ext → Ticked (LedgerState (SimpleBlock c ext)) ValuesMK → Except (LedgerErr (LedgerState (SimpleBlock c ext))) (LedgerResult (LedgerState (SimpleBlock c ext)) (LedgerState (SimpleBlock c ext) DiffMK)) Source # applyBlockLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (LedgerState (SimpleBlock c ext)) → SimpleBlock c ext → Ticked (LedgerState (SimpleBlock c ext)) ValuesMK → Except (LedgerErr (LedgerState (SimpleBlock c ext))) (LedgerResult (LedgerState (SimpleBlock c ext)) (LedgerState (SimpleBlock c ext) DiffMK)) Source # reapplyBlockLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (LedgerState (SimpleBlock c ext)) → SimpleBlock c ext → Ticked (LedgerState (SimpleBlock c ext)) ValuesMK → LedgerResult (LedgerState (SimpleBlock c ext)) (LedgerState (SimpleBlock c ext) DiffMK) Source # getBlockKeySets ∷ SimpleBlock c ext → LedgerTables (LedgerState (SimpleBlock c ext)) KeysMK Source # | |||||||||
SerialiseNodeToClient (MockBlock ext) (Serialised (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → Serialised (MockBlock ext) → Encoding Source # decodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → ∀ s. Decoder s (Serialised (MockBlock ext)) Source # | |||||||||
SerialiseNodeToNode (MockBlock ext) (Serialised (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → Serialised (MockBlock ext) → Encoding Source # decodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → ∀ s. Decoder s (Serialised (MockBlock ext)) Source # | |||||||||
DecodeDisk (MockBlock ext) (LedgerState (MockBlock ext) EmptyMK) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods decodeDisk ∷ CodecConfig (MockBlock ext) → ∀ s. Decoder s (LedgerState (MockBlock ext) EmptyMK) Source # | |||||||||
Serialise ext ⇒ DecodeDisk (MockBlock ext) (ByteString → Header (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods decodeDisk ∷ CodecConfig (MockBlock ext) → ∀ s. Decoder s (ByteString → Header (MockBlock ext)) Source # | |||||||||
Serialise ext ⇒ DecodeDisk (MockBlock ext) (ByteString → MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods decodeDisk ∷ CodecConfig (MockBlock ext) → ∀ s. Decoder s (ByteString → MockBlock ext) Source # | |||||||||
EncodeDisk (MockBlock ext) (LedgerState (MockBlock ext) EmptyMK) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeDisk ∷ CodecConfig (MockBlock ext) → LedgerState (MockBlock ext) EmptyMK → Encoding Source # | |||||||||
Generic (LedgerState (SimpleBlock c ext) mk) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods from ∷ LedgerState (SimpleBlock c ext) mk → Rep (LedgerState (SimpleBlock c ext) mk) x # to ∷ Rep (LedgerState (SimpleBlock c ext) mk) x → LedgerState (SimpleBlock c ext) mk # | |||||||||
(SimpleCrypto c, Typeable ext, Show (mk TxIn TxOut)) ⇒ Show (LedgerState (SimpleBlock c ext) mk) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods showsPrec ∷ Int → LedgerState (SimpleBlock c ext) mk → ShowS # show ∷ LedgerState (SimpleBlock c ext) mk → String # showList ∷ [LedgerState (SimpleBlock c ext) mk] → ShowS # | |||||||||
(SimpleCrypto c, Typeable ext, Eq (mk TxIn TxOut)) ⇒ Eq (LedgerState (SimpleBlock c ext) mk) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods (==) ∷ LedgerState (SimpleBlock c ext) mk → LedgerState (SimpleBlock c ext) mk → Bool # (/=) ∷ LedgerState (SimpleBlock c ext) mk → LedgerState (SimpleBlock c ext) mk → Bool # | |||||||||
(SimpleCrypto c, Typeable ext, NoThunks (mk TxIn TxOut)) ⇒ NoThunks (LedgerState (SimpleBlock c ext) mk) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods noThunks ∷ Context → LedgerState (SimpleBlock c ext) mk → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → LedgerState (SimpleBlock c ext) mk → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (LedgerState (SimpleBlock c ext) mk) → String Source # | |||||||||
(SimpleCrypto c, Typeable ext) ⇒ GetPrevHash (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods headerPrevHash ∷ Header (SimpleBlock c ext) → ChainHash (SimpleBlock c ext) Source # | |||||||||
(BlockSupportsProtocol (SimpleBlock c ext), Show (SelectView (BlockProtocol (SimpleBlock c ext)))) ⇒ BlockSupportsDiffusionPipelining (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node Associated Types
Methods initialTentativeHeaderState ∷ Proxy (SimpleBlock c ext) → TentativeHeaderState (SimpleBlock c ext) Source # tentativeHeaderView ∷ BlockConfig (SimpleBlock c ext) → Header (SimpleBlock c ext) → TentativeHeaderView (SimpleBlock c ext) Source # applyTentativeHeaderView ∷ Proxy (SimpleBlock c ext) → TentativeHeaderView (SimpleBlock c ext) → TentativeHeaderState (SimpleBlock c ext) → Maybe (TentativeHeaderState (SimpleBlock c ext)) Source # | |||||||||
BlockSupportsMetrics (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node Methods isSelfIssued ∷ BlockConfig (SimpleBlock c ext) → Header (SimpleBlock c ext) → WhetherSelfIssued Source # | |||||||||
(SimpleCrypto c, PraosCrypto c', Signable (PraosKES c') (SignedSimplePraos c c')) ⇒ BlockSupportsProtocol (SimpleBlock c (SimplePraosExt c c')) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos Methods validateView ∷ BlockConfig (SimpleBlock c (SimplePraosExt c c')) → Header (SimpleBlock c (SimplePraosExt c c')) → ValidateView (BlockProtocol (SimpleBlock c (SimplePraosExt c c'))) Source # selectView ∷ BlockConfig (SimpleBlock c (SimplePraosExt c c')) → Header (SimpleBlock c (SimplePraosExt c c')) → SelectView (BlockProtocol (SimpleBlock c (SimplePraosExt c c'))) Source # projectChainOrderConfig ∷ BlockConfig (SimpleBlock c (SimplePraosExt c c')) → ChainOrderConfig (SelectView (BlockProtocol (SimpleBlock c (SimplePraosExt c c')))) Source # | |||||||||
SimpleCrypto c ⇒ BlockSupportsProtocol (SimpleBlock c SimplePraosRuleExt) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule Methods validateView ∷ BlockConfig (SimpleBlock c SimplePraosRuleExt) → Header (SimpleBlock c SimplePraosRuleExt) → ValidateView (BlockProtocol (SimpleBlock c SimplePraosRuleExt)) Source # selectView ∷ BlockConfig (SimpleBlock c SimplePraosRuleExt) → Header (SimpleBlock c SimplePraosRuleExt) → SelectView (BlockProtocol (SimpleBlock c SimplePraosRuleExt)) Source # projectChainOrderConfig ∷ BlockConfig (SimpleBlock c SimplePraosRuleExt) → ChainOrderConfig (SelectView (BlockProtocol (SimpleBlock c SimplePraosRuleExt))) Source # | |||||||||
(SimpleCrypto c, BftCrypto c', Signable (BftDSIGN c') (SignedSimpleBft c c')) ⇒ BlockSupportsProtocol (SimpleBftBlock c c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT Methods validateView ∷ BlockConfig (SimpleBftBlock c c') → Header (SimpleBftBlock c c') → ValidateView (BlockProtocol (SimpleBftBlock c c')) Source # selectView ∷ BlockConfig (SimpleBftBlock c c') → Header (SimpleBftBlock c c') → SelectView (BlockProtocol (SimpleBftBlock c c')) Source # projectChainOrderConfig ∷ BlockConfig (SimpleBftBlock c c') → ChainOrderConfig (SelectView (BlockProtocol (SimpleBftBlock c c'))) Source # | |||||||||
(SimpleCrypto c, Signable MockDSIGN (SignedSimplePBft c PBftMockCrypto)) ⇒ BlockSupportsProtocol (SimplePBftBlock c PBftMockCrypto) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT Methods validateView ∷ BlockConfig (SimplePBftBlock c PBftMockCrypto) → Header (SimplePBftBlock c PBftMockCrypto) → ValidateView (BlockProtocol (SimplePBftBlock c PBftMockCrypto)) Source # selectView ∷ BlockConfig (SimplePBftBlock c PBftMockCrypto) → Header (SimplePBftBlock c PBftMockCrypto) → SelectView (BlockProtocol (SimplePBftBlock c PBftMockCrypto)) Source # projectChainOrderConfig ∷ BlockConfig (SimplePBftBlock c PBftMockCrypto) → ChainOrderConfig (SelectView (BlockProtocol (SimplePBftBlock c PBftMockCrypto))) Source # | |||||||||
ConsensusProtocol (BlockProtocol (SimpleBlock c ext)) ⇒ BlockSupportsSanityCheck (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node Methods configAllSecurityParams ∷ TopLevelConfig (SimpleBlock c ext) → NonEmpty SecurityParam Source # | |||||||||
RunMockBlock c ext ⇒ ConfigSupportsNode (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Abstract Methods getSystemStart ∷ BlockConfig (SimpleBlock c ext) → SystemStart Source # getNetworkMagic ∷ BlockConfig (SimpleBlock c ext) → NetworkMagic Source # | |||||||||
HasHardForkHistory (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods hardForkSummary ∷ ∀ (mk ∷ MapKind). LedgerConfig (SimpleBlock c ext) → LedgerState (SimpleBlock c ext) mk → Summary (HardForkIndices (SimpleBlock c ext)) Source # | |||||||||
MockProtocolSpecific c ext ⇒ HasPartialLedgerConfig (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods completeLedgerConfig ∷ proxy (SimpleBlock c ext) → EpochInfo (Except PastHorizonException) → PartialLedgerConfig (SimpleBlock c ext) → LedgerConfig (SimpleBlock c ext) Source # | |||||||||
(SimpleCrypto c, Typeable ext) ⇒ BasicEnvelopeValidation (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods expectedFirstBlockNo ∷ proxy (SimpleBlock c ext) → BlockNo Source # expectedNextBlockNo ∷ proxy (SimpleBlock c ext) → TipInfo (SimpleBlock c ext) → TipInfo (SimpleBlock c ext) → BlockNo → BlockNo Source # minimumPossibleSlotNo ∷ Proxy (SimpleBlock c ext) → SlotNo Source # minimumNextSlotNo ∷ proxy (SimpleBlock c ext) → TipInfo (SimpleBlock c ext) → TipInfo (SimpleBlock c ext) → SlotNo → SlotNo Source # | |||||||||
(SimpleCrypto c, Typeable ext) ⇒ HasAnnTip (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods getTipInfo ∷ Header (SimpleBlock c ext) → TipInfo (SimpleBlock c ext) Source # tipInfoHash ∷ proxy (SimpleBlock c ext) → TipInfo (SimpleBlock c ext) → HeaderHash (SimpleBlock c ext) Source # | |||||||||
(SimpleCrypto c, Typeable ext) ⇒ ValidateEnvelope (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods additionalEnvelopeChecks ∷ TopLevelConfig (SimpleBlock c ext) → LedgerView (BlockProtocol (SimpleBlock c ext)) → Header (SimpleBlock c ext) → Except (OtherHeaderEnvelopeError (SimpleBlock c ext)) () Source # | |||||||||
MockProtocolSpecific c ext ⇒ UpdateLedger (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
GetTip (Ticked (LedgerState (SimpleBlock c ext))) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (SimpleBlock c ext)) mk → Point (Ticked (LedgerState (SimpleBlock c ext))) Source # | |||||||||
MockProtocolSpecific c ext ⇒ CommonProtocolParams (SimpleBlock c ext) Source # | Dummy values | ||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods maxHeaderSize ∷ ∀ (mk ∷ MapKind). LedgerState (SimpleBlock c ext) mk → Word32 Source # maxTxSize ∷ ∀ (mk ∷ MapKind). LedgerState (SimpleBlock c ext) mk → Word32 Source # | |||||||||
InspectLedger (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods inspectLedger ∷ ∀ (mk1 ∷ MapKind) (mk2 ∷ MapKind). TopLevelConfig (SimpleBlock c ext) → LedgerState (SimpleBlock c ext) mk1 → LedgerState (SimpleBlock c ext) mk2 → [LedgerEvent (SimpleBlock c ext)] Source # | |||||||||
MockProtocolSpecific c ext ⇒ BlockSupportsLedgerQuery (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods answerPureBlockQuery ∷ ExtLedgerCfg (SimpleBlock c ext) → BlockQuery (SimpleBlock c ext) 'QFNoTables result → ExtLedgerState (SimpleBlock c ext) EmptyMK → result Source # answerBlockQueryLookup ∷ MonadSTM m ⇒ ExtLedgerCfg (SimpleBlock c ext) → BlockQuery (SimpleBlock c ext) 'QFLookupTables result → ReadOnlyForker' m (SimpleBlock c ext) → m result Source # answerBlockQueryTraverse ∷ MonadSTM m ⇒ ExtLedgerCfg (SimpleBlock c ext) → BlockQuery (SimpleBlock c ext) 'QFTraverseTables result → ReadOnlyForker' m (SimpleBlock c ext) → m result Source # blockQueryIsSupportedOnVersion ∷ ∀ (fp ∷ QueryFootprint) result. BlockQuery (SimpleBlock c ext) fp result → BlockNodeToClientVersion (SimpleBlock c ext) → Bool Source # | |||||||||
HasTxs (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods extractTxs ∷ SimpleBlock c ext → [GenTx (SimpleBlock c ext)] Source # | |||||||||
MockProtocolSpecific c ext ⇒ LedgerSupportsMempool (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods txInvariant ∷ GenTx (SimpleBlock c ext) → Bool Source # applyTx ∷ LedgerConfig (SimpleBlock c ext) → WhetherToIntervene → SlotNo → GenTx (SimpleBlock c ext) → TickedLedgerState (SimpleBlock c ext) ValuesMK → Except (ApplyTxErr (SimpleBlock c ext)) (TickedLedgerState (SimpleBlock c ext) DiffMK, Validated (GenTx (SimpleBlock c ext))) Source # reapplyTx ∷ ComputeDiffs → LedgerConfig (SimpleBlock c ext) → SlotNo → Validated (GenTx (SimpleBlock c ext)) → TickedLedgerState (SimpleBlock c ext) ValuesMK → Except (ApplyTxErr (SimpleBlock c ext)) (TickedLedgerState (SimpleBlock c ext) TrackingMK) Source # reapplyTxs ∷ ComputeDiffs → LedgerConfig (SimpleBlock c ext) → SlotNo → [(Validated (GenTx (SimpleBlock c ext)), extra)] → TickedLedgerState (SimpleBlock c ext) ValuesMK → ReapplyTxsResult extra (SimpleBlock c ext) Source # txForgetValidated ∷ Validated (GenTx (SimpleBlock c ext)) → GenTx (SimpleBlock c ext) Source # getTransactionKeySets ∷ GenTx (SimpleBlock c ext) → LedgerTables (LedgerState (SimpleBlock c ext)) KeysMK Source # prependMempoolDiffs ∷ TickedLedgerState (SimpleBlock c ext) DiffMK → TickedLedgerState (SimpleBlock c ext) DiffMK → TickedLedgerState (SimpleBlock c ext) DiffMK Source # applyMempoolDiffs ∷ LedgerTables (LedgerState (SimpleBlock c ext)) ValuesMK → LedgerTables (LedgerState (SimpleBlock c ext)) KeysMK → TickedLedgerState (SimpleBlock c ext) DiffMK → TickedLedgerState (SimpleBlock c ext) ValuesMK Source # | |||||||||
TxLimits (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods txMeasure ∷ LedgerConfig (SimpleBlock c ext) → TickedLedgerState (SimpleBlock c ext) ValuesMK → GenTx (SimpleBlock c ext) → Except (ApplyTxErr (SimpleBlock c ext)) (TxMeasure (SimpleBlock c ext)) Source # blockCapacityTxMeasure ∷ ∀ (mk ∷ MapKind). LedgerConfig (SimpleBlock c ext) → TickedLedgerState (SimpleBlock c ext) mk → TxMeasure (SimpleBlock c ext) Source # | |||||||||
LedgerSupportsPeerSelection (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods getPeers ∷ ∀ (mk ∷ MapKind). LedgerState (SimpleBlock c ext) mk → [(PoolStake, NonEmpty StakePoolRelay)] Source # | |||||||||
(SimpleCrypto c, BftCrypto c', Signable (BftDSIGN c') (SignedSimpleBft c c')) ⇒ LedgerSupportsProtocol (SimpleBftBlock c c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT Methods protocolLedgerView ∷ ∀ (mk ∷ MapKind). LedgerConfig (SimpleBftBlock c c') → Ticked (LedgerState (SimpleBftBlock c c')) mk → LedgerView (BlockProtocol (SimpleBftBlock c c')) Source # ledgerViewForecastAt ∷ ∀ (mk ∷ MapKind). HasCallStack ⇒ LedgerConfig (SimpleBftBlock c c') → LedgerState (SimpleBftBlock c c') mk → Forecast (LedgerView (BlockProtocol (SimpleBftBlock c c'))) Source # | |||||||||
(SimpleCrypto c, Signable MockDSIGN (SignedSimplePBft c PBftMockCrypto)) ⇒ LedgerSupportsProtocol (SimplePBftBlock c PBftMockCrypto) Source # | The ledger view is constant for the mock instantiation of PBFT (mock blocks cannot change delegation) | ||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT Methods protocolLedgerView ∷ ∀ (mk ∷ MapKind). LedgerConfig (SimplePBftBlock c PBftMockCrypto) → Ticked (LedgerState (SimplePBftBlock c PBftMockCrypto)) mk → LedgerView (BlockProtocol (SimplePBftBlock c PBftMockCrypto)) Source # ledgerViewForecastAt ∷ ∀ (mk ∷ MapKind). HasCallStack ⇒ LedgerConfig (SimplePBftBlock c PBftMockCrypto) → LedgerState (SimplePBftBlock c PBftMockCrypto) mk → Forecast (LedgerView (BlockProtocol (SimplePBftBlock c PBftMockCrypto))) Source # | |||||||||
(SimpleCrypto c, PraosCrypto c', Signable (PraosKES c') (SignedSimplePraos c c')) ⇒ LedgerSupportsProtocol (SimplePraosBlock c c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos Methods protocolLedgerView ∷ ∀ (mk ∷ MapKind). LedgerConfig (SimplePraosBlock c c') → Ticked (LedgerState (SimplePraosBlock c c')) mk → LedgerView (BlockProtocol (SimplePraosBlock c c')) Source # ledgerViewForecastAt ∷ ∀ (mk ∷ MapKind). HasCallStack ⇒ LedgerConfig (SimplePraosBlock c c') → LedgerState (SimplePraosBlock c c') mk → Forecast (LedgerView (BlockProtocol (SimplePraosBlock c c'))) Source # | |||||||||
CanStowLedgerTables (Ticked (LedgerState (SimpleBlock c ext))) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods stowLedgerTables ∷ Ticked (LedgerState (SimpleBlock c ext)) ValuesMK → Ticked (LedgerState (SimpleBlock c ext)) EmptyMK Source # unstowLedgerTables ∷ Ticked (LedgerState (SimpleBlock c ext)) EmptyMK → Ticked (LedgerState (SimpleBlock c ext)) ValuesMK Source # | |||||||||
HasLedgerTables (Ticked (LedgerState (SimpleBlock c ext))) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (SimpleBlock c ext)) mk → LedgerTables (Ticked (LedgerState (SimpleBlock c ext))) mk Source # withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (SimpleBlock c ext)) any → LedgerTables (Ticked (LedgerState (SimpleBlock c ext))) mk → Ticked (LedgerState (SimpleBlock c ext)) mk Source # | |||||||||
NodeInitStorage (SimpleBlock SimpleMockCrypto ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node Methods nodeImmutableDbChunkInfo ∷ StorageConfig (SimpleBlock SimpleMockCrypto ext) → ChunkInfo Source # nodeCheckIntegrity ∷ StorageConfig (SimpleBlock SimpleMockCrypto ext) → SimpleBlock SimpleMockCrypto ext → Bool Source # nodeInitChainDB ∷ IOLike m ⇒ StorageConfig (SimpleBlock SimpleMockCrypto ext) → InitChainDB m (SimpleBlock SimpleMockCrypto ext) → m () Source # | |||||||||
SupportedNetworkProtocolVersion (SimpleBlock SimpleMockCrypto ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node Methods supportedNodeToNodeVersions ∷ Proxy (SimpleBlock SimpleMockCrypto ext) → Map NodeToNodeVersion (BlockNodeToNodeVersion (SimpleBlock SimpleMockCrypto ext)) Source # supportedNodeToClientVersions ∷ Proxy (SimpleBlock SimpleMockCrypto ext) → Map NodeToClientVersion (BlockNodeToClientVersion (SimpleBlock SimpleMockCrypto ext)) Source # latestReleasedNodeVersion ∷ Proxy (SimpleBlock SimpleMockCrypto ext) → (Maybe NodeToNodeVersion, Maybe NodeToClientVersion) Source # | |||||||||
(LedgerSupportsProtocol (SimpleBlock SimpleMockCrypto ext), Show (CannotForge (SimpleBlock SimpleMockCrypto ext)), Show (ForgeStateInfo (SimpleBlock SimpleMockCrypto ext)), Show (ForgeStateUpdateError (SimpleBlock SimpleMockCrypto ext)), Serialise ext, RunMockBlock SimpleMockCrypto ext) ⇒ RunNode (SimpleBlock SimpleMockCrypto ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node | |||||||||
SignedHeader (SimpleBftHeader c c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT Methods headerSigned ∷ SimpleBftHeader c c' → Signed (SimpleBftHeader c c') Source # | |||||||||
SignedHeader (SimplePBftHeader c c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT Methods headerSigned ∷ SimplePBftHeader c c' → Signed (SimplePBftHeader c c') Source # | |||||||||
PraosCrypto c' ⇒ SignedHeader (SimplePraosHeader c c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos Methods headerSigned ∷ SimplePraosHeader c c' → Signed (SimplePraosHeader c c') Source # | |||||||||
(SimpleCrypto c, Typeable ext) ⇒ ShowQuery (BlockQuery (SimpleBlock c ext) fp) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods showResult ∷ BlockQuery (SimpleBlock c ext) fp result → result → String Source # | |||||||||
DecodeDisk (SimpleBftBlock c c') () Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT Methods decodeDisk ∷ CodecConfig (SimpleBftBlock c c') → ∀ s. Decoder s () Source # | |||||||||
EncodeDisk (SimpleBftBlock c c') () Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT Methods encodeDisk ∷ CodecConfig (SimpleBftBlock c c') → () → Encoding Source # | |||||||||
IndexedMemPack (LedgerState (SimpleBlock c ext) EmptyMK) TxOut Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods indexedPackedByteCount ∷ LedgerState (SimpleBlock c ext) EmptyMK → TxOut → Int Source # indexedPackM ∷ LedgerState (SimpleBlock c ext) EmptyMK → TxOut → Pack s () Source # indexedUnpackM ∷ Buffer b ⇒ LedgerState (SimpleBlock c ext) EmptyMK → Unpack b TxOut Source # indexedTypeName ∷ LedgerState (SimpleBlock c ext) EmptyMK → String Source # | |||||||||
PBftCrypto c' ⇒ DecodeDisk (SimplePBftBlock c c') (PBftState c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT Methods decodeDisk ∷ CodecConfig (SimplePBftBlock c c') → ∀ s. Decoder s (PBftState c') Source # | |||||||||
PraosCrypto c' ⇒ DecodeDisk (SimplePraosBlock c c') (PraosChainDepState c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos Methods decodeDisk ∷ CodecConfig (SimplePraosBlock c c') → ∀ s. Decoder s (PraosChainDepState c') Source # | |||||||||
PBftCrypto c' ⇒ EncodeDisk (SimplePBftBlock c c') (PBftState c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT Methods encodeDisk ∷ CodecConfig (SimplePBftBlock c c') → PBftState c' → Encoding Source # | |||||||||
PraosCrypto c' ⇒ EncodeDisk (SimplePraosBlock c c') (PraosChainDepState c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos Methods encodeDisk ∷ CodecConfig (SimplePraosBlock c c') → PraosChainDepState c' → Encoding Source # | |||||||||
(Typeable c, Typeable ext) ⇒ ShowProxy (BlockQuery (SimpleBlock c ext) ∷ QueryFootprint → Type → Type) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods showProxy ∷ Proxy (BlockQuery (SimpleBlock c ext)) → String Source # | |||||||||
Serialise (MockLedgerConfig c ext) ⇒ SerialiseNodeToClient (SimpleBlock c ext) (SimpleLedgerConfig c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods encodeNodeToClient ∷ CodecConfig (SimpleBlock c ext) → BlockNodeToClientVersion (SimpleBlock c ext) → SimpleLedgerConfig c ext → Encoding Source # decodeNodeToClient ∷ CodecConfig (SimpleBlock c ext) → BlockNodeToClientVersion (SimpleBlock c ext) → ∀ s. Decoder s (SimpleLedgerConfig c ext) Source # | |||||||||
Generic (Ticked (LedgerState (SimpleBlock c ext)) mk) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods from ∷ Ticked (LedgerState (SimpleBlock c ext)) mk → Rep (Ticked (LedgerState (SimpleBlock c ext)) mk) x # to ∷ Rep (Ticked (LedgerState (SimpleBlock c ext)) mk) x → Ticked (LedgerState (SimpleBlock c ext)) mk # | |||||||||
Generic (SimpleBlock' c ext ext') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods from ∷ SimpleBlock' c ext ext' → Rep (SimpleBlock' c ext ext') x # to ∷ Rep (SimpleBlock' c ext ext') x → SimpleBlock' c ext ext' # | |||||||||
Show (NestedCtxt_ (SimpleBlock c ext) f a) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods showsPrec ∷ Int → NestedCtxt_ (SimpleBlock c ext) f a → ShowS # show ∷ NestedCtxt_ (SimpleBlock c ext) f a → String # showList ∷ [NestedCtxt_ (SimpleBlock c ext) f a] → ShowS # | |||||||||
Show (BlockQuery (SimpleBlock c ext) fp result) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods showsPrec ∷ Int → BlockQuery (SimpleBlock c ext) fp result → ShowS # show ∷ BlockQuery (SimpleBlock c ext) fp result → String # showList ∷ [BlockQuery (SimpleBlock c ext) fp result] → ShowS # | |||||||||
(SimpleCrypto c, Typeable ext, Show (LedgerState (SimpleBlock c ext) mk)) ⇒ Show (Ticked (LedgerState (SimpleBlock c ext)) mk) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods showsPrec ∷ Int → Ticked (LedgerState (SimpleBlock c ext)) mk → ShowS # show ∷ Ticked (LedgerState (SimpleBlock c ext)) mk → String # showList ∷ [Ticked (LedgerState (SimpleBlock c ext)) mk] → ShowS # | |||||||||
(SimpleCrypto c, Show ext', Typeable ext) ⇒ Show (SimpleBlock' c ext ext') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods showsPrec ∷ Int → SimpleBlock' c ext ext' → ShowS # show ∷ SimpleBlock' c ext ext' → String # showList ∷ [SimpleBlock' c ext ext'] → ShowS # | |||||||||
(SimpleCrypto c, Eq ext', Typeable ext) ⇒ Eq (SimpleBlock' c ext ext') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods (==) ∷ SimpleBlock' c ext ext' → SimpleBlock' c ext ext' → Bool # (/=) ∷ SimpleBlock' c ext ext' → SimpleBlock' c ext ext' → Bool # | |||||||||
(SimpleCrypto c, Typeable ext) ⇒ NoThunks (Ticked (LedgerState (SimpleBlock c ext)) TrackingMK) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods noThunks ∷ Context → Ticked (LedgerState (SimpleBlock c ext)) TrackingMK → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → Ticked (LedgerState (SimpleBlock c ext)) TrackingMK → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (Ticked (LedgerState (SimpleBlock c ext)) TrackingMK) → String Source # | |||||||||
SimpleCrypto c ⇒ ConvertRawHash (SimpleBlock' c ext ext') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods toRawHash ∷ proxy (SimpleBlock' c ext ext') → HeaderHash (SimpleBlock' c ext ext') → ByteString Source # fromRawHash ∷ proxy (SimpleBlock' c ext ext') → ByteString → HeaderHash (SimpleBlock' c ext ext') Source # toShortRawHash ∷ proxy (SimpleBlock' c ext ext') → HeaderHash (SimpleBlock' c ext ext') → ShortByteString Source # fromShortRawHash ∷ proxy (SimpleBlock' c ext ext') → ShortByteString → HeaderHash (SimpleBlock' c ext ext') Source # hashSize ∷ proxy (SimpleBlock' c ext ext') → Word32 Source # | |||||||||
(SimpleCrypto c, Typeable ext, Typeable ext') ⇒ GetHeader (SimpleBlock' c ext ext') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods getHeader ∷ SimpleBlock' c ext ext' → Header (SimpleBlock' c ext ext') Source # blockMatchesHeader ∷ Header (SimpleBlock' c ext ext') → SimpleBlock' c ext ext' → Bool Source # headerIsEBB ∷ Header (SimpleBlock' c ext ext') → Maybe EpochNo Source # | |||||||||
Condense ext' ⇒ Condense (SimpleBlock' c ext ext') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods condense ∷ SimpleBlock' c ext ext' → String Source # | |||||||||
HasMockTxs (SimpleBlock' c ext ext') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods getMockTxs ∷ SimpleBlock' c ext ext' → [Tx] Source # | |||||||||
(SimpleCrypto c, Typeable ext, Typeable ext') ⇒ HasHeader (SimpleBlock' c ext ext') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods getHeaderFields ∷ SimpleBlock' c ext ext' → HeaderFields (SimpleBlock' c ext ext') Source # | |||||||||
(SimpleCrypto c, Serialise ext') ⇒ Serialise (SimpleBlock' c ext ext') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods encode ∷ SimpleBlock' c ext ext' → Encoding Source # decode ∷ Decoder s (SimpleBlock' c ext ext') Source # encodeList ∷ [SimpleBlock' c ext ext'] → Encoding Source # decodeList ∷ Decoder s [SimpleBlock' c ext ext'] Source # | |||||||||
type TrivialIndex (NestedCtxt_ (SimpleBlock c ext) f ∷ Type → Type) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation | |||||||||
type HeaderHash (SimpleBlock' c ext ext' ∷ Type) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block type HeaderHash (SimpleBlock' c ext ext' ∷ Type) = Hash (SimpleHash c) (Header (SimpleBlock' c ext ext')) | |||||||||
type Rep (BlockConfig (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
type Rep (CodecConfig (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
type Rep (Header (SimpleBlock' c ext ext')) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block type Rep (Header (SimpleBlock' c ext ext')) = D1 ('MetaData "Header" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleHeader" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleHeaderHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HeaderHash (SimpleBlock' c ext ext'))) :*: (S1 ('MetaSel ('Just "simpleHeaderStd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SimpleStdHeader c ext)) :*: S1 ('MetaSel ('Just "simpleHeaderExt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ext')))) | |||||||||
type Rep (StorageConfig (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block type Rep (StorageConfig (SimpleBlock c ext)) = D1 ('MetaData "StorageConfig" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleStorageConfig" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SecurityParam))) | |||||||||
type Rep (Validated (GenTx (SimpleBlock c ext))) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
type Rep (GenTx (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block type Rep (GenTx (SimpleBlock c ext)) = D1 ('MetaData "GenTx" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleGenTx") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Tx) :*: S1 ('MetaSel ('Just "simpleGenTxId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxId))) | |||||||||
type Rep (TxId (GenTx (SimpleBlock c ext))) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block type Rep (TxId (GenTx (SimpleBlock c ext))) = D1 ('MetaData "TxId" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.26.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "SimpleGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSimpleGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxId))) | |||||||||
type BlockProtocol (SimplePraosRuleBlock c) Source # | |||||||||
type CannotForge (SimplePraosRuleBlock c) Source # | |||||||||
type ForgeStateInfo (SimplePraosRuleBlock c) Source # | |||||||||
type ForgeStateUpdateError (SimplePraosRuleBlock c) Source # | |||||||||
newtype Validated (GenTx (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block newtype Validated (GenTx (SimpleBlock c ext)) = ValidatedSimpleGenTx {
| |||||||||
type AuxLedgerEvent (LedgerState (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block type AuxLedgerEvent (LedgerState (SimpleBlock c ext)) = VoidLedgerEvent (LedgerState (SimpleBlock c ext)) | |||||||||
type LedgerCfg (LedgerState (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
type LedgerErr (LedgerState (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
newtype TxId (GenTx (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
type TxIn (LedgerState (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
type TxOut (LedgerState (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
type BlockNodeToClientVersion (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation | |||||||||
type BlockNodeToNodeVersion (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation | |||||||||
type Rep (LedgerState (SimpleBlock c ext) mk) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block type Rep (LedgerState (SimpleBlock c ext) mk) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleLedgerState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MockState (SimpleBlock c ext))) :*: S1 ('MetaSel ('Just "simpleLedgerTables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerTables (LedgerState (SimpleBlock c ext)) mk)))) | |||||||||
data BlockConfig (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
type BlockProtocol (SimpleBftBlock c c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT | |||||||||
type BlockProtocol (SimplePBftBlock c c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT | |||||||||
type BlockProtocol (SimplePraosBlock c c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos | |||||||||
data CodecConfig (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
data StorageConfig (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
type CannotForge (SimpleBftBlock c c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT | |||||||||
type CannotForge (SimplePBftBlock c c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT | |||||||||
type CannotForge (SimplePraosBlock c c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos | |||||||||
type ForgeStateInfo (SimpleBftBlock c c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT | |||||||||
type ForgeStateInfo (SimplePBftBlock c c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT | |||||||||
type ForgeStateInfo (SimplePraosBlock c c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos | |||||||||
type ForgeStateUpdateError (SimpleBftBlock c c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT | |||||||||
type ForgeStateUpdateError (SimplePBftBlock c c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT | |||||||||
type ForgeStateUpdateError (SimplePraosBlock c c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos | |||||||||
data NestedCtxt_ (SimpleBlock c ext) f a Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation data NestedCtxt_ (SimpleBlock c ext) f a where
| |||||||||
type TentativeHeaderState (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node type TentativeHeaderState (SimpleBlock c ext) = TentativeHeaderState (SelectViewDiffusionPipelining (SimpleBlock c ext)) | |||||||||
type TentativeHeaderView (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node type TentativeHeaderView (SimpleBlock c ext) = TentativeHeaderView (SelectViewDiffusionPipelining (SimpleBlock c ext)) | |||||||||
type HardForkIndices (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
type PartialLedgerConfig (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
type OtherHeaderEnvelopeError (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
type TipInfo (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
data LedgerState (SimpleBlock c ext) mk Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block data LedgerState (SimpleBlock c ext) mk = SimpleLedgerState {
| |||||||||
type LedgerUpdate (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
type LedgerWarning (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
data BlockQuery (SimpleBlock c ext) fp result Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block data BlockQuery (SimpleBlock c ext) fp result where
| |||||||||
type ApplyTxErr (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
data GenTx (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
type TxMeasure (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
type Signed (SimpleBftHeader c c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT | |||||||||
type Signed (SimplePBftHeader c c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT | |||||||||
type Signed (SimplePraosHeader c c') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos | |||||||||
newtype Ticked (LedgerState (SimpleBlock c ext) ∷ MapKind → Type) (mk ∷ MapKind) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block newtype Ticked (LedgerState (SimpleBlock c ext) ∷ MapKind → Type) (mk ∷ MapKind) = TickedSimpleLedgerState {
| |||||||||
type Rep (Ticked (LedgerState (SimpleBlock c ext)) mk) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block type Rep (Ticked (LedgerState (SimpleBlock c ext)) mk) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.26.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "TickedSimpleLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTickedSimpleLedgerState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerState (SimpleBlock c ext) mk)))) | |||||||||
type Rep (SimpleBlock' c ext ext') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block type Rep (SimpleBlock' c ext ext') = D1 ('MetaData "SimpleBlock'" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleBlock" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Header (SimpleBlock' c ext ext'))) :*: S1 ('MetaSel ('Just "simpleBody") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SimpleBody))) | |||||||||
data Header (SimpleBlock' c ext ext') Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block data Header (SimpleBlock' c ext ext') = SimpleHeader {
|
data SimpleBody Source #
Constructors
SimpleBody | |
Instances
ToCBOR SimpleBody Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods toCBOR ∷ SimpleBody → Encoding Source # encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy SimpleBody → Size Source # encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [SimpleBody] → Size Source # | |||||
Generic SimpleBody Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
| |||||
Show SimpleBody Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods showsPrec ∷ Int → SimpleBody → ShowS # show ∷ SimpleBody → String # showList ∷ [SimpleBody] → ShowS # | |||||
Eq SimpleBody Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||
HasMockTxs SimpleBody Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods getMockTxs ∷ SimpleBody → [Tx] Source # | |||||
Serialise SimpleBody Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods encode ∷ SimpleBody → Encoding Source # decode ∷ Decoder s SimpleBody Source # encodeList ∷ [SimpleBody] → Encoding Source # decodeList ∷ Decoder s [SimpleBody] Source # | |||||
type Rep SimpleBody Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block type Rep SimpleBody = D1 ('MetaData "SimpleBody" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleBody" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleTxs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tx]))) |
type family SimpleHash c Source #
Instances
type SimpleHash SimpleMockCrypto Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |
type SimpleHash SimpleStandardCrypto Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.Block |
type SimpleHeader c ext = Header (SimpleBlock c ext) Source #
data SimpleStdHeader c ext Source #
Constructors
SimpleStdHeader | |
Fields
|
Instances
Generic (SimpleStdHeader c ext) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods from ∷ SimpleStdHeader c ext → Rep (SimpleStdHeader c ext) x # to ∷ Rep (SimpleStdHeader c ext) x → SimpleStdHeader c ext # | |||||
(SimpleCrypto c, Typeable ext) ⇒ Show (SimpleStdHeader c ext) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods showsPrec ∷ Int → SimpleStdHeader c ext → ShowS # show ∷ SimpleStdHeader c ext → String # showList ∷ [SimpleStdHeader c ext] → ShowS # | |||||
(SimpleCrypto c, Typeable ext) ⇒ Eq (SimpleStdHeader c ext) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods (==) ∷ SimpleStdHeader c ext → SimpleStdHeader c ext → Bool # (/=) ∷ SimpleStdHeader c ext → SimpleStdHeader c ext → Bool # | |||||
(SimpleCrypto c, Typeable ext) ⇒ NoThunks (SimpleStdHeader c ext) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||
KnownNat (SizeHash (SimpleHash c)) ⇒ Serialise (SimpleStdHeader c ext) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods encode ∷ SimpleStdHeader c ext → Encoding Source # decode ∷ Decoder s (SimpleStdHeader c ext) Source # encodeList ∷ [SimpleStdHeader c ext] → Encoding Source # decodeList ∷ Decoder s [SimpleStdHeader c ext] Source # | |||||
type Rep (SimpleStdHeader c ext) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block type Rep (SimpleStdHeader c ext) = D1 ('MetaData "SimpleStdHeader" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleStdHeader" 'PrefixI 'True) ((S1 ('MetaSel ('Just "simplePrev") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ChainHash (SimpleBlock c ext))) :*: S1 ('MetaSel ('Just "simpleSlotNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SlotNo)) :*: (S1 ('MetaSel ('Just "simpleBlockNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockNo) :*: (S1 ('MetaSel ('Just "simpleBodyHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Hash (SimpleHash c) SimpleBody)) :*: S1 ('MetaSel ('Just "simpleBodySize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SizeInBytes))))) |
Working with SimpleBlock
countSimpleGenTxs ∷ SimpleBlock c ext → Word64 Source #
matchesSimpleHeader ∷ SimpleCrypto c ⇒ Header (SimpleBlock' c ext ext') → SimpleBlock' c ext ext'' → Bool Source #
Check whether the block matches the header
mkSimpleHeader ∷ SimpleCrypto c ⇒ (ext' → Encoding) → SimpleStdHeader c ext → ext' → Header (SimpleBlock' c ext ext') Source #
Create a header by hashing the header without hash and adding to the resulting value.
Configuration
data family BlockConfig blk Source #
Static configuration required to work with this type of blocks
Instances
Isomorphic BlockConfig | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary Methods project ∷ NoHardForks blk ⇒ BlockConfig (HardForkBlock '[blk]) → BlockConfig blk Source # inject ∷ NoHardForks blk ⇒ BlockConfig blk → BlockConfig (HardForkBlock '[blk]) Source # | |||||
Generic (BlockConfig (TestBlockWith ptype)) | |||||
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 (BlockConfig (SimpleBlock c ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods from ∷ BlockConfig (SimpleBlock c ext) → Rep (BlockConfig (SimpleBlock c ext)) x # to ∷ Rep (BlockConfig (SimpleBlock c ext)) x → BlockConfig (SimpleBlock c ext) # | |||||
Show (BlockConfig (TestBlockWith ptype)) | |||||
Defined in Test.Util.TestBlock Methods showsPrec ∷ Int → BlockConfig (TestBlockWith ptype) → ShowS # show ∷ BlockConfig (TestBlockWith ptype) → String # showList ∷ [BlockConfig (TestBlockWith ptype)] → ShowS # | |||||
CanHardFork xs ⇒ NoThunks (BlockConfig (HardForkBlock xs)) | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Methods noThunks ∷ Context → BlockConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → BlockConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (BlockConfig (HardForkBlock xs)) → String Source # | |||||
NoThunks (BlockConfig (DualBlock m a)) | |||||
NoThunks (BlockConfig (TestBlockWith ptype)) | |||||
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 (BlockConfig (SimpleBlock c ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods noThunks ∷ Context → BlockConfig (SimpleBlock c ext) → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → BlockConfig (SimpleBlock c ext) → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (BlockConfig (SimpleBlock c ext)) → String Source # | |||||
type Rep (BlockConfig (TestBlockWith ptype)) | |||||
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 (BlockConfig (SimpleBlock c ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||
newtype BlockConfig (DisableDiffusionPipelining blk) | |||||
Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining newtype BlockConfig (DisableDiffusionPipelining blk) = DisableDiffusionPipeliningBlockConfig (BlockConfig blk) | |||||
newtype BlockConfig (SelectViewDiffusionPipelining blk) | |||||
Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining newtype BlockConfig (SelectViewDiffusionPipelining blk) = SelectViewDiffusionPipeliningBlockConfig (BlockConfig blk) | |||||
newtype BlockConfig (HardForkBlock xs) | |||||
data BlockConfig (TestBlockWith ptype) | |||||
Defined in Test.Util.TestBlock | |||||
data BlockConfig (DualBlock m a) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||
data BlockConfig (SimpleBlock c ext) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block |
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) | |||||
Defined in Test.Util.TestBlock Associated Types
Methods from ∷ CodecConfig TestBlock → Rep (CodecConfig TestBlock) x # to ∷ Rep (CodecConfig TestBlock) x → CodecConfig TestBlock # | |||||
Generic (CodecConfig (SimpleBlock c ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods from ∷ CodecConfig (SimpleBlock c ext) → Rep (CodecConfig (SimpleBlock c ext)) x # to ∷ Rep (CodecConfig (SimpleBlock c ext)) x → CodecConfig (SimpleBlock c ext) # | |||||
Show (CodecConfig TestBlock) | |||||
Defined in Test.Util.TestBlock | |||||
CanHardFork xs ⇒ NoThunks (CodecConfig (HardForkBlock xs)) | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Methods noThunks ∷ Context → CodecConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → CodecConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (CodecConfig (HardForkBlock xs)) → String Source # | |||||
(NoThunks (CodecConfig m), NoThunks (CodecConfig a)) ⇒ NoThunks (CodecConfig (DualBlock m a)) | |||||
NoThunks (CodecConfig TestBlock) | |||||
NoThunks (CodecConfig (SimpleBlock c ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods noThunks ∷ Context → CodecConfig (SimpleBlock c ext) → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → CodecConfig (SimpleBlock c ext) → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (CodecConfig (SimpleBlock c ext)) → String Source # | |||||
data CodecConfig TestBlock | The | ||||
Defined in Test.Util.TestBlock | |||||
type Rep (CodecConfig (DualBlock m a)) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual type Rep (CodecConfig (DualBlock m a)) = D1 ('MetaData "CodecConfig" "Ouroboros.Consensus.Ledger.Dual" "ouroboros-consensus-0.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) | |||||
type Rep (CodecConfig (SimpleBlock c ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||
newtype CodecConfig (HardForkBlock xs) | |||||
data CodecConfig (DualBlock m a) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual data CodecConfig (DualBlock m a) = DualCodecConfig {
| |||||
data CodecConfig (SimpleBlock c ext) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block |
data SimpleLedgerConfig c ext Source #
Constructors
SimpleLedgerConfig | |
Fields
|
Instances
Generic (SimpleLedgerConfig c ext) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods from ∷ SimpleLedgerConfig c ext → Rep (SimpleLedgerConfig c ext) x # to ∷ Rep (SimpleLedgerConfig c ext) x → SimpleLedgerConfig c ext # | |||||
Show (MockLedgerConfig c ext) ⇒ Show (SimpleLedgerConfig c ext) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods showsPrec ∷ Int → SimpleLedgerConfig c ext → ShowS # show ∷ SimpleLedgerConfig c ext → String # showList ∷ [SimpleLedgerConfig c ext] → ShowS # | |||||
Eq (MockLedgerConfig c ext) ⇒ Eq (SimpleLedgerConfig c ext) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods (==) ∷ SimpleLedgerConfig c ext → SimpleLedgerConfig c ext → Bool # (/=) ∷ SimpleLedgerConfig c ext → SimpleLedgerConfig c ext → Bool # | |||||
NoThunks (MockLedgerConfig c ext) ⇒ NoThunks (SimpleLedgerConfig c ext) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||
Serialise (MockLedgerConfig c ext) ⇒ Serialise (SimpleLedgerConfig c ext) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods encode ∷ SimpleLedgerConfig c ext → Encoding Source # decode ∷ Decoder s (SimpleLedgerConfig c ext) Source # encodeList ∷ [SimpleLedgerConfig c ext] → Encoding Source # decodeList ∷ Decoder s [SimpleLedgerConfig c ext] Source # | |||||
Serialise (MockLedgerConfig c ext) ⇒ SerialiseNodeToClient (SimpleBlock c ext) (SimpleLedgerConfig c ext) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods encodeNodeToClient ∷ CodecConfig (SimpleBlock c ext) → BlockNodeToClientVersion (SimpleBlock c ext) → SimpleLedgerConfig c ext → Encoding Source # decodeNodeToClient ∷ CodecConfig (SimpleBlock c ext) → BlockNodeToClientVersion (SimpleBlock c ext) → ∀ s. Decoder s (SimpleLedgerConfig c ext) Source # | |||||
type Rep (SimpleLedgerConfig c ext) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block type Rep (SimpleLedgerConfig c ext) = D1 ('MetaData "SimpleLedgerConfig" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleLedgerConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleMockLedgerConfig") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (MockLedgerConfig c ext)) :*: (S1 ('MetaSel ('Just "simpleLedgerEraParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EraParams) :*: S1 ('MetaSel ('Just "simpleLedgerMockConfig") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MockConfig)))) |
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) | |||||
Defined in Test.Util.TestBlock Associated Types
Methods from ∷ StorageConfig TestBlock → Rep (StorageConfig TestBlock) x # to ∷ Rep (StorageConfig TestBlock) x → StorageConfig TestBlock # | |||||
Generic (StorageConfig (SimpleBlock c ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods from ∷ StorageConfig (SimpleBlock c ext) → Rep (StorageConfig (SimpleBlock c ext)) x # to ∷ Rep (StorageConfig (SimpleBlock c ext)) x → StorageConfig (SimpleBlock c ext) # | |||||
Show (StorageConfig TestBlock) | |||||
Defined in Test.Util.TestBlock | |||||
CanHardFork xs ⇒ NoThunks (StorageConfig (HardForkBlock xs)) | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Basics Methods noThunks ∷ Context → StorageConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → StorageConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (StorageConfig (HardForkBlock xs)) → String Source # | |||||
(NoThunks (StorageConfig m), NoThunks (StorageConfig a)) ⇒ NoThunks (StorageConfig (DualBlock m a)) | |||||
NoThunks (StorageConfig TestBlock) | |||||
NoThunks (StorageConfig (SimpleBlock c ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods noThunks ∷ Context → StorageConfig (SimpleBlock c ext) → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → StorageConfig (SimpleBlock c ext) → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (StorageConfig (SimpleBlock c ext)) → String Source # | |||||
data StorageConfig TestBlock | The | ||||
Defined in Test.Util.TestBlock | |||||
type Rep (StorageConfig (DualBlock m a)) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual type Rep (StorageConfig (DualBlock m a)) = D1 ('MetaData "StorageConfig" "Ouroboros.Consensus.Ledger.Dual" "ouroboros-consensus-0.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) | |||||
type Rep (StorageConfig (SimpleBlock c ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block type Rep (StorageConfig (SimpleBlock c ext)) = D1 ('MetaData "StorageConfig" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleStorageConfig" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SecurityParam))) | |||||
newtype StorageConfig (HardForkBlock xs) | |||||
data StorageConfig (DualBlock m a) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||
data StorageConfig (SimpleBlock c ext) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block |
Protocol-specific part
class (SimpleCrypto c, Typeable ext, Show (MockLedgerConfig c ext), NoThunks (MockLedgerConfig c ext), Serialise (MockLedgerConfig c ext)) ⇒ MockProtocolSpecific c ext Source #
Associated Types
type MockLedgerConfig c ext Source #
Instances
SimpleCrypto c ⇒ MockProtocolSpecific c SimplePraosRuleExt Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule Associated Types
| |||||
(SimpleCrypto c, Typeable c') ⇒ MockProtocolSpecific c (SimpleBftExt c c') Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT Associated Types
| |||||
(SimpleCrypto c, PBftCrypto c', Serialise (PBftVerKeyHash c')) ⇒ MockProtocolSpecific c (SimplePBftExt c c') Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT Associated Types
| |||||
(SimpleCrypto c, Typeable c') ⇒ MockProtocolSpecific c (SimplePraosExt c c') Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos Associated Types
|
UpdateLedger
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)) | |||||||||
Defined in Test.Util.TestBlock Methods getTip ∷ ∀ (mk ∷ MapKind). LedgerState (TestBlockWith ptype) mk → Point (LedgerState (TestBlockWith ptype)) Source # | |||||||||
GetTip (LedgerState (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods getTip ∷ ∀ (mk ∷ MapKind). LedgerState (SimpleBlock c ext) mk → Point (LedgerState (SimpleBlock c ext)) 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)) | |||||||||
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 # | |||||||||
MockProtocolSpecific c ext ⇒ IsLedger (LedgerState (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods applyChainTickLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (LedgerState (SimpleBlock c ext)) → SlotNo → LedgerState (SimpleBlock c ext) EmptyMK → LedgerResult (LedgerState (SimpleBlock c ext)) (Ticked (LedgerState (SimpleBlock c ext)) 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) | |||||||||
CanStowLedgerTables (LedgerState (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods stowLedgerTables ∷ LedgerState (SimpleBlock c ext) ValuesMK → LedgerState (SimpleBlock c ext) EmptyMK Source # unstowLedgerTables ∷ LedgerState (SimpleBlock c ext) EmptyMK → LedgerState (SimpleBlock c ext) 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 (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) | |||||||||
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 # | |||||||||
HasLedgerTables (LedgerState (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerState (SimpleBlock c ext) mk → LedgerTables (LedgerState (SimpleBlock c ext)) mk Source # withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerState (SimpleBlock c ext) any → LedgerTables (LedgerState (SimpleBlock c ext)) mk → LedgerState (SimpleBlock c ext) mk Source # | |||||||||
LedgerTablesAreTrivial (LedgerState TestBlock) | |||||||||
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 # | |||||||||
(Ord k, MemPack k, MemPack v) ⇒ SerializeTablesWithHint (LedgerState (OTBlock k v)) | |||||||||
Defined in Test.Util.LedgerStateOnlyTables Methods encodeTablesWithHint ∷ SerializeTablesHint (LedgerTables (LedgerState (OTBlock k v)) ValuesMK) → LedgerTables (LedgerState (OTBlock k v)) ValuesMK → Encoding Source # decodeTablesWithHint ∷ SerializeTablesHint (LedgerTables (LedgerState (OTBlock k v)) ValuesMK) → Decoder s (LedgerTables (LedgerState (OTBlock k v)) ValuesMK) Source # | |||||||||
SerializeTablesWithHint (LedgerState TestBlock) | |||||||||
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 # | |||||||||
SerializeTablesWithHint (LedgerState (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods encodeTablesWithHint ∷ SerializeTablesHint (LedgerTables (LedgerState (SimpleBlock c ext)) ValuesMK) → LedgerTables (LedgerState (SimpleBlock c ext)) ValuesMK → Encoding Source # decodeTablesWithHint ∷ SerializeTablesHint (LedgerTables (LedgerState (SimpleBlock c ext)) ValuesMK) → Decoder s (LedgerTables (LedgerState (SimpleBlock c ext)) 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 (OTBlock k v)) | |||||||||
Defined in Test.Util.LedgerStateOnlyTables Methods upgradeTables ∷ ∀ (mk1 ∷ MapKind) (mk2 ∷ MapKind). LedgerState (OTBlock k v) mk1 → LedgerState (OTBlock k v) mk2 → LedgerTables (LedgerState (OTBlock k v)) ValuesMK → LedgerTables (LedgerState (OTBlock k v)) ValuesMK Source # | |||||||||
CanUpgradeLedgerTables (LedgerState TestBlock) | |||||||||
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 # | |||||||||
CanUpgradeLedgerTables (LedgerState (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods upgradeTables ∷ ∀ (mk1 ∷ MapKind) (mk2 ∷ MapKind). LedgerState (SimpleBlock c ext) mk1 → LedgerState (SimpleBlock c ext) mk2 → LedgerTables (LedgerState (SimpleBlock c ext)) ValuesMK → LedgerTables (LedgerState (SimpleBlock c ext)) ValuesMK Source # | |||||||||
PayloadSemantics ptype ⇒ ApplyBlock (LedgerState (TestBlockWith ptype)) (TestBlockWith ptype) | |||||||||
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 # | |||||||||
MockProtocolSpecific c ext ⇒ ApplyBlock (LedgerState (SimpleBlock c ext)) (SimpleBlock c ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods applyBlockLedgerResultWithValidation ∷ ValidationPolicy → ComputeLedgerEvents → LedgerCfg (LedgerState (SimpleBlock c ext)) → SimpleBlock c ext → Ticked (LedgerState (SimpleBlock c ext)) ValuesMK → Except (LedgerErr (LedgerState (SimpleBlock c ext))) (LedgerResult (LedgerState (SimpleBlock c ext)) (LedgerState (SimpleBlock c ext) DiffMK)) Source # applyBlockLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (LedgerState (SimpleBlock c ext)) → SimpleBlock c ext → Ticked (LedgerState (SimpleBlock c ext)) ValuesMK → Except (LedgerErr (LedgerState (SimpleBlock c ext))) (LedgerResult (LedgerState (SimpleBlock c ext)) (LedgerState (SimpleBlock c ext) DiffMK)) Source # reapplyBlockLedgerResult ∷ ComputeLedgerEvents → LedgerCfg (LedgerState (SimpleBlock c ext)) → SimpleBlock c ext → Ticked (LedgerState (SimpleBlock c ext)) ValuesMK → LedgerResult (LedgerState (SimpleBlock c ext)) (LedgerState (SimpleBlock c ext) DiffMK) Source # getBlockKeySets ∷ SimpleBlock c ext → LedgerTables (LedgerState (SimpleBlock c ext)) KeysMK Source # | |||||||||
PayloadSemantics ptype ⇒ DecodeDisk (TestBlockWith ptype) (LedgerState (TestBlockWith ptype) EmptyMK) | |||||||||
Defined in Test.Util.TestBlock Methods decodeDisk ∷ CodecConfig (TestBlockWith ptype) → ∀ s. Decoder s (LedgerState (TestBlockWith ptype) EmptyMK) Source # | |||||||||
DecodeDisk (MockBlock ext) (LedgerState (MockBlock ext) EmptyMK) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods decodeDisk ∷ CodecConfig (MockBlock ext) → ∀ s. Decoder s (LedgerState (MockBlock ext) EmptyMK) Source # | |||||||||
PayloadSemantics ptype ⇒ EncodeDisk (TestBlockWith ptype) (LedgerState (TestBlockWith ptype) EmptyMK) | |||||||||
Defined in Test.Util.TestBlock Methods encodeDisk ∷ CodecConfig (TestBlockWith ptype) → LedgerState (TestBlockWith ptype) EmptyMK → Encoding Source # | |||||||||
EncodeDisk (MockBlock ext) (LedgerState (MockBlock ext) EmptyMK) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeDisk ∷ CodecConfig (MockBlock ext) → LedgerState (MockBlock ext) EmptyMK → Encoding Source # | |||||||||
Generic (LedgerState (OTBlock k v) mk) | |||||||||
Defined in Test.Util.LedgerStateOnlyTables Associated Types
Methods from ∷ LedgerState (OTBlock k v) mk → Rep (LedgerState (OTBlock k v) mk) x # to ∷ Rep (LedgerState (OTBlock k v) mk) x → LedgerState (OTBlock k v) mk # | |||||||||
Generic (LedgerState (TestBlockWith ptype) mk) | |||||||||
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 # | |||||||||
Generic (LedgerState (SimpleBlock c ext) mk) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods from ∷ LedgerState (SimpleBlock c ext) mk → Rep (LedgerState (SimpleBlock c ext) mk) x # to ∷ Rep (LedgerState (SimpleBlock c ext) mk) x → LedgerState (SimpleBlock c ext) 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) | |||||||||
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 # | |||||||||
(SimpleCrypto c, Typeable ext, Show (mk TxIn TxOut)) ⇒ Show (LedgerState (SimpleBlock c ext) mk) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods showsPrec ∷ Int → LedgerState (SimpleBlock c ext) mk → ShowS # show ∷ LedgerState (SimpleBlock c ext) mk → String # showList ∷ [LedgerState (SimpleBlock c ext) 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) | |||||||||
Defined in Test.Util.TestBlock Methods (==) ∷ LedgerState (TestBlockWith ptype) mk → LedgerState (TestBlockWith ptype) mk → Bool # (/=) ∷ LedgerState (TestBlockWith ptype) mk → LedgerState (TestBlockWith ptype) mk → Bool # | |||||||||
(SimpleCrypto c, Typeable ext, Eq (mk TxIn TxOut)) ⇒ Eq (LedgerState (SimpleBlock c ext) mk) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods (==) ∷ LedgerState (SimpleBlock c ext) mk → LedgerState (SimpleBlock c ext) mk → Bool # (/=) ∷ LedgerState (SimpleBlock c ext) mk → LedgerState (SimpleBlock c ext) 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) | |||||||||
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 # | |||||||||
(SimpleCrypto c, Typeable ext, NoThunks (mk TxIn TxOut)) ⇒ NoThunks (LedgerState (SimpleBlock c ext) mk) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods noThunks ∷ Context → LedgerState (SimpleBlock c ext) mk → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → LedgerState (SimpleBlock c ext) mk → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (LedgerState (SimpleBlock c ext) mk) → String Source # | |||||||||
Bridge m a ⇒ GetTip (Ticked (LedgerState (DualBlock m a))) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
GetTip (Ticked (LedgerState (TestBlockWith ptype))) | |||||||||
Defined in Test.Util.TestBlock Methods getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (TestBlockWith ptype)) mk → Point (Ticked (LedgerState (TestBlockWith ptype))) Source # | |||||||||
GetTip (Ticked (LedgerState (SimpleBlock c ext))) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (SimpleBlock c ext)) mk → Point (Ticked (LedgerState (SimpleBlock c ext))) Source # | |||||||||
CanStowLedgerTables (Ticked (LedgerState (SimpleBlock c ext))) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods stowLedgerTables ∷ Ticked (LedgerState (SimpleBlock c ext)) ValuesMK → Ticked (LedgerState (SimpleBlock c ext)) EmptyMK Source # unstowLedgerTables ∷ Ticked (LedgerState (SimpleBlock c ext)) EmptyMK → Ticked (LedgerState (SimpleBlock c ext)) ValuesMK Source # | |||||||||
(Ord k, Eq v, MemPack k, MemPack v) ⇒ CanStowLedgerTables (OTLedgerState k v) | |||||||||
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)) | |||||||||
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 (SimpleBlock c ext))) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (SimpleBlock c ext)) mk → LedgerTables (Ticked (LedgerState (SimpleBlock c ext))) mk Source # withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (SimpleBlock c ext)) any → LedgerTables (Ticked (LedgerState (SimpleBlock c ext))) mk → Ticked (LedgerState (SimpleBlock c ext)) mk Source # | |||||||||
(Ord k, Eq v, Show k, Show v, MemPack k, MemPack v, NoThunks k, NoThunks v) ⇒ HasLedgerTables (OTLedgerState k v) | |||||||||
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)) | |||||||||
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) | |||||||||
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 # | |||||||||
MemPack v ⇒ IndexedMemPack (LedgerState (OTBlock k v) EmptyMK) v | |||||||||
Defined in Test.Util.LedgerStateOnlyTables Methods indexedPackedByteCount ∷ LedgerState (OTBlock k v) EmptyMK → v → Int Source # indexedPackM ∷ LedgerState (OTBlock k v) EmptyMK → v → Pack s () Source # indexedUnpackM ∷ Buffer b ⇒ LedgerState (OTBlock k v) EmptyMK → Unpack b v Source # indexedTypeName ∷ LedgerState (OTBlock k v) EmptyMK → String Source # | |||||||||
IndexedMemPack (LedgerState TestBlock EmptyMK) Void | |||||||||
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 # | |||||||||
IndexedMemPack (LedgerState (SimpleBlock c ext) EmptyMK) TxOut Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods indexedPackedByteCount ∷ LedgerState (SimpleBlock c ext) EmptyMK → TxOut → Int Source # indexedPackM ∷ LedgerState (SimpleBlock c ext) EmptyMK → TxOut → Pack s () Source # indexedUnpackM ∷ Buffer b ⇒ LedgerState (SimpleBlock c ext) EmptyMK → Unpack b TxOut Source # indexedTypeName ∷ LedgerState (SimpleBlock c ext) EmptyMK → String Source # | |||||||||
StandardHash blk ⇒ StandardHash (LedgerState blk ∷ MapKind → Type) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Basics | |||||||||
Generic (Ticked (LedgerState (TestBlockWith ptype)) mk) | |||||||||
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 # | |||||||||
Generic (Ticked (LedgerState (SimpleBlock c ext)) mk) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods from ∷ Ticked (LedgerState (SimpleBlock c ext)) mk → Rep (Ticked (LedgerState (SimpleBlock c ext)) mk) x # to ∷ Rep (Ticked (LedgerState (SimpleBlock c ext)) mk) x → Ticked (LedgerState (SimpleBlock c ext)) mk # | |||||||||
(SimpleCrypto c, Typeable ext, Show (LedgerState (SimpleBlock c ext) mk)) ⇒ Show (Ticked (LedgerState (SimpleBlock c ext)) mk) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods showsPrec ∷ Int → Ticked (LedgerState (SimpleBlock c ext)) mk → ShowS # show ∷ Ticked (LedgerState (SimpleBlock c ext)) mk → String # showList ∷ [Ticked (LedgerState (SimpleBlock c ext)) mk] → ShowS # | |||||||||
(Show k, Show v, Show (mk k v)) ⇒ Show (OTLedgerState k v mk) | |||||||||
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) | |||||||||
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) | |||||||||
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 # | |||||||||
(SimpleCrypto c, Typeable ext) ⇒ NoThunks (Ticked (LedgerState (SimpleBlock c ext)) TrackingMK) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods noThunks ∷ Context → Ticked (LedgerState (SimpleBlock c ext)) TrackingMK → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → Ticked (LedgerState (SimpleBlock c ext)) TrackingMK → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (Ticked (LedgerState (SimpleBlock c ext)) TrackingMK) → String Source # | |||||||||
(NoThunks k, NoThunks v, NoThunks (mk k v)) ⇒ NoThunks (OTLedgerState k v mk) | |||||||||
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)) | |||||||||
Defined in Test.Util.TestBlock type AuxLedgerEvent (LedgerState (TestBlockWith ptype)) = VoidLedgerEvent (LedgerState (TestBlockWith ptype)) | |||||||||
type AuxLedgerEvent (LedgerState (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block type AuxLedgerEvent (LedgerState (SimpleBlock c ext)) = VoidLedgerEvent (LedgerState (SimpleBlock c ext)) | |||||||||
type LedgerCfg (LedgerState (HardForkBlock xs)) | |||||||||
type LedgerCfg (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
type LedgerCfg (LedgerState (TestBlockWith ptype)) | |||||||||
Defined in Test.Util.TestBlock | |||||||||
type LedgerCfg (LedgerState (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
type LedgerErr (LedgerState (HardForkBlock xs)) | |||||||||
type LedgerErr (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
type LedgerErr (LedgerState (TestBlockWith ptype)) | |||||||||
Defined in Test.Util.TestBlock | |||||||||
type LedgerErr (LedgerState (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
newtype LedgerState (HardForkBlock xs) mk | |||||||||
data LedgerState (TestBlockWith ptype) mk | |||||||||
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) | |||||||||
Defined in Test.Util.TestBlock | |||||||||
type TxIn (LedgerState (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
type TxOut (LedgerState (HardForkBlock xs)) | Must be the | ||||||||
type TxOut (LedgerState (DualBlock m a)) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
type TxOut (LedgerState TestBlock) | |||||||||
Defined in Test.Util.TestBlock | |||||||||
type TxOut (LedgerState (SimpleBlock c ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
type Rep (LedgerState (OTBlock k v) mk) | |||||||||
Defined in Test.Util.LedgerStateOnlyTables type Rep (LedgerState (OTBlock k v) mk) = D1 ('MetaData "LedgerState" "Test.Util.LedgerStateOnlyTables" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "OTLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "otlsLedgerState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ValuesMK k v)) :*: S1 ('MetaSel ('Just "otlsLedgerTables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OTLedgerTables k v mk)))) | |||||||||
type Rep (LedgerState (TestBlockWith ptype) mk) | |||||||||
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)))) | |||||||||
type Rep (LedgerState (SimpleBlock c ext) mk) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block type Rep (LedgerState (SimpleBlock c ext) mk) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleLedgerState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MockState (SimpleBlock c ext))) :*: S1 ('MetaSel ('Just "simpleLedgerTables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerTables (LedgerState (SimpleBlock c ext)) mk)))) | |||||||||
data LedgerState (DualBlock m a) mk | |||||||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||||||
data LedgerState (OTBlock k v) mk | |||||||||
Defined in Test.Util.LedgerStateOnlyTables data LedgerState (OTBlock k v) mk = OTLedgerState {
| |||||||||
data LedgerState (SimpleBlock c ext) mk Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block data LedgerState (SimpleBlock c ext) mk = SimpleLedgerState {
| |||||||||
type TxIn (OTLedgerState k v) | |||||||||
Defined in Test.Util.LedgerStateOnlyTables | |||||||||
type TxOut (OTLedgerState k v) | |||||||||
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) | |||||||||
Defined in Test.Util.TestBlock newtype Ticked (LedgerState (TestBlockWith ptype) ∷ MapKind → Type) (mk ∷ MapKind) = TickedTestLedger {
| |||||||||
newtype Ticked (LedgerState (SimpleBlock c ext) ∷ MapKind → Type) (mk ∷ MapKind) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block newtype Ticked (LedgerState (SimpleBlock c ext) ∷ MapKind → Type) (mk ∷ MapKind) = TickedSimpleLedgerState {
| |||||||||
type HeaderHash (LedgerState blk ∷ MapKind → Type) | |||||||||
Defined in Ouroboros.Consensus.Ledger.Basics | |||||||||
type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) | |||||||||
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)))) | |||||||||
type Rep (Ticked (LedgerState (SimpleBlock c ext)) mk) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block type Rep (Ticked (LedgerState (SimpleBlock c ext)) mk) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.26.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "TickedSimpleLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTickedSimpleLedgerState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerState (SimpleBlock c ext) mk)))) |
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 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))) | |||||
Defined in Test.Util.TestBlock Methods getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (TestBlockWith ptype)) mk → Point (Ticked (LedgerState (TestBlockWith ptype))) Source # | |||||
GetTip (Ticked (LedgerState (SimpleBlock c ext))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (SimpleBlock c ext)) mk → Point (Ticked (LedgerState (SimpleBlock c ext))) 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 # | |||||
CanStowLedgerTables (Ticked (LedgerState (SimpleBlock c ext))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods stowLedgerTables ∷ Ticked (LedgerState (SimpleBlock c ext)) ValuesMK → Ticked (LedgerState (SimpleBlock c ext)) EmptyMK Source # unstowLedgerTables ∷ Ticked (LedgerState (SimpleBlock c ext)) EmptyMK → Ticked (LedgerState (SimpleBlock c ext)) 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)) | |||||
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 (SimpleBlock c ext))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (SimpleBlock c ext)) mk → LedgerTables (Ticked (LedgerState (SimpleBlock c ext))) mk Source # withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (SimpleBlock c ext)) any → LedgerTables (Ticked (LedgerState (SimpleBlock c ext))) mk → Ticked (LedgerState (SimpleBlock c ext)) 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)) | |||||
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) | |||||
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 # | |||||
Generic (Ticked (LedgerState (SimpleBlock c ext)) mk) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods from ∷ Ticked (LedgerState (SimpleBlock c ext)) mk → Rep (Ticked (LedgerState (SimpleBlock c ext)) mk) x # to ∷ Rep (Ticked (LedgerState (SimpleBlock c ext)) mk) x → Ticked (LedgerState (SimpleBlock c ext)) mk # | |||||
(SimpleCrypto c, Typeable ext, Show (LedgerState (SimpleBlock c ext) mk)) ⇒ Show (Ticked (LedgerState (SimpleBlock c ext)) mk) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods showsPrec ∷ Int → Ticked (LedgerState (SimpleBlock c ext)) mk → ShowS # show ∷ Ticked (LedgerState (SimpleBlock c ext)) mk → String # showList ∷ [Ticked (LedgerState (SimpleBlock c ext)) mk] → ShowS # | |||||
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) | |||||
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 # | |||||
(SimpleCrypto c, Typeable ext) ⇒ NoThunks (Ticked (LedgerState (SimpleBlock c ext)) TrackingMK) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods noThunks ∷ Context → Ticked (LedgerState (SimpleBlock c ext)) TrackingMK → IO (Maybe ThunkInfo) Source # wNoThunks ∷ Context → Ticked (LedgerState (SimpleBlock c ext)) TrackingMK → IO (Maybe ThunkInfo) Source # showTypeOf ∷ Proxy (Ticked (LedgerState (SimpleBlock c ext)) TrackingMK) → 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 | |||||
data Ticked (PraosChainDepState c ∷ Type) Source # | Ticking the Praos chain dep state has no effect For the real Praos implementation, ticking is crucial, as it determines the point where the "nonce under construction" is swapped out for the "active" nonce. However, for the mock implementation, we keep the full history, and choose the right nonce from that; this means that ticking has no effect. We do however need access to the ticked stake distribution. | ||||
Defined in Ouroboros.Consensus.Mock.Protocol.Praos | |||||
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) | |||||
Defined in Test.Util.TestBlock newtype Ticked (LedgerState (TestBlockWith ptype) ∷ MapKind → Type) (mk ∷ MapKind) = TickedTestLedger {
| |||||
newtype Ticked (LedgerState (SimpleBlock c ext) ∷ MapKind → Type) (mk ∷ MapKind) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block newtype Ticked (LedgerState (SimpleBlock c ext) ∷ MapKind → Type) (mk ∷ MapKind) = TickedSimpleLedgerState {
| |||||
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) | |||||
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)))) | |||||
type Rep (Ticked (LedgerState (SimpleBlock c ext)) mk) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block type Rep (Ticked (LedgerState (SimpleBlock c ext)) mk) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.26.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "TickedSimpleLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTickedSimpleLedgerState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerState (SimpleBlock c ext) mk)))) |
genesisSimpleLedgerState ∷ AddrDist → LedgerState (SimpleBlock c ext) ValuesMK Source #
updateSimpleLedgerState ∷ ∀ c ext (mk1 ∷ MapKind). (SimpleCrypto c, Typeable ext) ⇒ LedgerConfig (SimpleBlock c ext) → SimpleBlock c ext → TickedLedgerState (SimpleBlock c ext) mk1 → Except (MockError (SimpleBlock c ext)) (LedgerState (SimpleBlock c ext) mk1) Source #
ApplyTx
(mempool support)
data family GenTx blk Source #
Generalized transaction
The mempool (and, accordingly, blocks) consist of "generalized transactions"; this could be "proper" transactions (transferring funds) but also other kinds of things such as update proposals, delegations, etc.
Instances
Inject GenTx | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Nary Methods inject ∷ ∀ x (xs ∷ [Type]). (CanHardFork xs, HasCanonicalTxIn xs, HasHardForkTxOut xs) ⇒ InjectionIndex xs x → GenTx x → GenTx (HardForkBlock xs) Source # | |||||
Isomorphic GenTx | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary Methods project ∷ NoHardForks blk ⇒ GenTx (HardForkBlock '[blk]) → GenTx blk Source # inject ∷ NoHardForks blk ⇒ GenTx blk → GenTx (HardForkBlock '[blk]) Source # | |||||
(Typeable m, Typeable a) ⇒ ShowProxy (GenTx (DualBlock m a) ∷ Type) | |||||
(Typeable c, Typeable ext) ⇒ ShowProxy (GenTx (SimpleBlock c ext) ∷ Type) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||
(Typeable m, Typeable a) ⇒ ShowProxy (TxId (GenTx (DualBlock m a)) ∷ Type) | |||||
(Typeable c, Typeable ext) ⇒ ShowProxy (TxId (GenTx (SimpleBlock c ext)) ∷ Type) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||
Generic (Validated (GenTx (SimpleBlock c ext))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods from ∷ Validated (GenTx (SimpleBlock c ext)) → Rep (Validated (GenTx (SimpleBlock c ext))) x # to ∷ Rep (Validated (GenTx (SimpleBlock c ext))) x → Validated (GenTx (SimpleBlock c ext)) # | |||||
Generic (GenTx (SimpleBlock c ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods from ∷ GenTx (SimpleBlock c ext) → Rep (GenTx (SimpleBlock c ext)) x # to ∷ Rep (GenTx (SimpleBlock c ext)) x → GenTx (SimpleBlock c ext) # | |||||
Generic (TxId (GenTx (SimpleBlock c ext))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods from ∷ TxId (GenTx (SimpleBlock c ext)) → Rep (TxId (GenTx (SimpleBlock c ext))) x # to ∷ Rep (TxId (GenTx (SimpleBlock c ext))) x → TxId (GenTx (SimpleBlock c ext)) # | |||||
Bridge m a ⇒ Show (Validated (GenTx (DualBlock m a))) | |||||
Show (Validated (GenTx (SimpleBlock p c))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||
Bridge m a ⇒ Show (GenTx (DualBlock m a)) | |||||
Show (GenTx (SimpleBlock p c)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||
Show (GenTxId m) ⇒ Show (TxId (GenTx (DualBlock m a))) | |||||
Show (TxId (GenTx (SimpleBlock c ext))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||
Eq (Validated (GenTx (SimpleBlock c ext))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods (==) ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Bool # (/=) ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Bool # | |||||
Eq (GenTx (SimpleBlock c ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods (==) ∷ GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) → Bool # (/=) ∷ GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) → Bool # | |||||
Eq (GenTxId m) ⇒ Eq (TxId (GenTx (DualBlock m a))) | |||||
Eq (TxId (GenTx (SimpleBlock c ext))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods (==) ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → Bool # (/=) ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → Bool # | |||||
Ord (Validated (GenTx (SimpleBlock c ext))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods compare ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Ordering # (<) ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Bool # (<=) ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Bool # (>) ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Bool # (>=) ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Bool # max ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) # min ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) # | |||||
Ord (GenTx (SimpleBlock c ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods compare ∷ GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) → Ordering # (<) ∷ GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) → Bool # (<=) ∷ GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) → Bool # (>) ∷ GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) → Bool # (>=) ∷ GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) → Bool # max ∷ GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) # min ∷ GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) # | |||||
Ord (GenTxId m) ⇒ Ord (TxId (GenTx (DualBlock m a))) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods compare ∷ TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Ordering # (<) ∷ TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool # (<=) ∷ TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool # (>) ∷ TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool # (>=) ∷ TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool # max ∷ TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) # min ∷ TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) # | |||||
Ord (TxId (GenTx (SimpleBlock c ext))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods compare ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → Ordering # (<) ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → Bool # (<=) ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → Bool # (>) ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → Bool # (>=) ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → Bool # max ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) # min ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) # | |||||
NoThunks (Validated (GenTx (DualBlock m a))) | |||||
(Typeable p, Typeable c) ⇒ NoThunks (Validated (GenTx (SimpleBlock p c))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||
NoThunks (GenTx (DualBlock m a)) | |||||
(Typeable p, Typeable c) ⇒ NoThunks (GenTx (SimpleBlock p c)) Source # | |||||
NoThunks (TxId (GenTx (DualBlock m a))) | |||||
NoThunks (TxId (GenTx (SimpleBlock c ext))) Source # | |||||
Bridge m a ⇒ HasTxId (GenTx (DualBlock m a)) | |||||
HasTxId (GenTx (SimpleBlock c ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods txId ∷ GenTx (SimpleBlock c ext) → TxId (GenTx (SimpleBlock c ext)) Source # | |||||
Condense (GenTx (SimpleBlock p c)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||
Condense (GenTxId (SimpleBlock p c)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||
HasMockTxs (GenTx (SimpleBlock p c)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods getMockTxs ∷ GenTx (SimpleBlock p c) → [Tx] Source # | |||||
Serialise (GenTx (SimpleBlock c ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods encode ∷ GenTx (SimpleBlock c ext) → Encoding Source # decode ∷ Decoder s (GenTx (SimpleBlock c ext)) Source # encodeList ∷ [GenTx (SimpleBlock c ext)] → Encoding Source # decodeList ∷ Decoder s [GenTx (SimpleBlock c ext)] Source # | |||||
Serialise (TxId (GenTx (SimpleBlock c ext))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods encode ∷ TxId (GenTx (SimpleBlock c ext)) → Encoding Source # decode ∷ Decoder s (TxId (GenTx (SimpleBlock c ext))) Source # encodeList ∷ [TxId (GenTx (SimpleBlock c ext))] → Encoding Source # decodeList ∷ Decoder s [TxId (GenTx (SimpleBlock c ext))] Source # | |||||
SerialiseNodeToClient (MockBlock ext) (GenTx (MockBlock ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → GenTx (MockBlock ext) → Encoding Source # decodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → ∀ s. Decoder s (GenTx (MockBlock ext)) Source # | |||||
SerialiseNodeToClient (MockBlock ext) (GenTxId (MockBlock ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → GenTxId (MockBlock ext) → Encoding Source # decodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → ∀ s. Decoder s (GenTxId (MockBlock ext)) Source # | |||||
SerialiseNodeToNode (MockBlock ext) (GenTx (MockBlock ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → GenTx (MockBlock ext) → Encoding Source # decodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → ∀ s. Decoder s (GenTx (MockBlock ext)) Source # | |||||
SerialiseNodeToNode (MockBlock ext) (GenTxId (MockBlock ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → GenTxId (MockBlock ext) → Encoding Source # decodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → ∀ s. Decoder s (GenTxId (MockBlock ext)) Source # | |||||
type Rep (Validated (GenTx (HardForkBlock xs))) | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool type Rep (Validated (GenTx (HardForkBlock xs))) = D1 ('MetaData "Validated" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "HardForkValidatedGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkValidatedGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraValidatedGenTx xs)))) | |||||
type Rep (Validated (GenTx (SimpleBlock c ext))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||
type Rep (GenTx (HardForkBlock xs)) | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool type Rep (GenTx (HardForkBlock xs)) = D1 ('MetaData "GenTx" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "HardForkGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTx xs)))) | |||||
type Rep (GenTx (SimpleBlock c ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block type Rep (GenTx (SimpleBlock c ext)) = D1 ('MetaData "GenTx" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleGenTx") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Tx) :*: S1 ('MetaSel ('Just "simpleGenTxId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxId))) | |||||
type Rep (TxId (GenTx (HardForkBlock xs))) | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool type Rep (TxId (GenTx (HardForkBlock xs))) = D1 ('MetaData "TxId" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "HardForkGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTxId xs)))) | |||||
type Rep (TxId (GenTx (SimpleBlock c ext))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block type Rep (TxId (GenTx (SimpleBlock c ext))) = D1 ('MetaData "TxId" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.26.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "SimpleGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSimpleGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxId))) | |||||
newtype Validated (GenTx (HardForkBlock xs)) | |||||
data Validated (GenTx (DualBlock m a)) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual data Validated (GenTx (DualBlock m a)) = ValidatedDualGenTx {
| |||||
newtype Validated (GenTx (SimpleBlock c ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block newtype Validated (GenTx (SimpleBlock c ext)) = ValidatedSimpleGenTx {
| |||||
newtype GenTx (HardForkBlock xs) | |||||
newtype TxId (GenTx (HardForkBlock xs)) | |||||
newtype TxId (GenTx (DualBlock m a)) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||
newtype TxId (GenTx (SimpleBlock c ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||
data GenTx (DualBlock m a) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual data GenTx (DualBlock m a) = DualGenTx {
| |||||
data GenTx (SimpleBlock c ext) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block |
A generalized transaction, GenTx
, identifier.
Instances
(Typeable m, Typeable a) ⇒ ShowProxy (TxId (GenTx (DualBlock m a)) ∷ Type) | |||||
(Typeable c, Typeable ext) ⇒ ShowProxy (TxId (GenTx (SimpleBlock c ext)) ∷ Type) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||
Generic (TxId (GenTx (SimpleBlock c ext))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods from ∷ TxId (GenTx (SimpleBlock c ext)) → Rep (TxId (GenTx (SimpleBlock c ext))) x # to ∷ Rep (TxId (GenTx (SimpleBlock c ext))) x → TxId (GenTx (SimpleBlock c ext)) # | |||||
Show (GenTxId m) ⇒ Show (TxId (GenTx (DualBlock m a))) | |||||
Show (TxId (GenTx (SimpleBlock c ext))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||
Eq (GenTxId m) ⇒ Eq (TxId (GenTx (DualBlock m a))) | |||||
Eq (TxId (GenTx (SimpleBlock c ext))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods (==) ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → Bool # (/=) ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → Bool # | |||||
Ord (GenTxId m) ⇒ Ord (TxId (GenTx (DualBlock m a))) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual Methods compare ∷ TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Ordering # (<) ∷ TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool # (<=) ∷ TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool # (>) ∷ TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool # (>=) ∷ TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool # max ∷ TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) # min ∷ TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) # | |||||
Ord (TxId (GenTx (SimpleBlock c ext))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods compare ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → Ordering # (<) ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → Bool # (<=) ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → Bool # (>) ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → Bool # (>=) ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → Bool # max ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) # min ∷ TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) # | |||||
NoThunks (TxId (GenTx (DualBlock m a))) | |||||
NoThunks (TxId (GenTx (SimpleBlock c ext))) Source # | |||||
Condense (GenTxId (SimpleBlock p c)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||
Serialise (TxId (GenTx (SimpleBlock c ext))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods encode ∷ TxId (GenTx (SimpleBlock c ext)) → Encoding Source # decode ∷ Decoder s (TxId (GenTx (SimpleBlock c ext))) Source # encodeList ∷ [TxId (GenTx (SimpleBlock c ext))] → Encoding Source # decodeList ∷ Decoder s [TxId (GenTx (SimpleBlock c ext))] Source # | |||||
SerialiseNodeToClient (MockBlock ext) (GenTxId (MockBlock ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → GenTxId (MockBlock ext) → Encoding Source # decodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → ∀ s. Decoder s (GenTxId (MockBlock ext)) Source # | |||||
SerialiseNodeToNode (MockBlock ext) (GenTxId (MockBlock ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → GenTxId (MockBlock ext) → Encoding Source # decodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → ∀ s. Decoder s (GenTxId (MockBlock ext)) Source # | |||||
type Rep (TxId (GenTx (HardForkBlock xs))) | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool type Rep (TxId (GenTx (HardForkBlock xs))) = D1 ('MetaData "TxId" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "HardForkGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTxId xs)))) | |||||
type Rep (TxId (GenTx (SimpleBlock c ext))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block type Rep (TxId (GenTx (SimpleBlock c ext))) = D1 ('MetaData "TxId" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.26.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "SimpleGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSimpleGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxId))) | |||||
newtype TxId (GenTx (HardForkBlock xs)) | |||||
newtype TxId (GenTx (DualBlock m a)) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual | |||||
newtype TxId (GenTx (SimpleBlock c ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block |
data family Validated x Source #
" Validated " transaction or block
The ledger defines how to validate transactions and blocks. It's possible the type before and after validation may be distinct (eg Alonzo transactions), which originally motivated this family.
We also gain the related benefit that certain interface functions, such as those that reapply blocks, can have a more precise type now. TODO
Similarly, the Node-to-Client mini protocols can explicitly indicate that the
client trusts the blocks from the local server, by having the server send
Validated
blocks to the client. TODO
Note that validation has different implications for a transaction than for a block. In particular, a validated transaction can be " reapplied " to different ledger states, whereas a validated block must only be " reapplied " to the exact same ledger state (eg as part of rebuilding from an on-disk ledger snapshot).
Since the ledger defines validation, see the ledger details for concrete
examples of what determines the validity (wrt to a LedgerState
) of a
transaction and/or block. Example properties include: a transaction's claimed
inputs exist and are still unspent, a block carries a sufficient
cryptographic signature, etc.
Instances
Generic (Validated (GenTx (SimpleBlock c ext))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
Methods from ∷ Validated (GenTx (SimpleBlock c ext)) → Rep (Validated (GenTx (SimpleBlock c ext))) x # to ∷ Rep (Validated (GenTx (SimpleBlock c ext))) x → Validated (GenTx (SimpleBlock c ext)) # | |||||
Bridge m a ⇒ Show (Validated (GenTx (DualBlock m a))) | |||||
Show (Validated (GenTx (SimpleBlock p c))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||
Eq (Validated (GenTx (SimpleBlock c ext))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods (==) ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Bool # (/=) ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Bool # | |||||
Ord (Validated (GenTx (SimpleBlock c ext))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods compare ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Ordering # (<) ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Bool # (<=) ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Bool # (>) ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Bool # (>=) ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Bool # max ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) # min ∷ Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) # | |||||
NoThunks (Validated (GenTx (DualBlock m a))) | |||||
(Typeable p, Typeable c) ⇒ NoThunks (Validated (GenTx (SimpleBlock p c))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||
type Rep (Validated (GenTx (HardForkBlock xs))) | |||||
Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool type Rep (Validated (GenTx (HardForkBlock xs))) = D1 ('MetaData "Validated" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "HardForkValidatedGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkValidatedGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraValidatedGenTx xs)))) | |||||
type Rep (Validated (GenTx (SimpleBlock c ext))) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||
newtype Validated (GenTx (HardForkBlock xs)) | |||||
data Validated (GenTx (DualBlock m a)) | |||||
Defined in Ouroboros.Consensus.Ledger.Dual data Validated (GenTx (DualBlock m a)) = ValidatedDualGenTx {
| |||||
newtype Validated (GenTx (SimpleBlock c ext)) Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block newtype Validated (GenTx (SimpleBlock c ext)) = ValidatedSimpleGenTx {
|
genTxSize ∷ GenTx (SimpleBlock c ext) → ByteSize32 Source #
mkSimpleGenTx ∷ Tx → GenTx (SimpleBlock c ext) Source #
Crypto
class (KnownNat (SizeHash (SimpleHash c)), HashAlgorithm (SimpleHash c), Typeable c) ⇒ SimpleCrypto c Source #
Instances
SimpleCrypto SimpleMockCrypto Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
| |||||
SimpleCrypto SimpleStandardCrypto Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
|
data SimpleMockCrypto Source #
Instances
SimpleCrypto SimpleMockCrypto Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
| |||||||||
Serialise ext ⇒ ReconstructNestedCtxt Header (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods reconstructPrefixLen ∷ proxy (Header (MockBlock ext)) → PrefixLen Source # reconstructNestedCtxt ∷ proxy (Header (MockBlock ext)) → ShortByteString → SizeInBytes → SomeSecond (NestedCtxt Header) (MockBlock ext) Source # | |||||||||
SerialiseBlockQueryResult (MockBlock ext) BlockQuery Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeBlockQueryResult ∷ ∀ (fp ∷ QueryFootprint) result. CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → BlockQuery (MockBlock ext) fp result → result → Encoding Source # decodeBlockQueryResult ∷ ∀ (fp ∷ QueryFootprint) result. CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → BlockQuery (MockBlock ext) fp result → ∀ s. Decoder s result Source # | |||||||||
HasNetworkProtocolVersion (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Associated Types
| |||||||||
(Serialise ext, Typeable ext, Serialise (MockLedgerConfig SimpleMockCrypto ext), MockProtocolSpecific SimpleMockCrypto ext) ⇒ SerialiseNodeToClientConstraints (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation | |||||||||
Serialise ext ⇒ SerialiseNodeToNodeConstraints (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods estimateBlockSize ∷ Header (MockBlock ext) → SizeInBytes Source # | |||||||||
(Serialise ext, RunMockBlock SimpleMockCrypto ext) ⇒ SerialiseDiskConstraints (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation | |||||||||
(Serialise ext, Typeable ext) ⇒ HasBinaryBlockInfo (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods getBinaryBlockInfo ∷ MockBlock ext → BinaryBlockInfo Source # | |||||||||
SerialiseNodeToClient (MockBlock ext) SlotNo Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → SlotNo → Encoding Source # decodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → ∀ s. Decoder s SlotNo Source # | |||||||||
SerialiseNodeToClient (MockBlock ext) (SomeBlockQuery (BlockQuery (MockBlock ext))) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → SomeBlockQuery (BlockQuery (MockBlock ext)) → Encoding Source # decodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → ∀ s. Decoder s (SomeBlockQuery (BlockQuery (MockBlock ext))) Source # | |||||||||
SerialiseNodeToClient (MockBlock ext) (GenTx (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → GenTx (MockBlock ext) → Encoding Source # decodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → ∀ s. Decoder s (GenTx (MockBlock ext)) Source # | |||||||||
SerialiseNodeToClient (MockBlock ext) (GenTxId (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → GenTxId (MockBlock ext) → Encoding Source # decodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → ∀ s. Decoder s (GenTxId (MockBlock ext)) Source # | |||||||||
SerialiseNodeToClient (MockBlock ext) (MockError (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → MockError (MockBlock ext) → Encoding Source # decodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → ∀ s. Decoder s (MockError (MockBlock ext)) Source # | |||||||||
Serialise ext ⇒ SerialiseNodeToClient (MockBlock ext) (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → MockBlock ext → Encoding Source # decodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → ∀ s. Decoder s (MockBlock ext) Source # | |||||||||
Serialise ext ⇒ SerialiseNodeToNode (MockBlock ext) (Header (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → Header (MockBlock ext) → Encoding Source # decodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → ∀ s. Decoder s (Header (MockBlock ext)) Source # | |||||||||
SerialiseNodeToNode (MockBlock ext) (GenTx (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → GenTx (MockBlock ext) → Encoding Source # decodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → ∀ s. Decoder s (GenTx (MockBlock ext)) Source # | |||||||||
SerialiseNodeToNode (MockBlock ext) (GenTxId (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → GenTxId (MockBlock ext) → Encoding Source # decodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → ∀ s. Decoder s (GenTxId (MockBlock ext)) Source # | |||||||||
Serialise ext ⇒ SerialiseNodeToNode (MockBlock ext) (SerialisedHeader (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → SerialisedHeader (MockBlock ext) → Encoding Source # decodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → ∀ s. Decoder s (SerialisedHeader (MockBlock ext)) Source # | |||||||||
Serialise ext ⇒ SerialiseNodeToNode (MockBlock ext) (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → MockBlock ext → Encoding Source # decodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → ∀ s. Decoder s (MockBlock ext) Source # | |||||||||
DecodeDisk (MockBlock ext) (AnnTip (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods decodeDisk ∷ CodecConfig (MockBlock ext) → ∀ s. Decoder s (AnnTip (MockBlock ext)) Source # | |||||||||
Serialise ext ⇒ DecodeDiskDep (NestedCtxt Header) (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods decodeDiskDep ∷ CodecConfig (MockBlock ext) → NestedCtxt Header (MockBlock ext) a → ∀ s. Decoder s (ByteString → a) Source # | |||||||||
Serialise ext ⇒ DecodeDiskDepIx (NestedCtxt Header) (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods decodeDiskDepIx ∷ CodecConfig (MockBlock ext) → Decoder s (SomeSecond (NestedCtxt Header) (MockBlock ext)) Source # | |||||||||
Serialise ext ⇒ EncodeDisk (MockBlock ext) (Header (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeDisk ∷ CodecConfig (MockBlock ext) → Header (MockBlock ext) → Encoding Source # | |||||||||
EncodeDisk (MockBlock ext) (AnnTip (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeDisk ∷ CodecConfig (MockBlock ext) → AnnTip (MockBlock ext) → Encoding Source # | |||||||||
Serialise ext ⇒ EncodeDisk (MockBlock ext) (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeDisk ∷ CodecConfig (MockBlock ext) → MockBlock ext → Encoding Source # | |||||||||
Serialise ext ⇒ EncodeDiskDep (NestedCtxt Header) (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeDiskDep ∷ CodecConfig (MockBlock ext) → NestedCtxt Header (MockBlock ext) a → a → Encoding Source # | |||||||||
Serialise ext ⇒ EncodeDiskDepIx (NestedCtxt Header) (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeDiskDepIx ∷ CodecConfig (MockBlock ext) → SomeSecond (NestedCtxt Header) (MockBlock ext) → Encoding Source # | |||||||||
SerialiseNodeToClient (MockBlock ext) (Serialised (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → Serialised (MockBlock ext) → Encoding Source # decodeNodeToClient ∷ CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → ∀ s. Decoder s (Serialised (MockBlock ext)) Source # | |||||||||
SerialiseNodeToNode (MockBlock ext) (Serialised (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → Serialised (MockBlock ext) → Encoding Source # decodeNodeToNode ∷ CodecConfig (MockBlock ext) → BlockNodeToNodeVersion (MockBlock ext) → ∀ s. Decoder s (Serialised (MockBlock ext)) Source # | |||||||||
DecodeDisk (MockBlock ext) (LedgerState (MockBlock ext) EmptyMK) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods decodeDisk ∷ CodecConfig (MockBlock ext) → ∀ s. Decoder s (LedgerState (MockBlock ext) EmptyMK) Source # | |||||||||
Serialise ext ⇒ DecodeDisk (MockBlock ext) (ByteString → Header (MockBlock ext)) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods decodeDisk ∷ CodecConfig (MockBlock ext) → ∀ s. Decoder s (ByteString → Header (MockBlock ext)) Source # | |||||||||
Serialise ext ⇒ DecodeDisk (MockBlock ext) (ByteString → MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods decodeDisk ∷ CodecConfig (MockBlock ext) → ∀ s. Decoder s (ByteString → MockBlock ext) Source # | |||||||||
EncodeDisk (MockBlock ext) (LedgerState (MockBlock ext) EmptyMK) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation Methods encodeDisk ∷ CodecConfig (MockBlock ext) → LedgerState (MockBlock ext) EmptyMK → Encoding Source # | |||||||||
NodeInitStorage (SimpleBlock SimpleMockCrypto ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node Methods nodeImmutableDbChunkInfo ∷ StorageConfig (SimpleBlock SimpleMockCrypto ext) → ChunkInfo Source # nodeCheckIntegrity ∷ StorageConfig (SimpleBlock SimpleMockCrypto ext) → SimpleBlock SimpleMockCrypto ext → Bool Source # nodeInitChainDB ∷ IOLike m ⇒ StorageConfig (SimpleBlock SimpleMockCrypto ext) → InitChainDB m (SimpleBlock SimpleMockCrypto ext) → m () Source # | |||||||||
SupportedNetworkProtocolVersion (SimpleBlock SimpleMockCrypto ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node Methods supportedNodeToNodeVersions ∷ Proxy (SimpleBlock SimpleMockCrypto ext) → Map NodeToNodeVersion (BlockNodeToNodeVersion (SimpleBlock SimpleMockCrypto ext)) Source # supportedNodeToClientVersions ∷ Proxy (SimpleBlock SimpleMockCrypto ext) → Map NodeToClientVersion (BlockNodeToClientVersion (SimpleBlock SimpleMockCrypto ext)) Source # latestReleasedNodeVersion ∷ Proxy (SimpleBlock SimpleMockCrypto ext) → (Maybe NodeToNodeVersion, Maybe NodeToClientVersion) Source # | |||||||||
(LedgerSupportsProtocol (SimpleBlock SimpleMockCrypto ext), Show (CannotForge (SimpleBlock SimpleMockCrypto ext)), Show (ForgeStateInfo (SimpleBlock SimpleMockCrypto ext)), Show (ForgeStateUpdateError (SimpleBlock SimpleMockCrypto ext)), Serialise ext, RunMockBlock SimpleMockCrypto ext) ⇒ RunNode (SimpleBlock SimpleMockCrypto ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node | |||||||||
type SimpleHash SimpleMockCrypto Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |||||||||
type BlockNodeToClientVersion (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation | |||||||||
type BlockNodeToNodeVersion (MockBlock ext) Source # | |||||||||
Defined in Ouroboros.Consensus.Mock.Node.Serialisation |
data SimpleStandardCrypto Source #
Instances
SimpleCrypto SimpleStandardCrypto Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types
| |||||
type SimpleHash SimpleStandardCrypto Source # | |||||
Defined in Ouroboros.Consensus.Mock.Ledger.Block |
Serialisation
decodeSimpleHeader ∷ SimpleCrypto c ⇒ (ext' → Encoding) → (∀ s. Decoder s ext') → ∀ s. Decoder s (Header (SimpleBlock' c ext ext')) Source #
encodeSimpleHeader ∷ KnownNat (SizeHash (SimpleHash c)) ⇒ (ext' → Encoding) → Header (SimpleBlock' c ext ext') → Encoding Source #
simpleBlockBinaryBlockInfo ∷ (SimpleCrypto c, Serialise ext', Typeable ext, Typeable ext') ⇒ SimpleBlock' c ext ext' → BinaryBlockInfo Source #