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

Ouroboros.Consensus.Block.NestedContent

Synopsis

Block contents

class (∀ a. Show (NestedCtxt_ blk f a), SameDepIndex (NestedCtxt_ blk f)) ⇒ HasNestedContent f blk where Source #

Nested content inside a block

Consider a simplified version of the hard fork combinator, defining

type HardFork a b = Either a b

Then encoding Hardfork ByronBlock ShelleyBlock is easy, in the same way that we encode any Either. The header of such a block will have type

HardFork (Header ByronBlock) (Header ShelleyBlock)

and encoding those (for example, to send them across the network) is similarly trivial. But now suppose we want to read a header from disk. We do not store headers directly, but instead store the blocks. The DB will know the offset and length (both in bytes) of the header inside the block, but how do we decode such a header? If it's a Byron block, we should use the decoder for Header ByronBlock, and similarly for Shelley, but how should we express this more generally?

Here is where HasNestedContent comes in. Continuing the example, we can unnest a Header (HardFork ByronBlock ShelleyBlock) into a pair of values, where the first value (a NestedCtxt) tells us what type of block we have, and the second value gives us the actual header. So, if the first value says "this is a Byron block", the second value is a Header ByronBlock, and vice versa. In other words, this is a dependent pair.

This then solves the serialisation problem: we expect a dependent decoder which, given a NestedCtxt identifying the block type, decodes the raw bytes from the block into the type indicated by that NestedCtxt.

TODO: We could perhaps define this independent of blocks in GenDepPair.

Minimal complete definition

Nothing

Methods

unnest ∷ f blk → DepPair (NestedCtxt f blk) Source #

default unnest ∷ (TrivialDependency (NestedCtxt f blk), TrivialIndex (NestedCtxt f blk) ~ f blk) ⇒ f blk → DepPair (NestedCtxt f blk) Source #

nestDepPair (NestedCtxt f blk) → f blk Source #

default nest ∷ (TrivialDependency (NestedCtxt f blk), TrivialIndex (NestedCtxt f blk) ~ f blk) ⇒ DepPair (NestedCtxt f blk) → f blk Source #

data family NestedCtxt_ blk ∷ (TypeType) → TypeType Source #

Context identifying what kind of block we have

In almost all places we will use NestedCtxt rather than NestedCtxt_.

Instances

Instances details
CanHardFork xs ⇒ SameDepIndex (NestedCtxt_ (HardForkBlock xs) Header) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

SameDepIndex (NestedCtxt_ m f) ⇒ SameDepIndex (NestedCtxt_ (DualBlock m a) f) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

sameDepIndexNestedCtxt_ (DualBlock m a) f a0 → NestedCtxt_ (DualBlock m a) f b → Maybe (a0 :~: b) Source #

All SingleEraBlock xs ⇒ Show (NestedCtxt_ (HardForkBlock xs) Header a) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

Show (NestedCtxt_ m f x) ⇒ Show (NestedCtxt_ (DualBlock m a) f x) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntNestedCtxt_ (DualBlock m a) f x → ShowS #

showNestedCtxt_ (DualBlock m a) f x → String #

showList ∷ [NestedCtxt_ (DualBlock m a) f x] → ShowS #

data NestedCtxt_ (HardForkBlock xs) a b Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

data NestedCtxt_ (HardForkBlock xs) a b where
newtype NestedCtxt_ (DualBlock m a) f x Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

newtype NestedCtxt_ (DualBlock m a) f x where

curriedNestHasNestedContent f blk ⇒ NestedCtxt f blk a → a → f blk Source #

Flip type arguments

newtype NestedCtxt f blk a Source #

Version of NestedCtxt_ with the type arguments swapped

NestedCtxt must be indexed on blk: it is the block that determines this type. However, we often want to partially apply the second argument (the functor), leaving the block type not yet defined.

Constructors

NestedCtxt 

Fields

Instances

