ouroboros-consensus-0.18.0.0: Consensus layer for the Ouroboros blockchain protocol
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ouroboros.Consensus.Mock.Ledger

Synopsis

Documentation

type Ix = Word Source #

data Addr Source #

Mock address

Instances

Instances details
IsString Addr Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Address

Methods

fromStringStringAddr #

Show Addr Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Address

Methods

showsPrecIntAddrShowS #

showAddrString #

showList ∷ [Addr] → ShowS #

FromCBOR Addr Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Address

ToCBOR Addr Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Address

Methods

toCBORAddrEncoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy AddrSize Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [Addr] → Size Source #

NFData Addr Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Address

Methods

rnfAddr → () #

Eq Addr Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Address

Methods

(==)AddrAddrBool #

(/=)AddrAddrBool #

Ord Addr Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Address

Methods

compareAddrAddrOrdering #

(<)AddrAddrBool #

(<=)AddrAddrBool #

(>)AddrAddrBool #

(>=)AddrAddrBool #

maxAddrAddrAddr #

minAddrAddrAddr #

NoThunks Addr Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Address

Condense Addr Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Address

Methods

condenseAddrString Source #

Serialise Addr Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Address

data family Header blk Source #

Instances

Instances details
Serialise ext ⇒ ReconstructNestedCtxt Header (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

HasHeader blk ⇒ StandardHash (Header blk ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

(Typeable c, Typeable ext, Typeable ext') ⇒ ShowProxy (Header (SimpleBlock' c ext ext') ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showProxyProxy (Header (SimpleBlock' c ext ext')) → String Source #

Generic (Header (SimpleBlock' c ext ext')) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (Header (SimpleBlock' c ext ext')) ∷ TypeType #

Methods

fromHeader (SimpleBlock' c ext ext') → Rep (Header (SimpleBlock' c ext ext')) x #

toRep (Header (SimpleBlock' c ext ext')) x → Header (SimpleBlock' c ext ext') #

(SimpleCrypto c, Show ext', Typeable ext) ⇒ Show (Header (SimpleBlock' c ext ext')) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showsPrecIntHeader (SimpleBlock' c ext ext') → ShowS #

showHeader (SimpleBlock' c ext ext') → String #

showList ∷ [Header (SimpleBlock' c ext ext')] → ShowS #

(SimpleCrypto c, Eq ext', Typeable ext) ⇒ Eq (Header (SimpleBlock' c ext ext')) Source # 
Instance details

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 #

(SimpleCrypto c, NoThunks ext', Typeable ext) ⇒ NoThunks (Header (SimpleBlock' c ext ext')) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

noThunksContextHeader (SimpleBlock' c ext ext') → IO (Maybe ThunkInfo) Source #

wNoThunksContextHeader (SimpleBlock' c ext ext') → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (Header (SimpleBlock' c ext ext')) → String Source #

Condense ext' ⇒ Condense (Header (SimpleBlock' c ext ext')) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

condenseHeader (SimpleBlock' c ext ext') → String Source #

(SimpleCrypto c, Typeable ext, Typeable ext') ⇒ HasHeader (Header (SimpleBlock' c ext ext')) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

getHeaderFieldsHeader (SimpleBlock' c ext ext') → HeaderFields (Header (SimpleBlock' c ext ext')) Source #

(SimpleCrypto c, Serialise ext') ⇒ Serialise (Header (SimpleBlock' c ext ext')) Source #

Custom Serialise instance that doesn't serialise the hash

Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

encodeHeader (SimpleBlock' c ext ext') → Encoding Source #

decodeDecoder s (Header (SimpleBlock' c ext ext')) Source #

encodeList ∷ [Header (SimpleBlock' c ext ext')] → Encoding Source #

decodeListDecoder s [Header (SimpleBlock' c ext ext')] Source #

Serialise ext ⇒ SerialiseNodeToNode (MockBlock ext) (Header (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ DecodeDiskDep (NestedCtxt Header) (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Methods

decodeDiskDepCodecConfig (MockBlock ext) → NestedCtxt Header (MockBlock ext) a → ∀ s. Decoder s (ByteString → a) Source #

Serialise ext ⇒ DecodeDiskDepIx (NestedCtxt Header) (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ EncodeDisk (MockBlock ext) (Header (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ EncodeDiskDep (NestedCtxt Header) (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ EncodeDiskDepIx (NestedCtxt Header) (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ DecodeDisk (MockBlock ext) (ByteStringHeader (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Methods

decodeDiskCodecConfig (MockBlock ext) → ∀ s. Decoder s (ByteStringHeader (MockBlock ext)) Source #

SignedHeader (SimpleBftHeader c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

SignedHeader (SimplePBftHeader c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

PraosCrypto c' ⇒ SignedHeader (SimplePraosHeader c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

type HeaderHash (Header blk ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

type HeaderHash (Header blk ∷ Type) = HeaderHash blk
type Rep (Header (SimpleBlock' c ext ext')) Source # 
Instance details

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.18.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 BlockProtocol (Header blk) 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

newtype Header (DisableDiffusionPipelining blk) 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype Header (SelectViewDiffusionPipelining blk) 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

type Signed (SimpleBftHeader c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

type Signed (SimplePBftHeader c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

type Signed (SimplePraosHeader c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

data Header (SimpleBlock' c ext ext') Source # 
Instance details

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

Instances details
Generic (StorageConfig (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (StorageConfig (SimpleBlock c ext)) ∷ TypeType #

Methods

fromStorageConfig (SimpleBlock c ext) → Rep (StorageConfig (SimpleBlock c ext)) x #

toRep (StorageConfig (SimpleBlock c ext)) x → StorageConfig (SimpleBlock c ext) #

NoThunks (StorageConfig (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (StorageConfig (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (StorageConfig (SimpleBlock c ext)) = D1 ('MetaData "StorageConfig" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleStorageConfig" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SecurityParam)))
data StorageConfig (SimpleBlock c ext) Source # 
Instance details

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

Instances details
Generic (CodecConfig (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (CodecConfig (SimpleBlock c ext)) ∷ TypeType #

Methods

fromCodecConfig (SimpleBlock c ext) → Rep (CodecConfig (SimpleBlock c ext)) x #

toRep (CodecConfig (SimpleBlock c ext)) x → CodecConfig (SimpleBlock c ext) #

NoThunks (CodecConfig (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (CodecConfig (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (CodecConfig (SimpleBlock c ext)) = D1 ('MetaData "CodecConfig" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleCodecConfig" 'PrefixI 'False) (U1TypeType))
data CodecConfig (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

data family BlockConfig blk Source #

Static configuration required to work with this type of blocks

Instances

Instances details
Generic (BlockConfig (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (BlockConfig (SimpleBlock c ext)) ∷ TypeType #

Methods

fromBlockConfig (SimpleBlock c ext) → Rep (BlockConfig (SimpleBlock c ext)) x #

toRep (BlockConfig (SimpleBlock c ext)) x → BlockConfig (SimpleBlock c ext) #

NoThunks (BlockConfig (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (BlockConfig (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (BlockConfig (SimpleBlock c ext)) = D1 ('MetaData "BlockConfig" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleBlockConfig" 'PrefixI 'False) (U1TypeType))
newtype BlockConfig (DisableDiffusionPipelining blk) 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype BlockConfig (SelectViewDiffusionPipelining blk) 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

data BlockConfig (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

data family Ticked st Source #

" Ticked " piece of state, either LedgerState or ChainDepState

Ticking refers to the passage of time (the ticking of the clock). When a piece of state is marked as ticked, it means that time-related changes have been applied to the state. There are exactly two methods in the interface that do that: tickChainDepState and applyChainTickLedgerResult.

Also note that a successful forecast forecastFor (ledgerViewForecastAt cfg st) slot must equal protocolLedgerView cfg (applyChainTick cfg slot st). Thus a 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

Instances details
Generic (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (Ticked (LedgerState (SimpleBlock c ext))) ∷ TypeType #

Methods

fromTicked (LedgerState (SimpleBlock c ext)) → Rep (Ticked (LedgerState (SimpleBlock c ext))) x #

toRep (Ticked (LedgerState (SimpleBlock c ext))) x → Ticked (LedgerState (SimpleBlock c ext)) #

(SimpleCrypto c, Typeable ext) ⇒ Show (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Show (Ticked ()) 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecIntTicked () → ShowS #

showTicked () → String #

showList ∷ [Ticked ()] → ShowS #

(SimpleCrypto c, Typeable ext) ⇒ Eq (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

(==)Ticked (LedgerState (SimpleBlock c ext)) → Ticked (LedgerState (SimpleBlock c ext)) → Bool #

(/=)Ticked (LedgerState (SimpleBlock c ext)) → Ticked (LedgerState (SimpleBlock c ext)) → Bool #

(SimpleCrypto c, Typeable ext) ⇒ NoThunks (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

GetTip (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

IsLedger (LedgerState blk) ⇒ GetTip (Ticked (ExtLedgerState blk)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Show (Ticked (f a)) ⇒ Show ((Ticked :.: f) a) 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecInt → (Ticked :.: f) a → ShowS #

show ∷ (Ticked :.: f) a → String #

showList ∷ [(Ticked :.: f) a] → ShowS #

NoThunks (Ticked (f a)) ⇒ NoThunks ((Ticked :.: f) a) 
Instance details

Defined in Ouroboros.Consensus.Ticked

data Ticked () 
Instance details

Defined in Ouroboros.Consensus.Ticked

type HeaderHash (Ticked l ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.Ticked

type HeaderHash (Ticked l ∷ Type) = HeaderHash l
type Rep (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (Ticked (LedgerState (SimpleBlock c ext))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "TickedSimpleLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTickedSimpleLedgerState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerState (SimpleBlock c ext)))))
data Ticked (HeaderState blk) 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

newtype Ticked (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

data Ticked (ExtLedgerState blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

data Ticked (PBftState c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

newtype Ticked (WrapChainDepState blk) 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

data Ticked (PraosChainDepState c) 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.

Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

data family LedgerState blk Source #

Ledger state associated with a block

This is the Consensus notion of a ledger state. Each block type is associated with one of the Ledger types for the ledger state. Virtually every concept in this codebase revolves around this type, or the referenced blk. Whenever we use the type variable l, we intend to denote that the expected instantiation is either a LedgerState or some wrapper over it (like the ExtLedgerState).

The main operations we can do with a LedgerState are ticking (defined in IsLedger), and applying a block (defined in ApplyBlock).

Instances

Instances details
Generic (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (LedgerState (SimpleBlock c ext)) ∷ TypeType #

Methods

fromLedgerState (SimpleBlock c ext) → Rep (LedgerState (SimpleBlock c ext)) x #

toRep (LedgerState (SimpleBlock c ext)) x → LedgerState (SimpleBlock c ext) #

Generic (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (Ticked (LedgerState (SimpleBlock c ext))) ∷ TypeType #

Methods

fromTicked (LedgerState (SimpleBlock c ext)) → Rep (Ticked (LedgerState (SimpleBlock c ext))) x #

toRep (Ticked (LedgerState (SimpleBlock c ext))) x → Ticked (LedgerState (SimpleBlock c ext)) #

(SimpleCrypto c, Typeable ext) ⇒ Show (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showsPrecIntLedgerState (SimpleBlock c ext) → ShowS #

showLedgerState (SimpleBlock c ext) → String #

showList ∷ [LedgerState (SimpleBlock c ext)] → ShowS #

(SimpleCrypto c, Typeable ext) ⇒ Show (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

(SimpleCrypto c, Typeable ext) ⇒ Eq (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

(==)LedgerState (SimpleBlock c ext) → LedgerState (SimpleBlock c ext) → Bool #

(/=)LedgerState (SimpleBlock c ext) → LedgerState (SimpleBlock c ext) → Bool #

(SimpleCrypto c, Typeable ext) ⇒ Eq (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

(==)Ticked (LedgerState (SimpleBlock c ext)) → Ticked (LedgerState (SimpleBlock c ext)) → Bool #

(/=)Ticked (LedgerState (SimpleBlock c ext)) → Ticked (LedgerState (SimpleBlock c ext)) → Bool #

(SimpleCrypto c, Typeable ext) ⇒ NoThunks (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

(SimpleCrypto c, Typeable ext) ⇒ NoThunks (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

GetTip (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

GetTip (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

MockProtocolSpecific c ext ⇒ IsLedger (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type LedgerErr (LedgerState (SimpleBlock c ext)) Source #

type AuxLedgerEvent (LedgerState (SimpleBlock c ext)) Source #

Serialise (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

DecodeDisk (MockBlock ext) (LedgerState (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Methods

decodeDiskCodecConfig (MockBlock ext) → ∀ s. Decoder s (LedgerState (MockBlock ext)) Source #

EncodeDisk (MockBlock ext) (LedgerState (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

MockProtocolSpecific c ext ⇒ ApplyBlock (LedgerState (SimpleBlock c ext)) (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type HeaderHash (LedgerState blk ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

type HeaderHash (LedgerState blk ∷ Type) = HeaderHash blk
type Rep (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (LedgerState (SimpleBlock c ext)) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "SimpleLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleLedgerState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MockState (SimpleBlock c ext)))))
type Rep (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (Ticked (LedgerState (SimpleBlock c ext))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "TickedSimpleLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTickedSimpleLedgerState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerState (SimpleBlock c ext)))))
type AuxLedgerEvent (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type LedgerCfg (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type LedgerErr (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

newtype Ticked (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

newtype LedgerState (SimpleBlock c ext) Source # 
Instance details

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

Instances details
Generic (Validated (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (Validated (GenTx (SimpleBlock c ext))) ∷ TypeType #

Methods

fromValidated (GenTx (SimpleBlock c ext)) → Rep (Validated (GenTx (SimpleBlock c ext))) x #

toRep (Validated (GenTx (SimpleBlock c ext))) x → Validated (GenTx (SimpleBlock c ext)) #

Show (Validated (GenTx (SimpleBlock p c))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Eq (Validated (GenTx (SimpleBlock c ext))) Source # 
Instance details

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 # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

compareValidated (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 #

maxValidated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) #

minValidated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) #

(Typeable p, Typeable c) ⇒ NoThunks (Validated (GenTx (SimpleBlock p c))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (Validated (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (Validated (GenTx (SimpleBlock c ext))) = Rep (GenTx (SimpleBlock c ext))
newtype Validated (GenTx (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

data family TxId tx Source #

A generalized transaction, GenTx, identifier.

Instances

Instances details
(Typeable c, Typeable ext) ⇒ ShowProxy (TxId (GenTx (SimpleBlock c ext)) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showProxyProxy (TxId (GenTx (SimpleBlock c ext))) → String Source #

Generic (TxId (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (TxId (GenTx (SimpleBlock c ext))) ∷ TypeType #

Methods

fromTxId (GenTx (SimpleBlock c ext)) → Rep (TxId (GenTx (SimpleBlock c ext))) x #

toRep (TxId (GenTx (SimpleBlock c ext))) x → TxId (GenTx (SimpleBlock c ext)) #

Show (TxId (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showsPrecIntTxId (GenTx (SimpleBlock c ext)) → ShowS #

showTxId (GenTx (SimpleBlock c ext)) → String #

showList ∷ [TxId (GenTx (SimpleBlock c ext))] → ShowS #

Eq (TxId (GenTx (SimpleBlock c ext))) Source # 
Instance details

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 (TxId (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

compareTxId (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 #

maxTxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) #

minTxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) #

NoThunks (TxId (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Condense (GenTxId (SimpleBlock p c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

condenseGenTxId (SimpleBlock p c) → String Source #

Serialise (TxId (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

SerialiseNodeToClient (MockBlock ext) (GenTxId (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

SerialiseNodeToNode (MockBlock ext) (GenTxId (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

type Rep (TxId (GenTx (SimpleBlock c ext))) Source # 
Instance details

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.18.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "SimpleGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSimpleGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxId)))
newtype TxId (GenTx (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

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

Instances details
(Typeable c, Typeable ext) ⇒ ShowProxy (GenTx (SimpleBlock c ext) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showProxyProxy (GenTx (SimpleBlock c ext)) → String Source #

(Typeable c, Typeable ext) ⇒ ShowProxy (TxId (GenTx (SimpleBlock c ext)) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showProxyProxy (TxId (GenTx (SimpleBlock c ext))) → String Source #

Generic (Validated (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (Validated (GenTx (SimpleBlock c ext))) ∷ TypeType #

Methods

fromValidated (GenTx (SimpleBlock c ext)) → Rep (Validated (GenTx (SimpleBlock c ext))) x #

toRep (Validated (GenTx (SimpleBlock c ext))) x → Validated (GenTx (SimpleBlock c ext)) #

Generic (GenTx (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (GenTx (SimpleBlock c ext)) ∷ TypeType #

Methods

fromGenTx (SimpleBlock c ext) → Rep (GenTx (SimpleBlock c ext)) x #

toRep (GenTx (SimpleBlock c ext)) x → GenTx (SimpleBlock c ext) #

Generic (TxId (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (TxId (GenTx (SimpleBlock c ext))) ∷ TypeType #

Methods

fromTxId (GenTx (SimpleBlock c ext)) → Rep (TxId (GenTx (SimpleBlock c ext))) x #

toRep (TxId (GenTx (SimpleBlock c ext))) x → TxId (GenTx (SimpleBlock c ext)) #

Show (Validated (GenTx (SimpleBlock p c))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Show (GenTx (SimpleBlock p c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showsPrecIntGenTx (SimpleBlock p c) → ShowS #

showGenTx (SimpleBlock p c) → String #

showList ∷ [GenTx (SimpleBlock p c)] → ShowS #

Show (TxId (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showsPrecIntTxId (GenTx (SimpleBlock c ext)) → ShowS #

showTxId (GenTx (SimpleBlock c ext)) → String #

showList ∷ [TxId (GenTx (SimpleBlock c ext))] → ShowS #

Eq (Validated (GenTx (SimpleBlock c ext))) Source # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

compareValidated (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 #

maxValidated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) #

minValidated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) #

Ord (GenTx (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

compareGenTx (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 #

maxGenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) #

minGenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) #

Ord (TxId (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

compareTxId (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 #

maxTxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) #

minTxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) #

(Typeable p, Typeable c) ⇒ NoThunks (Validated (GenTx (SimpleBlock p c))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

(Typeable p, Typeable c) ⇒ NoThunks (GenTx (SimpleBlock p c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

NoThunks (TxId (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

HasTxId (GenTx (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

txIdGenTx (SimpleBlock c ext) → TxId (GenTx (SimpleBlock c ext)) Source #

Condense (GenTx (SimpleBlock p c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

condenseGenTx (SimpleBlock p c) → String Source #

Condense (GenTxId (SimpleBlock p c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

condenseGenTxId (SimpleBlock p c) → String Source #

HasMockTxs (GenTx (SimpleBlock p c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

getMockTxsGenTx (SimpleBlock p c) → [Tx] Source #

Serialise (GenTx (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Serialise (TxId (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

SerialiseNodeToClient (MockBlock ext) (GenTx (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

SerialiseNodeToClient (MockBlock ext) (GenTxId (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

SerialiseNodeToNode (MockBlock ext) (GenTx (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

SerialiseNodeToNode (MockBlock ext) (GenTxId (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

type Rep (Validated (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (Validated (GenTx (SimpleBlock c ext))) = Rep (GenTx (SimpleBlock c ext))
type Rep (GenTx (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (GenTx (SimpleBlock c ext)) = D1 ('MetaData "GenTx" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.18.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 # 
Instance details

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.18.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "SimpleGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSimpleGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxId)))
newtype Validated (GenTx (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

newtype TxId (GenTx (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

data GenTx (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

data family BlockQuery blk ∷ TypeType Source #

Different queries supported by the ledger, indexed by the result type.

Instances

Instances details
SameDepIndex (BlockQuery (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

sameDepIndexBlockQuery (SimpleBlock c ext) a → BlockQuery (SimpleBlock c ext) b → Maybe (a :~: b) Source #

(SimpleCrypto c, Typeable ext) ⇒ ShowQuery (BlockQuery (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showResultBlockQuery (SimpleBlock c ext) result → result → String Source #

SerialiseResult (MockBlock ext) (BlockQuery (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Methods

encodeResultCodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → BlockQuery (MockBlock ext) result → result → Encoding Source #

decodeResultCodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → BlockQuery (MockBlock ext) result → ∀ s. Decoder s result Source #

SerialiseNodeToClient (MockBlock ext) (SomeSecond BlockQuery (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Show (BlockQuery (SimpleBlock c ext) result) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showsPrecIntBlockQuery (SimpleBlock c ext) result → ShowS #

showBlockQuery (SimpleBlock c ext) result → String #

showList ∷ [BlockQuery (SimpleBlock c ext) result] → ShowS #

(Typeable c, Typeable ext) ⇒ ShowProxy (BlockQuery (SimpleBlock c ext) ∷ TypeType) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

(∀ result. Show (BlockQuery blk result)) ⇒ Show (SomeSecond BlockQuery blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Query

SameDepIndex (BlockQuery blk) ⇒ Eq (SomeSecond BlockQuery blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Query

data BlockQuery (SimpleBlock c ext) result Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

data BlockQuery (SimpleBlock c ext) result where

data MockState blk Source #

Constructors

MockState 

Fields

Instances

Instances details
Generic (MockState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.State

Associated Types

type Rep (MockState blk) ∷ TypeType #

Methods

fromMockState blk → Rep (MockState blk) x #

toRep (MockState blk) x → MockState blk #

StandardHash blk ⇒ Show (MockState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.State

Methods

showsPrecIntMockState blk → ShowS #

showMockState blk → String #

showList ∷ [MockState blk] → ShowS #

StandardHash blk ⇒ Eq (MockState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.State

Methods

(==)MockState blk → MockState blk → Bool #

(/=)MockState blk → MockState blk → Bool #

StandardHash blk ⇒ NoThunks (MockState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.State

Serialise (HeaderHash blk) ⇒ Serialise (MockState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.State

type Rep (MockState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.State

type Rep (MockState blk) = D1 ('MetaData "MockState" "Ouroboros.Consensus.Mock.Ledger.State" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" '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)))))

type AddrDist = Map Addr NodeId Source #

Mapping from addresses to node IDs

This is needed in order to assign stake to nodes.

type SimpleBlock c ext = SimpleBlock' c ext ext Source #

data SimpleBlock' c ext ext' Source #

Constructors

SimpleBlock 

Fields

Instances

Instances details
Serialise ext ⇒ ReconstructNestedCtxt Header (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

(Typeable c, Typeable ext, Typeable ext') ⇒ ShowProxy (Header (SimpleBlock' c ext ext') ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showProxyProxy (Header (SimpleBlock' c ext ext')) → String Source #

(Typeable c, Typeable ext) ⇒ ShowProxy (GenTx (SimpleBlock c ext) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showProxyProxy (GenTx (SimpleBlock c ext)) → String Source #

(Typeable c, Typeable ext) ⇒ ShowProxy (TxId (GenTx (SimpleBlock c ext)) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showProxyProxy (TxId (GenTx (SimpleBlock c ext))) → String Source #

HasNestedContent f (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Methods

unnest ∷ f (SimpleBlock c ext) → DepPair (NestedCtxt f (SimpleBlock c ext)) Source #

nestDepPair (NestedCtxt f (SimpleBlock c ext)) → f (SimpleBlock c ext) Source #

(SimpleCrypto c, Typeable ext, Typeable ext') ⇒ StandardHash (SimpleBlock' c ext ext' ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

(Typeable c, Typeable ext, Typeable ext') ⇒ ShowProxy (SimpleBlock' c ext ext' ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showProxyProxy (SimpleBlock' c ext ext') → String Source #

Generic (BlockConfig (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (BlockConfig (SimpleBlock c ext)) ∷ TypeType #

Methods

fromBlockConfig (SimpleBlock c ext) → Rep (BlockConfig (SimpleBlock c ext)) x #

toRep (BlockConfig (SimpleBlock c ext)) x → BlockConfig (SimpleBlock c ext) #

Generic (CodecConfig (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (CodecConfig (SimpleBlock c ext)) ∷ TypeType #

Methods

fromCodecConfig (SimpleBlock c ext) → Rep (CodecConfig (SimpleBlock c ext)) x #

toRep (CodecConfig (SimpleBlock c ext)) x → CodecConfig (SimpleBlock c ext) #

Generic (Header (SimpleBlock' c ext ext')) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (Header (SimpleBlock' c ext ext')) ∷ TypeType #

Methods

fromHeader (SimpleBlock' c ext ext') → Rep (Header (SimpleBlock' c ext ext')) x #

toRep (Header (SimpleBlock' c ext ext')) x → Header (SimpleBlock' c ext ext') #

Generic (StorageConfig (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (StorageConfig (SimpleBlock c ext)) ∷ TypeType #

Methods

fromStorageConfig (SimpleBlock c ext) → Rep (StorageConfig (SimpleBlock c ext)) x #

toRep (StorageConfig (SimpleBlock c ext)) x → StorageConfig (SimpleBlock c ext) #

Generic (Validated (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (Validated (GenTx (SimpleBlock c ext))) ∷ TypeType #

Methods

fromValidated (GenTx (SimpleBlock c ext)) → Rep (Validated (GenTx (SimpleBlock c ext))) x #

toRep (Validated (GenTx (SimpleBlock c ext))) x → Validated (GenTx (SimpleBlock c ext)) #

Generic (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (LedgerState (SimpleBlock c ext)) ∷ TypeType #

Methods

fromLedgerState (SimpleBlock c ext) → Rep (LedgerState (SimpleBlock c ext)) x #

toRep (LedgerState (SimpleBlock c ext)) x → LedgerState (SimpleBlock c ext) #

Generic (GenTx (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (GenTx (SimpleBlock c ext)) ∷ TypeType #

Methods

fromGenTx (SimpleBlock c ext) → Rep (GenTx (SimpleBlock c ext)) x #

toRep (GenTx (SimpleBlock c ext)) x → GenTx (SimpleBlock c ext) #

Generic (TxId (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (TxId (GenTx (SimpleBlock c ext))) ∷ TypeType #

Methods

fromTxId (GenTx (SimpleBlock c ext)) → Rep (TxId (GenTx (SimpleBlock c ext))) x #

toRep (TxId (GenTx (SimpleBlock c ext))) x → TxId (GenTx (SimpleBlock c ext)) #

Generic (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (Ticked (LedgerState (SimpleBlock c ext))) ∷ TypeType #

Methods

fromTicked (LedgerState (SimpleBlock c ext)) → Rep (Ticked (LedgerState (SimpleBlock c ext))) x #

toRep (Ticked (LedgerState (SimpleBlock c ext))) x → Ticked (LedgerState (SimpleBlock c ext)) #

(SimpleCrypto c, Show ext', Typeable ext) ⇒ Show (Header (SimpleBlock' c ext ext')) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showsPrecIntHeader (SimpleBlock' c ext ext') → ShowS #

showHeader (SimpleBlock' c ext ext') → String #

showList ∷ [Header (SimpleBlock' c ext ext')] → ShowS #

Show (Validated (GenTx (SimpleBlock p c))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

(SimpleCrypto c, Typeable ext) ⇒ Show (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showsPrecIntLedgerState (SimpleBlock c ext) → ShowS #

showLedgerState (SimpleBlock c ext) → String #

showList ∷ [LedgerState (SimpleBlock c ext)] → ShowS #

Show (GenTx (SimpleBlock p c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showsPrecIntGenTx (SimpleBlock p c) → ShowS #

showGenTx (SimpleBlock p c) → String #

showList ∷ [GenTx (SimpleBlock p c)] → ShowS #

Show (TxId (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showsPrecIntTxId (GenTx (SimpleBlock c ext)) → ShowS #

showTxId (GenTx (SimpleBlock c ext)) → String #

showList ∷ [TxId (GenTx (SimpleBlock c ext))] → ShowS #

(SimpleCrypto c, Typeable ext) ⇒ Show (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

(SimpleCrypto c, Eq ext', Typeable ext) ⇒ Eq (Header (SimpleBlock' c ext ext')) Source # 
Instance details

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 # 
Instance details

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 #

(SimpleCrypto c, Typeable ext) ⇒ Eq (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

(==)LedgerState (SimpleBlock c ext) → LedgerState (SimpleBlock c ext) → Bool #

(/=)LedgerState (SimpleBlock c ext) → LedgerState (SimpleBlock c ext) → Bool #

Eq (GenTx (SimpleBlock c ext)) Source # 
Instance details

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 # 
Instance details

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 #

(SimpleCrypto c, Typeable ext) ⇒ Eq (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

(==)Ticked (LedgerState (SimpleBlock c ext)) → Ticked (LedgerState (SimpleBlock c ext)) → Bool #

(/=)Ticked (LedgerState (SimpleBlock c ext)) → Ticked (LedgerState (SimpleBlock c ext)) → Bool #

Ord (Validated (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

compareValidated (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 #

maxValidated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) #

minValidated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) → Validated (GenTx (SimpleBlock c ext)) #

Ord (GenTx (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

compareGenTx (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 #

maxGenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) #

minGenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) → GenTx (SimpleBlock c ext) #

Ord (TxId (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

compareTxId (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 #

maxTxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) #

minTxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) → TxId (GenTx (SimpleBlock c ext)) #

NoThunks (BlockConfig (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

NoThunks (CodecConfig (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

(SimpleCrypto c, NoThunks ext', Typeable ext) ⇒ NoThunks (Header (SimpleBlock' c ext ext')) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

noThunksContextHeader (SimpleBlock' c ext ext') → IO (Maybe ThunkInfo) Source #

wNoThunksContextHeader (SimpleBlock' c ext ext') → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (Header (SimpleBlock' c ext ext')) → String Source #

NoThunks (StorageConfig (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

(Typeable p, Typeable c) ⇒ NoThunks (Validated (GenTx (SimpleBlock p c))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

(SimpleCrypto c, Typeable ext) ⇒ NoThunks (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

(Typeable p, Typeable c) ⇒ NoThunks (GenTx (SimpleBlock p c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

NoThunks (TxId (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

(SimpleCrypto c, Typeable ext) ⇒ NoThunks (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

GetTip (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

GetTip (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

MockProtocolSpecific c ext ⇒ IsLedger (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type LedgerErr (LedgerState (SimpleBlock c ext)) Source #

type AuxLedgerEvent (LedgerState (SimpleBlock c ext)) Source #

HasTxId (GenTx (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

txIdGenTx (SimpleBlock c ext) → TxId (GenTx (SimpleBlock c ext)) Source #

SimpleCrypto c ⇒ LedgerSupportsProtocol (SimplePraosRuleBlock c) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

(Serialise ext, Typeable ext) ⇒ SerialiseNodeToClientConstraints (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ SerialiseNodeToNodeConstraints (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

(Serialise ext, RunMockBlock SimpleMockCrypto ext) ⇒ SerialiseDiskConstraints (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

(Serialise ext, Typeable ext) ⇒ HasBinaryBlockInfo (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Condense ext' ⇒ Condense (Header (SimpleBlock' c ext ext')) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

condenseHeader (SimpleBlock' c ext ext') → String Source #

Condense (GenTx (SimpleBlock p c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

condenseGenTx (SimpleBlock p c) → String Source #

Condense (GenTxId (SimpleBlock p c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

condenseGenTxId (SimpleBlock p c) → String Source #

SameDepIndex (BlockQuery (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

sameDepIndexBlockQuery (SimpleBlock c ext) a → BlockQuery (SimpleBlock c ext) b → Maybe (a :~: b) Source #

HasMockTxs (GenTx (SimpleBlock p c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

getMockTxsGenTx (SimpleBlock p c) → [Tx] Source #

(SimpleCrypto c, Typeable ext, Typeable ext') ⇒ HasHeader (Header (SimpleBlock' c ext ext')) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

getHeaderFieldsHeader (SimpleBlock' c ext ext') → HeaderFields (Header (SimpleBlock' c ext ext')) Source #

(SimpleCrypto c, Typeable ext) ⇒ ShowQuery (BlockQuery (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showResultBlockQuery (SimpleBlock c ext) result → result → String Source #

(SimpleCrypto c, Serialise ext') ⇒ Serialise (Header (SimpleBlock' c ext ext')) Source #

Custom Serialise instance that doesn't serialise the hash

Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

encodeHeader (SimpleBlock' c ext ext') → Encoding Source #

decodeDecoder s (Header (SimpleBlock' c ext ext')) Source #

encodeList ∷ [Header (SimpleBlock' c ext ext')] → Encoding Source #

decodeListDecoder s [Header (SimpleBlock' c ext ext')] Source #

Serialise (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Serialise (GenTx (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Serialise (TxId (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

SerialiseNodeToClient (MockBlock ext) SlotNo Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

DecodeDisk (SimplePraosRuleBlock c) () Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

EncodeDisk (SimplePraosRuleBlock c) () Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

SerialiseNodeToClient (MockBlock ext) (GenTx (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

SerialiseNodeToClient (MockBlock ext) (GenTxId (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

SerialiseNodeToClient (MockBlock ext) (MockError (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ SerialiseNodeToClient (MockBlock ext) (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ SerialiseNodeToNode (MockBlock ext) (Header (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

SerialiseNodeToNode (MockBlock ext) (GenTx (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

SerialiseNodeToNode (MockBlock ext) (GenTxId (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ SerialiseNodeToNode (MockBlock ext) (SerialisedHeader (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ SerialiseNodeToNode (MockBlock ext) (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

SerialiseResult (MockBlock ext) (BlockQuery (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Methods

encodeResultCodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → BlockQuery (MockBlock ext) result → result → Encoding Source #

decodeResultCodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → BlockQuery (MockBlock ext) result → ∀ s. Decoder s result Source #

DecodeDisk (MockBlock ext) (AnnTip (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Methods

decodeDiskCodecConfig (MockBlock ext) → ∀ s. Decoder s (AnnTip (MockBlock ext)) Source #

DecodeDisk (MockBlock ext) (LedgerState (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Methods

decodeDiskCodecConfig (MockBlock ext) → ∀ s. Decoder s (LedgerState (MockBlock ext)) Source #

Serialise ext ⇒ DecodeDiskDep (NestedCtxt Header) (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Methods

decodeDiskDepCodecConfig (MockBlock ext) → NestedCtxt Header (MockBlock ext) a → ∀ s. Decoder s (ByteString → a) Source #

Serialise ext ⇒ DecodeDiskDepIx (NestedCtxt Header) (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ EncodeDisk (MockBlock ext) (Header (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

EncodeDisk (MockBlock ext) (AnnTip (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

EncodeDisk (MockBlock ext) (LedgerState (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ EncodeDisk (MockBlock ext) (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ EncodeDiskDep (NestedCtxt Header) (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ EncodeDiskDepIx (NestedCtxt Header) (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

MockProtocolSpecific c ext ⇒ ApplyBlock (LedgerState (SimpleBlock c ext)) (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

SerialiseNodeToClient (MockBlock ext) (Serialised (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

SerialiseNodeToNode (MockBlock ext) (Serialised (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ DecodeDisk (MockBlock ext) (ByteStringHeader (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Methods

decodeDiskCodecConfig (MockBlock ext) → ∀ s. Decoder s (ByteStringHeader (MockBlock ext)) Source #

Serialise ext ⇒ DecodeDisk (MockBlock ext) (ByteStringMockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Methods

decodeDiskCodecConfig (MockBlock ext) → ∀ s. Decoder s (ByteStringMockBlock ext) Source #

SerialiseNodeToClient (MockBlock ext) (SomeSecond BlockQuery (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Show (BlockQuery (SimpleBlock c ext) result) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showsPrecIntBlockQuery (SimpleBlock c ext) result → ShowS #

showBlockQuery (SimpleBlock c ext) result → String #

showList ∷ [BlockQuery (SimpleBlock c ext) result] → ShowS #

(SimpleCrypto c, Typeable ext) ⇒ GetPrevHash (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

(BlockSupportsProtocol (SimpleBlock c ext), Show (SelectView (BlockProtocol (SimpleBlock c ext)))) ⇒ BlockSupportsDiffusionPipelining (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node

BlockSupportsMetrics (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node

(SimpleCrypto c, PraosCrypto c', Signable (PraosKES c') (SignedSimplePraos c c')) ⇒ BlockSupportsProtocol (SimpleBlock c (SimplePraosExt c c')) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

SimpleCrypto c ⇒ BlockSupportsProtocol (SimpleBlock c SimplePraosRuleExt) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

(SimpleCrypto c, BftCrypto c', Signable (BftDSIGN c') (SignedSimpleBft c c')) ⇒ BlockSupportsProtocol (SimpleBftBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

(SimpleCrypto c, Signable MockDSIGN (SignedSimplePBft c PBftMockCrypto)) ⇒ BlockSupportsProtocol (SimplePBftBlock c PBftMockCrypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

RunMockBlock c ext ⇒ ConfigSupportsNode (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Abstract

HasHardForkHistory (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type HardForkIndices (SimpleBlock c ext) ∷ [Type] Source #

(SimpleCrypto c, Typeable ext) ⇒ BasicEnvelopeValidation (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

(SimpleCrypto c, Typeable ext) ⇒ HasAnnTip (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type TipInfo (SimpleBlock c ext) Source #

Methods

getTipInfoHeader (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 # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type OtherHeaderEnvelopeError (SimpleBlock c ext) Source #

MockProtocolSpecific c ext ⇒ UpdateLedger (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

MockProtocolSpecific c ext ⇒ CommonProtocolParams (SimpleBlock c ext) Source #

Dummy values

Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

InspectLedger (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type LedgerWarning (SimpleBlock c ext) Source #

type LedgerUpdate (SimpleBlock c ext) Source #

MockProtocolSpecific c ext ⇒ BlockSupportsLedgerQuery (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

answerBlockQueryExtLedgerCfg (SimpleBlock c ext) → BlockQuery (SimpleBlock c ext) result → ExtLedgerState (SimpleBlock c ext) → result Source #

HasTxs (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

extractTxsSimpleBlock c ext → [GenTx (SimpleBlock c ext)] Source #

MockProtocolSpecific c ext ⇒ LedgerSupportsMempool (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

LedgerSupportsPeerSelection (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

(SimpleCrypto c, BftCrypto c', Signable (BftDSIGN c') (SignedSimpleBft c c')) ⇒ LedgerSupportsProtocol (SimpleBftBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

(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)

Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

(SimpleCrypto c, PraosCrypto c', Signable (PraosKES c') (SignedSimplePraos c c')) ⇒ LedgerSupportsProtocol (SimplePraosBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

NodeInitStorage (SimpleBlock SimpleMockCrypto ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node

HasNetworkProtocolVersion (SimpleBlock SimpleMockCrypto ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node

SupportedNetworkProtocolVersion (SimpleBlock SimpleMockCrypto ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node

(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 # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node

SignedHeader (SimpleBftHeader c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

SignedHeader (SimplePBftHeader c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

PraosCrypto c' ⇒ SignedHeader (SimplePraosHeader c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

SameDepIndex (NestedCtxt_ (SimpleBlock c ext) f) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Methods

sameDepIndexNestedCtxt_ (SimpleBlock c ext) f a → NestedCtxt_ (SimpleBlock c ext) f b → Maybe (a :~: b) Source #

TrivialDependency (NestedCtxt_ (SimpleBlock c ext) f) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Associated Types

type TrivialIndex (NestedCtxt_ (SimpleBlock c ext) f) Source #

DecodeDisk (SimpleBftBlock c c') () Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

Methods

decodeDiskCodecConfig (SimpleBftBlock c c') → ∀ s. Decoder s () Source #

EncodeDisk (SimpleBftBlock c c') () Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

Methods

encodeDiskCodecConfig (SimpleBftBlock c c') → () → Encoding Source #

(Serialise (PBftVerKeyHash c'), PBftCrypto c') ⇒ DecodeDisk (SimplePBftBlock c c') (PBftState c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

Methods

decodeDiskCodecConfig (SimplePBftBlock c c') → ∀ s. Decoder s (PBftState c') Source #

PraosCrypto c' ⇒ DecodeDisk (SimplePraosBlock c c') (PraosChainDepState c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

(Serialise (PBftVerKeyHash c'), PBftCrypto c') ⇒ EncodeDisk (SimplePBftBlock c c') (PBftState c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

PraosCrypto c' ⇒ EncodeDisk (SimplePraosBlock c c') (PraosChainDepState c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

(Typeable c, Typeable ext) ⇒ ShowProxy (BlockQuery (SimpleBlock c ext) ∷ TypeType) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Generic (SimpleBlock' c ext ext') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (SimpleBlock' c ext ext') ∷ TypeType #

Methods

fromSimpleBlock' c ext ext' → Rep (SimpleBlock' c ext ext') x #

toRep (SimpleBlock' c ext ext') x → SimpleBlock' c ext ext' #

Show (NestedCtxt_ (SimpleBlock c ext) f a) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Methods

showsPrecIntNestedCtxt_ (SimpleBlock c ext) f a → ShowS #

showNestedCtxt_ (SimpleBlock c ext) f a → String #

showList ∷ [NestedCtxt_ (SimpleBlock c ext) f a] → ShowS #

(SimpleCrypto c, Show ext', Typeable ext) ⇒ Show (SimpleBlock' c ext ext') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showsPrecIntSimpleBlock' c ext ext' → ShowS #

showSimpleBlock' c ext ext' → String #

showList ∷ [SimpleBlock' c ext ext'] → ShowS #

(SimpleCrypto c, Eq ext', Typeable ext) ⇒ Eq (SimpleBlock' c ext ext') Source # 
Instance details

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 ⇒ ConvertRawHash (SimpleBlock' c ext ext') Source # 
Instance details

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') → ByteStringHeaderHash (SimpleBlock' c ext ext') Source #

toShortRawHash ∷ proxy (SimpleBlock' c ext ext') → HeaderHash (SimpleBlock' c ext ext') → ShortByteString Source #

fromShortRawHash ∷ proxy (SimpleBlock' c ext ext') → ShortByteStringHeaderHash (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 # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

getHeaderSimpleBlock' c ext ext' → Header (SimpleBlock' c ext ext') Source #

blockMatchesHeaderHeader (SimpleBlock' c ext ext') → SimpleBlock' c ext ext' → Bool Source #

headerIsEBBHeader (SimpleBlock' c ext ext') → Maybe EpochNo Source #

Condense ext' ⇒ Condense (SimpleBlock' c ext ext') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

condenseSimpleBlock' c ext ext' → String Source #

HasMockTxs (SimpleBlock' c ext ext') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

getMockTxsSimpleBlock' c ext ext' → [Tx] Source #

(SimpleCrypto c, Typeable ext, Typeable ext') ⇒ HasHeader (SimpleBlock' c ext ext') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

getHeaderFieldsSimpleBlock' c ext ext' → HeaderFields (SimpleBlock' c ext ext') Source #

(SimpleCrypto c, Serialise ext') ⇒ Serialise (SimpleBlock' c ext ext') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

encodeSimpleBlock' c ext ext' → Encoding Source #

decodeDecoder s (SimpleBlock' c ext ext') Source #

encodeList ∷ [SimpleBlock' c ext ext'] → Encoding Source #

decodeListDecoder s [SimpleBlock' c ext ext'] Source #

type HeaderHash (SimpleBlock' c ext ext' ∷ Type) Source # 
Instance details

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 # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (BlockConfig (SimpleBlock c ext)) = D1 ('MetaData "BlockConfig" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleBlockConfig" 'PrefixI 'False) (U1TypeType))
type Rep (CodecConfig (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (CodecConfig (SimpleBlock c ext)) = D1 ('MetaData "CodecConfig" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleCodecConfig" 'PrefixI 'False) (U1TypeType))
type Rep (Header (SimpleBlock' c ext ext')) Source # 
Instance details

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.18.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 # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (StorageConfig (SimpleBlock c ext)) = D1 ('MetaData "StorageConfig" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleStorageConfig" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SecurityParam)))
type Rep (Validated (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (Validated (GenTx (SimpleBlock c ext))) = Rep (GenTx (SimpleBlock c ext))
type Rep (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (LedgerState (SimpleBlock c ext)) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "SimpleLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleLedgerState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MockState (SimpleBlock c ext)))))
type Rep (GenTx (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (GenTx (SimpleBlock c ext)) = D1 ('MetaData "GenTx" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.18.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 # 
Instance details

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.18.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "SimpleGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSimpleGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxId)))
type Rep (Ticked (LedgerState (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (Ticked (LedgerState (SimpleBlock c ext))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "TickedSimpleLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTickedSimpleLedgerState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerState (SimpleBlock c ext)))))
type BlockProtocol (SimplePraosRuleBlock c) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

type CannotForge (SimplePraosRuleBlock c) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

type ForgeStateInfo (SimplePraosRuleBlock c) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

type ForgeStateUpdateError (SimplePraosRuleBlock c) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

newtype Validated (GenTx (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type AuxLedgerEvent (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type LedgerCfg (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type LedgerErr (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

newtype TxId (GenTx (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

newtype Ticked (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

data BlockConfig (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type BlockProtocol (SimpleBftBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

type BlockProtocol (SimplePBftBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

type BlockProtocol (SimplePraosBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

data CodecConfig (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

data StorageConfig (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type CannotForge (SimpleBftBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

type CannotForge (SimplePBftBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

type CannotForge (SimplePraosBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

type ForgeStateInfo (SimpleBftBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

type ForgeStateInfo (SimplePBftBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

type ForgeStateInfo (SimplePraosBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

type ForgeStateUpdateError (SimpleBftBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

type ForgeStateUpdateError (SimplePBftBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

type ForgeStateUpdateError (SimplePraosBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

data NestedCtxt_ (SimpleBlock c ext) f a Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

data NestedCtxt_ (SimpleBlock c ext) f a where
type TentativeHeaderState (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node

type TentativeHeaderView (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node

type HardForkIndices (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type HardForkIndices (SimpleBlock c ext) = '[SimpleBlock c ext]
type OtherHeaderEnvelopeError (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type TipInfo (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type TipInfo (SimpleBlock c ext) = HeaderHash (SimpleBlock c ext)
newtype LedgerState (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type LedgerUpdate (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type LedgerWarning (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

data BlockQuery (SimpleBlock c ext) result Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

data BlockQuery (SimpleBlock c ext) result where
type ApplyTxErr (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

data GenTx (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type BlockNodeToClientVersion (SimpleBlock SimpleMockCrypto ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node

type BlockNodeToNodeVersion (SimpleBlock SimpleMockCrypto ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node

type Signed (SimpleBftHeader c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

type Signed (SimplePBftHeader c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

type Signed (SimplePraosHeader c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

type TrivialIndex (NestedCtxt_ (SimpleBlock c ext) f) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

type TrivialIndex (NestedCtxt_ (SimpleBlock c ext) f) = f (SimpleBlock c ext)
type Rep (SimpleBlock' c ext ext') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (SimpleBlock' c ext ext') = D1 ('MetaData "SimpleBlock'" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.18.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 # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

data SimpleBody Source #

Constructors

SimpleBody 

Fields

Instances

Instances details
Generic SimpleBody Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep SimpleBodyTypeType #

Show SimpleBody Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

ToCBOR SimpleBody Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

toCBORSimpleBodyEncoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy SimpleBodySize Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [SimpleBody] → Size Source #

Eq SimpleBody Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

(==)SimpleBodySimpleBodyBool #

(/=)SimpleBodySimpleBodyBool #

HasMockTxs SimpleBody Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

getMockTxsSimpleBody → [Tx] Source #

Serialise SimpleBody Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep SimpleBody Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep SimpleBody = D1 ('MetaData "SimpleBody" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleBody" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleTxs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tx])))

class (HashAlgorithm (SimpleHash c), Typeable c) ⇒ SimpleCrypto c Source #

Associated Types

type SimpleHash c ∷ Type Source #

type SimpleHeader c ext = Header (SimpleBlock c ext) Source #

data SimpleStdHeader c ext Source #

Instances

Instances details
Generic (SimpleStdHeader c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (SimpleStdHeader c ext) ∷ TypeType #

Methods

fromSimpleStdHeader c ext → Rep (SimpleStdHeader c ext) x #

toRep (SimpleStdHeader c ext) x → SimpleStdHeader c ext #

(SimpleCrypto c, Typeable ext) ⇒ Show (SimpleStdHeader c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showsPrecIntSimpleStdHeader c ext → ShowS #

showSimpleStdHeader c ext → String #

showList ∷ [SimpleStdHeader c ext] → ShowS #

(SimpleCrypto c, Typeable ext) ⇒ Eq (SimpleStdHeader c ext) Source # 
Instance details

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 # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Serialise (SimpleStdHeader c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (SimpleStdHeader c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (SimpleStdHeader c ext) = D1 ('MetaData "SimpleStdHeader" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.18.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)))))

data SimpleLedgerConfig c ext Source #

Constructors

SimpleLedgerConfig 

Fields

Instances

Instances details
Generic (SimpleLedgerConfig c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (SimpleLedgerConfig c ext) ∷ TypeType #

Methods

fromSimpleLedgerConfig c ext → Rep (SimpleLedgerConfig c ext) x #

toRep (SimpleLedgerConfig c ext) x → SimpleLedgerConfig c ext #

Show (MockLedgerConfig c ext) ⇒ Show (SimpleLedgerConfig c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showsPrecIntSimpleLedgerConfig c ext → ShowS #

showSimpleLedgerConfig c ext → String #

showList ∷ [SimpleLedgerConfig c ext] → ShowS #

NoThunks (MockLedgerConfig c ext) ⇒ NoThunks (SimpleLedgerConfig c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (SimpleLedgerConfig c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (SimpleLedgerConfig c ext) = D1 ('MetaData "SimpleLedgerConfig" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.18.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)))

data SimpleMockCrypto Source #

Instances

Instances details
SimpleCrypto SimpleMockCrypto Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type SimpleHash SimpleMockCrypto Source #

Serialise ext ⇒ ReconstructNestedCtxt Header (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

(Serialise ext, Typeable ext) ⇒ SerialiseNodeToClientConstraints (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ SerialiseNodeToNodeConstraints (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

(Serialise ext, RunMockBlock SimpleMockCrypto ext) ⇒ SerialiseDiskConstraints (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

(Serialise ext, Typeable ext) ⇒ HasBinaryBlockInfo (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

SerialiseNodeToClient (MockBlock ext) SlotNo Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

SerialiseNodeToClient (MockBlock ext) (GenTx (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

SerialiseNodeToClient (MockBlock ext) (GenTxId (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

SerialiseNodeToClient (MockBlock ext) (MockError (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ SerialiseNodeToClient (MockBlock ext) (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ SerialiseNodeToNode (MockBlock ext) (Header (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

SerialiseNodeToNode (MockBlock ext) (GenTx (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

SerialiseNodeToNode (MockBlock ext) (GenTxId (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ SerialiseNodeToNode (MockBlock ext) (SerialisedHeader (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ SerialiseNodeToNode (MockBlock ext) (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

SerialiseResult (MockBlock ext) (BlockQuery (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Methods

encodeResultCodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → BlockQuery (MockBlock ext) result → result → Encoding Source #

decodeResultCodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → BlockQuery (MockBlock ext) result → ∀ s. Decoder s result Source #

DecodeDisk (MockBlock ext) (AnnTip (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Methods

decodeDiskCodecConfig (MockBlock ext) → ∀ s. Decoder s (AnnTip (MockBlock ext)) Source #

DecodeDisk (MockBlock ext) (LedgerState (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Methods

decodeDiskCodecConfig (MockBlock ext) → ∀ s. Decoder s (LedgerState (MockBlock ext)) Source #

Serialise ext ⇒ DecodeDiskDep (NestedCtxt Header) (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Methods

decodeDiskDepCodecConfig (MockBlock ext) → NestedCtxt Header (MockBlock ext) a → ∀ s. Decoder s (ByteString → a) Source #

Serialise ext ⇒ DecodeDiskDepIx (NestedCtxt Header) (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ EncodeDisk (MockBlock ext) (Header (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

EncodeDisk (MockBlock ext) (AnnTip (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

EncodeDisk (MockBlock ext) (LedgerState (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ EncodeDisk (MockBlock ext) (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ EncodeDiskDep (NestedCtxt Header) (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ EncodeDiskDepIx (NestedCtxt Header) (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

SerialiseNodeToClient (MockBlock ext) (Serialised (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

SerialiseNodeToNode (MockBlock ext) (Serialised (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ext ⇒ DecodeDisk (MockBlock ext) (ByteStringHeader (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Methods

decodeDiskCodecConfig (MockBlock ext) → ∀ s. Decoder s (ByteStringHeader (MockBlock ext)) Source #

Serialise ext ⇒ DecodeDisk (MockBlock ext) (ByteStringMockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Methods

decodeDiskCodecConfig (MockBlock ext) → ∀ s. Decoder s (ByteStringMockBlock ext) Source #

SerialiseNodeToClient (MockBlock ext) (SomeSecond BlockQuery (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

NodeInitStorage (SimpleBlock SimpleMockCrypto ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node

HasNetworkProtocolVersion (SimpleBlock SimpleMockCrypto ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node

SupportedNetworkProtocolVersion (SimpleBlock SimpleMockCrypto ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node

(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 # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node

type SimpleHash SimpleMockCrypto Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type BlockNodeToClientVersion (SimpleBlock SimpleMockCrypto ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node

type BlockNodeToNodeVersion (SimpleBlock SimpleMockCrypto ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node

data SignedSimpleBft c c' Source #

Part of the block that gets signed

Instances

Instances details
Generic (SignedSimpleBft c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

Associated Types

type Rep (SignedSimpleBft c c') ∷ TypeType #

Methods

fromSignedSimpleBft c c' → Rep (SignedSimpleBft c c') x #

toRep (SignedSimpleBft c c') x → SignedSimpleBft c c' #

(Typeable c', SimpleCrypto c) ⇒ ToCBOR (SignedSimpleBft c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

Methods

toCBORSignedSimpleBft c c' → Encoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (SignedSimpleBft c c') → Size Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [SignedSimpleBft c c'] → Size Source #

SimpleCrypto c ⇒ SignableRepresentation (SignedSimpleBft c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

SimpleCrypto c ⇒ Serialise (SignedSimpleBft c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

type Rep (SignedSimpleBft c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

type Rep (SignedSimpleBft c c') = D1 ('MetaData "SignedSimpleBft" "Ouroboros.Consensus.Mock.Ledger.Block.BFT" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SignedSimpleBft" 'PrefixI 'True) (S1 ('MetaSel ('Just "signedSimpleBft") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SimpleStdHeader c (SimpleBftExt c c')))))

type SimpleBftBlock c c' = SimpleBlock c (SimpleBftExt c c') Source #

Simple block extended with the fields required for BFT

c is crypto used for the block itself c' is crypto used for the consensus protocol

newtype SimpleBftExt c c' Source #

Block extension required for BFT

Constructors

SimpleBftExt 

Fields

Instances

Instances details
(SimpleCrypto c, Typeable c') ⇒ MockProtocolSpecific c (SimpleBftExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

Associated Types

type MockLedgerConfig c (SimpleBftExt c c') Source #

(SimpleCrypto c, BftCrypto c') ⇒ RunMockBlock c (SimpleBftExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

BftCrypto c' ⇒ Show (SimpleBftExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

Methods

showsPrecIntSimpleBftExt c c' → ShowS #

showSimpleBftExt c c' → String #

showList ∷ [SimpleBftExt c c'] → ShowS #

BftCrypto c' ⇒ Eq (SimpleBftExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

Methods

(==)SimpleBftExt c c' → SimpleBftExt c c' → Bool #

(/=)SimpleBftExt c c' → SimpleBftExt c c' → Bool #

(BftCrypto c', Typeable c) ⇒ NoThunks (SimpleBftExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

(SimpleCrypto c, BftCrypto c', Signable (BftDSIGN c') (SignedSimpleBft c c')) ⇒ BlockSupportsProtocol (SimpleBftBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

(SimpleCrypto c, BftCrypto c', Signable (BftDSIGN c') (SignedSimpleBft c c')) ⇒ LedgerSupportsProtocol (SimpleBftBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

SignedHeader (SimpleBftHeader c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

BftCrypto c' ⇒ Condense (SimpleBftExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

Methods

condenseSimpleBftExt c c' → String Source #

BftCrypto c' ⇒ Serialise (SimpleBftExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

DecodeDisk (SimpleBftBlock c c') () Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

Methods

decodeDiskCodecConfig (SimpleBftBlock c c') → ∀ s. Decoder s () Source #

EncodeDisk (SimpleBftBlock c c') () Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

Methods

encodeDiskCodecConfig (SimpleBftBlock c c') → () → Encoding Source #

type MockLedgerConfig c (SimpleBftExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

type MockLedgerConfig c (SimpleBftExt c c') = ()
type BlockProtocol (SimpleBftBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

type CannotForge (SimpleBftBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

type ForgeStateInfo (SimpleBftBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

type ForgeStateUpdateError (SimpleBftBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

type Signed (SimpleBftHeader c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.BFT

type SimpleBftHeader c c' = SimpleHeader c (SimpleBftExt c c') Source #

Header for BFT

data SignedSimplePBft c c' Source #

Part of the block that gets signed

We just sign the standard header, i.e., without the PBFT extensions. In particular, the signature does not cover the issuer.

The signature does not cover the body explicitly, but since the standard header includes a hash of the body, the signature covers the body implicitly.

Instances

Instances details
Generic (SignedSimplePBft c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

Associated Types

type Rep (SignedSimplePBft c c') ∷ TypeType #

Methods

fromSignedSimplePBft c c' → Rep (SignedSimplePBft c c') x #

toRep (SignedSimplePBft c c') x → SignedSimplePBft c c' #

(Typeable c', SimpleCrypto c) ⇒ ToCBOR (SignedSimplePBft c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

Methods

toCBORSignedSimplePBft c c' → Encoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (SignedSimplePBft c c') → Size Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [SignedSimplePBft c c'] → Size Source #

SimpleCrypto c ⇒ SignableRepresentation (SignedSimplePBft c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

SimpleCrypto c ⇒ Serialise (SignedSimplePBft c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

type Rep (SignedSimplePBft c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

type Rep (SignedSimplePBft c c') = D1 ('MetaData "SignedSimplePBft" "Ouroboros.Consensus.Mock.Ledger.Block.PBFT" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SignedSimplePBft" 'PrefixI 'True) (S1 ('MetaSel ('Just "signedSimplePBft") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SimpleStdHeader c (SimplePBftExt c c')))))

type SimplePBftBlock c c' = SimpleBlock c (SimplePBftExt c c') Source #

Simple block extended with the fields required for PBFT

c is crypto used for the block itself c' is crypto used for the consensus protocol

newtype SimplePBftExt c c' Source #

Block extension required for PBFT

Constructors

SimplePBftExt 

Instances

Instances details
(SimpleCrypto c, PBftCrypto c') ⇒ MockProtocolSpecific c (SimplePBftExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

Associated Types

type MockLedgerConfig c (SimplePBftExt c c') Source #

(SimpleCrypto c, PBftCrypto c', Serialise (PBftVerKeyHash c')) ⇒ RunMockBlock c (SimplePBftExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

Generic (SimplePBftExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

Associated Types

type Rep (SimplePBftExt c c') ∷ TypeType #

Methods

fromSimplePBftExt c c' → Rep (SimplePBftExt c c') x #

toRep (SimplePBftExt c c') x → SimplePBftExt c c' #

PBftCrypto c' ⇒ Show (SimplePBftExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

Methods

showsPrecIntSimplePBftExt c c' → ShowS #

showSimplePBftExt c c' → String #

showList ∷ [SimplePBftExt c c'] → ShowS #

PBftCrypto c' ⇒ Eq (SimplePBftExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

Methods

(==)SimplePBftExt c c' → SimplePBftExt c c' → Bool #

(/=)SimplePBftExt c c' → SimplePBftExt c c' → Bool #

(PBftCrypto c', Typeable c) ⇒ NoThunks (SimplePBftExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

(SimpleCrypto c, Signable MockDSIGN (SignedSimplePBft c PBftMockCrypto)) ⇒ BlockSupportsProtocol (SimplePBftBlock c PBftMockCrypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

(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)

Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

SignedHeader (SimplePBftHeader c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

PBftCrypto c' ⇒ Condense (SimplePBftExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

Methods

condenseSimplePBftExt c c' → String Source #

PBftCrypto c' ⇒ Serialise (SimplePBftExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

(Serialise (PBftVerKeyHash c'), PBftCrypto c') ⇒ DecodeDisk (SimplePBftBlock c c') (PBftState c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

Methods

decodeDiskCodecConfig (SimplePBftBlock c c') → ∀ s. Decoder s (PBftState c') Source #

(Serialise (PBftVerKeyHash c'), PBftCrypto c') ⇒ EncodeDisk (SimplePBftBlock c c') (PBftState c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

type MockLedgerConfig c (SimplePBftExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

type Rep (SimplePBftExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

type Rep (SimplePBftExt c c') = D1 ('MetaData "SimplePBftExt" "Ouroboros.Consensus.Mock.Ledger.Block.PBFT" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "SimplePBftExt" 'PrefixI 'True) (S1 ('MetaSel ('Just "simplePBftExt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PBftFields c' (SignedSimplePBft c c')))))
type BlockProtocol (SimplePBftBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

type CannotForge (SimplePBftBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

type ForgeStateInfo (SimplePBftBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

type ForgeStateUpdateError (SimplePBftBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

type Signed (SimplePBftHeader c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PBFT

type SimplePBftHeader c c' = SimpleHeader c (SimplePBftExt c c') Source #

Header for PBFT

data SignedSimplePraos c c' Source #

Part of the block that gets signed

TODO: Right now we sign all of the extra Praos fields. This may or may not be needed. https://github.com/IntersectMBO/cardano-ledger/issues/530 Of course, this Praos is merely a proof of concept so it doesn't really matter either way; we include them here primarily to show that we can.

type SimplePraosBlock c c' = SimpleBlock c (SimplePraosExt c c') Source #

Simple block extended with the fields required for Praos

c is crypto used for the block itself c' is crypto used for the consensus protocol

newtype SimplePraosExt c c' Source #

Block extension required for Praos

Constructors

SimplePraosExt 

Instances

Instances details
(SimpleCrypto c, Typeable c') ⇒ MockProtocolSpecific c (SimplePraosExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

Associated Types

type MockLedgerConfig c (SimplePraosExt c c') Source #

(SimpleCrypto c, PraosCrypto c') ⇒ RunMockBlock c (SimplePraosExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

Generic (SimplePraosExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

Associated Types

type Rep (SimplePraosExt c c') ∷ TypeType #

Methods

fromSimplePraosExt c c' → Rep (SimplePraosExt c c') x #

toRep (SimplePraosExt c c') x → SimplePraosExt c c' #

PraosCrypto c' ⇒ Show (SimplePraosExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

Methods

showsPrecIntSimplePraosExt c c' → ShowS #

showSimplePraosExt c c' → String #

showList ∷ [SimplePraosExt c c'] → ShowS #

PraosCrypto c' ⇒ Eq (SimplePraosExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

Methods

(==)SimplePraosExt c c' → SimplePraosExt c c' → Bool #

(/=)SimplePraosExt c c' → SimplePraosExt c c' → Bool #

(PraosCrypto c', Typeable c) ⇒ NoThunks (SimplePraosExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

(SimpleCrypto c, PraosCrypto c', Signable (PraosKES c') (SignedSimplePraos c c')) ⇒ BlockSupportsProtocol (SimpleBlock c (SimplePraosExt c c')) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

(SimpleCrypto c, PraosCrypto c', Signable (PraosKES c') (SignedSimplePraos c c')) ⇒ LedgerSupportsProtocol (SimplePraosBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

PraosCrypto c' ⇒ SignedHeader (SimplePraosHeader c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

PraosCrypto c' ⇒ Condense (SimplePraosExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

Methods

condenseSimplePraosExt c c' → String Source #

PraosCrypto c' ⇒ Serialise (SimplePraosExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

PraosCrypto c' ⇒ DecodeDisk (SimplePraosBlock c c') (PraosChainDepState c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

PraosCrypto c' ⇒ EncodeDisk (SimplePraosBlock c c') (PraosChainDepState c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

type MockLedgerConfig c (SimplePraosExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

type Rep (SimplePraosExt c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

type Rep (SimplePraosExt c c') = D1 ('MetaData "SimplePraosExt" "Ouroboros.Consensus.Mock.Ledger.Block.Praos" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "SimplePraosExt" 'PrefixI 'True) (S1 ('MetaSel ('Just "simplePraosExt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PraosFields c' (SignedSimplePraos c c')))))
type BlockProtocol (SimplePraosBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

type CannotForge (SimplePraosBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

type ForgeStateInfo (SimplePraosBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

type ForgeStateUpdateError (SimplePraosBlock c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

type Signed (SimplePraosHeader c c') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.Praos

type SimplePraosHeader c c' = SimpleHeader c (SimplePraosExt c c') Source #

Header for Proas

type SimplePraosRuleBlock c = SimpleBlock c SimplePraosRuleExt Source #

Simple block extended with the fields required for Praos

c is crypto used for the block itself With an explicit leader schedule we need no crypto for the consensus protocol.

This is an example of a block which is not an instance of SignedBlock.

newtype SimplePraosRuleExt Source #

Required extension

The WithLeaderSchedule doesn't require anything in the block header. We add the CoreNodeId just so that we can check that the schedule matches the chain.

Instances

Instances details
Generic SimplePraosRuleExt Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

Associated Types

type Rep SimplePraosRuleExtTypeType #

Show SimplePraosRuleExt Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

Eq SimplePraosRuleExt Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

NoThunks SimplePraosRuleExt Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

Condense SimplePraosRuleExt Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

Serialise SimplePraosRuleExt Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

SimpleCrypto c ⇒ MockProtocolSpecific c SimplePraosRuleExt Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

SimpleCrypto c ⇒ RunMockBlock c SimplePraosRuleExt Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

SimpleCrypto c ⇒ LedgerSupportsProtocol (SimplePraosRuleBlock c) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

DecodeDisk (SimplePraosRuleBlock c) () Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

EncodeDisk (SimplePraosRuleBlock c) () Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

SimpleCrypto c ⇒ BlockSupportsProtocol (SimpleBlock c SimplePraosRuleExt) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

type Rep SimplePraosRuleExt Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

type Rep SimplePraosRuleExt = D1 ('MetaData "SimplePraosRuleExt" "Ouroboros.Consensus.Mock.Ledger.Block.PraosRule" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "SimplePraosRuleExt" 'PrefixI 'True) (S1 ('MetaSel ('Just "simplePraosRuleExt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CoreNodeId)))
type MockLedgerConfig c SimplePraosRuleExt Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

type BlockProtocol (SimplePraosRuleBlock c) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

type CannotForge (SimplePraosRuleBlock c) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

type ForgeStateInfo (SimplePraosRuleBlock c) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

type ForgeStateUpdateError (SimplePraosRuleBlock c) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block.PraosRule

newtype ForgeExt c ext Source #

Construct the protocol specific part of the block

This is used in forgeSimple, which takes care of the generic part of the mock block.

Note: this is a newtype and not a type class to allow for things in the closure. For example, if Praos had to use a stateful KES key, it could refer to it in its closure.

Constructors

ForgeExt 

Fields

data StakeHolder Source #

Constructors

StakeCore CoreNodeId

Stake of a core node

StakeEverybodyElse

Stake for everybody else (we don't need to distinguish)

newtype StakeDist Source #

In the mock setup, only core nodes have stake

INVARIANT: The rationals should sum to 1.

data MockError blk Source #

Constructors

MockExpired !SlotNo !SlotNo

The transaction expired in the first SlotNo, and it failed to validate in the second SlotNo.

MockUtxoError UtxoError 
MockInvalidHash (ChainHash blk) (ChainHash blk) 

Instances

Instances details
Typeable blk ⇒ ShowProxy (MockError blk ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.State

Methods

showProxyProxy (MockError blk) → String Source #

Generic (MockError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.State

Associated Types

type Rep (MockError blk) ∷ TypeType #

Methods

fromMockError blk → Rep (MockError blk) x #

toRep (MockError blk) x → MockError blk #

StandardHash blk ⇒ Show (MockError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.State

Methods

showsPrecIntMockError blk → ShowS #

showMockError blk → String #

showList ∷ [MockError blk] → ShowS #

StandardHash blk ⇒ Eq (MockError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.State

Methods

(==)MockError blk → MockError blk → Bool #

(/=)MockError blk → MockError blk → Bool #

(StandardHash blk, Typeable blk) ⇒ NoThunks (MockError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.State

Serialise (HeaderHash blk) ⇒ Serialise (MockError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.State

SerialiseNodeToClient (MockBlock ext) (MockError (MockBlock ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

type Rep (MockError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.State

type Rep (MockError blk) = D1 ('MetaData "MockError" "Ouroboros.Consensus.Mock.Ledger.State" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "MockExpired" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo)) :+: (C1 ('MetaCons "MockUtxoError" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UtxoError)) :+: C1 ('MetaCons "MockInvalidHash" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ChainHash blk)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ChainHash blk)))))

data Expiry Source #

Instances

Instances details
Generic Expiry Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Associated Types

type Rep ExpiryTypeType #

Methods

fromExpiryRep Expiry x #

toRep Expiry x → Expiry #

Show Expiry Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Methods

showsPrecIntExpiryShowS #

showExpiryString #

showList ∷ [Expiry] → ShowS #

NFData Expiry Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Methods

rnfExpiry → () #

Eq Expiry Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Methods

(==)ExpiryExpiryBool #

(/=)ExpiryExpiryBool #

Ord Expiry Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Methods

compareExpiryExpiryOrdering #

(<)ExpiryExpiryBool #

(<=)ExpiryExpiryBool #

(>)ExpiryExpiryBool #

(>=)ExpiryExpiryBool #

maxExpiryExpiryExpiry #

minExpiryExpiryExpiry #

NoThunks Expiry Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Condense Expiry Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Methods

condenseExpiryString Source #

Serialise Expiry Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

type Rep Expiry Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

type Rep Expiry = D1 ('MetaData "Expiry" "Ouroboros.Consensus.Mock.Ledger.UTxO" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "DoNotExpire" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "ExpireAtOnsetOf" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo)))

data Tx where Source #

Bundled Patterns

pattern TxExpirySet TxIn → [TxOut] → Tx 

Instances

Instances details
Generic Tx Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Associated Types

type Rep TxTypeType #

Methods

fromTxRep Tx x #

toRep Tx x → Tx #

Show Tx Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Methods

showsPrecIntTxShowS #

showTxString #

showList ∷ [Tx] → ShowS #

ToCBOR Tx Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Methods

toCBORTxEncoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy TxSize Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [Tx] → Size Source #

NFData Tx Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Methods

rnfTx → () #

Eq Tx Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Methods

(==)TxTxBool #

(/=)TxTxBool #

Ord Tx Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Methods

compareTxTxOrdering #

(<)TxTxBool #

(<=)TxTxBool #

(>)TxTxBool #

(>=)TxTxBool #

maxTxTxTx #

minTxTxTx #

NoThunks Tx Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Condense Tx Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Methods

condenseTxString Source #

HasMockTxs Tx Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Methods

getMockTxsTx → [Tx] Source #

Serialise Tx Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

type Rep Tx Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

type Rep Tx = D1 ('MetaData "Tx" "Ouroboros.Consensus.Mock.Ledger.UTxO" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "UnsafeTx" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Expiry) :*: (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set TxIn)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TxOut]))))

type TxIn = (TxId, Ix) Source #

class HasMockTxs a where Source #

Methods

getMockTxs ∷ a → [Tx] Source #

The transactions in the order they are to be applied

Instances

Instances details
HasMockTxs SimpleBody Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

getMockTxsSimpleBody → [Tx] Source #

HasMockTxs Tx Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Methods

getMockTxsTx → [Tx] Source #

HasMockTxs (GenTx (SimpleBlock p c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

getMockTxsGenTx (SimpleBlock p c) → [Tx] Source #

HasMockTxs a ⇒ HasMockTxs (Chain a) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Methods

getMockTxsChain a → [Tx] Source #

HasMockTxs a ⇒ HasMockTxs [a] Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Methods

getMockTxs ∷ [a] → [Tx] Source #

HasMockTxs (SimpleBlock' c ext ext') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

getMockTxsSimpleBlock' c ext ext' → [Tx] Source #

data UtxoError Source #

Constructors

MissingInput TxIn 
InputOutputMismatch 

Fields

Instances

Instances details
Generic UtxoError Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Associated Types

type Rep UtxoErrorTypeType #

Methods

fromUtxoErrorRep UtxoError x #

toRep UtxoError x → UtxoError #

Show UtxoError Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Methods

showsPrecIntUtxoErrorShowS #

showUtxoErrorString #

showList ∷ [UtxoError] → ShowS #

Eq UtxoError Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Methods

(==)UtxoErrorUtxoErrorBool #

(/=)UtxoErrorUtxoErrorBool #

NoThunks UtxoError Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Condense UtxoError Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

Serialise UtxoError Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

type Rep UtxoError Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.UTxO

type Rep UtxoError = D1 ('MetaData "UtxoError" "Ouroboros.Consensus.Mock.Ledger.UTxO" "ouroboros-consensus-0.18.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "MissingInput" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxIn)) :+: C1 ('MetaCons "InputOutputMismatch" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Amount)))

mkAddrDistNumCoreNodesAddrDist Source #

Construct address to node ID mapping

matchesSimpleHeaderSimpleCrypto c ⇒ Header (SimpleBlock' c ext ext') → SimpleBlock' c ext ext'' → Bool Source #

Check whether the block matches the header

mkSimpleHeaderSimpleCrypto 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.

decodeSimpleHeaderSimpleCrypto c ⇒ (ext' → Encoding) → (∀ s. Decoder s ext') → ∀ s. Decoder s (Header (SimpleBlock' c ext ext')) Source #

encodeSimpleHeader ∷ (ext' → Encoding) → Header (SimpleBlock' c ext ext') → Encoding Source #

forgeSimple Source #

Arguments

∷ ∀ c ext. SimpleCrypto c 
ForgeExt c ext 
TopLevelConfig (SimpleBlock c ext) 
BlockNo

Current block number

SlotNo

Current slot number

TickedLedgerState (SimpleBlock c ext)

Current ledger

→ [GenTx (SimpleBlock c ext)]

Txs to include

IsLeader (BlockProtocol (SimpleBlock c ext)) 
SimpleBlock c ext 

equalStakeDistAddrDistStakeDist Source #

Stake distribution where every address has equal state

genesisStakeDistAddrDistStakeDist Source #

Genesis stake distribution

totalStakesMap Addr NodeIdUtxoMap 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.

updateMockState ∷ (GetPrevHash blk, HasMockTxs blk) ⇒ blk → MockState blk → Except (MockError blk) (MockState blk) Source #

updateMockTipGetPrevHash blk ⇒ Header blk → MockState blk → Except (MockError blk) (MockState blk) Source #

updateMockUTxOHasMockTxs a ⇒ SlotNo → a → MockState blk → Except (MockError blk) (MockState blk) Source #

confirmedHasMockTxs a ⇒ a → Set TxId Source #

confirmed stands for all the transaction hashes present in the given collection.

txInsHasMockTxs a ⇒ a → Set TxIn Source #

txOutsHasMockTxs a ⇒ a → Utxo Source #

updateUtxoHasMockTxs a ⇒ a → UtxoExcept UtxoError Utxo Source #

Update the Utxo with the transactions from the given a, by removing the inputs and adding the outputs.

genesisTxAddrDistTx Source #

Transaction giving initial stake to the nodes