Safe Haskell | None |
---|---|
Language | Haskell2010 |
Ouroboros.Consensus.Mock.Ledger
Synopsis
- data family BlockQuery blk ∷ Type → Type
- data family GenTx blk
- data family TxId tx
- data family Validated x
- data family LedgerState blk
- data family BlockConfig blk
- data family CodecConfig blk
- data family StorageConfig blk
- data family Header blk
- data family Ticked st
- type AddrDist = Map Addr NodeId
- data Addr
- mkAddrDist ∷ NumCoreNodes → AddrDist
- class HasMockTxs a where
- getMockTxs ∷ a → [Tx]
- data UtxoError
- type Utxo = Map TxIn TxOut
- type TxOut = (Addr, Amount)
- type TxIn = (TxId, Ix)
- type Amount = Word
- type Ix = Word
- data Tx where
- data Expiry
- txIns ∷ HasMockTxs a ⇒ a → Set TxIn
- txOuts ∷ HasMockTxs a ⇒ a → Utxo
- confirmed ∷ HasMockTxs a ⇒ a → Set TxId
- updateUtxo ∷ HasMockTxs a ⇒ a → Utxo → Except UtxoError Utxo
- genesisTx ∷ AddrDist → Tx
- genesisUtxo ∷ AddrDist → Utxo
- data MockError blk
- = MockExpired !SlotNo !SlotNo
- | MockUtxoError UtxoError
- | MockInvalidHash (ChainHash blk) (ChainHash blk)
- data MockState blk = MockState {}
- updateMockState ∷ (GetPrevHash blk, HasMockTxs blk) ⇒ blk → MockState blk → Except (MockError blk) (MockState blk)
- updateMockTip ∷ GetPrevHash blk ⇒ Header blk → MockState blk → Except (MockError blk) (MockState blk)
- updateMockUTxO ∷ HasMockTxs a ⇒ SlotNo → a → MockState blk → Except (MockError blk) (MockState blk)
- genesisMockState ∷ AddrDist → MockState blk
- newtype StakeDist = StakeDist {}
- data StakeHolder
- stakeWithDefault ∷ Rational → CoreNodeId → StakeDist → Rational
- relativeStakes ∷ Map StakeHolder Amount → StakeDist
- totalStakes ∷ Map Addr NodeId → Utxo → Map StakeHolder Amount
- equalStakeDist ∷ AddrDist → StakeDist
- genesisStakeDist ∷ AddrDist → StakeDist
- data SimpleMockCrypto
- data SimpleStandardCrypto
- class (HashAlgorithm (SimpleHash c), Typeable c) ⇒ SimpleCrypto c where
- type SimpleHash c ∷ Type
- data SimpleLedgerConfig c ext = SimpleLedgerConfig {}
- class (SimpleCrypto c, Typeable ext, Show (MockLedgerConfig c ext), NoThunks (MockLedgerConfig c ext)) ⇒ MockProtocolSpecific c ext where
- type MockLedgerConfig c ext ∷ Type
- data SimpleBody = SimpleBody {}
- data SimpleStdHeader c ext = SimpleStdHeader {
- simplePrev ∷ ChainHash (SimpleBlock c ext)
- simpleSlotNo ∷ SlotNo
- simpleBlockNo ∷ BlockNo
- simpleBodyHash ∷ Hash (SimpleHash c) SimpleBody
- simpleBodySize ∷ Word32
- data SimpleBlock' c ext ext' = SimpleBlock {
- simpleHeader ∷ Header (SimpleBlock' c ext ext')
- simpleBody ∷ SimpleBody
- type SimpleHeader c ext = Header (SimpleBlock c ext)
- type SimpleBlock c ext = SimpleBlock' c ext ext
- mkSimpleHeader ∷ SimpleCrypto c ⇒ (ext' → Encoding) → SimpleStdHeader c ext → ext' → Header (SimpleBlock' c ext ext')
- matchesSimpleHeader ∷ SimpleCrypto c ⇒ Header (SimpleBlock' c ext ext') → SimpleBlock' c ext ext'' → Bool
- countSimpleGenTxs ∷ SimpleBlock c ext → Word64
- updateSimpleLedgerState ∷ (SimpleCrypto c, Typeable ext) ⇒ SimpleBlock c ext → TickedLedgerState (SimpleBlock c ext) → Except (MockError (SimpleBlock c ext)) (LedgerState (SimpleBlock c ext))
- genesisSimpleLedgerState ∷ AddrDist → LedgerState (SimpleBlock c ext)
- mkSimpleGenTx ∷ Tx → GenTx (SimpleBlock c ext)
- txSize ∷ GenTx (SimpleBlock c ext) → Word32
- encodeSimpleHeader ∷ (ext' → Encoding) → Header (SimpleBlock' c ext ext') → Encoding
- decodeSimpleHeader ∷ SimpleCrypto c ⇒ (ext' → Encoding) → (∀ s. Decoder s ext') → ∀ s. Decoder s (Header (SimpleBlock' c ext ext'))
- simpleBlockBinaryBlockInfo ∷ (SimpleCrypto c, Serialise ext', Typeable ext, Typeable ext') ⇒ SimpleBlock' c ext ext' → BinaryBlockInfo
- newtype ForgeExt c ext = ForgeExt {
- forgeExt ∷ TopLevelConfig (SimpleBlock c ext) → IsLeader (BlockProtocol (SimpleBlock c ext)) → SimpleBlock' c ext () → SimpleBlock c ext
- forgeSimple ∷ ∀ c ext. (SimpleCrypto c, MockProtocolSpecific c ext) ⇒ ForgeExt c ext → TopLevelConfig (SimpleBlock c ext) → BlockNo → SlotNo → TickedLedgerState (SimpleBlock c ext) → [GenTx (SimpleBlock c ext)] → IsLeader (BlockProtocol (SimpleBlock c ext)) → SimpleBlock c ext
- data SignedSimplePBft c c' = SignedSimplePBft {
- signedSimplePBft ∷ SimpleStdHeader c (SimplePBftExt c c')
- newtype SimplePBftExt c c' = SimplePBftExt {
- simplePBftExt ∷ PBftFields c' (SignedSimplePBft c c')
- type SimplePBftHeader c c' = SimpleHeader c (SimplePBftExt c c')
- type SimplePBftBlock c c' = SimpleBlock c (SimplePBftExt c c')
- forgePBftExt ∷ ∀ c c'. (SimpleCrypto c, PBftCrypto c', Signable (PBftDSIGN c') (SignedSimplePBft c c'), ContextDSIGN (PBftDSIGN c') ~ ()) ⇒ ForgeExt c (SimplePBftExt c c')
- data SignedSimpleBft c c' = SignedSimpleBft {
- signedSimpleBft ∷ SimpleStdHeader c (SimpleBftExt c c')
- newtype SimpleBftExt c c' = SimpleBftExt {
- simpleBftExt ∷ BftFields c' (SignedSimpleBft c c')
- type SimpleBftHeader c c' = SimpleHeader c (SimpleBftExt c c')
- type SimpleBftBlock c c' = SimpleBlock c (SimpleBftExt c c')
- forgeBftExt ∷ ∀ c c'. (SimpleCrypto c, BftCrypto c', Signable (BftDSIGN c') (SignedSimpleBft c c')) ⇒ ForgeExt c (SimpleBftExt c c')
- data PraosCryptoUnused
- newtype SimplePraosRuleExt = SimplePraosRuleExt {}
- type SimplePraosRuleHeader c = SimpleHeader c SimplePraosRuleExt
- type SimplePraosRuleBlock c = SimpleBlock c SimplePraosRuleExt
- forgePraosRuleExt ∷ SimpleCrypto c ⇒ ForgeExt c SimplePraosRuleExt
- data SignedSimplePraos c c' = SignedSimplePraos {}
- newtype SimplePraosExt c c' = SimplePraosExt {
- simplePraosExt ∷ PraosFields c' (SignedSimplePraos c c')
- type SimplePraosHeader c c' = SimpleHeader c (SimplePraosExt c c')
- type SimplePraosBlock c c' = SimpleBlock c (SimplePraosExt c c')
- forgePraosExt ∷ ∀ c c'. (SimpleCrypto c, PraosCrypto c', Signable (PraosKES c') (SignedSimplePraos c c')) ⇒ HotKey c' → ForgeExt c (SimplePraosExt c c')
Documentation
data family BlockQuery blk ∷ Type → Type Source #
Different queries supported by the ledger, indexed by the result type.
Instances
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
A generalized transaction, GenTx
, identifier.
Instances
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
data family LedgerState blk Source #
Ledger state associated with a block
Instances
data family BlockConfig blk Source #
Static configuration required to work with this type of blocks
Instances
Generic (BlockConfig (SimpleBlock c ext)) Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types type Rep (BlockConfig (SimpleBlock c ext)) ∷ Type → Type Source # Methods from ∷ BlockConfig (SimpleBlock c ext) → Rep (BlockConfig (SimpleBlock c ext)) x Source # to ∷ Rep (BlockConfig (SimpleBlock c ext)) x → BlockConfig (SimpleBlock c ext) Source # | |
NoThunks (BlockConfig (SimpleBlock c ext)) Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods noThunks ∷ Context → BlockConfig (SimpleBlock c ext) → IO (Maybe ThunkInfo) # wNoThunks ∷ Context → BlockConfig (SimpleBlock c ext) → IO (Maybe ThunkInfo) # showTypeOf ∷ Proxy (BlockConfig (SimpleBlock c ext)) → String # | |
type Rep (BlockConfig (SimpleBlock c ext)) Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |
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
Generic (CodecConfig (SimpleBlock c ext)) Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.Block Associated Types type Rep (CodecConfig (SimpleBlock c ext)) ∷ Type → Type Source # Methods from ∷ CodecConfig (SimpleBlock c ext) → Rep (CodecConfig (SimpleBlock c ext)) x Source # to ∷ Rep (CodecConfig (SimpleBlock c ext)) x → CodecConfig (SimpleBlock c ext) Source # | |
NoThunks (CodecConfig (SimpleBlock c ext)) Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods noThunks ∷ Context → CodecConfig (SimpleBlock c ext) → IO (Maybe ThunkInfo) # wNoThunks ∷ Context → CodecConfig (SimpleBlock c ext) → IO (Maybe ThunkInfo) # showTypeOf ∷ Proxy (CodecConfig (SimpleBlock c ext)) → String # | |
type Rep (CodecConfig (SimpleBlock c ext)) Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.Block | |
data CodecConfig (SimpleBlock c ext) Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.Block |
data family StorageConfig blk Source #
Config needed for the
NodeInitStorage
class. Defined here to
avoid circular dependencies.
Instances
data family Header blk Source #
Instances
data family Ticked st Source #
" Ticked " piece of state (LedgerState
, LedgerView
, ChainIndepState
)
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 (or forecast).
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
type AddrDist = Map Addr NodeId Source #
Mapping from addresses to node IDs
This is needed in order to assign stake to nodes.
Mock address
Instances
Eq Addr Source # | |
Ord Addr Source # | |
Show Addr Source # | |
IsString Addr Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.Address Methods fromString ∷ String → Addr Source # | |
NFData Addr Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.Address | |
Serialise Addr Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.Address | |
Condense Addr Source # | |
NoThunks Addr Source # | |
mkAddrDist ∷ NumCoreNodes → AddrDist Source #
Construct address to node ID mapping
class HasMockTxs a where Source #
Instances
HasMockTxs Tx Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.UTxO Methods getMockTxs ∷ Tx → [Tx] Source # | |
HasMockTxs SimpleBody Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods getMockTxs ∷ SimpleBody → [Tx] Source # | |
HasMockTxs a ⇒ HasMockTxs [a] Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.UTxO Methods getMockTxs ∷ [a] → [Tx] Source # | |
HasMockTxs a ⇒ HasMockTxs (Chain a) Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.UTxO Methods getMockTxs ∷ Chain a → [Tx] Source # | |
HasMockTxs (GenTx (SimpleBlock p c)) Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods getMockTxs ∷ GenTx (SimpleBlock p c) → [Tx] Source # | |
HasMockTxs (SimpleBlock' c ext ext') Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.Block Methods getMockTxs ∷ SimpleBlock' c ext ext' → [Tx] Source # |
Constructors
MissingInput TxIn | |
InputOutputMismatch | |
Instances
Eq UtxoError Source # | |
Show UtxoError Source # | |
Generic UtxoError Source # | |
Serialise UtxoError Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.UTxO | |
Condense UtxoError Source # | |
NoThunks UtxoError Source # | |
type Rep UtxoError Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.UTxO type Rep UtxoError = D1 ('MetaData "UtxoError" "Ouroboros.Consensus.Mock.Ledger.UTxO" "ouroboros-consensus-mock-0.1.0.0-inplace" 'False) (C1 ('MetaCons "MissingInput" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxIn)) :+: C1 ('MetaCons "InputOutputMismatch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount))) |
Instances
Constructors
DoNotExpire | |
ExpireAtOnsetOf !SlotNo |
Instances
Eq Expiry Source # | |
Ord Expiry Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.UTxO | |
Show Expiry Source # | |
Generic Expiry Source # | |
NFData Expiry Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.UTxO | |
Serialise Expiry Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.UTxO | |
Condense Expiry Source # | |
NoThunks Expiry Source # | |
type Rep Expiry Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.UTxO type Rep Expiry = D1 ('MetaData "Expiry" "Ouroboros.Consensus.Mock.Ledger.UTxO" "ouroboros-consensus-mock-0.1.0.0-inplace" 'False) (C1 ('MetaCons "DoNotExpire" 'PrefixI 'False) (U1 ∷ Type → Type) :+: C1 ('MetaCons "ExpireAtOnsetOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo))) |
txOuts ∷ HasMockTxs a ⇒ a → Utxo Source #
confirmed ∷ HasMockTxs a ⇒ a → Set TxId Source #
confirmed
stands for all the transaction hashes present in the given
collection.
updateUtxo ∷ HasMockTxs a ⇒ a → Utxo → Except UtxoError Utxo Source #
Update the Utxo with the transactions from the given a
, by removing the
inputs and adding the outputs.
genesisUtxo ∷ AddrDist → Utxo Source #
Constructors
MockExpired !SlotNo !SlotNo | The transaction expired in the first |
MockUtxoError UtxoError | |
MockInvalidHash (ChainHash blk) (ChainHash blk) |
Instances
Instances
StandardHash blk ⇒ Eq (MockState blk) Source # | |
StandardHash blk ⇒ Show (MockState blk) Source # | |
Generic (MockState blk) Source # | |
Serialise (HeaderHash blk) ⇒ Serialise (MockState blk) Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.State | |
StandardHash blk ⇒ NoThunks (MockState blk) Source # | |
type Rep (MockState blk) Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.State type Rep (MockState blk) = D1 ('MetaData "MockState" "Ouroboros.Consensus.Mock.Ledger.State" "ouroboros-consensus-mock-0.1.0.0-inplace" 'False) (C1 ('MetaCons "MockState" 'PrefixI 'True) (S1 ('MetaSel ('Just "mockUtxo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Utxo) :*: (S1 ('MetaSel ('Just "mockConfirmed") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Set TxId)) :*: S1 ('MetaSel ('Just "mockTip") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Point blk))))) |
updateMockState ∷ (GetPrevHash blk, HasMockTxs blk) ⇒ blk → MockState blk → Except (MockError blk) (MockState blk) Source #
updateMockTip ∷ GetPrevHash blk ⇒ Header blk → MockState blk → Except (MockError blk) (MockState blk) Source #
updateMockUTxO ∷ HasMockTxs a ⇒ SlotNo → a → MockState blk → Except (MockError blk) (MockState blk) Source #
genesisMockState ∷ AddrDist → MockState blk Source #
In the mock setup, only core nodes have stake
INVARIANT: The rationals should sum to 1.
Constructors
StakeDist | |
Fields |
data StakeHolder Source #
Constructors
StakeCore CoreNodeId | Stake of a core node |
StakeEverybodyElse | Stake for everybody else (we don't need to distinguish) |
Instances
Eq StakeHolder Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.Stake Methods (==) ∷ StakeHolder → StakeHolder → Bool Source # (/=) ∷ StakeHolder → StakeHolder → Bool Source # | |
Ord StakeHolder Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.Stake Methods compare ∷ StakeHolder → StakeHolder → Ordering Source # (<) ∷ StakeHolder → StakeHolder → Bool Source # (<=) ∷ StakeHolder → StakeHolder → Bool Source # (>) ∷ StakeHolder → StakeHolder → Bool Source # (>=) ∷ StakeHolder → StakeHolder → Bool Source # max ∷ StakeHolder → StakeHolder → StakeHolder Source # min ∷ StakeHolder → StakeHolder → StakeHolder Source # | |
Show StakeHolder Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.Stake |
totalStakes ∷ Map Addr NodeId → Utxo → Map StakeHolder Amount Source #
Compute stakes of all nodes
The Nothing
value holds the total stake of all addresses that don't
get mapped to a NodeId.
equalStakeDist ∷ AddrDist → StakeDist Source #
Stake distribution where every address has equal state
genesisStakeDist ∷ AddrDist → StakeDist Source #
Genesis stake distribution
data SimpleMockCrypto Source #
Instances
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 |
class (HashAlgorithm (SimpleHash c), Typeable c) ⇒ SimpleCrypto c Source #
Associated Types
type SimpleHash c ∷ Type 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 SimpleLedgerConfig c ext Source #
Constructors
SimpleLedgerConfig | |
Fields
|
Instances
class (SimpleCrypto c, Typeable ext, Show (MockLedgerConfig c ext), NoThunks (MockLedgerConfig c ext)) ⇒ MockProtocolSpecific c ext Source #
Associated Types
type MockLedgerConfig c ext ∷ Type Source #
Instances
SimpleCrypto c ⇒ MockProtocolSpecific c SimplePraosRuleExt Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule Associated Types | |
(SimpleCrypto c, PBftCrypto c') ⇒ MockProtocolSpecific c (SimplePBftExt c c') Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT Associated Types type MockLedgerConfig c (SimplePBftExt c c') Source # | |
(SimpleCrypto c, Typeable c') ⇒ MockProtocolSpecific c (SimpleBftExt c c') Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT Associated Types type MockLedgerConfig c (SimpleBftExt c c') Source # | |
(SimpleCrypto c, Typeable c') ⇒ MockProtocolSpecific c (SimplePraosExt c c') Source # | |
Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos Associated Types type MockLedgerConfig c (SimplePraosExt c c') Source # |
data SimpleBody Source #
Constructors
SimpleBody | |
Instances
data SimpleStdHeader c ext Source #
Constructors
SimpleStdHeader | |
Fields
|
Instances
data SimpleBlock' c ext ext' Source #
Constructors
SimpleBlock | |
Fields
|