ouroboros-consensus-0.26.0.0: Consensus layer for the Ouroboros blockchain protocol
Safe HaskellNone
LanguageHaskell2010

Ouroboros.Consensus.Mock.Ledger.Block

Description

Simple block to go with the mock ledger

None of the definitions in this module depend on, or even refer to, any specific consensus protocols.

Synopsis

Documentation

data family BlockQueryTypeQueryFootprintTypeType Source #

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

Instances

Instances details
SameDepIndex2 (BlockQuery (DualBlock m a) ∷ QueryFootprintTypeType) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

sameDepIndex2 ∷ ∀ (x ∷ QueryFootprint) a0 (y ∷ QueryFootprint) b. BlockQuery (DualBlock m a) x a0 → BlockQuery (DualBlock m a) y b → Maybe ('(x, a0) :~: '(y, b)) Source #

SameDepIndex2 (BlockQuery TestBlock) 
Instance details

Defined in Test.Util.TestBlock

Methods

sameDepIndex2 ∷ ∀ (x ∷ QueryFootprint) a (y ∷ QueryFootprint) b. BlockQuery TestBlock x a → BlockQuery TestBlock y b → Maybe ('(x, a) :~: '(y, b)) Source #

SameDepIndex2 (BlockQuery (SimpleBlock c ext) ∷ QueryFootprintTypeType) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

sameDepIndex2 ∷ ∀ (x ∷ QueryFootprint) a (y ∷ QueryFootprint) b. BlockQuery (SimpleBlock c ext) x a → BlockQuery (SimpleBlock c ext) y b → Maybe ('(x, a) :~: '(y, b)) Source #

SerialiseBlockQueryResult (MockBlock ext) BlockQuery Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Methods

encodeBlockQueryResult ∷ ∀ (fp ∷ QueryFootprint) result. CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → BlockQuery (MockBlock ext) fp result → result → Encoding Source #

decodeBlockQueryResult ∷ ∀ (fp ∷ QueryFootprint) result. CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → BlockQuery (MockBlock ext) fp result → ∀ s. Decoder s result Source #

