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

Test.Util.TestBlock

Description

Minimal instantiation of the consensus layer to be able to run the ChainDB

Synopsis

Blocks

data family BlockConfig blk Source #

Static configuration required to work with this type of blocks

Instances

Instances details
Generic (BlockConfig (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (BlockConfig (TestBlockWith ptype)) ∷ TypeType #

Methods

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

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

Show (BlockConfig (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

NoThunks (BlockConfig (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (BlockConfig (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

data family BlockQuery blk ∷ TypeType Source #

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

Instances

Instances details
SameDepIndex (BlockQuery TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

ShowQuery (BlockQuery TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showResultBlockQuery TestBlock result → result → String Source #

Show (BlockQuery TestBlock result) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showsPrecIntBlockQuery TestBlock result → ShowS #

showBlockQuery TestBlock result → String #

showList ∷ [BlockQuery TestBlock result] → ShowS #

Eq (BlockQuery TestBlock result) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

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

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

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

Defined in Ouroboros.Consensus.Ledger.Query

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

Defined in Ouroboros.Consensus.Ledger.Query

data BlockQuery TestBlock result Source # 
Instance details

Defined in Test.Util.TestBlock

data BlockQuery (HardForkBlock xs) a 
Instance details

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

data BlockQuery (HardForkBlock xs) a where

data family CodecConfig blk Source #

Static configuration required for serialisation and deserialisation of types pertaining to this type of block.

Data family instead of type family to get better type inference.

Instances

Instances details
Generic (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (CodecConfig TestBlock) ∷ TypeType #

Show (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

NoThunks (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

data CodecConfig TestBlock Source #

The TestBlock does not need any codec config

Instance details

Defined in Test.Util.TestBlock

type Rep (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (CodecConfig TestBlock) = D1 ('MetaData "CodecConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.18.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockCodecConfig" 'PrefixI 'False) (U1TypeType))
newtype CodecConfig (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data family Header blk Source #

Instances

Instances details
ReconstructNestedCtxt Header (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Block.Abstract

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

Defined in Test.Util.TestBlock

Methods

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

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

Defined in Test.Util.TestBlock

Methods

showsPrecIntHeader (TestBlockWith ptype) → ShowS #

showHeader (TestBlockWith ptype) → String #

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

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

Defined in Test.Util.TestBlock

Methods

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

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

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

Defined in Test.Util.TestBlock

SignedHeader (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

Methods

condenseHeader (TestBlockWith ptype) → String Source #

(Typeable ptype, Eq ptype) ⇒ HasHeader (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

Serialise ptype ⇒ DecodeDiskDep (NestedCtxt Header) (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

decodeDiskDepCodecConfig (TestBlockWith ptype) → NestedCtxt Header (TestBlockWith ptype) a → ∀ s. Decoder s (ByteString → a) Source #

Serialise ptype ⇒ EncodeDisk (TestBlockWith ptype) (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

Serialise ptype ⇒ DecodeDisk (TestBlockWith ptype) (ByteStringHeader (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

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

type HeaderHash (Header blk ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

type HeaderHash (Header blk ∷ Type) = HeaderHash blk
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) Source # 
Instance details

Defined in Test.Util.TestBlock

type Signed (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

type Signed (Header (TestBlockWith ptype)) = ()

data family StorageConfig blk Source #

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

Instances

Instances details
Generic (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (StorageConfig TestBlock) ∷ TypeType #

Show (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

NoThunks (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

data StorageConfig TestBlock Source #

The TestBlock does not need any storage config

Instance details

Defined in Test.Util.TestBlock

type Rep (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (StorageConfig TestBlock) = D1 ('MetaData "StorageConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.18.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockStorageConfig" 'PrefixI 'False) (U1TypeType))
newtype StorageConfig (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data TestBlockError ptype Source #

Constructors

InvalidHash

The hashes don't line up

Fields

InvalidBlock

The block itself is invalid

InvalidPayload (PayloadDependentError ptype) 

Instances

Instances details
Generic (TestBlockError ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (TestBlockError ptype) ∷ TypeType #

Methods

fromTestBlockError ptype → Rep (TestBlockError ptype) x #

toRep (TestBlockError ptype) x → TestBlockError ptype #

Show (PayloadDependentError ptype) ⇒ Show (TestBlockError ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showsPrecIntTestBlockError ptype → ShowS #

showTestBlockError ptype → String #

showList ∷ [TestBlockError ptype] → ShowS #

Eq (PayloadDependentError ptype) ⇒ Eq (TestBlockError ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

(==)TestBlockError ptype → TestBlockError ptype → Bool #

(/=)TestBlockError ptype → TestBlockError ptype → Bool #

(Typeable ptype, Generic (PayloadDependentError ptype), NoThunks (PayloadDependentError ptype)) ⇒ NoThunks (TestBlockError ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (TestBlockError ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (TestBlockError ptype) = D1 ('MetaData "TestBlockError" "Test.Util.TestBlock" "ouroboros-consensus-0.18.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "InvalidHash" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ChainHash (TestBlockWith ptype))) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ChainHash (TestBlockWith ptype)))) :+: (C1 ('MetaCons "InvalidBlock" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "InvalidPayload" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PayloadDependentError ptype)))))

data TestBlockWith ptype Source #

Test block parametrized on the payload type

For blocks without payload see the TestBlock type alias.

By defining a PayloadSemantics it is possible to obtain an ApplyBlock instance. See the former class for more details.

Instances

Instances details
HasHardForkHistory TestBlock Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type HardForkIndices TestBlock ∷ [Type] Source #

BlockSupportsLedgerQuery TestBlock Source # 
Instance details

Defined in Test.Util.TestBlock

ShowProxy TestBlock Source # 
Instance details

Defined in Test.Util.TestBlock

HasNestedContent f (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

unnest ∷ f (TestBlockWith ptype) → DepPair (NestedCtxt f (TestBlockWith ptype)) Source #

nestDepPair (NestedCtxt f (TestBlockWith ptype)) → f (TestBlockWith ptype) Source #

ReconstructNestedCtxt Header (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

StandardHash (TestBlockWith ptype ∷ Type) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

Methods

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

Generic (BlockConfig (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (BlockConfig (TestBlockWith ptype)) ∷ TypeType #

Methods

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

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

Generic (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (CodecConfig TestBlock) ∷ TypeType #

Generic (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (StorageConfig TestBlock) ∷ TypeType #

Generic (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (LedgerState (TestBlockWith ptype)) ∷ TypeType #

Methods

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

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

Generic (Ticked (LedgerState (TestBlockWith ptype))) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (Ticked (LedgerState (TestBlockWith ptype))) ∷ TypeType #

Generic (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (TestBlockWith ptype) ∷ TypeType #

Methods

fromTestBlockWith ptype → Rep (TestBlockWith ptype) x #

toRep (TestBlockWith ptype) x → TestBlockWith ptype #

Show (BlockConfig (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Show (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

Methods

showsPrecIntHeader (TestBlockWith ptype) → ShowS #

showHeader (TestBlockWith ptype) → String #

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

Show (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ Show (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ Show (Ticked (LedgerState (TestBlockWith ptype))) Source # 
Instance details

Defined in Test.Util.TestBlock

Show ptype ⇒ Show (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showsPrecIntTestBlockWith ptype → ShowS #

showTestBlockWith ptype → String #

showList ∷ [TestBlockWith ptype] → ShowS #

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

Defined in Test.Util.TestBlock

Methods

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

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

PayloadSemantics ptype ⇒ Eq (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ Eq (Ticked (LedgerState (TestBlockWith ptype))) Source # 
Instance details

Defined in Test.Util.TestBlock

Eq ptype ⇒ Eq (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

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

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

Ord ptype ⇒ Ord (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

compareTestBlockWith ptype → TestBlockWith ptype → Ordering #

(<)TestBlockWith ptype → TestBlockWith ptype → Bool #

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

(>)TestBlockWith ptype → TestBlockWith ptype → Bool #

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

maxTestBlockWith ptype → TestBlockWith ptype → TestBlockWith ptype #

minTestBlockWith ptype → TestBlockWith ptype → TestBlockWith ptype #

NoThunks (BlockConfig (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

NoThunks (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

NoThunks (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ NoThunks (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ NoThunks (Ticked (LedgerState (TestBlockWith ptype))) Source # 
Instance details

Defined in Test.Util.TestBlock

NoThunks ptype ⇒ NoThunks (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

ConvertRawHash (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

(Typeable ptype, Eq ptype) ⇒ GetHeader (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

(Typeable ptype, Eq ptype) ⇒ GetPrevHash (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

BlockSupportsProtocol (TestBlockWith ptype) ⇒ BlockSupportsDiffusionPipelining (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

(Typeable ptype, Eq ptype, NoThunks ptype, NoThunks (CodecConfig (TestBlockWith ptype)), NoThunks (StorageConfig (TestBlockWith ptype))) ⇒ BlockSupportsProtocol (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

ConfigSupportsNode (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ BasicEnvelopeValidation (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ HasAnnTip (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type TipInfo (TestBlockWith ptype) Source #

PayloadSemantics ptype ⇒ ValidateEnvelope (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type OtherHeaderEnvelopeError (TestBlockWith ptype) Source #

PayloadSemantics ptype ⇒ UpdateLedger (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

GetTip (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

InspectLedger (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type LedgerWarning (TestBlockWith ptype) Source #

type LedgerUpdate (TestBlockWith ptype) Source #

PayloadSemantics ptype ⇒ LedgerSupportsProtocol (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

HasNetworkProtocolVersion (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

SignedHeader (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

(Serialise ptype, PayloadSemantics ptype) ⇒ SerialiseDiskConstraints (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Serialise ptype ⇒ HasBinaryBlockInfo (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

Methods

condenseHeader (TestBlockWith ptype) → String Source #

(Typeable ptype, Eq ptype) ⇒ Condense (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

condenseTestBlockWith ptype → String Source #

SameDepIndex (BlockQuery TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

(Typeable ptype, Eq ptype) ⇒ HasHeader (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

(Typeable ptype, Eq ptype) ⇒ HasHeader (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

ShowQuery (BlockQuery TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showResultBlockQuery TestBlock result → result → String Source #

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

Defined in Test.Util.TestBlock

Serialise (RealPoint (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Serialise (AnnTip (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ Serialise (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ Serialise (ExtLedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Serialise ptype ⇒ Serialise (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ ToExpr (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ ToExpr (Ticked (LedgerState (TestBlockWith ptype))) Source # 
Instance details

Defined in Test.Util.TestBlock

ToExpr ptype ⇒ ToExpr (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

toExprTestBlockWith ptype → Expr Source #

listToExpr ∷ [TestBlockWith ptype] → Expr Source #

DecodeDisk (TestBlockWith ptype) () Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

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

EncodeDisk (TestBlockWith ptype) () Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

encodeDiskCodecConfig (TestBlockWith ptype) → () → Encoding Source #

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

Defined in Test.Util.TestBlock

DecodeDisk (TestBlockWith ptype) (AnnTip (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

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

PayloadSemantics ptype ⇒ DecodeDisk (TestBlockWith ptype) (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

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

Serialise ptype ⇒ DecodeDiskDep (NestedCtxt Header) (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

decodeDiskDepCodecConfig (TestBlockWith ptype) → NestedCtxt Header (TestBlockWith ptype) a → ∀ s. Decoder s (ByteString → a) Source #

Serialise ptype ⇒ EncodeDisk (TestBlockWith ptype) (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

EncodeDisk (TestBlockWith ptype) (AnnTip (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ EncodeDisk (TestBlockWith ptype) (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Serialise ptype ⇒ EncodeDisk (TestBlockWith ptype) (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

Serialise ptype ⇒ DecodeDisk (TestBlockWith ptype) (ByteStringHeader (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

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

Serialise ptype ⇒ DecodeDisk (TestBlockWith ptype) (ByteStringTestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

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

Show (BlockQuery TestBlock result) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showsPrecIntBlockQuery TestBlock result → ShowS #

showBlockQuery TestBlock result → String #

showList ∷ [BlockQuery TestBlock result] → ShowS #

Eq (BlockQuery TestBlock result) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

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

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

Condense (ChainHash (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

SameDepIndex (NestedCtxt_ (TestBlockWith ptype) f) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

sameDepIndexNestedCtxt_ (TestBlockWith ptype) f a → NestedCtxt_ (TestBlockWith ptype) f b → Maybe (a :~: b) Source #

TrivialDependency (NestedCtxt_ (TestBlockWith ptype) f) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type TrivialIndex (NestedCtxt_ (TestBlockWith ptype) f) Source #

Show (NestedCtxt_ (TestBlockWith ptype) f a) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showsPrecIntNestedCtxt_ (TestBlockWith ptype) f a → ShowS #

showNestedCtxt_ (TestBlockWith ptype) f a → String #

showList ∷ [NestedCtxt_ (TestBlockWith ptype) f a] → ShowS #

data CodecConfig TestBlock Source #

The TestBlock does not need any codec config

Instance details

Defined in Test.Util.TestBlock

data StorageConfig TestBlock Source #

The TestBlock does not need any storage config

Instance details

Defined in Test.Util.TestBlock

type HardForkIndices TestBlock Source # 
Instance details

Defined in Test.Util.TestBlock

data BlockQuery TestBlock result Source # 
Instance details

Defined in Test.Util.TestBlock

type HeaderHash (TestBlockWith ptype ∷ Type) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (BlockConfig (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

type Rep (StorageConfig TestBlock) = D1 ('MetaData "StorageConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.18.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockStorageConfig" 'PrefixI 'False) (U1TypeType))
type Rep (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (LedgerState (TestBlockWith ptype)) = D1 ('MetaData "LedgerState" "Test.Util.TestBlock" "ouroboros-consensus-0.18.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))))
type Rep (Ticked (LedgerState (TestBlockWith ptype))) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

type Rep (TestBlockWith ptype) = D1 ('MetaData "TestBlockWith" "Test.Util.TestBlock" "ouroboros-consensus-0.18.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockWith" 'PrefixI 'True) ((S1 ('MetaSel ('Just "tbHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TestHash) :*: S1 ('MetaSel ('Just "tbSlot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SlotNo)) :*: (S1 ('MetaSel ('Just "tbValid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Validity) :*: S1 ('MetaSel ('Just "tbPayload") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ptype))))
data BlockConfig (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type BlockProtocol (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

newtype Header (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

data NestedCtxt_ (TestBlockWith ptype) f a Source # 
Instance details

Defined in Test.Util.TestBlock

data NestedCtxt_ (TestBlockWith ptype) f a where
type TentativeHeaderState (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type TentativeHeaderView (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type OtherHeaderEnvelopeError (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type TipInfo (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type AuxLedgerEvent (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

type LedgerCfg (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

type LedgerErr (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

data LedgerState (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type LedgerUpdate (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type LedgerWarning (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type BlockNodeToClientVersion (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type BlockNodeToNodeVersion (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type Signed (Header (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

type Signed (Header (TestBlockWith ptype)) = ()
newtype Ticked (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

type TrivialIndex (NestedCtxt_ (TestBlockWith ptype) f) Source # 
Instance details

Defined in Test.Util.TestBlock

data TestHash where Source #

Bundled Patterns

pattern TestHashNonEmpty Word64TestHash 

Instances

Instances details
Generic TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep TestHashTypeType #

Methods

fromTestHashRep TestHash x #

toRep TestHash x → TestHash #

Show TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showsPrecIntTestHashShowS #

showTestHashString #

showList ∷ [TestHash] → ShowS #

Eq TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

(==)TestHashTestHashBool #

(/=)TestHashTestHashBool #

Ord TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

NoThunks TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

Condense TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

Serialise TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

ToExpr TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep TestHash = D1 ('MetaData "TestHash" "Test.Util.TestBlock" "ouroboros-consensus-0.18.0.0-inplace-unstable-consensus-testlib" 'True) (C1 ('MetaCons "UnsafeTestHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTestHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Word64))))

data Validity Source #

Constructors

Valid 
Invalid 

Instances

Instances details
Bounded Validity Source # 
Instance details

Defined in Test.Util.TestBlock

Enum Validity Source # 
Instance details

Defined in Test.Util.TestBlock

Generic Validity Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep ValidityTypeType #

Methods

fromValidityRep Validity x #

toRep Validity x → Validity #

Show Validity Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showsPrecIntValidityShowS #

showValidityString #

showList ∷ [Validity] → ShowS #

Eq Validity Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

(==)ValidityValidityBool #

(/=)ValidityValidityBool #

Ord Validity Source # 
Instance details

Defined in Test.Util.TestBlock

NoThunks Validity Source # 
Instance details

Defined in Test.Util.TestBlock

Serialise Validity Source # 
Instance details

Defined in Test.Util.TestBlock

ToExpr Validity Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep Validity Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep Validity = D1 ('MetaData "Validity" "Test.Util.TestBlock" "ouroboros-consensus-0.18.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "Valid" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "Invalid" 'PrefixI 'False) (U1TypeType))

firstBlockWithPayloadWord64 → ptype → TestBlockWith ptype Source #

Create the first block in the given fork, [fork], with the given payload. The SlotNo will be 1.

successorBlockWithPayloadTestHashSlotNo → ptype → TestBlockWith ptype Source #

Create the successor of the given block without forking: b -> b ++ [0] (in the printed representation) The SlotNo is increased by 1.

In Zipper parlance, this corresponds to going down in a tree.

Test block without payload

type TestBlock = TestBlockWith () Source #

Block without payload

Payload semantics

applyDirectlyToPayloadDependentStatePayloadSemantics ptype ⇒ Ticked (LedgerState (TestBlockWith ptype)) → ptype → Either (PayloadDependentError ptype) (Ticked (LedgerState (TestBlockWith ptype))) Source #

Apply the payload directly to the payload dependent state portion of a ticked state, leaving the rest of the input ticked state unaltered.

LedgerState

data family LedgerState blk Source #

Ledger state associated with a block

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

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

Instances

Instances details
(IsNonEmpty xs, SListI xs, All (Compose Arbitrary LedgerState) xs) ⇒ Arbitrary (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Test.Util.Orphans.Arbitrary

Generic (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (LedgerState (TestBlockWith ptype)) ∷ TypeType #

Methods

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

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

Generic (Ticked (LedgerState (TestBlockWith ptype))) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (Ticked (LedgerState (TestBlockWith ptype))) ∷ TypeType #

CanHardFork xs ⇒ Show (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

PayloadSemantics ptype ⇒ Show (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ Show (Ticked (LedgerState (TestBlockWith ptype))) Source # 
Instance details

Defined in Test.Util.TestBlock

CanHardFork xs ⇒ Eq (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

PayloadSemantics ptype ⇒ Eq (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ Eq (Ticked (LedgerState (TestBlockWith ptype))) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

PayloadSemantics ptype ⇒ NoThunks (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ NoThunks (Ticked (LedgerState (TestBlockWith ptype))) Source # 
Instance details

Defined in Test.Util.TestBlock

GetTip (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ Serialise (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ ToExpr (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ ToExpr (Ticked (LedgerState (TestBlockWith ptype))) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ DecodeDisk (TestBlockWith ptype) (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

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

PayloadSemantics ptype ⇒ EncodeDisk (TestBlockWith ptype) (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

type HeaderHash (LedgerState blk ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

type HeaderHash (LedgerState blk ∷ Type) = HeaderHash blk
type Rep (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (LedgerState (TestBlockWith ptype)) = D1 ('MetaData "LedgerState" "Test.Util.TestBlock" "ouroboros-consensus-0.18.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))))
type Rep (Ticked (LedgerState (HardForkBlock xs))) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type Rep (Ticked (LedgerState (HardForkBlock xs))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.HardFork.Combinator.Ledger" "ouroboros-consensus-0.18.0.0-inplace" 'False) (C1 ('MetaCons "TickedHardForkLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "tickedHardForkLedgerStateTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TransitionInfo) :*: S1 ('MetaSel ('Just "tickedHardForkLedgerStatePerEra") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HardForkState (Ticked :.: LedgerState) xs))))
type Rep (Ticked (LedgerState (TestBlockWith ptype))) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type AuxLedgerEvent (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

type LedgerCfg (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type LedgerCfg (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

type LedgerErr (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type LedgerErr (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

newtype LedgerState (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data LedgerState (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

data Ticked (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

newtype Ticked (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

data family Ticked st Source #

" Ticked " piece of state, either LedgerState or ChainDepState

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

Also note that a successful forecast forecastFor (ledgerViewForecastAt cfg st) slot must equal protocolLedgerView cfg (applyChainTick cfg slot st). Thus a LedgerView can only be projected from a Ticked state, but cannot itself be ticked.

Some examples of time related changes:

  • Scheduled delegations might have been applied in Byron
  • New leader schedule computed for Shelley
  • Transition from Byron to Shelley activated in the hard fork combinator.
  • Nonces switched out at the start of a new epoch.

Instances

Instances details
Generic (Ticked (LedgerState (TestBlockWith ptype))) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (Ticked (LedgerState (TestBlockWith ptype))) ∷ TypeType #

PayloadSemantics ptype ⇒ Show (Ticked (LedgerState (TestBlockWith ptype))) Source # 
Instance details

Defined in Test.Util.TestBlock

Show (Ticked ()) 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecIntTicked () → ShowS #

showTicked () → String #

showList ∷ [Ticked ()] → ShowS #

PayloadSemantics ptype ⇒ Eq (Ticked (LedgerState (TestBlockWith ptype))) Source # 
Instance details

Defined in Test.Util.TestBlock

PayloadSemantics ptype ⇒ NoThunks (Ticked (LedgerState (TestBlockWith ptype))) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Ledger.Extended

PayloadSemantics ptype ⇒ ToExpr (Ticked (LedgerState (TestBlockWith ptype))) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.Ticked

Methods

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

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

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

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

Defined in Ouroboros.Consensus.Ticked

data Ticked () 
Instance details

Defined in Ouroboros.Consensus.Ticked

type HeaderHash (Ticked l ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.Ticked

type HeaderHash (Ticked l ∷ Type) = HeaderHash l
type Rep (Ticked (LedgerState (HardForkBlock xs))) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type Rep (Ticked (LedgerState (HardForkBlock xs))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.HardFork.Combinator.Ledger" "ouroboros-consensus-0.18.0.0-inplace" 'False) (C1 ('MetaCons "TickedHardForkLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "tickedHardForkLedgerStateTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TransitionInfo) :*: S1 ('MetaSel ('Just "tickedHardForkLedgerStatePerEra") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HardForkState (Ticked :.: LedgerState) xs))))
type Rep (Ticked (LedgerState (TestBlockWith ptype))) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

data Ticked (HeaderState blk) 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

data Ticked (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

newtype Ticked (LedgerState (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

data Ticked (ExtLedgerState blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

newtype Ticked (WrapChainDepState blk) 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

Chain

newtype BlockChain Source #

Constructors

BlockChain Word64 

Instances

Instances details
Arbitrary BlockChain Source # 
Instance details

Defined in Test.Util.TestBlock

Show BlockChain Source # 
Instance details

Defined in Test.Util.TestBlock

Tree

newtype BlockTree Source #

Constructors

BlockTree (Tree ()) 

Instances

Instances details
Arbitrary BlockTree Source # 
Instance details

Defined in Test.Util.TestBlock

Show BlockTree Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showsPrecIntBlockTreeShowS #

showBlockTreeString #

showList ∷ [BlockTree] → ShowS #

Ledger infrastructure

singleNodeTestConfigTopLevelConfig TestBlock Source #

Trivial test configuration with a single core node

Support for tests

newtype Permutation Source #

Constructors

Permutation Int 

Instances

Instances details
Arbitrary Permutation Source # 
Instance details

Defined in Test.Util.TestBlock

Show Permutation Source # 
Instance details

Defined in Test.Util.TestBlock

data TestBlockLedgerConfig Source #

Constructors

TestBlockLedgerConfig 

Fields

Instances

Instances details
Generic TestBlockLedgerConfig Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep TestBlockLedgerConfigTypeType #

Show TestBlockLedgerConfig Source # 
Instance details

Defined in Test.Util.TestBlock

Eq TestBlockLedgerConfig Source # 
Instance details

Defined in Test.Util.TestBlock

NoThunks TestBlockLedgerConfig Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep TestBlockLedgerConfig Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep TestBlockLedgerConfig = D1 ('MetaData "TestBlockLedgerConfig" "Test.Util.TestBlock" "ouroboros-consensus-0.18.0.0-inplace-unstable-consensus-testlib" 'False) (C1 ('MetaCons "TestBlockLedgerConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "tblcHardForkParams") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EraParams) :*: S1 ('MetaSel ('Just "tblcForecastRange") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SlotNo))))

isAncestorOfTestBlockTestBlockBool Source #

A block b1 is the ancestor of another block b2 if there exists a chain of blocks from b1 to b2. For test blocks in particular, this can be seen in the hash: the hash of b1 should be a prefix of the hash of b2.

Note that this is a partial comparison function. In particular, it does hold that for all b1 and b2, b1 isDescendentOf b2 === b2 isAncestorOf b1 but it does not hold that for all b1 and b2, b1 isDescendentOf b2 === not (b1 isAncestorOf b2) || b1 == b2.

isDescendentOfTestBlockTestBlockBool Source #

A block b1 is the descendent of another block b2 if there exists a chain of blocks from b2 to b1. For test blocks in particular, this can be seen in the hash: the hash of b2 should be a prefix of the hash of b1.

Note that this is a partial comparison function. In particular, it does hold that for all b1 and b2, b1 isDescendentOf b2 === b2 isAncestorOf b1 but it does not hold that for all b1 and b2, b1 isDescendentOf b2 === not (b1 isAncestorOf b2) || b1 == b2.

isStrictAncestorOfTestBlockTestBlockBool Source #

Variant of isAncestorOf that returns False when the two blocks are equal.

isStrictDescendentOfTestBlockTestBlockBool Source #

Variant of isDescendentOf that returns False when the two blocks are equal.

permutePermutation → [a] → [a] Source #

unsafeTestBlockWithPayloadTestHashSlotNoValidity → ptype → TestBlockWith ptype Source #

Create a block directly with the given parameters. This allows creating inconsistent blocks; prefer firstBlockWithPayload or successorBlockWithPayload.

updateToNextNumeralRealPoint TestBlock → (Point TestBlock, NonEmpty TestBlock) Source #

Given a point to a chain of length L, generates a SwitchFork that switches to the "next" block of length L, where "next" is determined by interpreting the "forks" in the TestHash as binary digits (except the deepest, which is a simple counter).

For example, the following are input and outputs for a chains of length 3, where the TestHashes and Points are denoted by numerals (the SlotNo is merely the number of digits).

000 :-> [RollBack 00, AddBlock 001]
001 :-> [RollBack 0 , AddBlock 01 , AddBlock 010]
010 :-> [RollBack 01, AddBlock 011]
011 :-> [RollBack G , AddBlock 1  , AddBlock 10 , AddBlock 100]

100 :-> [RollBack 10, AddBlock 101]
101 :-> [RollBack 1 , AddBlock 11 , AddBlock 110]
110 :-> [RollBack 11, AddBlock 111]
111 :-> [RollBack G , AddBlock 2  , AddBlock 20 , AddBlock 200]

200 :-> [RollBack 20, AddBlock 201]
201 :-> [RollBack 2 , AddBlock 21 , AddBlock 210]
210 :-> [RollBack 21, AddBlock 211]
211 :-> [RollBack G , AddBlock 3  , AddBlock 30 , AddBlock 300]

etc