Instances details
SerialiseHFC xs ⇒ DecodeDiskDep (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

SerialiseHFC xs ⇒ DecodeDiskDepIx (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

SerialiseHFC xs ⇒ EncodeDiskDep (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

SerialiseHFC xs ⇒ EncodeDiskDepIx (NestedCtxt Header) (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

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

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

Defined in Ouroboros.Consensus.Ledger.Dual

(HasNestedContent f blk, ∀ a. Show (g a)) ⇒ Show (GenDepPair g (NestedCtxt f blk)) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.NestedContent

Methods

showsPrecIntGenDepPair g (NestedCtxt f blk) → ShowS #

showGenDepPair g (NestedCtxt f blk) → String #

showList ∷ [GenDepPair g (NestedCtxt f blk)] → ShowS #

SameDepIndex (NestedCtxt_ blk f) ⇒ SameDepIndex (NestedCtxt f blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.NestedContent

Methods

sameDepIndexNestedCtxt f blk a → NestedCtxt f blk b → Maybe (a :~: b) Source #

TrivialDependency (NestedCtxt_ blk f) ⇒ TrivialDependency (NestedCtxt f blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.NestedContent

Associated Types

type TrivialIndex (NestedCtxt f blk) Source #

Methods

hasSingleIndexNestedCtxt f blk a → NestedCtxt f blk b → a :~: b Source #

indexIsTrivialNestedCtxt f blk (TrivialIndex (NestedCtxt f blk)) Source #

Show (NestedCtxt_ blk f a) ⇒ Show (NestedCtxt f blk a) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.NestedContent

Methods

showsPrecIntNestedCtxt f blk a → ShowS #

showNestedCtxt f blk a → String #

showList ∷ [NestedCtxt f blk a] → ShowS #

Isomorphic (SomeSecond (NestedCtxt f)) Source # 
Instance details

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

HasNestedContent f blk ⇒ Show (SomeSecond (NestedCtxt f) blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.NestedContent

Methods

showsPrecIntSomeSecond (NestedCtxt f) blk → ShowS #

showSomeSecond (NestedCtxt f) blk → String #

showList ∷ [SomeSecond (NestedCtxt f) blk] → ShowS #

SameDepIndex (NestedCtxt_ blk f) ⇒ Eq (SomeSecond (NestedCtxt f) blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.NestedContent

Methods

(==)SomeSecond (NestedCtxt f) blk → SomeSecond (NestedCtxt f) blk → Bool #

(/=)SomeSecond (NestedCtxt f) blk → SomeSecond (NestedCtxt f) blk → Bool #

(Typeable f, Typeable blk) ⇒ NoThunks (SomeSecond (NestedCtxt f) blk) Source #

We can write a manual instance using the following quantified constraint:

forall a. NoThunks (f blk a)

However, this constraint would have to be propagated all the way up, which is rather verbose and annoying (standalone deriving has to be used), hence we use InspectHeap for convenience.

Instance details

Defined in Ouroboros.Consensus.Block.NestedContent

type TrivialIndex (NestedCtxt f blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.NestedContent

castNestedCtxt ∷ (NestedCtxt_ blk f a → NestedCtxt_ blk' f a) → NestedCtxt f blk a → NestedCtxt f blk' a Source #

mapNestedCtxt ∷ (NestedCtxt_ blk f a → NestedCtxt_ blk' f' a') → NestedCtxt f blk a → NestedCtxt f' blk' a' Source #

Existentials

castSomeNestedCtxt ∷ (∀ a. NestedCtxt_ blk f a → NestedCtxt_ blk' f a) → SomeSecond (NestedCtxt f) blk → SomeSecond (NestedCtxt f) blk' Source #

mapSomeNestedCtxt ∷ (∀ a. NestedCtxt_ blk f a → NestedCtxt_ blk' f' a) → SomeSecond (NestedCtxt f) blk → SomeSecond (NestedCtxt f') blk' Source #

Convenience re-exports

data SomeSecond f a where Source #

Hide the second type argument of some functor

SomeSecond f a is isomorphic to Some (f a), but is more convenient in partial applications.

Constructors

SomeSecond ∷ !(f a b) → SomeSecond f a 

Instances

Instances details
SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) (SomeSecond BlockQuery (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToClient

Inject (SomeSecond BlockQuery) Source # 
Instance details

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

Methods

inject ∷ ∀ x (xs ∷ [Type]). CanHardFork xs ⇒ Exactly xs BoundIndex xs x → SomeSecond BlockQuery x → SomeSecond BlockQuery (HardForkBlock xs) Source #

Isomorphic (SomeSecond (NestedCtxt f)) Source # 
Instance details

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

HasNestedContent f blk ⇒ Show (SomeSecond (NestedCtxt f) blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.NestedContent

Methods

showsPrecIntSomeSecond (NestedCtxt f) blk → ShowS #

showSomeSecond (NestedCtxt f) blk → String #

showList ∷ [SomeSecond (NestedCtxt f) blk] → ShowS #

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

Defined in Ouroboros.Consensus.Ledger.Query

Show (SomeSecond BlockQuery blk) ⇒ Show (SomeSecond Query blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Query

Methods

showsPrecIntSomeSecond Query blk → ShowS #

showSomeSecond Query blk → String #

showList ∷ [SomeSecond Query blk] → ShowS #

SameDepIndex (NestedCtxt_ blk f) ⇒ Eq (SomeSecond (NestedCtxt f) blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Block.NestedContent

Methods

(==)SomeSecond (NestedCtxt f) blk → SomeSecond (NestedCtxt f) blk → Bool #

(/=)SomeSecond (NestedCtxt f) blk → SomeSecond (NestedCtxt f) blk → Bool #

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

Defined in Ouroboros.Consensus.Ledger.Query

Eq (SomeSecond BlockQuery blk) ⇒ Eq (SomeSecond Query blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Query

Methods

(==)SomeSecond Query blk → SomeSecond Query blk → Bool #

(/=)SomeSecond Query blk → SomeSecond Query blk → Bool #

(Typeable f, Typeable blk) ⇒ NoThunks (SomeSecond (NestedCtxt f) blk) Source #

We can write a manual instance using the following quantified constraint:

forall a. NoThunks (f blk a)

However, this constraint would have to be propagated all the way up, which is rather verbose and annoying (standalone deriving has to be used), hence we use InspectHeap for convenience.

Instance details

Defined in Ouroboros.Consensus.Block.NestedContent