(∀ (footprint ∷ QueryFootprint) result. Show (BlockQuery blk footprint result)) ⇒ Show (SomeBlockQuery (BlockQuery blk)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Query

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

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

ShowQuery (BlockQuery (DualBlock m a) footprint) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showResultBlockQuery (DualBlock m a) footprint result → result → String Source #

ShowQuery (BlockQuery TestBlock fp) 
Instance details

Defined in Test.Util.TestBlock

Methods

showResultBlockQuery TestBlock fp result → result → String Source #

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

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

(Typeable m, Typeable a) ⇒ ShowProxy (BlockQuery (DualBlock m a) ∷ QueryFootprintTypeType) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Show (BlockQuery (DualBlock m a) footprint result) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntBlockQuery (DualBlock m a) footprint result → ShowS #

showBlockQuery (DualBlock m a) footprint result → String #

showList ∷ [BlockQuery (DualBlock m a) footprint result] → ShowS #

Show (BlockQuery TestBlock fp result) 
Instance details

Defined in Test.Util.TestBlock

Methods

showsPrecIntBlockQuery TestBlock fp result → ShowS #

showBlockQuery TestBlock fp result → String #

showList ∷ [BlockQuery TestBlock fp result] → ShowS #

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showsPrecIntBlockQuery (SimpleBlock c ext) fp result → ShowS #

showBlockQuery (SimpleBlock c ext) fp result → String #

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

Eq (BlockQuery TestBlock fp result) 
Instance details

Defined in Test.Util.TestBlock

Methods

(==)BlockQuery TestBlock fp result → BlockQuery TestBlock fp result → Bool #

(/=)BlockQuery TestBlock fp result → BlockQuery TestBlock fp result → Bool #

Inject (SomeBlockQuery :.: BlockQuery) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Nary

data BlockQuery TestBlock fp result 
Instance details

Defined in Test.Util.TestBlock

data BlockQuery (HardForkBlock xs) footprint result 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger.Query

data BlockQuery (HardForkBlock xs) footprint result where
data BlockQuery (DualBlock m a) footprint result 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data BlockQuery (DualBlock m a) footprint result
data BlockQuery (SimpleBlock c ext) fp result Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

data BlockQuery (SimpleBlock c ext) fp result where

data family Header blk Source #

Instances

Instances details
GetHeader1 Header 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

Methods

getHeader1Header blk → Header blk Source #

Inject Header 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Nary

Methods

inject ∷ ∀ x (xs ∷ [Type]). (CanHardFork xs, HasCanonicalTxIn xs, HasHardForkTxOut xs) ⇒ InjectionIndex xs x → Header x → Header (HardForkBlock xs) Source #

Isomorphic Header 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary

Methods

projectNoHardForks blk ⇒ Header (HardForkBlock '[blk]) → Header blk Source #

injectNoHardForks blk ⇒ Header blk → Header (HardForkBlock '[blk]) Source #

ReconstructNestedCtxt Header (TestBlockWith ptype) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

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

Defined in Ouroboros.Consensus.Block.Abstract

Typeable ptype ⇒ ShowProxy (Header (TestBlockWith ptype) ∷ Type) 
Instance details

Defined in Test.Util.TestBlock

Methods

showProxyProxy (Header (TestBlockWith ptype)) → String Source #

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

HasNestedContent Header m ⇒ HasNestedContent Header (DualBlock m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

ReconstructNestedCtxt Header m ⇒ ReconstructNestedCtxt Header (DualBlock m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

(Typeable m, Typeable a) ⇒ ShowProxy (DualHeader m a ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showProxyProxy (DualHeader m a) → 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')) 
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.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleHeader" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleHeaderHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HeaderHash (SimpleBlock' c ext ext'))) :*: (S1 ('MetaSel ('Just "simpleHeaderStd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SimpleStdHeader c ext)) :*: S1 ('MetaSel ('Just "simpleHeaderExt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ext'))))

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') #

Show ptype ⇒ Show (Header (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

Methods

showsPrecIntHeader (TestBlockWith ptype) → ShowS #

showHeader (TestBlockWith ptype) → String #

showList ∷ [Header (TestBlockWith ptype)] → ShowS #

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

Eq ptype ⇒ Eq (Header (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

Methods

(==)Header (TestBlockWith ptype) → Header (TestBlockWith ptype) → Bool #

(/=)Header (TestBlockWith ptype) → Header (TestBlockWith ptype) → Bool #

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

NoThunks (Header (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

NoThunks ptype ⇒ NoThunks (Header (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

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

SignedHeader (Header (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

(Typeable ptype, Eq ptype) ⇒ Condense (Header (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

Methods

condenseHeader (TestBlockWith ptype) → 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 #

Typeable ptype ⇒ HasHeader (Header (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

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

Serialise ptype ⇒ Serialise (Header (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

(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 ptype ⇒ DecodeDiskDep (NestedCtxt Header) (TestBlockWith ptype) 
Instance details

Defined in Test.Util.TestBlock

Methods

decodeDiskDepCodecConfig (TestBlockWith ptype) → NestedCtxt Header (TestBlockWith ptype) a → ∀ s. Decoder s (ByteString → a) 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 ptype ⇒ EncodeDisk (TestBlockWith ptype) (Header (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialise ptype ⇒ EncodeDiskDep (NestedCtxt Header) (TestBlockWith ptype) 
Instance details

Defined in Test.Util.TestBlock

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 ptype ⇒ DecodeDisk (TestBlockWith ptype) (ByteStringHeader (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

Methods

decodeDiskCodecConfig (TestBlockWith ptype) → ∀ s. Decoder s (ByteStringHeader (TestBlockWith ptype)) Source #

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 #

EncodeDiskDep (NestedCtxt Header) m ⇒ EncodeDiskDep (NestedCtxt Header) (DualBlock m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

encodeDiskDepCodecConfig (DualBlock m a) → NestedCtxt Header (DualBlock m a) a0 → a0 → Encoding Source #

EncodeDiskDepIx (NestedCtxt Header) m ⇒ EncodeDiskDepIx (NestedCtxt Header) (DualBlock m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Show (Header m) ⇒ Show (DualHeader m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntDualHeader m a → ShowS #

showDualHeader m a → String #

showList ∷ [DualHeader m a] → ShowS #

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

Bridge m a ⇒ HasHeader (DualHeader m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleHeader" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleHeaderHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HeaderHash (SimpleBlock' c ext ext'))) :*: (S1 ('MetaSel ('Just "simpleHeaderStd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SimpleStdHeader c ext)) :*: S1 ('MetaSel ('Just "simpleHeaderExt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ext'))))
type 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

newtype Header (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

newtype Header (TestBlockWith ptype) 
Instance details

Defined in Test.Util.TestBlock

type Signed (Header (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

type Signed (Header (TestBlockWith ptype)) = ()
newtype Header (DualBlock m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

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

data SimpleBlock' c ext ext' Source #

Constructors

SimpleBlock 

Fields

Instances

Instances details
SameDepIndex2 (BlockQuery (SimpleBlock c ext) ∷ QueryFootprintTypeType) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

sameDepIndex2 ∷ ∀ (x ∷ QueryFootprint) a (y ∷ QueryFootprint) b. BlockQuery (SimpleBlock c ext) x a → BlockQuery (SimpleBlock c ext) y b → Maybe ('(x, a) :~: '(y, b)) Source #

Serialise ext ⇒ ReconstructNestedCtxt Header (MockBlock ext) Source # 
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 #

SerialiseBlockQueryResult (MockBlock ext) BlockQuery Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Methods

encodeBlockQueryResult ∷ ∀ (fp ∷ QueryFootprint) result. CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → BlockQuery (MockBlock ext) fp result → result → Encoding Source #

decodeBlockQueryResult ∷ ∀ (fp ∷ QueryFootprint) result. CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → BlockQuery (MockBlock ext) fp result → ∀ s. Decoder s result Source #

HasNestedContent f (SimpleBlock c ext) Source # 
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 #

SameDepIndex (NestedCtxt_ (SimpleBlock c ext) f ∷ TypeType) 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 ∷ TypeType) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

(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)) 
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.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleBlockConfig" 'PrefixI 'False) (U1TypeType))

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)) 
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.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleCodecConfig" 'PrefixI 'False) (U1TypeType))

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')) 
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.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleHeader" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleHeaderHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HeaderHash (SimpleBlock' c ext ext'))) :*: (S1 ('MetaSel ('Just "simpleHeaderStd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SimpleStdHeader c ext)) :*: S1 ('MetaSel ('Just "simpleHeaderExt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ext'))))

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)) 
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.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleStorageConfig" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SecurityParam)))

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (Validated (GenTx (SimpleBlock c ext))) = Rep (GenTx (SimpleBlock c ext))

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)) 
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.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleGenTx") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Tx) :*: S1 ('MetaSel ('Just "simpleGenTxId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxId)))

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))) 
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.26.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "SimpleGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSimpleGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxId)))

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

(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

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, 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 #

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

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

(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

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

getTip ∷ ∀ (mk ∷ MapKind). LedgerState (SimpleBlock c ext) mk → Point (LedgerState (SimpleBlock c ext)) Source #

MockProtocolSpecific c ext ⇒ IsLedger (LedgerState (SimpleBlock c ext)) Source # 
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 #

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

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

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerState (SimpleBlock c ext) mk → LedgerTables (LedgerState (SimpleBlock c ext)) mk Source #

withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerState (SimpleBlock c ext) any → LedgerTables (LedgerState (SimpleBlock c ext)) mk → LedgerState (SimpleBlock c ext) mk Source #

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

HasNetworkProtocolVersion (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

(Serialise ext, Typeable ext, Serialise (MockLedgerConfig SimpleMockCrypto ext), MockProtocolSpecific SimpleMockCrypto 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

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

upgradeTables ∷ ∀ (mk1 ∷ MapKind) (mk2 ∷ MapKind). LedgerState (SimpleBlock c ext) mk1 → LedgerState (SimpleBlock c ext) mk2 → LedgerTables (LedgerState (SimpleBlock c ext)) ValuesMKLedgerTables (LedgerState (SimpleBlock c ext)) ValuesMK Source #

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

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, 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 (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) (SomeBlockQuery (BlockQuery (MockBlock ext))) 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

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 #

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

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

DecodeDisk (MockBlock ext) (LedgerState (MockBlock ext) EmptyMK) 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 #

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

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (LedgerState (SimpleBlock c ext) mk) 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (LedgerState (SimpleBlock c ext) mk) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleLedgerState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MockState (SimpleBlock c ext))) :*: S1 ('MetaSel ('Just "simpleLedgerTables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerTables (LedgerState (SimpleBlock c ext)) mk))))

Methods

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

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

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showsPrecIntLedgerState (SimpleBlock c ext) mk → ShowS #

showLedgerState (SimpleBlock c ext) mk → String #

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

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

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

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

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

(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

ConsensusProtocol (BlockProtocol (SimpleBlock c ext)) ⇒ BlockSupportsSanityCheck (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type HardForkIndices (SimpleBlock c ext) = '[SimpleBlock c ext]

Methods

hardForkSummary ∷ ∀ (mk ∷ MapKind). LedgerConfig (SimpleBlock c ext) → LedgerState (SimpleBlock c ext) mk → Summary (HardForkIndices (SimpleBlock c ext)) Source #

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type PartialLedgerConfig (SimpleBlock c ext) 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type TipInfo (SimpleBlock c ext) = HeaderHash (SimpleBlock c ext)

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

MockProtocolSpecific c ext ⇒ UpdateLedger (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

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (SimpleBlock c ext)) mk → Point (Ticked (LedgerState (SimpleBlock c ext))) Source #

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

Dummy values

Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

maxHeaderSize ∷ ∀ (mk ∷ MapKind). LedgerState (SimpleBlock c ext) mk → Word32 Source #

maxTxSize ∷ ∀ (mk ∷ MapKind). LedgerState (SimpleBlock c ext) mk → Word32 Source #

InspectLedger (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type LedgerWarning (SimpleBlock c ext) 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type LedgerUpdate (SimpleBlock c ext) 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

inspectLedger ∷ ∀ (mk1 ∷ MapKind) (mk2 ∷ MapKind). TopLevelConfig (SimpleBlock c ext) → LedgerState (SimpleBlock c ext) mk1 → LedgerState (SimpleBlock c ext) mk2 → [LedgerEvent (SimpleBlock c ext)] Source #

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

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

Methods

txInvariantGenTx (SimpleBlock c ext) → Bool Source #

applyTxLedgerConfig (SimpleBlock c ext) → WhetherToInterveneSlotNoGenTx (SimpleBlock c ext) → TickedLedgerState (SimpleBlock c ext) ValuesMKExcept (ApplyTxErr (SimpleBlock c ext)) (TickedLedgerState (SimpleBlock c ext) DiffMK, Validated (GenTx (SimpleBlock c ext))) Source #

reapplyTxComputeDiffsLedgerConfig (SimpleBlock c ext) → SlotNoValidated (GenTx (SimpleBlock c ext)) → TickedLedgerState (SimpleBlock c ext) ValuesMKExcept (ApplyTxErr (SimpleBlock c ext)) (TickedLedgerState (SimpleBlock c ext) TrackingMK) Source #

reapplyTxsComputeDiffsLedgerConfig (SimpleBlock c ext) → SlotNo → [(Validated (GenTx (SimpleBlock c ext)), extra)] → TickedLedgerState (SimpleBlock c ext) ValuesMKReapplyTxsResult extra (SimpleBlock c ext) Source #

txForgetValidatedValidated (GenTx (SimpleBlock c ext)) → GenTx (SimpleBlock c ext) Source #

getTransactionKeySetsGenTx (SimpleBlock c ext) → LedgerTables (LedgerState (SimpleBlock c ext)) KeysMK Source #

prependMempoolDiffsTickedLedgerState (SimpleBlock c ext) DiffMKTickedLedgerState (SimpleBlock c ext) DiffMKTickedLedgerState (SimpleBlock c ext) DiffMK Source #

applyMempoolDiffsLedgerTables (LedgerState (SimpleBlock c ext)) ValuesMKLedgerTables (LedgerState (SimpleBlock c ext)) KeysMKTickedLedgerState (SimpleBlock c ext) DiffMKTickedLedgerState (SimpleBlock c ext) ValuesMK Source #

TxLimits (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type TxMeasure (SimpleBlock c ext) 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

LedgerSupportsPeerSelection (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

getPeers ∷ ∀ (mk ∷ MapKind). LedgerState (SimpleBlock c ext) mk → [(PoolStake, NonEmpty StakePoolRelay)] Source #

(SimpleCrypto c, BftCrypto c', Signable (BftDSIGN c') (SignedSimpleBft c c')) ⇒ LedgerSupportsProtocol (SimpleBftBlock c c') Source # 
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

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (SimpleBlock c ext)) mk → LedgerTables (Ticked (LedgerState (SimpleBlock c ext))) mk Source #

withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (SimpleBlock c ext)) any → LedgerTables (Ticked (LedgerState (SimpleBlock c ext))) mk → Ticked (LedgerState (SimpleBlock c ext)) mk Source #

NodeInitStorage (SimpleBlock SimpleMockCrypto ext) Source # 
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

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showResultBlockQuery (SimpleBlock c ext) fp result → result → String 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 #

IndexedMemPack (LedgerState (SimpleBlock c ext) EmptyMK) TxOut Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

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

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) ∷ QueryFootprintTypeType) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Serialise (MockLedgerConfig c ext) ⇒ SerialiseNodeToClient (SimpleBlock c ext) (SimpleLedgerConfig c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (Ticked (LedgerState (SimpleBlock c ext)) mk) 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

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

Methods

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

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

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (SimpleBlock' c ext ext') 
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.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleBlock" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Header (SimpleBlock' c ext ext'))) :*: S1 ('MetaSel ('Just "simpleBody") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SimpleBody)))

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 #

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showsPrecIntBlockQuery (SimpleBlock c ext) fp result → ShowS #

showBlockQuery (SimpleBlock c ext) fp result → String #

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

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showsPrecIntTicked (LedgerState (SimpleBlock c ext)) mk → ShowS #

showTicked (LedgerState (SimpleBlock c ext)) mk → String #

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

(SimpleCrypto c, Show ext', Typeable ext) ⇒ Show (SimpleBlock' c ext ext') Source # 
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, Typeable ext) ⇒ NoThunks (Ticked (LedgerState (SimpleBlock c ext)) TrackingMK) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

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 TrivialIndex (NestedCtxt_ (SimpleBlock c ext) f ∷ TypeType) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

type TrivialIndex (NestedCtxt_ (SimpleBlock c ext) f ∷ TypeType) = f (SimpleBlock c ext)
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.26.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.26.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.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleHeader" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleHeaderHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HeaderHash (SimpleBlock' c ext ext'))) :*: (S1 ('MetaSel ('Just "simpleHeaderStd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SimpleStdHeader c ext)) :*: S1 ('MetaSel ('Just "simpleHeaderExt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ext'))))
type Rep (StorageConfig (SimpleBlock c ext)) Source # 
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.26.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 (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.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleGenTx") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Tx) :*: S1 ('MetaSel ('Just "simpleGenTxId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxId)))
type Rep (TxId (GenTx (SimpleBlock c ext))) Source # 
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.26.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "SimpleGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSimpleGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxId)))
type BlockProtocol (SimplePraosRuleBlock c) Source # 
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

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type TxIn (LedgerState (SimpleBlock c ext)) = TxIn
type TxOut (LedgerState (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type BlockNodeToClientVersion (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

type BlockNodeToNodeVersion (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

type Rep (LedgerState (SimpleBlock c ext) mk) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (LedgerState (SimpleBlock c ext) mk) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleLedgerState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MockState (SimpleBlock c ext))) :*: S1 ('MetaSel ('Just "simpleLedgerTables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerTables (LedgerState (SimpleBlock c ext)) mk))))
data BlockConfig (SimpleBlock c ext) Source # 
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 PartialLedgerConfig (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

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)
data LedgerState (SimpleBlock c ext) mk 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) fp result Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

data BlockQuery (SimpleBlock c ext) fp 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 TxMeasure (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

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

newtype Ticked (LedgerState (SimpleBlock c ext) ∷ MapKindType) (mk ∷ MapKind) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (Ticked (LedgerState (SimpleBlock c ext)) mk) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (Ticked (LedgerState (SimpleBlock c ext)) mk) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.26.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "TickedSimpleLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTickedSimpleLedgerState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerState (SimpleBlock c ext) mk))))
type Rep (SimpleBlock' c ext ext') Source # 
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.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleBlock" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Header (SimpleBlock' c ext ext'))) :*: S1 ('MetaSel ('Just "simpleBody") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SimpleBody)))
data Header (SimpleBlock' c ext ext') Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

data SimpleBody Source #

Constructors

SimpleBody 

Fields

Instances

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

Generic SimpleBody Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep SimpleBody 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

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.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleBody" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleTxs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Tx])))

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) 
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.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleStdHeader" 'PrefixI 'True) ((S1 ('MetaSel ('Just "simplePrev") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ChainHash (SimpleBlock c ext))) :*: S1 ('MetaSel ('Just "simpleSlotNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SlotNo)) :*: (S1 ('MetaSel ('Just "simpleBlockNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockNo) :*: (S1 ('MetaSel ('Just "simpleBodyHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Hash (SimpleHash c) SimpleBody)) :*: S1 ('MetaSel ('Just "simpleBodySize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SizeInBytes)))))

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

KnownNat (SizeHash (SimpleHash c)) ⇒ 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.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleStdHeader" 'PrefixI 'True) ((S1 ('MetaSel ('Just "simplePrev") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ChainHash (SimpleBlock c ext))) :*: S1 ('MetaSel ('Just "simpleSlotNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SlotNo)) :*: (S1 ('MetaSel ('Just "simpleBlockNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockNo) :*: (S1 ('MetaSel ('Just "simpleBodyHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Hash (SimpleHash c) SimpleBody)) :*: S1 ('MetaSel ('Just "simpleBodySize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SizeInBytes)))))

Working with SimpleBlock

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.

Configuration

data family BlockConfig blk Source #

Static configuration required to work with this type of blocks

Instances

Instances details
Isomorphic BlockConfig 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary

Generic (BlockConfig (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (BlockConfig (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

type Rep (BlockConfig (TestBlockWith ptype)) = D1 ('MetaData "BlockConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "testBlockNumCoreNodes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NumCoreNodes)))

Methods

fromBlockConfig (TestBlockWith ptype) → Rep (BlockConfig (TestBlockWith ptype)) x #

toRep (BlockConfig (TestBlockWith ptype)) x → BlockConfig (TestBlockWith ptype) #

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (BlockConfig (SimpleBlock c ext)) 
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.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleBlockConfig" 'PrefixI 'False) (U1TypeType))

Methods

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

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

Show (BlockConfig (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

CanHardFork xs ⇒ NoThunks (BlockConfig (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

NoThunks (BlockConfig (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

NoThunks (BlockConfig (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (BlockConfig (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

type Rep (BlockConfig (TestBlockWith ptype)) = D1 ('MetaData "BlockConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "testBlockNumCoreNodes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NumCoreNodes)))
type Rep (BlockConfig (SimpleBlock c ext)) Source # 
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.26.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

newtype BlockConfig (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data BlockConfig (TestBlockWith ptype) 
Instance details

Defined in Test.Util.TestBlock

data BlockConfig (DualBlock m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data BlockConfig (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
Isomorphic CodecConfig 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary

Generic (CodecConfig (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Associated Types

type Rep (CodecConfig (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type Rep (CodecConfig (DualBlock m a)) = D1 ('MetaData "CodecConfig" "Ouroboros.Consensus.Ledger.Dual" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "DualCodecConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "dualCodecConfigMain") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (CodecConfig m)) :*: S1 ('MetaSel ('Just "dualCodecConfigAux") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (CodecConfig a))))

Methods

fromCodecConfig (DualBlock m a) → Rep (CodecConfig (DualBlock m a)) x #

toRep (CodecConfig (DualBlock m a)) x → CodecConfig (DualBlock m a) #

Generic (CodecConfig TestBlock) 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (CodecConfig TestBlock) 
Instance details

Defined in Test.Util.TestBlock

type Rep (CodecConfig TestBlock) = D1 ('MetaData "CodecConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockCodecConfig" 'PrefixI 'False) (U1TypeType))
Generic (CodecConfig (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (CodecConfig (SimpleBlock c ext)) 
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.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleCodecConfig" 'PrefixI 'False) (U1TypeType))

Methods

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

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

Show (CodecConfig TestBlock) 
Instance details

Defined in Test.Util.TestBlock

CanHardFork xs ⇒ NoThunks (CodecConfig (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

(NoThunks (CodecConfig m), NoThunks (CodecConfig a)) ⇒ NoThunks (CodecConfig (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

NoThunks (CodecConfig TestBlock) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

data CodecConfig TestBlock

The TestBlock does not need any codec config

Instance details

Defined in Test.Util.TestBlock

type Rep (CodecConfig (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type Rep (CodecConfig (DualBlock m a)) = D1 ('MetaData "CodecConfig" "Ouroboros.Consensus.Ledger.Dual" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "DualCodecConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "dualCodecConfigMain") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (CodecConfig m)) :*: S1 ('MetaSel ('Just "dualCodecConfigAux") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (CodecConfig a))))
type Rep (CodecConfig TestBlock) 
Instance details

Defined in Test.Util.TestBlock

type Rep (CodecConfig TestBlock) = D1 ('MetaData "CodecConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockCodecConfig" '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.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleCodecConfig" 'PrefixI 'False) (U1TypeType))
newtype CodecConfig (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data CodecConfig (DualBlock m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data CodecConfig (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

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) 
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.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleLedgerConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleMockLedgerConfig") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (MockLedgerConfig c ext)) :*: (S1 ('MetaSel ('Just "simpleLedgerEraParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EraParams) :*: S1 ('MetaSel ('Just "simpleLedgerMockConfig") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MockConfig))))

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 #

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

(==)SimpleLedgerConfig c ext → SimpleLedgerConfig c ext → Bool #

(/=)SimpleLedgerConfig c ext → SimpleLedgerConfig c ext → Bool #

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Serialise (MockLedgerConfig c ext) ⇒ SerialiseNodeToClient (SimpleBlock c ext) (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.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleLedgerConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleMockLedgerConfig") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (MockLedgerConfig c ext)) :*: (S1 ('MetaSel ('Just "simpleLedgerEraParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EraParams) :*: S1 ('MetaSel ('Just "simpleLedgerMockConfig") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MockConfig))))

data family StorageConfig blk Source #

Config needed for the NodeInitStorage class. Defined here to avoid circular dependencies.

Instances

Instances details
Isomorphic StorageConfig 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary

Generic (StorageConfig (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Associated Types

type Rep (StorageConfig (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type Rep (StorageConfig (DualBlock m a)) = D1 ('MetaData "StorageConfig" "Ouroboros.Consensus.Ledger.Dual" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "DualStorageConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "dualStorageConfigMain") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StorageConfig m)) :*: S1 ('MetaSel ('Just "dualStorageConfigAux") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StorageConfig a))))
Generic (StorageConfig TestBlock) 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (StorageConfig TestBlock) 
Instance details

Defined in Test.Util.TestBlock

type Rep (StorageConfig TestBlock) = D1 ('MetaData "StorageConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockStorageConfig" 'PrefixI 'False) (U1TypeType))
Generic (StorageConfig (SimpleBlock c ext)) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (StorageConfig (SimpleBlock c ext)) 
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.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleStorageConfig" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SecurityParam)))

Methods

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

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

Show (StorageConfig TestBlock) 
Instance details

Defined in Test.Util.TestBlock

CanHardFork xs ⇒ NoThunks (StorageConfig (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

(NoThunks (StorageConfig m), NoThunks (StorageConfig a)) ⇒ NoThunks (StorageConfig (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

NoThunks (StorageConfig TestBlock) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

data StorageConfig TestBlock

The TestBlock does not need any storage config

Instance details

Defined in Test.Util.TestBlock

type Rep (StorageConfig (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type Rep (StorageConfig (DualBlock m a)) = D1 ('MetaData "StorageConfig" "Ouroboros.Consensus.Ledger.Dual" "ouroboros-consensus-0.26.0.0-inplace" 'False) (C1 ('MetaCons "DualStorageConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "dualStorageConfigMain") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StorageConfig m)) :*: S1 ('MetaSel ('Just "dualStorageConfigAux") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StorageConfig a))))
type Rep (StorageConfig TestBlock) 
Instance details

Defined in Test.Util.TestBlock

type Rep (StorageConfig TestBlock) = D1 ('MetaData "StorageConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockStorageConfig" 'PrefixI 'False) (U1TypeType))
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.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleStorageConfig" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SecurityParam)))
newtype StorageConfig (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data StorageConfig (DualBlock m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data StorageConfig (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Protocol-specific part

class (SimpleCrypto c, Typeable ext, Show (MockLedgerConfig c ext), NoThunks (MockLedgerConfig c ext), Serialise (MockLedgerConfig c ext)) ⇒ MockProtocolSpecific c ext Source #

Associated Types

type MockLedgerConfig c ext Source #

UpdateLedger

data family LedgerState blk (mk ∷ MapKind) Source #

Ledger state associated with a block

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

This type is parametrized over mk :: MapKind to express the LedgerTables contained in such a LedgerState. See LedgerTables for a more thorough description.

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

Instances

Instances details
Bridge m a ⇒ GetTip (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

getTip ∷ ∀ (mk ∷ MapKind). LedgerState (DualBlock m a) mk → Point (LedgerState (DualBlock m a)) Source #

GetTip (LedgerState (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

Methods

getTip ∷ ∀ (mk ∷ MapKind). LedgerState (TestBlockWith ptype) mk → Point (LedgerState (TestBlockWith ptype)) Source #

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

getTip ∷ ∀ (mk ∷ MapKind). LedgerState (SimpleBlock c ext) mk → Point (LedgerState (SimpleBlock c ext)) Source #

Bridge m a ⇒ IsLedger (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Associated Types

type LedgerErr (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type AuxLedgerEvent (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

PayloadSemantics ptype ⇒ IsLedger (LedgerState (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type LedgerErr (LedgerState (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

type AuxLedgerEvent (LedgerState (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

CanStowLedgerTables (LedgerState m) ⇒ CanStowLedgerTables (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanStowLedgerTables (LedgerState TestBlock) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

(Bridge m a, NoThunks (TxOut (LedgerState m)), NoThunks (TxIn (LedgerState m)), Show (TxOut (LedgerState m)), Show (TxIn (LedgerState m)), Eq (TxOut (LedgerState m)), Ord (TxIn (LedgerState m)), MemPack (TxIn (LedgerState m))) ⇒ HasLedgerTables (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerState (DualBlock m a) mk → LedgerTables (LedgerState (DualBlock m a)) mk Source #

withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerState (DualBlock m a) any → LedgerTables (LedgerState (DualBlock m a)) mk → LedgerState (DualBlock m a) mk Source #

HasLedgerTables (LedgerState TestBlock) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerState (SimpleBlock c ext) mk → LedgerTables (LedgerState (SimpleBlock c ext)) mk Source #

withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerState (SimpleBlock c ext) any → LedgerTables (LedgerState (SimpleBlock c ext)) mk → LedgerState (SimpleBlock c ext) mk Source #

LedgerTablesAreTrivial (LedgerState TestBlock) 
Instance details

Defined in Test.Util.TestBlock

Methods

convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). LedgerState TestBlock mk → LedgerState TestBlock mk' Source #

(Ord (TxIn (LedgerState m)), MemPack (TxIn (LedgerState m)), MemPack (TxOut (LedgerState m))) ⇒ SerializeTablesWithHint (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

(Ord k, MemPack k, MemPack v) ⇒ SerializeTablesWithHint (LedgerState (OTBlock k v)) 
Instance details

Defined in Test.Util.LedgerStateOnlyTables

SerializeTablesWithHint (LedgerState TestBlock) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

CanUpgradeLedgerTables (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanUpgradeLedgerTables (LedgerState (OTBlock k v)) 
Instance details

Defined in Test.Util.LedgerStateOnlyTables

Methods

upgradeTables ∷ ∀ (mk1 ∷ MapKind) (mk2 ∷ MapKind). LedgerState (OTBlock k v) mk1 → LedgerState (OTBlock k v) mk2 → LedgerTables (LedgerState (OTBlock k v)) ValuesMKLedgerTables (LedgerState (OTBlock k v)) ValuesMK Source #

CanUpgradeLedgerTables (LedgerState TestBlock) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

upgradeTables ∷ ∀ (mk1 ∷ MapKind) (mk2 ∷ MapKind). LedgerState (SimpleBlock c ext) mk1 → LedgerState (SimpleBlock c ext) mk2 → LedgerTables (LedgerState (SimpleBlock c ext)) ValuesMKLedgerTables (LedgerState (SimpleBlock c ext)) ValuesMK Source #

PayloadSemantics ptype ⇒ ApplyBlock (LedgerState (TestBlockWith ptype)) (TestBlockWith ptype) 
Instance details

Defined in Test.Util.TestBlock

Bridge m a ⇒ ApplyBlock (LedgerState (DualBlock m a)) (DualBlock m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

PayloadSemantics ptype ⇒ DecodeDisk (TestBlockWith ptype) (LedgerState (TestBlockWith ptype) EmptyMK) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

PayloadSemantics ptype ⇒ EncodeDisk (TestBlockWith ptype) (LedgerState (TestBlockWith ptype) EmptyMK) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Generic (LedgerState (OTBlock k v) mk) 
Instance details

Defined in Test.Util.LedgerStateOnlyTables

Associated Types

type Rep (LedgerState (OTBlock k v) mk) 
Instance details

Defined in Test.Util.LedgerStateOnlyTables

type Rep (LedgerState (OTBlock k v) mk) = D1 ('MetaData "LedgerState" "Test.Util.LedgerStateOnlyTables" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "OTLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "otlsLedgerState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ValuesMK k v)) :*: S1 ('MetaSel ('Just "otlsLedgerTables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OTLedgerTables k v mk))))

Methods

fromLedgerState (OTBlock k v) mk → Rep (LedgerState (OTBlock k v) mk) x #

toRep (LedgerState (OTBlock k v) mk) x → LedgerState (OTBlock k v) mk #

Generic (LedgerState (TestBlockWith ptype) mk) 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (LedgerState (TestBlockWith ptype) mk) 
Instance details

Defined in Test.Util.TestBlock

type Rep (LedgerState (TestBlockWith ptype) mk) = D1 ('MetaData "LedgerState" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "lastAppliedPoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Point (TestBlockWith ptype))) :*: S1 ('MetaSel ('Just "payloadDependentState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PayloadDependentState ptype mk))))

Methods

fromLedgerState (TestBlockWith ptype) mk → Rep (LedgerState (TestBlockWith ptype) mk) x #

toRep (LedgerState (TestBlockWith ptype) mk) x → LedgerState (TestBlockWith ptype) mk #

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (LedgerState (SimpleBlock c ext) mk) 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (LedgerState (SimpleBlock c ext) mk) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleLedgerState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MockState (SimpleBlock c ext))) :*: S1 ('MetaSel ('Just "simpleLedgerTables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerTables (LedgerState (SimpleBlock c ext)) mk))))

Methods

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

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

(ShowMK mk, CanHardFork xs) ⇒ Show (LedgerState (HardForkBlock xs) mk) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

(Bridge m a, ShowMK mk) ⇒ Show (LedgerState (DualBlock m a) mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntLedgerState (DualBlock m a) mk → ShowS #

showLedgerState (DualBlock m a) mk → String #

showList ∷ [LedgerState (DualBlock m a) mk] → ShowS #

(ShowMK mk, PayloadSemantics ptype) ⇒ Show (LedgerState (TestBlockWith ptype) mk) 
Instance details

Defined in Test.Util.TestBlock

Methods

showsPrecIntLedgerState (TestBlockWith ptype) mk → ShowS #

showLedgerState (TestBlockWith ptype) mk → String #

showList ∷ [LedgerState (TestBlockWith ptype) mk] → ShowS #

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showsPrecIntLedgerState (SimpleBlock c ext) mk → ShowS #

showLedgerState (SimpleBlock c ext) mk → String #

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

(EqMK mk, CanHardFork xs) ⇒ Eq (LedgerState (HardForkBlock xs) mk) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

(Bridge m a, EqMK mk) ⇒ Eq (LedgerState (DualBlock m a) mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

(==)LedgerState (DualBlock m a) mk → LedgerState (DualBlock m a) mk → Bool #

(/=)LedgerState (DualBlock m a) mk → LedgerState (DualBlock m a) mk → Bool #

Eq (PayloadDependentState ptype mk) ⇒ Eq (LedgerState (TestBlockWith ptype) mk) 
Instance details

Defined in Test.Util.TestBlock

Methods

(==)LedgerState (TestBlockWith ptype) mk → LedgerState (TestBlockWith ptype) mk → Bool #

(/=)LedgerState (TestBlockWith ptype) mk → LedgerState (TestBlockWith ptype) mk → Bool #

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

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

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

(NoThunksMK mk, CanHardFork xs) ⇒ NoThunks (LedgerState (HardForkBlock xs) mk) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

NoThunks (LedgerState (DualBlock m a) mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

NoThunks (PayloadDependentState ptype mk) ⇒ NoThunks (LedgerState (TestBlockWith ptype) mk) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Bridge m a ⇒ GetTip (Ticked (LedgerState (DualBlock m a))) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (DualBlock m a)) mk → Point (Ticked (LedgerState (DualBlock m a))) Source #

GetTip (Ticked (LedgerState (TestBlockWith ptype))) 
Instance details

Defined in Test.Util.TestBlock

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (TestBlockWith ptype)) mk → Point (Ticked (LedgerState (TestBlockWith ptype))) Source #

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (SimpleBlock c ext)) mk → Point (Ticked (LedgerState (SimpleBlock c ext))) Source #

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

(Ord k, Eq v, MemPack k, MemPack v) ⇒ CanStowLedgerTables (OTLedgerState k v) 
Instance details

Defined in Test.Util.LedgerStateOnlyTables

(Bridge m a, NoThunks (TxOut (LedgerState m)), NoThunks (TxIn (LedgerState m)), Show (TxOut (LedgerState m)), Show (TxIn (LedgerState m)), Eq (TxOut (LedgerState m)), Ord (TxIn (LedgerState m)), MemPack (TxIn (LedgerState m))) ⇒ HasLedgerTables (Ticked (LedgerState (DualBlock m a))) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

HasLedgerTables (Ticked (LedgerState TestBlock)) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (SimpleBlock c ext)) mk → LedgerTables (Ticked (LedgerState (SimpleBlock c ext))) mk Source #

withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (SimpleBlock c ext)) any → LedgerTables (Ticked (LedgerState (SimpleBlock c ext))) mk → Ticked (LedgerState (SimpleBlock c ext)) mk Source #

(Ord k, Eq v, Show k, Show v, MemPack k, MemPack v, NoThunks k, NoThunks v) ⇒ HasLedgerTables (OTLedgerState k v) 
Instance details

Defined in Test.Util.LedgerStateOnlyTables

Methods

projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ OTLedgerState k v mk → LedgerTables (OTLedgerState k v) mk Source #

withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ OTLedgerState k v any → LedgerTables (OTLedgerState k v) mk → OTLedgerState k v mk Source #

LedgerTablesAreTrivial (Ticked (LedgerState TestBlock)) 
Instance details

Defined in Test.Util.TestBlock

Methods

convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). Ticked (LedgerState TestBlock) mk → Ticked (LedgerState TestBlock) mk' Source #

PayloadSemantics ptype ⇒ Serialise (LedgerState (TestBlockWith ptype) EmptyMK) 
Instance details

Defined in Test.Util.TestBlock

(txout ~ TxOut (LedgerState m), IndexedMemPack (LedgerState m EmptyMK) txout) ⇒ IndexedMemPack (LedgerState (DualBlock m a) EmptyMK) txout 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

MemPack v ⇒ IndexedMemPack (LedgerState (OTBlock k v) EmptyMK) v 
Instance details

Defined in Test.Util.LedgerStateOnlyTables

Methods

indexedPackedByteCountLedgerState (OTBlock k v) EmptyMK → v → Int Source #

indexedPackMLedgerState (OTBlock k v) EmptyMK → v → Pack s () Source #

indexedUnpackMBuffer b ⇒ LedgerState (OTBlock k v) EmptyMKUnpack b v Source #

indexedTypeNameLedgerState (OTBlock k v) EmptyMKString Source #

IndexedMemPack (LedgerState TestBlock EmptyMK) Void 
Instance details

Defined in Test.Util.TestBlock

IndexedMemPack (LedgerState (SimpleBlock c ext) EmptyMK) TxOut Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

StandardHash blk ⇒ StandardHash (LedgerState blk ∷ MapKindType) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

Generic (Ticked (LedgerState (TestBlockWith ptype)) mk) 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) 
Instance details

Defined in Test.Util.TestBlock

type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) = D1 ('MetaData "Ticked" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'True) (C1 ('MetaCons "TickedTestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTickedTestLedger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerState (TestBlockWith ptype) mk))))

Methods

fromTicked (LedgerState (TestBlockWith ptype)) mk → Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) x #

toRep (Ticked (LedgerState (TestBlockWith ptype)) mk) x → Ticked (LedgerState (TestBlockWith ptype)) mk #

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (Ticked (LedgerState (SimpleBlock c ext)) mk) 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

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

Methods

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

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

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showsPrecIntTicked (LedgerState (SimpleBlock c ext)) mk → ShowS #

showTicked (LedgerState (SimpleBlock c ext)) mk → String #

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

(Show k, Show v, Show (mk k v)) ⇒ Show (OTLedgerState k v mk) 
Instance details

Defined in Test.Util.LedgerStateOnlyTables

Methods

showsPrecIntOTLedgerState k v mk → ShowS #

showOTLedgerState k v mk → String #

showList ∷ [OTLedgerState k v mk] → ShowS #

(Ord k, Eq v, Eq (mk k v)) ⇒ Eq (OTLedgerState k v mk) 
Instance details

Defined in Test.Util.LedgerStateOnlyTables

Methods

(==)OTLedgerState k v mk → OTLedgerState k v mk → Bool #

(/=)OTLedgerState k v mk → OTLedgerState k v mk → Bool #

NoThunks (Ticked (LedgerState (DualBlock m a)) mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

(NoThunksMK mk, NoThunks (PayloadDependentState ptype mk)) ⇒ NoThunks (Ticked (LedgerState (TestBlockWith ptype)) mk) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

(NoThunks k, NoThunks v, NoThunks (mk k v)) ⇒ NoThunks (OTLedgerState k v mk) 
Instance details

Defined in Test.Util.LedgerStateOnlyTables

Inject (Flip LedgerState mk) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Nary

Methods

inject ∷ ∀ x (xs ∷ [Type]). (CanHardFork xs, HasCanonicalTxIn xs, HasHardForkTxOut xs) ⇒ InjectionIndex xs x → Flip LedgerState mk x → Flip LedgerState mk (HardForkBlock xs) Source #

Isomorphic (Flip LedgerState mk) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary

Methods

projectNoHardForks blk ⇒ Flip LedgerState mk (HardForkBlock '[blk]) → Flip LedgerState mk blk Source #

injectNoHardForks blk ⇒ Flip LedgerState mk blk → Flip LedgerState mk (HardForkBlock '[blk]) Source #

type AuxLedgerEvent (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type AuxLedgerEvent (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type AuxLedgerEvent (LedgerState (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type LedgerCfg (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type LedgerCfg (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type LedgerCfg (LedgerState (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type LedgerErr (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type LedgerErr (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type LedgerErr (LedgerState (TestBlockWith ptype)) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

newtype LedgerState (HardForkBlock xs) mk 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data LedgerState (TestBlockWith ptype) mk 
Instance details

Defined in Test.Util.TestBlock

type TxIn (LedgerState (HardForkBlock xs))

Must be the CannonicalTxIn type, but this will probably change in the future to NS WrapTxIn xs. See HasCanonicalTxIn.

Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type TxIn (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type TxIn (LedgerState TestBlock) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type TxIn (LedgerState (SimpleBlock c ext)) = TxIn
type TxOut (LedgerState (HardForkBlock xs))

Must be the HardForkTxOut type

Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type TxOut (LedgerState (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type TxOut (LedgerState TestBlock) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (LedgerState (OTBlock k v) mk) 
Instance details

Defined in Test.Util.LedgerStateOnlyTables

type Rep (LedgerState (OTBlock k v) mk) = D1 ('MetaData "LedgerState" "Test.Util.LedgerStateOnlyTables" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "OTLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "otlsLedgerState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ValuesMK k v)) :*: S1 ('MetaSel ('Just "otlsLedgerTables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OTLedgerTables k v mk))))
type Rep (LedgerState (TestBlockWith ptype) mk) 
Instance details

Defined in Test.Util.TestBlock

type Rep (LedgerState (TestBlockWith ptype) mk) = D1 ('MetaData "LedgerState" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "lastAppliedPoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Point (TestBlockWith ptype))) :*: S1 ('MetaSel ('Just "payloadDependentState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PayloadDependentState ptype mk))))
type Rep (LedgerState (SimpleBlock c ext) mk) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (LedgerState (SimpleBlock c ext) mk) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.Mock.Ledger.Block" "ouroboros-consensus-0.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleLedgerState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (MockState (SimpleBlock c ext))) :*: S1 ('MetaSel ('Just "simpleLedgerTables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerTables (LedgerState (SimpleBlock c ext)) mk))))
data LedgerState (DualBlock m a) mk 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data LedgerState (OTBlock k v) mk 
Instance details

Defined in Test.Util.LedgerStateOnlyTables

data LedgerState (SimpleBlock c ext) mk Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type TxIn (OTLedgerState k v) 
Instance details

Defined in Test.Util.LedgerStateOnlyTables

type TxIn (OTLedgerState k v) = k
type TxOut (OTLedgerState k v) 
Instance details

Defined in Test.Util.LedgerStateOnlyTables

type TxOut (OTLedgerState k v) = v
data Ticked (LedgerState (HardForkBlock xs) ∷ MapKindType) (mk ∷ MapKind) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

data Ticked (LedgerState (DualBlock m a) ∷ MapKindType) (mk ∷ MapKind) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

newtype Ticked (LedgerState (TestBlockWith ptype) ∷ MapKindType) (mk ∷ MapKind) 
Instance details

Defined in Test.Util.TestBlock

newtype Ticked (LedgerState (SimpleBlock c ext) ∷ MapKindType) (mk ∷ MapKind) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type HeaderHash (LedgerState blk ∷ MapKindType) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

type HeaderHash (LedgerState blk ∷ MapKindType) = HeaderHash blk
type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) 
Instance details

Defined in Test.Util.TestBlock

type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) = D1 ('MetaData "Ticked" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'True) (C1 ('MetaCons "TickedTestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTickedTestLedger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerState (TestBlockWith ptype) mk))))
type Rep (Ticked (LedgerState (SimpleBlock c ext)) mk) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

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

newtype LedgerTables (l ∷ LedgerStateKind) (mk ∷ MapKind) Source #

The Ledger Tables represent the portion of the data on disk that has been pulled from disk and attached to the in-memory Ledger State or that will eventually be written to disk.

With UTxO-HD and the split of the Ledger ledger state into the in-memory part and the on-disk part, this splitting was reflected in the new type parameter added to the (Consensus) LedgerState, to which we refer as "the MapKind" or mk.

Every LedgerState (or LedgerState-like type, such as the ExtLedgerState) is associated with a LedgerTables and they both share the mk. They both are of kind LedgerStateKind. LedgerTables is just a way to refer only to a partial view of the on-disk data without having the rest of the in-memory LedgerState in scope.

The mk can be instantiated to anything that is map-like, i.e. that expects two type parameters, the key and the value.

Constructors

LedgerTables 

Fields

Instances

Instances details
(Ord (TxIn l), Eq (TxOut l), Show (TxIn l), Show (TxOut l), NoThunks (TxIn l), NoThunks (TxOut l), MemPack (TxIn l), IndexedMemPack (MemPackIdx l EmptyMK) (TxOut l)) ⇒ HasLedgerTables (LedgerTables l) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables

Methods

projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerTables l mk → LedgerTables (LedgerTables l) mk Source #

withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerTables l any → LedgerTables (LedgerTables l) mk → LedgerTables l mk Source #

Generic (LedgerTables l mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

Associated Types

type Rep (LedgerTables l mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type Rep (LedgerTables l mk) = D1 ('MetaData "LedgerTables" "Ouroboros.Consensus.Ledger.Tables.Basics" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "LedgerTables" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLedgerTables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (mk (TxIn l) (TxOut l)))))

Methods

fromLedgerTables l mk → Rep (LedgerTables l mk) x #

toRep (LedgerTables l mk) x → LedgerTables l mk #

Show (mk (TxIn l) (TxOut l)) ⇒ Show (LedgerTables l mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

Methods

showsPrecIntLedgerTables l mk → ShowS #

showLedgerTables l mk → String #

showList ∷ [LedgerTables l mk] → ShowS #

Eq (mk (TxIn l) (TxOut l)) ⇒ Eq (LedgerTables l mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

Methods

(==)LedgerTables l mk → LedgerTables l mk → Bool #

(/=)LedgerTables l mk → LedgerTables l mk → Bool #

NoThunks (mk (TxIn l) (TxOut l)) ⇒ NoThunks (LedgerTables l mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type TxIn (LedgerTables l) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type TxIn (LedgerTables l) = TxIn l
type TxOut (LedgerTables l) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type TxOut (LedgerTables l) = TxOut l
type Rep (LedgerTables l mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type Rep (LedgerTables l mk) = D1 ('MetaData "LedgerTables" "Ouroboros.Consensus.Ledger.Tables.Basics" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "LedgerTables" 'PrefixI 'True) (S1 ('MetaSel ('Just "getLedgerTables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (mk (TxIn l) (TxOut l)))))
type SerializeTablesHint (LedgerTables l ValuesMK) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables

type InitHint (LedgerTables l ValuesMK) 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.V1.BackingStore.API

type ReadHint (LedgerTables l ValuesMK) 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.V1.BackingStore.API

type WriteHint (LedgerTables l DiffMK) 
Instance details

Defined in Ouroboros.Consensus.Storage.LedgerDB.V1.BackingStore.API

data family Ticked (st ∷ k) ∷ k Source #

" Ticked " piece of state, either LedgerState or ChainDepState

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

Also note that a successful forecast 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
Show (Ticked ()) 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecIntTicked () → ShowS #

showTicked () → String #

showList ∷ [Ticked ()] → ShowS #

Bridge m a ⇒ GetTip (Ticked (LedgerState (DualBlock m a))) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (DualBlock m a)) mk → Point (Ticked (LedgerState (DualBlock m a))) Source #

GetTip (Ticked (LedgerState (TestBlockWith ptype))) 
Instance details

Defined in Test.Util.TestBlock

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (TestBlockWith ptype)) mk → Point (Ticked (LedgerState (TestBlockWith ptype))) Source #

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (SimpleBlock c ext)) mk → Point (Ticked (LedgerState (SimpleBlock c ext))) Source #

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

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (ExtLedgerState blk) mk → Point (Ticked (ExtLedgerState blk)) Source #

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

(Bridge m a, NoThunks (TxOut (LedgerState m)), NoThunks (TxIn (LedgerState m)), Show (TxOut (LedgerState m)), Show (TxIn (LedgerState m)), Eq (TxOut (LedgerState m)), Ord (TxIn (LedgerState m)), MemPack (TxIn (LedgerState m))) ⇒ HasLedgerTables (Ticked (LedgerState (DualBlock m a))) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

HasLedgerTables (Ticked (LedgerState TestBlock)) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (SimpleBlock c ext)) mk → LedgerTables (Ticked (LedgerState (SimpleBlock c ext))) mk Source #

withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (SimpleBlock c ext)) any → LedgerTables (Ticked (LedgerState (SimpleBlock c ext))) mk → Ticked (LedgerState (SimpleBlock c ext)) mk Source #

(HasLedgerTables (Ticked (LedgerState blk)), NoThunks (TxOut (LedgerState blk)), NoThunks (TxIn (LedgerState blk)), Show (TxOut (LedgerState blk)), Show (TxIn (LedgerState blk)), Eq (TxOut (LedgerState blk)), Ord (TxIn (LedgerState blk)), MemPack (TxIn (LedgerState blk))) ⇒ HasLedgerTables (Ticked (ExtLedgerState blk)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (ExtLedgerState blk) mk → LedgerTables (Ticked (ExtLedgerState blk)) mk Source #

withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (ExtLedgerState blk) any → LedgerTables (Ticked (ExtLedgerState blk)) mk → Ticked (ExtLedgerState blk) mk Source #

LedgerTablesAreTrivial (Ticked (LedgerState TestBlock)) 
Instance details

Defined in Test.Util.TestBlock

Methods

convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). Ticked (LedgerState TestBlock) mk → Ticked (LedgerState TestBlock) mk' Source #

LedgerTablesAreTrivial (Ticked (LedgerState blk)) ⇒ LedgerTablesAreTrivial (Ticked (ExtLedgerState blk)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). Ticked (ExtLedgerState blk) mk → Ticked (ExtLedgerState blk) mk' Source #

Generic (Ticked (LedgerState (TestBlockWith ptype)) mk) 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) 
Instance details

Defined in Test.Util.TestBlock

type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) = D1 ('MetaData "Ticked" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'True) (C1 ('MetaCons "TickedTestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTickedTestLedger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerState (TestBlockWith ptype) mk))))

Methods

fromTicked (LedgerState (TestBlockWith ptype)) mk → Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) x #

toRep (Ticked (LedgerState (TestBlockWith ptype)) mk) x → Ticked (LedgerState (TestBlockWith ptype)) mk #

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

type Rep (Ticked (LedgerState (SimpleBlock c ext)) mk) 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

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

Methods

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

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

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Methods

showsPrecIntTicked (LedgerState (SimpleBlock c ext)) mk → ShowS #

showTicked (LedgerState (SimpleBlock c ext)) mk → String #

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

NoThunks (Ticked (LedgerState (DualBlock m a)) mk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

(NoThunksMK mk, NoThunks (PayloadDependentState ptype mk)) ⇒ NoThunks (Ticked (LedgerState (TestBlockWith ptype)) mk) 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

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

Defined in Ouroboros.Consensus.Ticked

Methods

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

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

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

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

Defined in Ouroboros.Consensus.Ticked

Methods

noThunksContext → ((TickedTypeType) :.: f) a → IO (Maybe ThunkInfo) Source #

wNoThunksContext → ((TickedTypeType) :.: f) a → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (((TickedTypeType) :.: f) a) → String Source #

data Ticked () 
Instance details

Defined in Ouroboros.Consensus.Ticked

data Ticked (HardForkChainDepState xs ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

data Ticked (HeaderState blk ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

data Ticked (PBftState c ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

newtype Ticked (WrapChainDepState blk ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

data Ticked (PraosChainDepState c ∷ Type) Source #

Ticking the Praos chain dep state has no effect

For the real Praos implementation, ticking is crucial, as it determines the point where the "nonce under construction" is swapped out for the "active" nonce. However, for the mock implementation, we keep the full history, and choose the right nonce from that; this means that ticking has no effect.

We do however need access to the ticked stake distribution.

Instance details

Defined in Ouroboros.Consensus.Mock.Protocol.Praos

type HeaderHash (Ticked l ∷ k) 
Instance details

Defined in Ouroboros.Consensus.Ticked

type HeaderHash (Ticked l ∷ k) = HeaderHash l
type TxIn (Ticked l) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type TxIn (Ticked l) = TxIn l
type TxOut (Ticked l) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type TxOut (Ticked l) = TxOut l
data Ticked (LedgerState (HardForkBlock xs) ∷ MapKindType) (mk ∷ MapKind) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

data Ticked (LedgerState (DualBlock m a) ∷ MapKindType) (mk ∷ MapKind) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

newtype Ticked (LedgerState (TestBlockWith ptype) ∷ MapKindType) (mk ∷ MapKind) 
Instance details

Defined in Test.Util.TestBlock

newtype Ticked (LedgerState (SimpleBlock c ext) ∷ MapKindType) (mk ∷ MapKind) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

data Ticked (ExtLedgerState blk ∷ MapKindType) (mk ∷ MapKind) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) 
Instance details

Defined in Test.Util.TestBlock

type Rep (Ticked (LedgerState (TestBlockWith ptype)) mk) = D1 ('MetaData "Ticked" "Test.Util.TestBlock" "ouroboros-consensus-0.26.0.0-inplace-unstable-consensus-testlib" 'True) (C1 ('MetaCons "TickedTestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTickedTestLedger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerState (TestBlockWith ptype) mk))))
type Rep (Ticked (LedgerState (SimpleBlock c ext)) mk) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

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

updateSimpleLedgerState ∷ ∀ c ext (mk1 ∷ MapKind). (SimpleCrypto c, Typeable ext) ⇒ LedgerConfig (SimpleBlock c ext) → SimpleBlock c ext → TickedLedgerState (SimpleBlock c ext) mk1 → Except (MockError (SimpleBlock c ext)) (LedgerState (SimpleBlock c ext) mk1) Source #

ApplyTx (mempool support)

data family GenTx blk Source #

Generalized transaction

The mempool (and, accordingly, blocks) consist of "generalized transactions"; this could be "proper" transactions (transferring funds) but also other kinds of things such as update proposals, delegations, etc.

Instances

Instances details
Inject GenTx 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Nary

Methods

inject ∷ ∀ x (xs ∷ [Type]). (CanHardFork xs, HasCanonicalTxIn xs, HasHardForkTxOut xs) ⇒ InjectionIndex xs x → GenTx x → GenTx (HardForkBlock xs) Source #

Isomorphic GenTx 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary

Methods

projectNoHardForks blk ⇒ GenTx (HardForkBlock '[blk]) → GenTx blk Source #

injectNoHardForks blk ⇒ GenTx blk → GenTx (HardForkBlock '[blk]) Source #

(Typeable m, Typeable a) ⇒ ShowProxy (GenTx (DualBlock m a) ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showProxyProxy (GenTx (DualBlock m a)) → 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 m, Typeable a) ⇒ ShowProxy (TxId (GenTx (DualBlock m a)) ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showProxyProxy (TxId (GenTx (DualBlock m a))) → 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))) 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (Validated (GenTx (SimpleBlock c ext))) = Rep (GenTx (SimpleBlock c ext))

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)) 
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.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleGenTx") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Tx) :*: S1 ('MetaSel ('Just "simpleGenTxId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxId)))

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))) 
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.26.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "SimpleGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSimpleGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxId)))

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

Bridge m a ⇒ Show (Validated (GenTx (DualBlock m a))) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntValidated (GenTx (DualBlock m a)) → ShowS #

showValidated (GenTx (DualBlock m a)) → String #

showList ∷ [Validated (GenTx (DualBlock m a))] → ShowS #

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Bridge m a ⇒ Show (GenTx (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntGenTx (DualBlock m a) → ShowS #

showGenTx (DualBlock m a) → String #

showList ∷ [GenTx (DualBlock m a)] → 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 (GenTxId m) ⇒ Show (TxId (GenTx (DualBlock m a))) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntTxId (GenTx (DualBlock m a)) → ShowS #

showTxId (GenTx (DualBlock m a)) → String #

showList ∷ [TxId (GenTx (DualBlock m a))] → 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 (GenTxId m) ⇒ Eq (TxId (GenTx (DualBlock m a))) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

(==)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

(/=)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → 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 (GenTxId m) ⇒ Ord (TxId (GenTx (DualBlock m a))) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

compareTxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Ordering #

(<)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

(<=)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

(>)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

(>=)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

maxTxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) #

minTxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) #

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 (Validated (GenTx (DualBlock m a))) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

NoThunks (GenTx (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

NoThunks (TxId (GenTx (DualBlock m a))) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Bridge m a ⇒ HasTxId (GenTx (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

txIdGenTx (DualBlock m a) → TxId (GenTx (DualBlock m a)) 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 #

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 (HardForkBlock xs))) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (Validated (GenTx (HardForkBlock xs))) = D1 ('MetaData "Validated" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "HardForkValidatedGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkValidatedGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraValidatedGenTx xs))))
type Rep (Validated (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (Validated (GenTx (SimpleBlock c ext))) = Rep (GenTx (SimpleBlock c ext))
type Rep (GenTx (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (GenTx (HardForkBlock xs)) = D1 ('MetaData "GenTx" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "HardForkGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTx xs))))
type Rep (GenTx (SimpleBlock c ext)) Source # 
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.26.0.0-inplace-unstable-mock-block" 'False) (C1 ('MetaCons "SimpleGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "simpleGenTx") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Tx) :*: S1 ('MetaSel ('Just "simpleGenTxId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxId)))
type Rep (TxId (GenTx (HardForkBlock xs))) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (TxId (GenTx (HardForkBlock xs))) = D1 ('MetaData "TxId" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "HardForkGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTxId xs))))
type Rep (TxId (GenTx (SimpleBlock c ext))) Source # 
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.26.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "SimpleGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSimpleGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxId)))
newtype Validated (GenTx (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

data Validated (GenTx (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

newtype GenTx (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

newtype TxId (GenTx (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

newtype TxId (GenTx (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

data GenTx (DualBlock m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data GenTx (SimpleBlock c ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

data family TxId blk Source #

A generalized transaction, GenTx, identifier.

Instances

Instances details
(Typeable m, Typeable a) ⇒ ShowProxy (TxId (GenTx (DualBlock m a)) ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showProxyProxy (TxId (GenTx (DualBlock m a))) → 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 (TxId (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Associated Types

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

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 (GenTxId m) ⇒ Show (TxId (GenTx (DualBlock m a))) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntTxId (GenTx (DualBlock m a)) → ShowS #

showTxId (GenTx (DualBlock m a)) → String #

showList ∷ [TxId (GenTx (DualBlock m a))] → 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 (GenTxId m) ⇒ Eq (TxId (GenTx (DualBlock m a))) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

(==)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

(/=)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → 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 (GenTxId m) ⇒ Ord (TxId (GenTx (DualBlock m a))) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

compareTxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Ordering #

(<)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

(<=)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

(>)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

(>=)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

maxTxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) #

minTxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) #

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 (DualBlock m a))) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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 (HardForkBlock xs))) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (TxId (GenTx (HardForkBlock xs))) = D1 ('MetaData "TxId" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "HardForkGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTxId xs))))
type Rep (TxId (GenTx (SimpleBlock c ext))) Source # 
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.26.0.0-inplace-unstable-mock-block" 'True) (C1 ('MetaCons "SimpleGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSimpleGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxId)))
newtype TxId (GenTx (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

newtype TxId (GenTx (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

newtype TxId (GenTx (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))) 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (Validated (GenTx (SimpleBlock c ext))) = Rep (GenTx (SimpleBlock c ext))

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

Bridge m a ⇒ Show (Validated (GenTx (DualBlock m a))) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntValidated (GenTx (DualBlock m a)) → ShowS #

showValidated (GenTx (DualBlock m a)) → String #

showList ∷ [Validated (GenTx (DualBlock m a))] → ShowS #

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

NoThunks (Validated (GenTx (DualBlock m a))) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (Validated (GenTx (HardForkBlock xs))) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (Validated (GenTx (HardForkBlock xs))) = D1 ('MetaData "Validated" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.26.0.0-inplace" 'True) (C1 ('MetaCons "HardForkValidatedGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkValidatedGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraValidatedGenTx xs))))
type Rep (Validated (GenTx (SimpleBlock c ext))) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

type Rep (Validated (GenTx (SimpleBlock c ext))) = Rep (GenTx (SimpleBlock c ext))
newtype Validated (GenTx (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

data Validated (GenTx (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Mock.Ledger.Block

Crypto

data SimpleMockCrypto Source #

Instances

Instances details
SimpleCrypto SimpleMockCrypto Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Ledger.Block

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

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

SerialiseBlockQueryResult (MockBlock ext) BlockQuery Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Methods

encodeBlockQueryResult ∷ ∀ (fp ∷ QueryFootprint) result. CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → BlockQuery (MockBlock ext) fp result → result → Encoding Source #

decodeBlockQueryResult ∷ ∀ (fp ∷ QueryFootprint) result. CodecConfig (MockBlock ext) → BlockNodeToClientVersion (MockBlock ext) → BlockQuery (MockBlock ext) fp result → ∀ s. Decoder s result Source #

HasNetworkProtocolVersion (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

(Serialise ext, Typeable ext, Serialise (MockLedgerConfig SimpleMockCrypto ext), MockProtocolSpecific SimpleMockCrypto 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) (SomeBlockQuery (BlockQuery (MockBlock ext))) 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

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 #

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

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

DecodeDisk (MockBlock ext) (LedgerState (MockBlock ext) EmptyMK) 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 #

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

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

NodeInitStorage (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 (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

type BlockNodeToNodeVersion (MockBlock ext) Source # 
Instance details

Defined in Ouroboros.Consensus.Mock.Node.Serialisation

Serialisation

decodeSimpleHeaderSimpleCrypto c ⇒ (ext' → Encoding) → (∀ s. Decoder s ext') → ∀ s. Decoder s (Header (SimpleBlock' c ext ext')) Source #

For tests