ouroboros-consensus-test-0.3.1.0: Tests of the consensus layer
Safe HaskellNone
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
Show (BlockConfig (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

Associated Types

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

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

noThunks ∷ Context → BlockConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → BlockConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) #

showTypeOfProxy (BlockConfig (HardForkBlock xs)) → String #

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

Defined in Test.Util.TestBlock

Methods

noThunks ∷ Context → BlockConfig (TestBlockWith ptype) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → BlockConfig (TestBlockWith ptype) → IO (Maybe ThunkInfo) #

showTypeOfProxy (BlockConfig (TestBlockWith ptype)) → String #

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-test-0.3.1.0-inplace" 'False) (C1 ('MetaCons "TestBlockConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "testBlockNumCoreNodes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NumCoreNodes)))
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 #

Eq (BlockQuery TestBlock result) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

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

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

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

Defined in Ouroboros.Consensus.Ledger.Query

Show (BlockQuery TestBlock result) Source # 
Instance details

Defined in Test.Util.TestBlock

(∀ result. Show (BlockQuery blk result)) ⇒ Show (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
Show (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Generic (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (CodecConfig TestBlock) ∷ TypeType Source #

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

noThunks ∷ Context → CodecConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → CodecConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) #

showTypeOfProxy (CodecConfig (HardForkBlock xs)) → String #

NoThunks (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

noThunks ∷ Context → CodecConfig TestBlockIO (Maybe ThunkInfo) #

wNoThunks ∷ Context → CodecConfig TestBlockIO (Maybe ThunkInfo) #

showTypeOfProxy (CodecConfig TestBlock) → String #

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-test-0.3.1.0-inplace" '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

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

Defined in Test.Util.TestBlock

Methods

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

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

Defined in Test.Util.TestBlock

Methods

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

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

Show ptype ⇒ Show (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

Methods

encodeHeader (TestBlockWith ptype) → Encoding #

decode ∷ Decoder s (Header (TestBlockWith ptype)) #

encodeList ∷ [Header (TestBlockWith ptype)] → Encoding #

decodeList ∷ Decoder s [Header (TestBlockWith ptype)] #

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

Defined in Test.Util.TestBlock

Methods

condenseHeader (TestBlockWith ptype) → String Source #

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

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

Methods

noThunks ∷ Context → Header (TestBlockWith ptype) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Header (TestBlockWith ptype) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Header (TestBlockWith ptype)) → String #

HasHeader blk ⇒ StandardHash (Header blk) 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

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

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

Methods

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

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

Defined in Test.Util.TestBlock

Methods

encodeDiskDepCodecConfig (TestBlockWith ptype) → NestedCtxt Header (TestBlockWith ptype) a → a → Encoding 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 ⇒ 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 BlockProtocol (Header blk) 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

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

Defined in Ouroboros.Consensus.Block.Abstract

type HeaderHash (Header blk) = HeaderHash blk

data family StorageConfig blk Source #

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

Instances

Instances details
Show (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Generic (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (StorageConfig TestBlock) ∷ TypeType Source #

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

noThunks ∷ Context → StorageConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → StorageConfig (HardForkBlock xs) → IO (Maybe ThunkInfo) #

showTypeOfProxy (StorageConfig (HardForkBlock xs)) → String #

NoThunks (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

noThunks ∷ Context → StorageConfig TestBlockIO (Maybe ThunkInfo) #

wNoThunks ∷ Context → StorageConfig TestBlockIO (Maybe ThunkInfo) #

showTypeOfProxy (StorageConfig TestBlock) → String #

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-test-0.3.1.0-inplace" '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
Eq (PayloadDependentError ptype) ⇒ Eq (TestBlockError ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

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

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

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

Defined in Test.Util.TestBlock

Generic (TestBlockError ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (TestBlockError ptype) ∷ TypeType Source #

Methods

fromTestBlockError ptype → Rep (TestBlockError ptype) x Source #

toRep (TestBlockError ptype) x → TestBlockError ptype Source #

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

Defined in Test.Util.TestBlock

Methods

noThunks ∷ Context → TestBlockError ptype → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → TestBlockError ptype → IO (Maybe ThunkInfo) #

showTypeOfProxy (TestBlockError ptype) → String #

type Rep (TestBlockError ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (TestBlockError ptype) = D1 ('MetaData "TestBlockError" "Test.Util.TestBlock" "ouroboros-consensus-test-0.3.1.0-inplace" '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
QueryLedger TestBlock Source # 
Instance details

Defined in Test.Util.TestBlock

HasHardForkHistory TestBlock Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type HardForkIndices TestBlock ∷ [Type] Source #

ReconstructNestedCtxt Header (TestBlockWith ptype) 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 #

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

Defined in Test.Util.TestBlock

Methods

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

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

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

Methods

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

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

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

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

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

Defined in Test.Util.TestBlock

Methods

compareTestBlockWith ptype → TestBlockWith ptype → Ordering Source #

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

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

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

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

maxTestBlockWith ptype → TestBlockWith ptype → TestBlockWith ptype Source #

minTestBlockWith ptype → TestBlockWith ptype → TestBlockWith ptype Source #

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

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

Show (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Show (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Show ptype ⇒ Show (Header (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 Source #

showTestBlockWith ptype → String Source #

showList ∷ [TestBlockWith ptype] → ShowS Source #

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

Defined in Test.Util.TestBlock

Associated Types

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

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

Defined in Test.Util.TestBlock

Associated Types

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

Generic (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (CodecConfig TestBlock) ∷ TypeType Source #

Generic (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (StorageConfig TestBlock) ∷ TypeType Source #

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

Defined in Test.Util.TestBlock

Associated Types

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

Generic (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep (TestBlockWith ptype) ∷ TypeType Source #

Methods

fromTestBlockWith ptype → Rep (TestBlockWith ptype) x Source #

toRep (TestBlockWith ptype) x → TestBlockWith ptype Source #

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

Defined in Test.Util.TestBlock

Methods

encodeExtLedgerState (TestBlockWith ptype) → Encoding #

decode ∷ Decoder s (ExtLedgerState (TestBlockWith ptype)) #

encodeList ∷ [ExtLedgerState (TestBlockWith ptype)] → Encoding #

decodeList ∷ Decoder s [ExtLedgerState (TestBlockWith ptype)] #

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

Defined in Test.Util.TestBlock

Methods

encodeAnnTip (TestBlockWith ptype) → Encoding #

decode ∷ Decoder s (AnnTip (TestBlockWith ptype)) #

encodeList ∷ [AnnTip (TestBlockWith ptype)] → Encoding #

decodeList ∷ Decoder s [AnnTip (TestBlockWith ptype)] #

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

Defined in Test.Util.TestBlock

Methods

encodeRealPoint (TestBlockWith ptype) → Encoding #

decode ∷ Decoder s (RealPoint (TestBlockWith ptype)) #

encodeList ∷ [RealPoint (TestBlockWith ptype)] → Encoding #

decodeList ∷ Decoder s [RealPoint (TestBlockWith ptype)] #

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

Defined in Test.Util.TestBlock

Methods

encodeLedgerState (TestBlockWith ptype) → Encoding #

decode ∷ Decoder s (LedgerState (TestBlockWith ptype)) #

encodeList ∷ [LedgerState (TestBlockWith ptype)] → Encoding #

decodeList ∷ Decoder s [LedgerState (TestBlockWith ptype)] #

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

Defined in Test.Util.TestBlock

Methods

encodeHeader (TestBlockWith ptype) → Encoding #

decode ∷ Decoder s (Header (TestBlockWith ptype)) #

encodeList ∷ [Header (TestBlockWith ptype)] → Encoding #

decodeList ∷ Decoder s [Header (TestBlockWith ptype)] #

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

Defined in Test.Util.TestBlock

Methods

encodeTestBlockWith ptype → Encoding #

decode ∷ Decoder s (TestBlockWith ptype) #

encodeList ∷ [TestBlockWith ptype] → Encoding #

decodeList ∷ Decoder s [TestBlockWith ptype] #

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

Defined in Test.Util.TestBlock

ConfigSupportsNode (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

Serialise ptype ⇒ HasBinaryBlockInfo (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 ⇒ HasAnnTip (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type TipInfo (TestBlockWith ptype) Source #

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

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

Associated Types

type OtherHeaderEnvelopeError (TestBlockWith ptype) Source #

(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

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

(Typeable ptype, Eq ptype) ⇒ GetPrevHash (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

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

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

Defined in Test.Util.TestBlock

(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

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

Defined in Test.Util.TestBlock

HasNetworkProtocolVersion (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

Methods

noThunks ∷ Context → LedgerState (TestBlockWith ptype) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → LedgerState (TestBlockWith ptype) → IO (Maybe ThunkInfo) #

showTypeOfProxy (LedgerState (TestBlockWith ptype)) → String #

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

Defined in Test.Util.TestBlock

Methods

noThunks ∷ Context → BlockConfig (TestBlockWith ptype) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → BlockConfig (TestBlockWith ptype) → IO (Maybe ThunkInfo) #

showTypeOfProxy (BlockConfig (TestBlockWith ptype)) → String #

NoThunks (CodecConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

noThunks ∷ Context → CodecConfig TestBlockIO (Maybe ThunkInfo) #

wNoThunks ∷ Context → CodecConfig TestBlockIO (Maybe ThunkInfo) #

showTypeOfProxy (CodecConfig TestBlock) → String #

NoThunks (StorageConfig TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

noThunks ∷ Context → StorageConfig TestBlockIO (Maybe ThunkInfo) #

wNoThunks ∷ Context → StorageConfig TestBlockIO (Maybe ThunkInfo) #

showTypeOfProxy (StorageConfig TestBlock) → String #

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

Defined in Test.Util.TestBlock

Methods

noThunks ∷ Context → Header (TestBlockWith ptype) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Header (TestBlockWith ptype) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Header (TestBlockWith ptype)) → String #

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

Defined in Test.Util.TestBlock

Methods

noThunks ∷ Context → Ticked (LedgerState (TestBlockWith ptype)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Ticked (LedgerState (TestBlockWith ptype)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Ticked (LedgerState (TestBlockWith ptype))) → String #

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

Defined in Test.Util.TestBlock

Methods

noThunks ∷ Context → TestBlockWith ptype → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → TestBlockWith ptype → IO (Maybe ThunkInfo) #

showTypeOfProxy (TestBlockWith ptype) → String #

ShowQuery (BlockQuery TestBlock) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

showResultBlockQuery TestBlock result → result → String Source #

StandardHash (TestBlockWith ptype) 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

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

Defined in Test.Util.TestBlock

Methods

toExprLedgerState (TestBlockWith ptype) → Expr

listToExpr ∷ [LedgerState (TestBlockWith ptype)] → Expr

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

Defined in Test.Util.TestBlock

Methods

toExprTicked (LedgerState (TestBlockWith ptype)) → Expr

listToExpr ∷ [Ticked (LedgerState (TestBlockWith ptype))] → Expr

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

Defined in Test.Util.TestBlock

Methods

toExprTestBlockWith ptype → Expr

listToExpr ∷ [TestBlockWith ptype] → Expr

EncodeDisk (TestBlockWith ptype) () Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

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

DecodeDisk (TestBlockWith ptype) () Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

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

ShowProxy TestBlock Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

Methods

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

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

Defined in Test.Util.TestBlock

Methods

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

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

Defined in Test.Util.TestBlock

Methods

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

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

Defined in Test.Util.TestBlock

Methods

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

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 #

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

Defined in Test.Util.TestBlock

Methods

encodeDiskDepCodecConfig (TestBlockWith ptype) → NestedCtxt Header (TestBlockWith ptype) a → a → Encoding 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 #

PayloadSemantics ptype ⇒ ApplyBlock (LedgerState (TestBlockWith ptype)) (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 #

Eq (BlockQuery TestBlock result) Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

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

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

Show (BlockQuery TestBlock result) 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 Source #

showNestedCtxt_ (TestBlockWith ptype) f a → String Source #

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

data BlockQuery TestBlock result Source # 
Instance details

Defined in Test.Util.TestBlock

type HardForkIndices 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

data StorageConfig TestBlock Source #

The TestBlock does not need any storage config

Instance details

Defined in Test.Util.TestBlock

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-test-0.3.1.0-inplace" '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 (BlockConfig (TestBlockWith ptype)) Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep (BlockConfig (TestBlockWith ptype)) = D1 ('MetaData "BlockConfig" "Test.Util.TestBlock" "ouroboros-consensus-test-0.3.1.0-inplace" '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-test-0.3.1.0-inplace" '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-test-0.3.1.0-inplace" 'False) (C1 ('MetaCons "TestBlockStorageConfig" 'PrefixI 'False) (U1TypeType))
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-test-0.3.1.0-inplace" '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-test-0.3.1.0-inplace" '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))))
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 TipInfo (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

type OtherHeaderEnvelopeError (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

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

Defined in Test.Util.TestBlock

type AuxLedgerEvent (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 BlockProtocol (TestBlockWith ptype) Source # 
Instance details

Defined in Test.Util.TestBlock

data BlockConfig (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
newtype Ticked (LedgerState (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)) = ()
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 HeaderHash (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
Eq TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

Ord TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

Show TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

Generic TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep TestHashTypeType Source #

Serialise TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

encodeTestHash → Encoding #

decode ∷ Decoder s TestHash #

encodeList ∷ [TestHash] → Encoding #

decodeList ∷ Decoder s [TestHash] #

Condense TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

NoThunks TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

noThunks ∷ Context → TestHashIO (Maybe ThunkInfo) #

wNoThunks ∷ Context → TestHashIO (Maybe ThunkInfo) #

showTypeOfProxy TestHashString #

ToExpr TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

toExprTestHash → Expr

listToExpr ∷ [TestHash] → Expr

type Rep TestHash Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep TestHash = D1 ('MetaData "TestHash" "Test.Util.TestBlock" "ouroboros-consensus-test-0.3.1.0-inplace" '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

Eq Validity Source # 
Instance details

Defined in Test.Util.TestBlock

Ord Validity Source # 
Instance details

Defined in Test.Util.TestBlock

Show Validity Source # 
Instance details

Defined in Test.Util.TestBlock

Generic Validity Source # 
Instance details

Defined in Test.Util.TestBlock

Associated Types

type Rep ValidityTypeType Source #

Serialise Validity Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

encodeValidity → Encoding #

decode ∷ Decoder s Validity #

encodeList ∷ [Validity] → Encoding #

decodeList ∷ Decoder s [Validity] #

NoThunks Validity Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

noThunks ∷ Context → ValidityIO (Maybe ThunkInfo) #

wNoThunks ∷ Context → ValidityIO (Maybe ThunkInfo) #

showTypeOfProxy ValidityString #

ToExpr Validity Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

toExprValidity → Expr

listToExpr ∷ [Validity] → Expr

type Rep Validity Source # 
Instance details

Defined in Test.Util.TestBlock

type Rep Validity = D1 ('MetaData "Validity" "Test.Util.TestBlock" "ouroboros-consensus-test-0.3.1.0-inplace" '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

Instances

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

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

Defined in Test.Util.TestBlock

Associated Types

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

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

Defined in Test.Util.TestBlock

Associated Types

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

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

Defined in Test.Util.TestBlock

Methods

encodeLedgerState (TestBlockWith ptype) → Encoding #

decode ∷ Decoder s (LedgerState (TestBlockWith ptype)) #

encodeList ∷ [LedgerState (TestBlockWith ptype)] → Encoding #

decodeList ∷ Decoder s [LedgerState (TestBlockWith ptype)] #

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

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

noThunks ∷ Context → LedgerState (HardForkBlock xs) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → LedgerState (HardForkBlock xs) → IO (Maybe ThunkInfo) #

showTypeOfProxy (LedgerState (HardForkBlock xs)) → String #

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

Defined in Test.Util.TestBlock

Methods

noThunks ∷ Context → LedgerState (TestBlockWith ptype) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → LedgerState (TestBlockWith ptype) → IO (Maybe ThunkInfo) #

showTypeOfProxy (LedgerState (TestBlockWith ptype)) → String #

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

Defined in Test.Util.TestBlock

Methods

noThunks ∷ Context → Ticked (LedgerState (TestBlockWith ptype)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Ticked (LedgerState (TestBlockWith ptype)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Ticked (LedgerState (TestBlockWith ptype))) → String #

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

Defined in Test.Util.Orphans.Arbitrary

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

Defined in Test.Util.TestBlock

Methods

toExprLedgerState (TestBlockWith ptype) → Expr

listToExpr ∷ [LedgerState (TestBlockWith ptype)] → Expr

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

Defined in Test.Util.TestBlock

Methods

toExprTicked (LedgerState (TestBlockWith ptype)) → Expr

listToExpr ∷ [Ticked (LedgerState (TestBlockWith ptype))] → Expr

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

Defined in Test.Util.TestBlock

Methods

encodeDiskCodecConfig (TestBlockWith ptype) → LedgerState (TestBlockWith ptype) → Encoding 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 #

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

Defined in Test.Util.TestBlock

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-test-0.3.1.0-inplace" '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.3.1.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-test-0.3.1.0-inplace" 'True) (C1 ('MetaCons "TickedTestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTickedTestLedger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerState (TestBlockWith ptype)))))
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 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 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

type HeaderHash (LedgerState blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

data family Ticked st Source #

" Ticked " piece of state (LedgerState, LedgerView, ChainIndepState)

Ticking refers to the passage of time (the ticking of the clock). When a piece of state is marked as ticked, it means that time-related changes have been applied to the state (or forecast).

Some examples of time related changes:

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

Instances

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

Defined in Test.Util.TestBlock

Show (Ticked ()) 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecIntTicked () → ShowS Source #

showTicked () → String Source #

showList ∷ [Ticked ()] → ShowS Source #

(SListI xs, Show (Ticked a)) ⇒ Show (Ticked (HardForkLedgerView_ (K a ∷ TypeType) xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol.LedgerView

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

Defined in Test.Util.TestBlock

Show (Ticked a) ⇒ Show (Ticked (K a x)) 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecIntTicked (K a x) → ShowS Source #

showTicked (K a x) → String Source #

showList ∷ [Ticked (K a x)] → ShowS Source #

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

Defined in Test.Util.TestBlock

Associated Types

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

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

Defined in Ouroboros.Consensus.Ledger.Extended

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

Methods

noThunks ∷ Context → Ticked (LedgerState (TestBlockWith ptype)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Ticked (LedgerState (TestBlockWith ptype)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Ticked (LedgerState (TestBlockWith ptype))) → String #

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

Defined in Test.Util.TestBlock

Methods

toExprTicked (LedgerState (TestBlockWith ptype)) → Expr

listToExpr ∷ [Ticked (LedgerState (TestBlockWith ptype))] → Expr

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

Defined in Ouroboros.Consensus.Ticked

Methods

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

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

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

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

Defined in Ouroboros.Consensus.Ticked

Methods

noThunks ∷ Context → (Ticked :.: f) a → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → (Ticked :.: f) a → IO (Maybe ThunkInfo) #

showTypeOfProxy ((Ticked :.: f) a) → String #

data Ticked () 
Instance details

Defined in Ouroboros.Consensus.Ticked

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.3.1.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-test-0.3.1.0-inplace" 'True) (C1 ('MetaCons "TickedTestLedger" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTickedTestLedger") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (LedgerState (TestBlockWith ptype)))))
newtype Ticked (PBftLedgerView c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

data Ticked (PBftState c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

data Ticked (HardForkChainDepState xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

data Ticked (ExtLedgerState blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

newtype Ticked (WrapChainDepState blk) 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

newtype Ticked (WrapLedgerView blk) 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

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

type HeaderHash (Ticked l) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

data Ticked (HardForkLedgerView_ f xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol.LedgerView

newtype Ticked (K a x) 
Instance details

Defined in Ouroboros.Consensus.Ticked

newtype Ticked (K a x) = TickedK {}

Chain

newtype BlockChain Source #

Constructors

BlockChain Word64 

Instances

Instances details
Show BlockChain Source # 
Instance details

Defined in Test.Util.TestBlock

Arbitrary BlockChain Source # 
Instance details

Defined in Test.Util.TestBlock

Tree

newtype BlockTree Source #

Constructors

BlockTree (Tree ()) 

Instances

Instances details
Show BlockTree Source # 
Instance details

Defined in Test.Util.TestBlock

Arbitrary BlockTree Source # 
Instance details

Defined in Test.Util.TestBlock

Methods

arbitrary ∷ Gen BlockTree

shrinkBlockTree → [BlockTree]

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
Show Permutation Source # 
Instance details

Defined in Test.Util.TestBlock

Arbitrary Permutation Source # 
Instance details

Defined in Test.Util.TestBlock

permutePermutation → [a] → [a] Source #