{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableSuperClasses #-}
{-# OPTIONS_GHC -Wno-orphans #-}
#if __GLASGOW_HASKELL__ <= 906
{-# OPTIONS_GHC -Wno-incomplete-patterns
-Wno-incomplete-uni-patterns
-Wno-incomplete-record-updates
-Wno-overlapping-patterns #-}
#endif
{-# OPTIONS_GHC -Wno-name-shadowing #-}
module Ouroboros.Consensus.Cardano.Node (
CardanoHardForkConstraints
, CardanoHardForkTrigger (..)
, CardanoHardForkTriggers (.., CardanoHardForkTriggers', triggerHardForkShelley, triggerHardForkAllegra, triggerHardForkMary, triggerHardForkAlonzo, triggerHardForkBabbage, triggerHardForkConway)
, CardanoProtocolParams (..)
, MaxMajorProtVer (..)
, TriggerHardFork (..)
, protocolClientInfoCardano
, protocolInfoCardano
, pattern CardanoNodeToClientVersion1
, pattern CardanoNodeToClientVersion10
, pattern CardanoNodeToClientVersion11
, pattern CardanoNodeToClientVersion12
, pattern CardanoNodeToClientVersion13
, pattern CardanoNodeToClientVersion14
, pattern CardanoNodeToClientVersion15
, pattern CardanoNodeToClientVersion2
, pattern CardanoNodeToClientVersion3
, pattern CardanoNodeToClientVersion4
, pattern CardanoNodeToClientVersion5
, pattern CardanoNodeToClientVersion6
, pattern CardanoNodeToClientVersion7
, pattern CardanoNodeToClientVersion8
, pattern CardanoNodeToClientVersion9
, pattern CardanoNodeToNodeVersion1
, pattern CardanoNodeToNodeVersion2
) where
import Cardano.Binary (DecoderError (..), enforceSize)
import Cardano.Chain.Slotting (EpochSlots)
import qualified Cardano.Ledger.Api.Era as L
import qualified Cardano.Ledger.Api.Transition as L
import qualified Cardano.Ledger.BaseTypes as SL
import qualified Cardano.Ledger.Shelley.API as SL
import Cardano.Prelude (cborError)
import qualified Cardano.Protocol.TPraos.OCert as Absolute (KESPeriod (..),
ocertKESPeriod)
import qualified Codec.CBOR.Decoding as CBOR
import Codec.CBOR.Encoding (Encoding)
import qualified Codec.CBOR.Encoding as CBOR
import Control.Exception (assert)
import qualified Data.ByteString.Short as Short
import Data.Functor.These (These1 (..))
import qualified Data.Map.Strict as Map
import Data.SOP.BasicFunctors
import Data.SOP.Counting
import Data.SOP.Index (Index (..))
import Data.SOP.OptNP (NonEmptyOptNP, OptNP (OptSkip))
import qualified Data.SOP.OptNP as OptNP
import Data.SOP.Strict
import Data.Word (Word16, Word64)
import Lens.Micro ((^.))
import Ouroboros.Consensus.Block
import Ouroboros.Consensus.Byron.Ledger (ByronBlock)
import qualified Ouroboros.Consensus.Byron.Ledger as Byron
import qualified Ouroboros.Consensus.Byron.Ledger.Conversions as Byron
import Ouroboros.Consensus.Byron.Ledger.NetworkProtocolVersion
import Ouroboros.Consensus.Byron.Node
import Ouroboros.Consensus.Cardano.Block
import Ouroboros.Consensus.Cardano.CanHardFork
import Ouroboros.Consensus.Config
import Ouroboros.Consensus.HardFork.Combinator
import Ouroboros.Consensus.HardFork.Combinator.Embed.Nary
import Ouroboros.Consensus.HardFork.Combinator.Serialisation
import qualified Ouroboros.Consensus.HardFork.History as History
import Ouroboros.Consensus.HeaderValidation
import Ouroboros.Consensus.Ledger.Extended
import Ouroboros.Consensus.Node.NetworkProtocolVersion
import Ouroboros.Consensus.Node.ProtocolInfo
import Ouroboros.Consensus.Node.Run
import qualified Ouroboros.Consensus.Protocol.Ledger.HotKey as HotKey
import Ouroboros.Consensus.Protocol.Praos (Praos, PraosParams (..))
import Ouroboros.Consensus.Protocol.Praos.Common
(praosCanBeLeaderOpCert)
import Ouroboros.Consensus.Protocol.TPraos (TPraos, TPraosParams (..))
import qualified Ouroboros.Consensus.Protocol.TPraos as Shelley
import Ouroboros.Consensus.Shelley.HFEras ()
import Ouroboros.Consensus.Shelley.Ledger (ShelleyBlock)
import qualified Ouroboros.Consensus.Shelley.Ledger as Shelley
import Ouroboros.Consensus.Shelley.Ledger.Block (IsShelleyBlock,
ShelleyBlockLedgerEra)
import Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion
import Ouroboros.Consensus.Shelley.Node
import Ouroboros.Consensus.Shelley.Node.Common (ShelleyEraWithCrypto,
shelleyBlockIssuerVKey)
import qualified Ouroboros.Consensus.Shelley.Node.Praos as Praos
import qualified Ouroboros.Consensus.Shelley.Node.TPraos as TPraos
import Ouroboros.Consensus.Storage.Serialisation
import Ouroboros.Consensus.TypeFamilyWrappers
import Ouroboros.Consensus.Util.Assert
import Ouroboros.Consensus.Util.IOLike
instance SerialiseConstraintsHFC ByronBlock
instance CardanoHardForkConstraints c => SerialiseHFC (CardanoEras c) where
encodeDiskHfcBlock :: CodecConfig (HardForkBlock (CardanoEras c))
-> HardForkBlock (CardanoEras c) -> Encoding
encodeDiskHfcBlock (CardanoCodecConfig CodecConfig ByronBlock
ccfgByron CodecConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
ccfgShelley CodecConfig (ShelleyBlock (TPraos c) (AllegraEra c))
ccfgAllegra CodecConfig (ShelleyBlock (TPraos c) (MaryEra c))
ccfgMary CodecConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
ccfgAlonzo CodecConfig (ShelleyBlock (Praos c) (BabbageEra c))
ccfgBabbage CodecConfig (ShelleyBlock (Praos c) (ConwayEra c))
ccfgConway) = \case
BlockByron ByronBlock
blockByron -> CodecConfig ByronBlock -> ByronBlock -> Encoding
forall blk a. EncodeDisk blk a => CodecConfig blk -> a -> Encoding
encodeDisk CodecConfig ByronBlock
ccfgByron ByronBlock
blockByron
BlockShelley ShelleyBlock (TPraos c) (ShelleyEra c)
blockShelley -> Word -> Encoding -> Encoding
prependTag Word
2 (Encoding -> Encoding) -> Encoding -> Encoding
forall a b. (a -> b) -> a -> b
$ CodecConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> ShelleyBlock (TPraos c) (ShelleyEra c) -> Encoding
forall blk a. EncodeDisk blk a => CodecConfig blk -> a -> Encoding
encodeDisk CodecConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
ccfgShelley ShelleyBlock (TPraos c) (ShelleyEra c)
blockShelley
BlockAllegra ShelleyBlock (TPraos c) (AllegraEra c)
blockAllegra -> Word -> Encoding -> Encoding
prependTag Word
3 (Encoding -> Encoding) -> Encoding -> Encoding
forall a b. (a -> b) -> a -> b
$ CodecConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> ShelleyBlock (TPraos c) (AllegraEra c) -> Encoding
forall blk a. EncodeDisk blk a => CodecConfig blk -> a -> Encoding
encodeDisk CodecConfig (ShelleyBlock (TPraos c) (AllegraEra c))
ccfgAllegra ShelleyBlock (TPraos c) (AllegraEra c)
blockAllegra
BlockMary ShelleyBlock (TPraos c) (MaryEra c)
blockMary -> Word -> Encoding -> Encoding
prependTag Word
4 (Encoding -> Encoding) -> Encoding -> Encoding
forall a b. (a -> b) -> a -> b
$ CodecConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> ShelleyBlock (TPraos c) (MaryEra c) -> Encoding
forall blk a. EncodeDisk blk a => CodecConfig blk -> a -> Encoding
encodeDisk CodecConfig (ShelleyBlock (TPraos c) (MaryEra c))
ccfgMary ShelleyBlock (TPraos c) (MaryEra c)
blockMary
BlockAlonzo ShelleyBlock (TPraos c) (AlonzoEra c)
blockAlonzo -> Word -> Encoding -> Encoding
prependTag Word
5 (Encoding -> Encoding) -> Encoding -> Encoding
forall a b. (a -> b) -> a -> b
$ CodecConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> ShelleyBlock (TPraos c) (AlonzoEra c) -> Encoding
forall blk a. EncodeDisk blk a => CodecConfig blk -> a -> Encoding
encodeDisk CodecConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
ccfgAlonzo ShelleyBlock (TPraos c) (AlonzoEra c)
blockAlonzo
BlockBabbage ShelleyBlock (Praos c) (BabbageEra c)
blockBabbage -> Word -> Encoding -> Encoding
prependTag Word
6 (Encoding -> Encoding) -> Encoding -> Encoding
forall a b. (a -> b) -> a -> b
$ CodecConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> ShelleyBlock (Praos c) (BabbageEra c) -> Encoding
forall blk a. EncodeDisk blk a => CodecConfig blk -> a -> Encoding
encodeDisk CodecConfig (ShelleyBlock (Praos c) (BabbageEra c))
ccfgBabbage ShelleyBlock (Praos c) (BabbageEra c)
blockBabbage
BlockConway ShelleyBlock (Praos c) (ConwayEra c)
blockConway -> Word -> Encoding -> Encoding
prependTag Word
7 (Encoding -> Encoding) -> Encoding -> Encoding
forall a b. (a -> b) -> a -> b
$ CodecConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> ShelleyBlock (Praos c) (ConwayEra c) -> Encoding
forall blk a. EncodeDisk blk a => CodecConfig blk -> a -> Encoding
encodeDisk CodecConfig (ShelleyBlock (Praos c) (ConwayEra c))
ccfgConway ShelleyBlock (Praos c) (ConwayEra c)
blockConway
decodeDiskHfcBlock :: CodecConfig (HardForkBlock (CardanoEras c))
-> forall s.
Decoder s (ByteString -> HardForkBlock (CardanoEras c))
decodeDiskHfcBlock (CardanoCodecConfig CodecConfig ByronBlock
ccfgByron CodecConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
ccfgShelley CodecConfig (ShelleyBlock (TPraos c) (AllegraEra c))
ccfgAllegra CodecConfig (ShelleyBlock (TPraos c) (MaryEra c))
ccfgMary CodecConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
ccfgAlonzo CodecConfig (ShelleyBlock (Praos c) (BabbageEra c))
ccfgBabbage CodecConfig (ShelleyBlock (Praos c) (ConwayEra c))
ccfgConway) = do
Text -> Int -> Decoder s ()
forall s. Text -> Int -> Decoder s ()
enforceSize Text
"CardanoBlock" Int
2
Decoder s Word
forall s. Decoder s Word
CBOR.decodeWord Decoder s Word
-> (Word
-> Decoder s (ByteString -> HardForkBlock (CardanoEras c)))
-> Decoder s (ByteString -> HardForkBlock (CardanoEras c))
forall a b. Decoder s a -> (a -> Decoder s b) -> Decoder s b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Word
0 -> (ByronBlock -> HardForkBlock (CardanoEras c))
-> (ByteString -> ByronBlock)
-> ByteString
-> HardForkBlock (CardanoEras c)
forall a b. (a -> b) -> (ByteString -> a) -> ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByronBlock -> HardForkBlock (CardanoEras c)
forall c. ByronBlock -> CardanoBlock c
BlockByron ((ByteString -> ByronBlock)
-> ByteString -> HardForkBlock (CardanoEras c))
-> Decoder s (ByteString -> ByronBlock)
-> Decoder s (ByteString -> HardForkBlock (CardanoEras c))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> EpochSlots -> Decoder s (ByteString -> ByronBlock)
forall s. EpochSlots -> Decoder s (ByteString -> ByronBlock)
Byron.decodeByronBoundaryBlock EpochSlots
epochSlots
Word
1 -> (ByronBlock -> HardForkBlock (CardanoEras c))
-> (ByteString -> ByronBlock)
-> ByteString
-> HardForkBlock (CardanoEras c)
forall a b. (a -> b) -> (ByteString -> a) -> ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByronBlock -> HardForkBlock (CardanoEras c)
forall c. ByronBlock -> CardanoBlock c
BlockByron ((ByteString -> ByronBlock)
-> ByteString -> HardForkBlock (CardanoEras c))
-> Decoder s (ByteString -> ByronBlock)
-> Decoder s (ByteString -> HardForkBlock (CardanoEras c))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> EpochSlots -> Decoder s (ByteString -> ByronBlock)
forall s. EpochSlots -> Decoder s (ByteString -> ByronBlock)
Byron.decodeByronRegularBlock EpochSlots
epochSlots
Word
2 -> (ShelleyBlock (TPraos c) (ShelleyEra c)
-> HardForkBlock (CardanoEras c))
-> (ByteString -> ShelleyBlock (TPraos c) (ShelleyEra c))
-> ByteString
-> HardForkBlock (CardanoEras c)
forall a b. (a -> b) -> (ByteString -> a) -> ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShelleyBlock (TPraos c) (ShelleyEra c)
-> HardForkBlock (CardanoEras c)
forall c. ShelleyBlock (TPraos c) (ShelleyEra c) -> CardanoBlock c
BlockShelley ((ByteString -> ShelleyBlock (TPraos c) (ShelleyEra c))
-> ByteString -> HardForkBlock (CardanoEras c))
-> Decoder s (ByteString -> ShelleyBlock (TPraos c) (ShelleyEra c))
-> Decoder s (ByteString -> HardForkBlock (CardanoEras c))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CodecConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> forall s.
Decoder s (ByteString -> ShelleyBlock (TPraos c) (ShelleyEra c))
forall blk a.
DecodeDisk blk a =>
CodecConfig blk -> forall s. Decoder s a
decodeDisk CodecConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
ccfgShelley
Word
3 -> (ShelleyBlock (TPraos c) (AllegraEra c)
-> HardForkBlock (CardanoEras c))
-> (ByteString -> ShelleyBlock (TPraos c) (AllegraEra c))
-> ByteString
-> HardForkBlock (CardanoEras c)
forall a b. (a -> b) -> (ByteString -> a) -> ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShelleyBlock (TPraos c) (AllegraEra c)
-> HardForkBlock (CardanoEras c)
forall c. ShelleyBlock (TPraos c) (AllegraEra c) -> CardanoBlock c
BlockAllegra ((ByteString -> ShelleyBlock (TPraos c) (AllegraEra c))
-> ByteString -> HardForkBlock (CardanoEras c))
-> Decoder s (ByteString -> ShelleyBlock (TPraos c) (AllegraEra c))
-> Decoder s (ByteString -> HardForkBlock (CardanoEras c))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CodecConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> forall s.
Decoder s (ByteString -> ShelleyBlock (TPraos c) (AllegraEra c))
forall blk a.
DecodeDisk blk a =>
CodecConfig blk -> forall s. Decoder s a
decodeDisk CodecConfig (ShelleyBlock (TPraos c) (AllegraEra c))
ccfgAllegra
Word
4 -> (ShelleyBlock (TPraos c) (MaryEra c)
-> HardForkBlock (CardanoEras c))
-> (ByteString -> ShelleyBlock (TPraos c) (MaryEra c))
-> ByteString
-> HardForkBlock (CardanoEras c)
forall a b. (a -> b) -> (ByteString -> a) -> ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShelleyBlock (TPraos c) (MaryEra c)
-> HardForkBlock (CardanoEras c)
forall c. ShelleyBlock (TPraos c) (MaryEra c) -> CardanoBlock c
BlockMary ((ByteString -> ShelleyBlock (TPraos c) (MaryEra c))
-> ByteString -> HardForkBlock (CardanoEras c))
-> Decoder s (ByteString -> ShelleyBlock (TPraos c) (MaryEra c))
-> Decoder s (ByteString -> HardForkBlock (CardanoEras c))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CodecConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> forall s.
Decoder s (ByteString -> ShelleyBlock (TPraos c) (MaryEra c))
forall blk a.
DecodeDisk blk a =>
CodecConfig blk -> forall s. Decoder s a
decodeDisk CodecConfig (ShelleyBlock (TPraos c) (MaryEra c))
ccfgMary
Word
5 -> (ShelleyBlock (TPraos c) (AlonzoEra c)
-> HardForkBlock (CardanoEras c))
-> (ByteString -> ShelleyBlock (TPraos c) (AlonzoEra c))
-> ByteString
-> HardForkBlock (CardanoEras c)
forall a b. (a -> b) -> (ByteString -> a) -> ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShelleyBlock (TPraos c) (AlonzoEra c)
-> HardForkBlock (CardanoEras c)
forall c. ShelleyBlock (TPraos c) (AlonzoEra c) -> CardanoBlock c
BlockAlonzo ((ByteString -> ShelleyBlock (TPraos c) (AlonzoEra c))
-> ByteString -> HardForkBlock (CardanoEras c))
-> Decoder s (ByteString -> ShelleyBlock (TPraos c) (AlonzoEra c))
-> Decoder s (ByteString -> HardForkBlock (CardanoEras c))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CodecConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> forall s.
Decoder s (ByteString -> ShelleyBlock (TPraos c) (AlonzoEra c))
forall blk a.
DecodeDisk blk a =>
CodecConfig blk -> forall s. Decoder s a
decodeDisk CodecConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
ccfgAlonzo
Word
6 -> (ShelleyBlock (Praos c) (BabbageEra c)
-> HardForkBlock (CardanoEras c))
-> (ByteString -> ShelleyBlock (Praos c) (BabbageEra c))
-> ByteString
-> HardForkBlock (CardanoEras c)
forall a b. (a -> b) -> (ByteString -> a) -> ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShelleyBlock (Praos c) (BabbageEra c)
-> HardForkBlock (CardanoEras c)
forall c. ShelleyBlock (Praos c) (BabbageEra c) -> CardanoBlock c
BlockBabbage ((ByteString -> ShelleyBlock (Praos c) (BabbageEra c))
-> ByteString -> HardForkBlock (CardanoEras c))
-> Decoder s (ByteString -> ShelleyBlock (Praos c) (BabbageEra c))
-> Decoder s (ByteString -> HardForkBlock (CardanoEras c))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CodecConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> forall s.
Decoder s (ByteString -> ShelleyBlock (Praos c) (BabbageEra c))
forall blk a.
DecodeDisk blk a =>
CodecConfig blk -> forall s. Decoder s a
decodeDisk CodecConfig (ShelleyBlock (Praos c) (BabbageEra c))
ccfgBabbage
Word
7 -> (ShelleyBlock (Praos c) (ConwayEra c)
-> HardForkBlock (CardanoEras c))
-> (ByteString -> ShelleyBlock (Praos c) (ConwayEra c))
-> ByteString
-> HardForkBlock (CardanoEras c)
forall a b. (a -> b) -> (ByteString -> a) -> ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShelleyBlock (Praos c) (ConwayEra c)
-> HardForkBlock (CardanoEras c)
forall c. ShelleyBlock (Praos c) (ConwayEra c) -> CardanoBlock c
BlockConway ((ByteString -> ShelleyBlock (Praos c) (ConwayEra c))
-> ByteString -> HardForkBlock (CardanoEras c))
-> Decoder s (ByteString -> ShelleyBlock (Praos c) (ConwayEra c))
-> Decoder s (ByteString -> HardForkBlock (CardanoEras c))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CodecConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> forall s.
Decoder s (ByteString -> ShelleyBlock (Praos c) (ConwayEra c))
forall blk a.
DecodeDisk blk a =>
CodecConfig blk -> forall s. Decoder s a
decodeDisk CodecConfig (ShelleyBlock (Praos c) (ConwayEra c))
ccfgConway
Word
t -> DecoderError
-> Decoder s (ByteString -> HardForkBlock (CardanoEras c))
forall e s a. Buildable e => e -> Decoder s a
cborError (DecoderError
-> Decoder s (ByteString -> HardForkBlock (CardanoEras c)))
-> DecoderError
-> Decoder s (ByteString -> HardForkBlock (CardanoEras c))
forall a b. (a -> b) -> a -> b
$ Text -> Word8 -> DecoderError
DecoderErrorUnknownTag Text
"CardanoBlock" (Word -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word
t)
where
epochSlots :: EpochSlots
epochSlots = CodecConfig ByronBlock -> EpochSlots
Byron.getByronEpochSlots CodecConfig ByronBlock
ccfgByron
reconstructHfcPrefixLen :: forall (proxy :: * -> *).
proxy (Header (HardForkBlock (CardanoEras c))) -> PrefixLen
reconstructHfcPrefixLen proxy (Header (HardForkBlock (CardanoEras c)))
_ = Word8 -> PrefixLen
PrefixLen Word8
2
reconstructHfcNestedCtxt :: forall (proxy :: * -> *).
proxy (Header (HardForkBlock (CardanoEras c)))
-> ShortByteString
-> SizeInBytes
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c))
reconstructHfcNestedCtxt proxy (Header (HardForkBlock (CardanoEras c)))
_ ShortByteString
prefix SizeInBytes
blockSize =
case HasCallStack => ShortByteString -> Int -> Word8
ShortByteString -> Int -> Word8
Short.index ShortByteString
prefix Int
1 of
Word8
0 -> NestedCtxt
Header (HardForkBlock (CardanoEras c)) (SlotNo, RawBoundaryHeader)
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c))
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (NestedCtxt
Header (HardForkBlock (CardanoEras c)) (SlotNo, RawBoundaryHeader)
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c)))
-> NestedCtxt
Header (HardForkBlock (CardanoEras c)) (SlotNo, RawBoundaryHeader)
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c))
forall a b. (a -> b) -> a -> b
$ NestedCtxt_
(HardForkBlock (CardanoEras c)) Header (SlotNo, RawBoundaryHeader)
-> NestedCtxt
Header (HardForkBlock (CardanoEras c)) (SlotNo, RawBoundaryHeader)
forall (f :: * -> *) blk a.
NestedCtxt_ blk f a -> NestedCtxt f blk a
NestedCtxt (NestedCtxt_ ByronBlock Header (SlotNo, RawBoundaryHeader)
-> NestedCtxt_
(HardForkBlock (CardanoEras c)) Header (SlotNo, RawBoundaryHeader)
forall x (a :: * -> *) b (xs1 :: [*]).
NestedCtxt_ x a b -> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCZ (SizeInBytes
-> NestedCtxt_ ByronBlock Header (SlotNo, RawBoundaryHeader)
Byron.CtxtByronBoundary SizeInBytes
blockSize))
Word8
1 -> NestedCtxt
Header (HardForkBlock (CardanoEras c)) (AHeader ByteString)
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c))
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (NestedCtxt
Header (HardForkBlock (CardanoEras c)) (AHeader ByteString)
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c)))
-> NestedCtxt
Header (HardForkBlock (CardanoEras c)) (AHeader ByteString)
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c))
forall a b. (a -> b) -> a -> b
$ NestedCtxt_
(HardForkBlock (CardanoEras c)) Header (AHeader ByteString)
-> NestedCtxt
Header (HardForkBlock (CardanoEras c)) (AHeader ByteString)
forall (f :: * -> *) blk a.
NestedCtxt_ blk f a -> NestedCtxt f blk a
NestedCtxt (NestedCtxt_ ByronBlock Header (AHeader ByteString)
-> NestedCtxt_
(HardForkBlock (CardanoEras c)) Header (AHeader ByteString)
forall x (a :: * -> *) b (xs1 :: [*]).
NestedCtxt_ x a b -> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCZ (SizeInBytes -> NestedCtxt_ ByronBlock Header (AHeader ByteString)
Byron.CtxtByronRegular SizeInBytes
blockSize))
Word8
2 -> NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c))
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c)))
-> NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c))
forall a b. (a -> b) -> a -> b
$ NestedCtxt_
(HardForkBlock (CardanoEras c))
Header
(Header (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (TPraos c) (ShelleyEra c)))
forall (f :: * -> *) blk a.
NestedCtxt_ blk f a -> NestedCtxt f blk a
NestedCtxt (NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> NestedCtxt_
(HardForkBlock (CardanoEras c))
Header
(Header (ShelleyBlock (TPraos c) (ShelleyEra c)))
forall (xs1 :: [*]) (a :: * -> *) b x.
NestedCtxt_ (HardForkBlock xs1) a b
-> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCS (NestedCtxt_
(ShelleyBlock (TPraos c) (ShelleyEra c))
Header
(Header (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (TPraos c) (ShelleyEra c)))
forall x (a :: * -> *) b (xs1 :: [*]).
NestedCtxt_ x a b -> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCZ NestedCtxt_
(ShelleyBlock (TPraos c) (ShelleyEra c))
Header
(Header (ShelleyBlock (TPraos c) (ShelleyEra c)))
forall proto era (f :: * -> *).
NestedCtxt_ (ShelleyBlock proto era) f (f (ShelleyBlock proto era))
Shelley.CtxtShelley))
Word8
3 -> NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (TPraos c) (AllegraEra c)))
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c))
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (TPraos c) (AllegraEra c)))
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c)))
-> NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (TPraos c) (AllegraEra c)))
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c))
forall a b. (a -> b) -> a -> b
$ NestedCtxt_
(HardForkBlock (CardanoEras c))
Header
(Header (ShelleyBlock (TPraos c) (AllegraEra c)))
-> NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (TPraos c) (AllegraEra c)))
forall (f :: * -> *) blk a.
NestedCtxt_ blk f a -> NestedCtxt f blk a
NestedCtxt (NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (TPraos c) (AllegraEra c)))
-> NestedCtxt_
(HardForkBlock (CardanoEras c))
Header
(Header (ShelleyBlock (TPraos c) (AllegraEra c)))
forall (xs1 :: [*]) (a :: * -> *) b x.
NestedCtxt_ (HardForkBlock xs1) a b
-> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCS (NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (TPraos c) (AllegraEra c)))
-> NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (TPraos c) (AllegraEra c)))
forall (xs1 :: [*]) (a :: * -> *) b x.
NestedCtxt_ (HardForkBlock xs1) a b
-> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCS (NestedCtxt_
(ShelleyBlock (TPraos c) (AllegraEra c))
Header
(Header (ShelleyBlock (TPraos c) (AllegraEra c)))
-> NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (TPraos c) (AllegraEra c)))
forall x (a :: * -> *) b (xs1 :: [*]).
NestedCtxt_ x a b -> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCZ NestedCtxt_
(ShelleyBlock (TPraos c) (AllegraEra c))
Header
(Header (ShelleyBlock (TPraos c) (AllegraEra c)))
forall proto era (f :: * -> *).
NestedCtxt_ (ShelleyBlock proto era) f (f (ShelleyBlock proto era))
Shelley.CtxtShelley)))
Word8
4 -> NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (TPraos c) (MaryEra c)))
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c))
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (TPraos c) (MaryEra c)))
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c)))
-> NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (TPraos c) (MaryEra c)))
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c))
forall a b. (a -> b) -> a -> b
$ NestedCtxt_
(HardForkBlock (CardanoEras c))
Header
(Header (ShelleyBlock (TPraos c) (MaryEra c)))
-> NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (TPraos c) (MaryEra c)))
forall (f :: * -> *) blk a.
NestedCtxt_ blk f a -> NestedCtxt f blk a
NestedCtxt (NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (TPraos c) (MaryEra c)))
-> NestedCtxt_
(HardForkBlock (CardanoEras c))
Header
(Header (ShelleyBlock (TPraos c) (MaryEra c)))
forall (xs1 :: [*]) (a :: * -> *) b x.
NestedCtxt_ (HardForkBlock xs1) a b
-> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCS (NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (TPraos c) (MaryEra c)))
-> NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (TPraos c) (MaryEra c)))
forall (xs1 :: [*]) (a :: * -> *) b x.
NestedCtxt_ (HardForkBlock xs1) a b
-> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCS (NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (TPraos c) (MaryEra c)))
-> NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (TPraos c) (MaryEra c)))
forall (xs1 :: [*]) (a :: * -> *) b x.
NestedCtxt_ (HardForkBlock xs1) a b
-> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCS (NestedCtxt_
(ShelleyBlock (TPraos c) (MaryEra c))
Header
(Header (ShelleyBlock (TPraos c) (MaryEra c)))
-> NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (TPraos c) (MaryEra c)))
forall x (a :: * -> *) b (xs1 :: [*]).
NestedCtxt_ x a b -> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCZ NestedCtxt_
(ShelleyBlock (TPraos c) (MaryEra c))
Header
(Header (ShelleyBlock (TPraos c) (MaryEra c)))
forall proto era (f :: * -> *).
NestedCtxt_ (ShelleyBlock proto era) f (f (ShelleyBlock proto era))
Shelley.CtxtShelley))))
Word8
5 -> NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c))
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c)))
-> NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c))
forall a b. (a -> b) -> a -> b
$ NestedCtxt_
(HardForkBlock (CardanoEras c))
Header
(Header (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (TPraos c) (AlonzoEra c)))
forall (f :: * -> *) blk a.
NestedCtxt_ blk f a -> NestedCtxt f blk a
NestedCtxt (NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> NestedCtxt_
(HardForkBlock (CardanoEras c))
Header
(Header (ShelleyBlock (TPraos c) (AlonzoEra c)))
forall (xs1 :: [*]) (a :: * -> *) b x.
NestedCtxt_ (HardForkBlock xs1) a b
-> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCS (NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (TPraos c) (AlonzoEra c)))
forall (xs1 :: [*]) (a :: * -> *) b x.
NestedCtxt_ (HardForkBlock xs1) a b
-> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCS (NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (TPraos c) (AlonzoEra c)))
forall (xs1 :: [*]) (a :: * -> *) b x.
NestedCtxt_ (HardForkBlock xs1) a b
-> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCS (NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (TPraos c) (AlonzoEra c)))
forall (xs1 :: [*]) (a :: * -> *) b x.
NestedCtxt_ (HardForkBlock xs1) a b
-> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCS (NestedCtxt_
(ShelleyBlock (TPraos c) (AlonzoEra c))
Header
(Header (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (TPraos c) (AlonzoEra c)))
forall x (a :: * -> *) b (xs1 :: [*]).
NestedCtxt_ x a b -> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCZ NestedCtxt_
(ShelleyBlock (TPraos c) (AlonzoEra c))
Header
(Header (ShelleyBlock (TPraos c) (AlonzoEra c)))
forall proto era (f :: * -> *).
NestedCtxt_ (ShelleyBlock proto era) f (f (ShelleyBlock proto era))
Shelley.CtxtShelley)))))
Word8
6 -> NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (Praos c) (BabbageEra c)))
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c))
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (Praos c) (BabbageEra c)))
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c)))
-> NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (Praos c) (BabbageEra c)))
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c))
forall a b. (a -> b) -> a -> b
$ NestedCtxt_
(HardForkBlock (CardanoEras c))
Header
(Header (ShelleyBlock (Praos c) (BabbageEra c)))
-> NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (Praos c) (BabbageEra c)))
forall (f :: * -> *) blk a.
NestedCtxt_ blk f a -> NestedCtxt f blk a
NestedCtxt (NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (Praos c) (BabbageEra c)))
-> NestedCtxt_
(HardForkBlock (CardanoEras c))
Header
(Header (ShelleyBlock (Praos c) (BabbageEra c)))
forall (xs1 :: [*]) (a :: * -> *) b x.
NestedCtxt_ (HardForkBlock xs1) a b
-> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCS (NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (Praos c) (BabbageEra c)))
-> NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (Praos c) (BabbageEra c)))
forall (xs1 :: [*]) (a :: * -> *) b x.
NestedCtxt_ (HardForkBlock xs1) a b
-> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCS (NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (Praos c) (BabbageEra c)))
-> NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (Praos c) (BabbageEra c)))
forall (xs1 :: [*]) (a :: * -> *) b x.
NestedCtxt_ (HardForkBlock xs1) a b
-> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCS (NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (Praos c) (BabbageEra c)))
-> NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (Praos c) (BabbageEra c)))
forall (xs1 :: [*]) (a :: * -> *) b x.
NestedCtxt_ (HardForkBlock xs1) a b
-> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCS (NestedCtxt_
(HardForkBlock
'[ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (Praos c) (BabbageEra c)))
-> NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (Praos c) (BabbageEra c)))
forall (xs1 :: [*]) (a :: * -> *) b x.
NestedCtxt_ (HardForkBlock xs1) a b
-> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCS (NestedCtxt_
(ShelleyBlock (Praos c) (BabbageEra c))
Header
(Header (ShelleyBlock (Praos c) (BabbageEra c)))
-> NestedCtxt_
(HardForkBlock
'[ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (Praos c) (BabbageEra c)))
forall x (a :: * -> *) b (xs1 :: [*]).
NestedCtxt_ x a b -> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCZ NestedCtxt_
(ShelleyBlock (Praos c) (BabbageEra c))
Header
(Header (ShelleyBlock (Praos c) (BabbageEra c)))
forall proto era (f :: * -> *).
NestedCtxt_ (ShelleyBlock proto era) f (f (ShelleyBlock proto era))
Shelley.CtxtShelley))))))
Word8
7 -> NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (Praos c) (ConwayEra c)))
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c))
forall {k1} {k2} (f :: k1 -> k2 -> *) (a :: k1) (b :: k2).
f a b -> SomeSecond f a
SomeSecond (NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (Praos c) (ConwayEra c)))
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c)))
-> NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (Praos c) (ConwayEra c)))
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c))
forall a b. (a -> b) -> a -> b
$ NestedCtxt_
(HardForkBlock (CardanoEras c))
Header
(Header (ShelleyBlock (Praos c) (ConwayEra c)))
-> NestedCtxt
Header
(HardForkBlock (CardanoEras c))
(Header (ShelleyBlock (Praos c) (ConwayEra c)))
forall (f :: * -> *) blk a.
NestedCtxt_ blk f a -> NestedCtxt f blk a
NestedCtxt (NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (Praos c) (ConwayEra c)))
-> NestedCtxt_
(HardForkBlock (CardanoEras c))
Header
(Header (ShelleyBlock (Praos c) (ConwayEra c)))
forall (xs1 :: [*]) (a :: * -> *) b x.
NestedCtxt_ (HardForkBlock xs1) a b
-> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCS (NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (Praos c) (ConwayEra c)))
-> NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (Praos c) (ConwayEra c)))
forall (xs1 :: [*]) (a :: * -> *) b x.
NestedCtxt_ (HardForkBlock xs1) a b
-> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCS (NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (Praos c) (ConwayEra c)))
-> NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (Praos c) (ConwayEra c)))
forall (xs1 :: [*]) (a :: * -> *) b x.
NestedCtxt_ (HardForkBlock xs1) a b
-> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCS (NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (Praos c) (ConwayEra c)))
-> NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (Praos c) (ConwayEra c)))
forall (xs1 :: [*]) (a :: * -> *) b x.
NestedCtxt_ (HardForkBlock xs1) a b
-> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCS (NestedCtxt_
(HardForkBlock
'[ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (Praos c) (ConwayEra c)))
-> NestedCtxt_
(HardForkBlock
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (Praos c) (ConwayEra c)))
forall (xs1 :: [*]) (a :: * -> *) b x.
NestedCtxt_ (HardForkBlock xs1) a b
-> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCS (NestedCtxt_
(HardForkBlock '[ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (Praos c) (ConwayEra c)))
-> NestedCtxt_
(HardForkBlock
'[ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (Praos c) (ConwayEra c)))
forall (xs1 :: [*]) (a :: * -> *) b x.
NestedCtxt_ (HardForkBlock xs1) a b
-> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCS (NestedCtxt_
(ShelleyBlock (Praos c) (ConwayEra c))
Header
(Header (ShelleyBlock (Praos c) (ConwayEra c)))
-> NestedCtxt_
(HardForkBlock '[ShelleyBlock (Praos c) (ConwayEra c)])
Header
(Header (ShelleyBlock (Praos c) (ConwayEra c)))
forall x (a :: * -> *) b (xs1 :: [*]).
NestedCtxt_ x a b -> NestedCtxt_ (HardForkBlock (x : xs1)) a b
NCZ NestedCtxt_
(ShelleyBlock (Praos c) (ConwayEra c))
Header
(Header (ShelleyBlock (Praos c) (ConwayEra c)))
forall proto era (f :: * -> *).
NestedCtxt_ (ShelleyBlock proto era) f (f (ShelleyBlock proto era))
Shelley.CtxtShelley)))))))
Word8
_ -> [Char]
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c))
forall a. HasCallStack => [Char] -> a
error ([Char]
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c)))
-> [Char]
-> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c))
forall a b. (a -> b) -> a -> b
$ [Char]
"CardanoBlock: invalid prefix " [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> ShortByteString -> [Char]
forall a. Show a => a -> [Char]
show ShortByteString
prefix
getHfcBinaryBlockInfo :: HardForkBlock (CardanoEras c) -> BinaryBlockInfo
getHfcBinaryBlockInfo = \case
BlockByron ByronBlock
blockByron ->
ByronBlock -> BinaryBlockInfo
forall blk. HasBinaryBlockInfo blk => blk -> BinaryBlockInfo
getBinaryBlockInfo ByronBlock
blockByron
BlockShelley ShelleyBlock (TPraos c) (ShelleyEra c)
blockShelley ->
Word16 -> BinaryBlockInfo -> BinaryBlockInfo
shiftHeaderOffset Word16
2 (BinaryBlockInfo -> BinaryBlockInfo)
-> BinaryBlockInfo -> BinaryBlockInfo
forall a b. (a -> b) -> a -> b
$ ShelleyBlock (TPraos c) (ShelleyEra c) -> BinaryBlockInfo
forall blk. HasBinaryBlockInfo blk => blk -> BinaryBlockInfo
getBinaryBlockInfo ShelleyBlock (TPraos c) (ShelleyEra c)
blockShelley
BlockAllegra ShelleyBlock (TPraos c) (AllegraEra c)
blockAllegra ->
Word16 -> BinaryBlockInfo -> BinaryBlockInfo
shiftHeaderOffset Word16
2 (BinaryBlockInfo -> BinaryBlockInfo)
-> BinaryBlockInfo -> BinaryBlockInfo
forall a b. (a -> b) -> a -> b
$ ShelleyBlock (TPraos c) (AllegraEra c) -> BinaryBlockInfo
forall blk. HasBinaryBlockInfo blk => blk -> BinaryBlockInfo
getBinaryBlockInfo ShelleyBlock (TPraos c) (AllegraEra c)
blockAllegra
BlockMary ShelleyBlock (TPraos c) (MaryEra c)
blockMary ->
Word16 -> BinaryBlockInfo -> BinaryBlockInfo
shiftHeaderOffset Word16
2 (BinaryBlockInfo -> BinaryBlockInfo)
-> BinaryBlockInfo -> BinaryBlockInfo
forall a b. (a -> b) -> a -> b
$ ShelleyBlock (TPraos c) (MaryEra c) -> BinaryBlockInfo
forall blk. HasBinaryBlockInfo blk => blk -> BinaryBlockInfo
getBinaryBlockInfo ShelleyBlock (TPraos c) (MaryEra c)
blockMary
BlockAlonzo ShelleyBlock (TPraos c) (AlonzoEra c)
blockAlonzo ->
Word16 -> BinaryBlockInfo -> BinaryBlockInfo
shiftHeaderOffset Word16
2 (BinaryBlockInfo -> BinaryBlockInfo)
-> BinaryBlockInfo -> BinaryBlockInfo
forall a b. (a -> b) -> a -> b
$ ShelleyBlock (TPraos c) (AlonzoEra c) -> BinaryBlockInfo
forall blk. HasBinaryBlockInfo blk => blk -> BinaryBlockInfo
getBinaryBlockInfo ShelleyBlock (TPraos c) (AlonzoEra c)
blockAlonzo
BlockBabbage ShelleyBlock (Praos c) (BabbageEra c)
blockBabbage ->
Word16 -> BinaryBlockInfo -> BinaryBlockInfo
shiftHeaderOffset Word16
2 (BinaryBlockInfo -> BinaryBlockInfo)
-> BinaryBlockInfo -> BinaryBlockInfo
forall a b. (a -> b) -> a -> b
$ ShelleyBlock (Praos c) (BabbageEra c) -> BinaryBlockInfo
forall blk. HasBinaryBlockInfo blk => blk -> BinaryBlockInfo
getBinaryBlockInfo ShelleyBlock (Praos c) (BabbageEra c)
blockBabbage
BlockConway ShelleyBlock (Praos c) (ConwayEra c)
blockConway ->
Word16 -> BinaryBlockInfo -> BinaryBlockInfo
shiftHeaderOffset Word16
2 (BinaryBlockInfo -> BinaryBlockInfo)
-> BinaryBlockInfo -> BinaryBlockInfo
forall a b. (a -> b) -> a -> b
$ ShelleyBlock (Praos c) (ConwayEra c) -> BinaryBlockInfo
forall blk. HasBinaryBlockInfo blk => blk -> BinaryBlockInfo
getBinaryBlockInfo ShelleyBlock (Praos c) (ConwayEra c)
blockConway
where
shiftHeaderOffset :: Word16 -> BinaryBlockInfo -> BinaryBlockInfo
shiftHeaderOffset :: Word16 -> BinaryBlockInfo -> BinaryBlockInfo
shiftHeaderOffset Word16
shift BinaryBlockInfo
binfo = BinaryBlockInfo
binfo {
headerOffset = headerOffset binfo + shift
}
estimateHfcBlockSize :: Header (HardForkBlock (CardanoEras c)) -> SizeInBytes
estimateHfcBlockSize = \case
HeaderByron Header ByronBlock
headerByron -> Header ByronBlock -> SizeInBytes
forall blk.
SerialiseNodeToNodeConstraints blk =>
Header blk -> SizeInBytes
estimateBlockSize Header ByronBlock
headerByron
HeaderShelley Header (ShelleyBlock (TPraos c) (ShelleyEra c))
headerShelley -> Header (ShelleyBlock (TPraos c) (ShelleyEra c)) -> SizeInBytes
forall blk.
SerialiseNodeToNodeConstraints blk =>
Header blk -> SizeInBytes
estimateBlockSize Header (ShelleyBlock (TPraos c) (ShelleyEra c))
headerShelley SizeInBytes -> SizeInBytes -> SizeInBytes
forall a. Num a => a -> a -> a
+ SizeInBytes
2
HeaderAllegra Header (ShelleyBlock (TPraos c) (AllegraEra c))
headerAllegra -> Header (ShelleyBlock (TPraos c) (AllegraEra c)) -> SizeInBytes
forall blk.
SerialiseNodeToNodeConstraints blk =>
Header blk -> SizeInBytes
estimateBlockSize Header (ShelleyBlock (TPraos c) (AllegraEra c))
headerAllegra SizeInBytes -> SizeInBytes -> SizeInBytes
forall a. Num a => a -> a -> a
+ SizeInBytes
2
HeaderMary Header (ShelleyBlock (TPraos c) (MaryEra c))
headerMary -> Header (ShelleyBlock (TPraos c) (MaryEra c)) -> SizeInBytes
forall blk.
SerialiseNodeToNodeConstraints blk =>
Header blk -> SizeInBytes
estimateBlockSize Header (ShelleyBlock (TPraos c) (MaryEra c))
headerMary SizeInBytes -> SizeInBytes -> SizeInBytes
forall a. Num a => a -> a -> a
+ SizeInBytes
2
HeaderAlonzo Header (ShelleyBlock (TPraos c) (AlonzoEra c))
headerAlonzo -> Header (ShelleyBlock (TPraos c) (AlonzoEra c)) -> SizeInBytes
forall blk.
SerialiseNodeToNodeConstraints blk =>
Header blk -> SizeInBytes
estimateBlockSize Header (ShelleyBlock (TPraos c) (AlonzoEra c))
headerAlonzo SizeInBytes -> SizeInBytes -> SizeInBytes
forall a. Num a => a -> a -> a
+ SizeInBytes
2
HeaderBabbage Header (ShelleyBlock (Praos c) (BabbageEra c))
headerBabbage -> Header (ShelleyBlock (Praos c) (BabbageEra c)) -> SizeInBytes
forall blk.
SerialiseNodeToNodeConstraints blk =>
Header blk -> SizeInBytes
estimateBlockSize Header (ShelleyBlock (Praos c) (BabbageEra c))
headerBabbage SizeInBytes -> SizeInBytes -> SizeInBytes
forall a. Num a => a -> a -> a
+ SizeInBytes
2
HeaderConway Header (ShelleyBlock (Praos c) (ConwayEra c))
headerConway -> Header (ShelleyBlock (Praos c) (ConwayEra c)) -> SizeInBytes
forall blk.
SerialiseNodeToNodeConstraints blk =>
Header blk -> SizeInBytes
estimateBlockSize Header (ShelleyBlock (Praos c) (ConwayEra c))
headerConway SizeInBytes -> SizeInBytes -> SizeInBytes
forall a. Num a => a -> a -> a
+ SizeInBytes
2
prependTag :: Word -> Encoding -> Encoding
prependTag :: Word -> Encoding -> Encoding
prependTag Word
tag Encoding
payload = [Encoding] -> Encoding
forall a. Monoid a => [a] -> a
mconcat [
Word -> Encoding
CBOR.encodeListLen Word
2
, Word -> Encoding
CBOR.encodeWord Word
tag
, Encoding
payload
]
pattern CardanoNodeToNodeVersion1 :: BlockNodeToNodeVersion (CardanoBlock c)
pattern $mCardanoNodeToNodeVersion1 :: forall {r} {c}.
BlockNodeToNodeVersion (CardanoBlock c)
-> ((# #) -> r) -> ((# #) -> r) -> r
$bCardanoNodeToNodeVersion1 :: forall c. BlockNodeToNodeVersion (CardanoBlock c)
CardanoNodeToNodeVersion1 =
HardForkNodeToNodeDisabled ByronNodeToNodeVersion1
pattern CardanoNodeToNodeVersion2 :: BlockNodeToNodeVersion (CardanoBlock c)
pattern $mCardanoNodeToNodeVersion2 :: forall {r} {c}.
BlockNodeToNodeVersion (CardanoBlock c)
-> ((# #) -> r) -> ((# #) -> r) -> r
$bCardanoNodeToNodeVersion2 :: forall c. BlockNodeToNodeVersion (CardanoBlock c)
CardanoNodeToNodeVersion2 =
HardForkNodeToNodeEnabled
HardForkSpecificNodeToNodeVersion1
( WrapNodeToNodeVersion ByronNodeToNodeVersion2
:* WrapNodeToNodeVersion ShelleyNodeToNodeVersion1
:* WrapNodeToNodeVersion ShelleyNodeToNodeVersion1
:* WrapNodeToNodeVersion ShelleyNodeToNodeVersion1
:* WrapNodeToNodeVersion ShelleyNodeToNodeVersion1
:* WrapNodeToNodeVersion ShelleyNodeToNodeVersion1
:* WrapNodeToNodeVersion ShelleyNodeToNodeVersion1
:* Nil
)
pattern CardanoNodeToClientVersion1 :: BlockNodeToClientVersion (CardanoBlock c)
pattern $mCardanoNodeToClientVersion1 :: forall {r} {c}.
BlockNodeToClientVersion (CardanoBlock c)
-> ((# #) -> r) -> ((# #) -> r) -> r
$bCardanoNodeToClientVersion1 :: forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion1 =
HardForkNodeToClientDisabled ByronNodeToClientVersion1
pattern CardanoNodeToClientVersion2 :: BlockNodeToClientVersion (CardanoBlock c)
pattern $mCardanoNodeToClientVersion2 :: forall {r} {c}.
BlockNodeToClientVersion (CardanoBlock c)
-> ((# #) -> r) -> ((# #) -> r) -> r
$bCardanoNodeToClientVersion2 :: forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion2 =
HardForkNodeToClientEnabled
HardForkSpecificNodeToClientVersion1
( EraNodeToClientEnabled ByronNodeToClientVersion1
:* EraNodeToClientEnabled ShelleyNodeToClientVersion1
:* EraNodeToClientDisabled
:* EraNodeToClientDisabled
:* EraNodeToClientDisabled
:* EraNodeToClientDisabled
:* EraNodeToClientDisabled
:* Nil
)
pattern CardanoNodeToClientVersion3 :: BlockNodeToClientVersion (CardanoBlock c)
pattern $mCardanoNodeToClientVersion3 :: forall {r} {c}.
BlockNodeToClientVersion (CardanoBlock c)
-> ((# #) -> r) -> ((# #) -> r) -> r
$bCardanoNodeToClientVersion3 :: forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion3 =
HardForkNodeToClientEnabled
HardForkSpecificNodeToClientVersion2
( EraNodeToClientEnabled ByronNodeToClientVersion1
:* EraNodeToClientEnabled ShelleyNodeToClientVersion2
:* EraNodeToClientDisabled
:* EraNodeToClientDisabled
:* EraNodeToClientDisabled
:* EraNodeToClientDisabled
:* EraNodeToClientDisabled
:* Nil
)
pattern CardanoNodeToClientVersion4 :: BlockNodeToClientVersion (CardanoBlock c)
pattern $mCardanoNodeToClientVersion4 :: forall {r} {c}.
BlockNodeToClientVersion (CardanoBlock c)
-> ((# #) -> r) -> ((# #) -> r) -> r
$bCardanoNodeToClientVersion4 :: forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion4 =
HardForkNodeToClientEnabled
HardForkSpecificNodeToClientVersion2
( EraNodeToClientEnabled ByronNodeToClientVersion1
:* EraNodeToClientEnabled ShelleyNodeToClientVersion2
:* EraNodeToClientEnabled ShelleyNodeToClientVersion2
:* EraNodeToClientDisabled
:* EraNodeToClientDisabled
:* EraNodeToClientDisabled
:* EraNodeToClientDisabled
:* Nil
)
pattern CardanoNodeToClientVersion5 :: BlockNodeToClientVersion (CardanoBlock c)
pattern $mCardanoNodeToClientVersion5 :: forall {r} {c}.
BlockNodeToClientVersion (CardanoBlock c)
-> ((# #) -> r) -> ((# #) -> r) -> r
$bCardanoNodeToClientVersion5 :: forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion5 =
HardForkNodeToClientEnabled
HardForkSpecificNodeToClientVersion2
( EraNodeToClientEnabled ByronNodeToClientVersion1
:* EraNodeToClientEnabled ShelleyNodeToClientVersion2
:* EraNodeToClientEnabled ShelleyNodeToClientVersion2
:* EraNodeToClientEnabled ShelleyNodeToClientVersion2
:* EraNodeToClientDisabled
:* EraNodeToClientDisabled
:* EraNodeToClientDisabled
:* Nil
)
pattern CardanoNodeToClientVersion6 :: BlockNodeToClientVersion (CardanoBlock c)
pattern $mCardanoNodeToClientVersion6 :: forall {r} {c}.
BlockNodeToClientVersion (CardanoBlock c)
-> ((# #) -> r) -> ((# #) -> r) -> r
$bCardanoNodeToClientVersion6 :: forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion6 =
HardForkNodeToClientEnabled
HardForkSpecificNodeToClientVersion2
( EraNodeToClientEnabled ByronNodeToClientVersion1
:* EraNodeToClientEnabled ShelleyNodeToClientVersion3
:* EraNodeToClientEnabled ShelleyNodeToClientVersion3
:* EraNodeToClientEnabled ShelleyNodeToClientVersion3
:* EraNodeToClientDisabled
:* EraNodeToClientDisabled
:* EraNodeToClientDisabled
:* Nil
)
pattern CardanoNodeToClientVersion7 :: BlockNodeToClientVersion (CardanoBlock c)
pattern $mCardanoNodeToClientVersion7 :: forall {r} {c}.
BlockNodeToClientVersion (CardanoBlock c)
-> ((# #) -> r) -> ((# #) -> r) -> r
$bCardanoNodeToClientVersion7 :: forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion7 =
HardForkNodeToClientEnabled
HardForkSpecificNodeToClientVersion2
( EraNodeToClientEnabled ByronNodeToClientVersion1
:* EraNodeToClientEnabled ShelleyNodeToClientVersion4
:* EraNodeToClientEnabled ShelleyNodeToClientVersion4
:* EraNodeToClientEnabled ShelleyNodeToClientVersion4
:* EraNodeToClientEnabled ShelleyNodeToClientVersion4
:* EraNodeToClientDisabled
:* EraNodeToClientDisabled
:* Nil
)
pattern CardanoNodeToClientVersion8 :: BlockNodeToClientVersion (CardanoBlock c)
pattern $mCardanoNodeToClientVersion8 :: forall {r} {c}.
BlockNodeToClientVersion (CardanoBlock c)
-> ((# #) -> r) -> ((# #) -> r) -> r
$bCardanoNodeToClientVersion8 :: forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion8 =
HardForkNodeToClientEnabled
HardForkSpecificNodeToClientVersion2
( EraNodeToClientEnabled ByronNodeToClientVersion1
:* EraNodeToClientEnabled ShelleyNodeToClientVersion5
:* EraNodeToClientEnabled ShelleyNodeToClientVersion5
:* EraNodeToClientEnabled ShelleyNodeToClientVersion5
:* EraNodeToClientEnabled ShelleyNodeToClientVersion5
:* EraNodeToClientDisabled
:* EraNodeToClientDisabled
:* Nil
)
pattern CardanoNodeToClientVersion9 :: BlockNodeToClientVersion (CardanoBlock c)
pattern $mCardanoNodeToClientVersion9 :: forall {r} {c}.
BlockNodeToClientVersion (CardanoBlock c)
-> ((# #) -> r) -> ((# #) -> r) -> r
$bCardanoNodeToClientVersion9 :: forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion9 =
HardForkNodeToClientEnabled
HardForkSpecificNodeToClientVersion2
( EraNodeToClientEnabled ByronNodeToClientVersion1
:* EraNodeToClientEnabled ShelleyNodeToClientVersion5
:* EraNodeToClientEnabled ShelleyNodeToClientVersion5
:* EraNodeToClientEnabled ShelleyNodeToClientVersion5
:* EraNodeToClientEnabled ShelleyNodeToClientVersion5
:* EraNodeToClientEnabled ShelleyNodeToClientVersion5
:* EraNodeToClientDisabled
:* Nil
)
pattern CardanoNodeToClientVersion10 :: BlockNodeToClientVersion (CardanoBlock c)
pattern $mCardanoNodeToClientVersion10 :: forall {r} {c}.
BlockNodeToClientVersion (CardanoBlock c)
-> ((# #) -> r) -> ((# #) -> r) -> r
$bCardanoNodeToClientVersion10 :: forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion10 =
HardForkNodeToClientEnabled
HardForkSpecificNodeToClientVersion2
( EraNodeToClientEnabled ByronNodeToClientVersion1
:* EraNodeToClientEnabled ShelleyNodeToClientVersion6
:* EraNodeToClientEnabled ShelleyNodeToClientVersion6
:* EraNodeToClientEnabled ShelleyNodeToClientVersion6
:* EraNodeToClientEnabled ShelleyNodeToClientVersion6
:* EraNodeToClientEnabled ShelleyNodeToClientVersion6
:* EraNodeToClientDisabled
:* Nil
)
pattern CardanoNodeToClientVersion11 :: BlockNodeToClientVersion (CardanoBlock c)
pattern $mCardanoNodeToClientVersion11 :: forall {r} {c}.
BlockNodeToClientVersion (CardanoBlock c)
-> ((# #) -> r) -> ((# #) -> r) -> r
$bCardanoNodeToClientVersion11 :: forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion11 =
HardForkNodeToClientEnabled
HardForkSpecificNodeToClientVersion2
( EraNodeToClientEnabled ByronNodeToClientVersion1
:* EraNodeToClientEnabled ShelleyNodeToClientVersion7
:* EraNodeToClientEnabled ShelleyNodeToClientVersion7
:* EraNodeToClientEnabled ShelleyNodeToClientVersion7
:* EraNodeToClientEnabled ShelleyNodeToClientVersion7
:* EraNodeToClientEnabled ShelleyNodeToClientVersion7
:* EraNodeToClientDisabled
:* Nil
)
pattern CardanoNodeToClientVersion12 :: BlockNodeToClientVersion (CardanoBlock c)
pattern $mCardanoNodeToClientVersion12 :: forall {r} {c}.
BlockNodeToClientVersion (CardanoBlock c)
-> ((# #) -> r) -> ((# #) -> r) -> r
$bCardanoNodeToClientVersion12 :: forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion12 =
HardForkNodeToClientEnabled
HardForkSpecificNodeToClientVersion3
( EraNodeToClientEnabled ByronNodeToClientVersion1
:* EraNodeToClientEnabled ShelleyNodeToClientVersion8
:* EraNodeToClientEnabled ShelleyNodeToClientVersion8
:* EraNodeToClientEnabled ShelleyNodeToClientVersion8
:* EraNodeToClientEnabled ShelleyNodeToClientVersion8
:* EraNodeToClientEnabled ShelleyNodeToClientVersion8
:* EraNodeToClientEnabled ShelleyNodeToClientVersion8
:* Nil
)
pattern CardanoNodeToClientVersion13 :: BlockNodeToClientVersion (CardanoBlock c)
pattern $mCardanoNodeToClientVersion13 :: forall {r} {c}.
BlockNodeToClientVersion (CardanoBlock c)
-> ((# #) -> r) -> ((# #) -> r) -> r
$bCardanoNodeToClientVersion13 :: forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion13 =
HardForkNodeToClientEnabled
HardForkSpecificNodeToClientVersion3
( EraNodeToClientEnabled ByronNodeToClientVersion1
:* EraNodeToClientEnabled ShelleyNodeToClientVersion9
:* EraNodeToClientEnabled ShelleyNodeToClientVersion9
:* EraNodeToClientEnabled ShelleyNodeToClientVersion9
:* EraNodeToClientEnabled ShelleyNodeToClientVersion9
:* EraNodeToClientEnabled ShelleyNodeToClientVersion9
:* EraNodeToClientEnabled ShelleyNodeToClientVersion9
:* Nil
)
pattern CardanoNodeToClientVersion14 :: BlockNodeToClientVersion (CardanoBlock c)
pattern $mCardanoNodeToClientVersion14 :: forall {r} {c}.
BlockNodeToClientVersion (CardanoBlock c)
-> ((# #) -> r) -> ((# #) -> r) -> r
$bCardanoNodeToClientVersion14 :: forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion14 =
HardForkNodeToClientEnabled
HardForkSpecificNodeToClientVersion3
( EraNodeToClientEnabled ByronNodeToClientVersion1
:* EraNodeToClientEnabled ShelleyNodeToClientVersion10
:* EraNodeToClientEnabled ShelleyNodeToClientVersion10
:* EraNodeToClientEnabled ShelleyNodeToClientVersion10
:* EraNodeToClientEnabled ShelleyNodeToClientVersion10
:* EraNodeToClientEnabled ShelleyNodeToClientVersion10
:* EraNodeToClientEnabled ShelleyNodeToClientVersion10
:* Nil
)
pattern CardanoNodeToClientVersion15 :: BlockNodeToClientVersion (CardanoBlock c)
pattern $mCardanoNodeToClientVersion15 :: forall {r} {c}.
BlockNodeToClientVersion (CardanoBlock c)
-> ((# #) -> r) -> ((# #) -> r) -> r
$bCardanoNodeToClientVersion15 :: forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion15 =
HardForkNodeToClientEnabled
HardForkSpecificNodeToClientVersion3
( EraNodeToClientEnabled ByronNodeToClientVersion1
:* EraNodeToClientEnabled ShelleyNodeToClientVersion11
:* EraNodeToClientEnabled ShelleyNodeToClientVersion11
:* EraNodeToClientEnabled ShelleyNodeToClientVersion11
:* EraNodeToClientEnabled ShelleyNodeToClientVersion11
:* EraNodeToClientEnabled ShelleyNodeToClientVersion11
:* EraNodeToClientEnabled ShelleyNodeToClientVersion11
:* Nil
)
instance CardanoHardForkConstraints c
=> SupportedNetworkProtocolVersion (CardanoBlock c) where
supportedNodeToNodeVersions :: Proxy (CardanoBlock c)
-> Map NodeToNodeVersion (BlockNodeToNodeVersion (CardanoBlock c))
supportedNodeToNodeVersions Proxy (CardanoBlock c)
_ = [(NodeToNodeVersion, BlockNodeToNodeVersion (CardanoBlock c))]
-> Map NodeToNodeVersion (BlockNodeToNodeVersion (CardanoBlock c))
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(NodeToNodeVersion, BlockNodeToNodeVersion (CardanoBlock c))]
-> Map NodeToNodeVersion (BlockNodeToNodeVersion (CardanoBlock c)))
-> [(NodeToNodeVersion, BlockNodeToNodeVersion (CardanoBlock c))]
-> Map NodeToNodeVersion (BlockNodeToNodeVersion (CardanoBlock c))
forall a b. (a -> b) -> a -> b
$
[ (NodeToNodeVersion
NodeToNodeV_13, BlockNodeToNodeVersion (CardanoBlock c)
forall c. BlockNodeToNodeVersion (CardanoBlock c)
CardanoNodeToNodeVersion2)
, (NodeToNodeVersion
NodeToNodeV_14, BlockNodeToNodeVersion (CardanoBlock c)
forall c. BlockNodeToNodeVersion (CardanoBlock c)
CardanoNodeToNodeVersion2)
]
supportedNodeToClientVersions :: Proxy (CardanoBlock c)
-> Map
NodeToClientVersion (BlockNodeToClientVersion (CardanoBlock c))
supportedNodeToClientVersions Proxy (CardanoBlock c)
_ = [(NodeToClientVersion, BlockNodeToClientVersion (CardanoBlock c))]
-> Map
NodeToClientVersion (BlockNodeToClientVersion (CardanoBlock c))
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(NodeToClientVersion, BlockNodeToClientVersion (CardanoBlock c))]
-> Map
NodeToClientVersion (BlockNodeToClientVersion (CardanoBlock c)))
-> [(NodeToClientVersion,
BlockNodeToClientVersion (CardanoBlock c))]
-> Map
NodeToClientVersion (BlockNodeToClientVersion (CardanoBlock c))
forall a b. (a -> b) -> a -> b
$
[ (NodeToClientVersion
NodeToClientV_9 , BlockNodeToClientVersion (CardanoBlock c)
forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion7)
, (NodeToClientVersion
NodeToClientV_10, BlockNodeToClientVersion (CardanoBlock c)
forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion7)
, (NodeToClientVersion
NodeToClientV_11, BlockNodeToClientVersion (CardanoBlock c)
forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion8)
, (NodeToClientVersion
NodeToClientV_12, BlockNodeToClientVersion (CardanoBlock c)
forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion8)
, (NodeToClientVersion
NodeToClientV_13, BlockNodeToClientVersion (CardanoBlock c)
forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion9)
, (NodeToClientVersion
NodeToClientV_14, BlockNodeToClientVersion (CardanoBlock c)
forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion10)
, (NodeToClientVersion
NodeToClientV_15, BlockNodeToClientVersion (CardanoBlock c)
forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion11)
, (NodeToClientVersion
NodeToClientV_16, BlockNodeToClientVersion (CardanoBlock c)
forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion12)
, (NodeToClientVersion
NodeToClientV_17, BlockNodeToClientVersion (CardanoBlock c)
forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion13)
, (NodeToClientVersion
NodeToClientV_18, BlockNodeToClientVersion (CardanoBlock c)
forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion14)
, (NodeToClientVersion
NodeToClientV_19, BlockNodeToClientVersion (CardanoBlock c)
forall c. BlockNodeToClientVersion (CardanoBlock c)
CardanoNodeToClientVersion15)
]
latestReleasedNodeVersion :: Proxy (CardanoBlock c)
-> (Maybe NodeToNodeVersion, Maybe NodeToClientVersion)
latestReleasedNodeVersion Proxy (CardanoBlock c)
_prx = (NodeToNodeVersion -> Maybe NodeToNodeVersion
forall a. a -> Maybe a
Just NodeToNodeVersion
NodeToNodeV_14, NodeToClientVersion -> Maybe NodeToClientVersion
forall a. a -> Maybe a
Just NodeToClientVersion
NodeToClientV_19)
data CardanoHardForkTrigger blk =
CardanoTriggerHardForkAtDefaultVersion
|
CardanoTriggerHardForkAtEpoch EpochNo
deriving stock (Int -> CardanoHardForkTrigger blk -> [Char] -> [Char]
[CardanoHardForkTrigger blk] -> [Char] -> [Char]
CardanoHardForkTrigger blk -> [Char]
(Int -> CardanoHardForkTrigger blk -> [Char] -> [Char])
-> (CardanoHardForkTrigger blk -> [Char])
-> ([CardanoHardForkTrigger blk] -> [Char] -> [Char])
-> Show (CardanoHardForkTrigger blk)
forall blk. Int -> CardanoHardForkTrigger blk -> [Char] -> [Char]
forall blk. [CardanoHardForkTrigger blk] -> [Char] -> [Char]
forall blk. CardanoHardForkTrigger blk -> [Char]
forall a.
(Int -> a -> [Char] -> [Char])
-> (a -> [Char]) -> ([a] -> [Char] -> [Char]) -> Show a
$cshowsPrec :: forall blk. Int -> CardanoHardForkTrigger blk -> [Char] -> [Char]
showsPrec :: Int -> CardanoHardForkTrigger blk -> [Char] -> [Char]
$cshow :: forall blk. CardanoHardForkTrigger blk -> [Char]
show :: CardanoHardForkTrigger blk -> [Char]
$cshowList :: forall blk. [CardanoHardForkTrigger blk] -> [Char] -> [Char]
showList :: [CardanoHardForkTrigger blk] -> [Char] -> [Char]
Show)
toTriggerHardFork ::
forall blk. L.Era (ShelleyBlockLedgerEra blk)
=> CardanoHardForkTrigger blk
-> TriggerHardFork
toTriggerHardFork :: forall blk.
Era (ShelleyBlockLedgerEra blk) =>
CardanoHardForkTrigger blk -> TriggerHardFork
toTriggerHardFork = \case
CardanoHardForkTrigger blk
CardanoTriggerHardForkAtDefaultVersion ->
Word16 -> TriggerHardFork
TriggerHardForkAtVersion (Word16 -> TriggerHardFork) -> Word16 -> TriggerHardFork
forall a b. (a -> b) -> a -> b
$
Version -> Word16
forall i. Integral i => Version -> i
SL.getVersion (forall era. Era era => Version
L.eraProtVerLow @(ShelleyBlockLedgerEra blk))
CardanoTriggerHardForkAtEpoch EpochNo
epochNo ->
EpochNo -> TriggerHardFork
TriggerHardForkAtEpoch EpochNo
epochNo
newtype CardanoHardForkTriggers = CardanoHardForkTriggers {
CardanoHardForkTriggers
-> NP CardanoHardForkTrigger (CardanoShelleyEras StandardCrypto)
getCardanoHardForkTriggers ::
NP CardanoHardForkTrigger (CardanoShelleyEras StandardCrypto)
}
pattern CardanoHardForkTriggers' ::
(c ~ StandardCrypto)
=> CardanoHardForkTrigger (ShelleyBlock (TPraos c) (ShelleyEra c))
-> CardanoHardForkTrigger (ShelleyBlock (TPraos c) (AllegraEra c))
-> CardanoHardForkTrigger (ShelleyBlock (TPraos c) (MaryEra c))
-> CardanoHardForkTrigger (ShelleyBlock (TPraos c) (AlonzoEra c))
-> CardanoHardForkTrigger (ShelleyBlock (Praos c) (BabbageEra c))
-> CardanoHardForkTrigger (ShelleyBlock (Praos c) (ConwayEra c))
-> CardanoHardForkTriggers
pattern $mCardanoHardForkTriggers' :: forall {r} {c}.
(c ~ StandardCrypto) =>
CardanoHardForkTriggers
-> (CardanoHardForkTrigger (ShelleyBlock (TPraos c) (ShelleyEra c))
-> CardanoHardForkTrigger (ShelleyBlock (TPraos c) (AllegraEra c))
-> CardanoHardForkTrigger (ShelleyBlock (TPraos c) (MaryEra c))
-> CardanoHardForkTrigger (ShelleyBlock (TPraos c) (AlonzoEra c))
-> CardanoHardForkTrigger (ShelleyBlock (Praos c) (BabbageEra c))
-> CardanoHardForkTrigger (ShelleyBlock (Praos c) (ConwayEra c))
-> r)
-> ((# #) -> r)
-> r
$bCardanoHardForkTriggers' :: forall c.
(c ~ StandardCrypto) =>
CardanoHardForkTrigger (ShelleyBlock (TPraos c) (ShelleyEra c))
-> CardanoHardForkTrigger (ShelleyBlock (TPraos c) (AllegraEra c))
-> CardanoHardForkTrigger (ShelleyBlock (TPraos c) (MaryEra c))
-> CardanoHardForkTrigger (ShelleyBlock (TPraos c) (AlonzoEra c))
-> CardanoHardForkTrigger (ShelleyBlock (Praos c) (BabbageEra c))
-> CardanoHardForkTrigger (ShelleyBlock (Praos c) (ConwayEra c))
-> CardanoHardForkTriggers
CardanoHardForkTriggers' {
forall c.
(c ~ StandardCrypto) =>
CardanoHardForkTriggers
-> CardanoHardForkTrigger (ShelleyBlock (TPraos c) (ShelleyEra c))
triggerHardForkShelley
, forall c.
(c ~ StandardCrypto) =>
CardanoHardForkTriggers
-> CardanoHardForkTrigger (ShelleyBlock (TPraos c) (AllegraEra c))
triggerHardForkAllegra
, forall c.
(c ~ StandardCrypto) =>
CardanoHardForkTriggers
-> CardanoHardForkTrigger (ShelleyBlock (TPraos c) (MaryEra c))
triggerHardForkMary
, forall c.
(c ~ StandardCrypto) =>
CardanoHardForkTriggers
-> CardanoHardForkTrigger (ShelleyBlock (TPraos c) (AlonzoEra c))
triggerHardForkAlonzo
, forall c.
(c ~ StandardCrypto) =>
CardanoHardForkTriggers
-> CardanoHardForkTrigger (ShelleyBlock (Praos c) (BabbageEra c))
triggerHardForkBabbage
, forall c.
(c ~ StandardCrypto) =>
CardanoHardForkTriggers
-> CardanoHardForkTrigger (ShelleyBlock (Praos c) (ConwayEra c))
triggerHardForkConway
} =
CardanoHardForkTriggers
( triggerHardForkShelley
:* triggerHardForkAllegra
:* triggerHardForkMary
:* triggerHardForkAlonzo
:* triggerHardForkBabbage
:* triggerHardForkConway
:* Nil
)
{-# COMPLETE CardanoHardForkTriggers' #-}
data CardanoProtocolParams c = CardanoProtocolParams {
forall c. CardanoProtocolParams c -> ProtocolParamsByron
byronProtocolParams :: ProtocolParamsByron
, forall c. CardanoProtocolParams c -> ProtocolParamsShelleyBased c
shelleyBasedProtocolParams :: ProtocolParamsShelleyBased c
, forall c. CardanoProtocolParams c -> CardanoHardForkTriggers
cardanoHardForkTriggers :: CardanoHardForkTriggers
, forall c.
CardanoProtocolParams c -> TransitionConfig (LatestKnownEra c)
cardanoLedgerTransitionConfig :: L.TransitionConfig (L.LatestKnownEra c)
, forall c.
CardanoProtocolParams c -> CheckpointsMap (CardanoBlock c)
cardanoCheckpoints :: CheckpointsMap (CardanoBlock c)
, forall c. CardanoProtocolParams c -> ProtVer
cardanoProtocolVersion :: ProtVer
}
protocolInfoCardano ::
forall c m. (IOLike m, CardanoHardForkConstraints c)
=> CardanoProtocolParams c
-> ( ProtocolInfo (CardanoBlock c)
, m [BlockForging m (CardanoBlock c)]
)
protocolInfoCardano :: forall c (m :: * -> *).
(IOLike m, CardanoHardForkConstraints c) =>
CardanoProtocolParams c
-> (ProtocolInfo (CardanoBlock c),
m [BlockForging m (CardanoBlock c)])
protocolInfoCardano CardanoProtocolParams c
paramsCardano
| Network
SL.Mainnet <- ShelleyGenesis c -> Network
forall c. ShelleyGenesis c -> Network
SL.sgNetworkId ShelleyGenesis c
genesisShelley
, [ShelleyLeaderCredentials c] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [ShelleyLeaderCredentials c]
credssShelleyBased Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
1
= [Char]
-> (ProtocolInfo (CardanoBlock c),
m [BlockForging m (CardanoBlock c)])
forall a. HasCallStack => [Char] -> a
error [Char]
"Multiple Shelley-based credentials not allowed for mainnet"
| Bool
otherwise
= Either [Char] ()
-> (ProtocolInfo (CardanoBlock c),
m [BlockForging m (CardanoBlock c)])
-> (ProtocolInfo (CardanoBlock c),
m [BlockForging m (CardanoBlock c)])
forall a. HasCallStack => Either [Char] () -> a -> a
assertWithMsg (ShelleyGenesis c -> Either [Char] ()
forall c. PraosCrypto c => ShelleyGenesis c -> Either [Char] ()
validateGenesis ShelleyGenesis c
genesisShelley)
( ProtocolInfo {
pInfoConfig :: TopLevelConfig (CardanoBlock c)
pInfoConfig = TopLevelConfig (CardanoBlock c)
cfg
, pInfoInitLedger :: ExtLedgerState (CardanoBlock c)
pInfoInitLedger = ExtLedgerState (CardanoBlock c)
initExtLedgerStateCardano
}
, m [BlockForging m (CardanoBlock c)]
blockForging
)
where
CardanoProtocolParams {
ProtocolParamsByron
byronProtocolParams :: forall c. CardanoProtocolParams c -> ProtocolParamsByron
byronProtocolParams :: ProtocolParamsByron
byronProtocolParams
, ProtocolParamsShelleyBased c
shelleyBasedProtocolParams :: forall c. CardanoProtocolParams c -> ProtocolParamsShelleyBased c
shelleyBasedProtocolParams :: ProtocolParamsShelleyBased c
shelleyBasedProtocolParams
, cardanoHardForkTriggers :: forall c. CardanoProtocolParams c -> CardanoHardForkTriggers
cardanoHardForkTriggers = CardanoHardForkTriggers' {
CardanoHardForkTrigger
(ShelleyBlock (TPraos StandardCrypto) (ShelleyEra StandardCrypto))
triggerHardForkShelley :: forall c.
(c ~ StandardCrypto) =>
CardanoHardForkTriggers
-> CardanoHardForkTrigger (ShelleyBlock (TPraos c) (ShelleyEra c))
triggerHardForkShelley :: CardanoHardForkTrigger
(ShelleyBlock (TPraos StandardCrypto) (ShelleyEra StandardCrypto))
triggerHardForkShelley
, CardanoHardForkTrigger
(ShelleyBlock (TPraos StandardCrypto) (AllegraEra StandardCrypto))
triggerHardForkAllegra :: forall c.
(c ~ StandardCrypto) =>
CardanoHardForkTriggers
-> CardanoHardForkTrigger (ShelleyBlock (TPraos c) (AllegraEra c))
triggerHardForkAllegra :: CardanoHardForkTrigger
(ShelleyBlock (TPraos StandardCrypto) (AllegraEra StandardCrypto))
triggerHardForkAllegra
, CardanoHardForkTrigger
(ShelleyBlock (TPraos StandardCrypto) (MaryEra StandardCrypto))
triggerHardForkMary :: forall c.
(c ~ StandardCrypto) =>
CardanoHardForkTriggers
-> CardanoHardForkTrigger (ShelleyBlock (TPraos c) (MaryEra c))
triggerHardForkMary :: CardanoHardForkTrigger
(ShelleyBlock (TPraos StandardCrypto) (MaryEra StandardCrypto))
triggerHardForkMary
, CardanoHardForkTrigger
(ShelleyBlock (TPraos StandardCrypto) (AlonzoEra StandardCrypto))
triggerHardForkAlonzo :: forall c.
(c ~ StandardCrypto) =>
CardanoHardForkTriggers
-> CardanoHardForkTrigger (ShelleyBlock (TPraos c) (AlonzoEra c))
triggerHardForkAlonzo :: CardanoHardForkTrigger
(ShelleyBlock (TPraos StandardCrypto) (AlonzoEra StandardCrypto))
triggerHardForkAlonzo
, CardanoHardForkTrigger
(ShelleyBlock (Praos StandardCrypto) (BabbageEra StandardCrypto))
triggerHardForkBabbage :: forall c.
(c ~ StandardCrypto) =>
CardanoHardForkTriggers
-> CardanoHardForkTrigger (ShelleyBlock (Praos c) (BabbageEra c))
triggerHardForkBabbage :: CardanoHardForkTrigger
(ShelleyBlock (Praos StandardCrypto) (BabbageEra StandardCrypto))
triggerHardForkBabbage
, CardanoHardForkTrigger
(ShelleyBlock (Praos StandardCrypto) (ConwayEra StandardCrypto))
triggerHardForkConway :: forall c.
(c ~ StandardCrypto) =>
CardanoHardForkTriggers
-> CardanoHardForkTrigger (ShelleyBlock (Praos c) (ConwayEra c))
triggerHardForkConway :: CardanoHardForkTrigger
(ShelleyBlock (Praos StandardCrypto) (ConwayEra StandardCrypto))
triggerHardForkConway
}
, TransitionConfig (LatestKnownEra c)
cardanoLedgerTransitionConfig :: forall c.
CardanoProtocolParams c -> TransitionConfig (LatestKnownEra c)
cardanoLedgerTransitionConfig :: TransitionConfig (LatestKnownEra c)
cardanoLedgerTransitionConfig
, CheckpointsMap (CardanoBlock c)
cardanoCheckpoints :: forall c.
CardanoProtocolParams c -> CheckpointsMap (CardanoBlock c)
cardanoCheckpoints :: CheckpointsMap (CardanoBlock c)
cardanoCheckpoints
, ProtVer
cardanoProtocolVersion :: forall c. CardanoProtocolParams c -> ProtVer
cardanoProtocolVersion :: ProtVer
cardanoProtocolVersion
} = CardanoProtocolParams c
paramsCardano
genesisShelley :: ShelleyGenesis c
genesisShelley = TransitionConfig (LatestKnownEra c)
cardanoLedgerTransitionConfig TransitionConfig (LatestKnownEra c)
-> Getting
(ShelleyGenesis c)
(TransitionConfig (LatestKnownEra c))
(ShelleyGenesis c)
-> ShelleyGenesis c
forall s a. s -> Getting a s a -> a
^. Getting
(ShelleyGenesis c)
(TransitionConfig (LatestKnownEra c))
(ShelleyGenesis c)
(ShelleyGenesis (EraCrypto (LatestKnownEra c))
-> Const
(ShelleyGenesis c) (ShelleyGenesis (EraCrypto (LatestKnownEra c))))
-> TransitionConfig (LatestKnownEra c)
-> Const (ShelleyGenesis c) (TransitionConfig (LatestKnownEra c))
forall era.
EraTransition era =>
Lens' (TransitionConfig era) (ShelleyGenesis (EraCrypto era))
Lens'
(TransitionConfig (LatestKnownEra c))
(ShelleyGenesis (EraCrypto (LatestKnownEra c)))
L.tcShelleyGenesisL
ProtocolParamsByron {
$sel:byronGenesis:ProtocolParamsByron :: ProtocolParamsByron -> Config
byronGenesis = Config
genesisByron
, $sel:byronLeaderCredentials:ProtocolParamsByron :: ProtocolParamsByron -> Maybe ByronLeaderCredentials
byronLeaderCredentials = Maybe ByronLeaderCredentials
mCredsByron
} = ProtocolParamsByron
byronProtocolParams
ProtocolParamsShelleyBased {
shelleyBasedInitialNonce :: forall c. ProtocolParamsShelleyBased c -> Nonce
shelleyBasedInitialNonce = Nonce
initialNonceShelley
, shelleyBasedLeaderCredentials :: forall c.
ProtocolParamsShelleyBased c -> [ShelleyLeaderCredentials c]
shelleyBasedLeaderCredentials = [ShelleyLeaderCredentials c]
credssShelleyBased
} = ProtocolParamsShelleyBased c
shelleyBasedProtocolParams
transitionConfigShelley :: TransitionConfig (ShelleyEra c)
transitionConfigShelley = TransitionConfig (AllegraEra c)
transitionConfigAllegra TransitionConfig (AllegraEra c)
-> Getting
(TransitionConfig (ShelleyEra c))
(TransitionConfig (AllegraEra c))
(TransitionConfig (ShelleyEra c))
-> TransitionConfig (ShelleyEra c)
forall s a. s -> Getting a s a -> a
^. (TransitionConfig (PreviousEra (AllegraEra c))
-> Const
(TransitionConfig (ShelleyEra c))
(TransitionConfig (PreviousEra (AllegraEra c))))
-> TransitionConfig (AllegraEra c)
-> Const
(TransitionConfig (ShelleyEra c)) (TransitionConfig (AllegraEra c))
Getting
(TransitionConfig (ShelleyEra c))
(TransitionConfig (AllegraEra c))
(TransitionConfig (ShelleyEra c))
forall era.
(EraTransition era, EraTransition (PreviousEra era)) =>
Lens' (TransitionConfig era) (TransitionConfig (PreviousEra era))
Lens'
(TransitionConfig (AllegraEra c))
(TransitionConfig (PreviousEra (AllegraEra c)))
L.tcPreviousEraConfigL
transitionConfigAllegra :: TransitionConfig (AllegraEra c)
transitionConfigAllegra = TransitionConfig (MaryEra c)
transitionConfigMary TransitionConfig (MaryEra c)
-> Getting
(TransitionConfig (AllegraEra c))
(TransitionConfig (MaryEra c))
(TransitionConfig (AllegraEra c))
-> TransitionConfig (AllegraEra c)
forall s a. s -> Getting a s a -> a
^. Getting
(TransitionConfig (AllegraEra c))
(TransitionConfig (MaryEra c))
(TransitionConfig (AllegraEra c))
(TransitionConfig (PreviousEra (MaryEra c))
-> Const
(TransitionConfig (AllegraEra c))
(TransitionConfig (PreviousEra (MaryEra c))))
-> TransitionConfig (MaryEra c)
-> Const
(TransitionConfig (AllegraEra c)) (TransitionConfig (MaryEra c))
forall era.
(EraTransition era, EraTransition (PreviousEra era)) =>
Lens' (TransitionConfig era) (TransitionConfig (PreviousEra era))
Lens'
(TransitionConfig (MaryEra c))
(TransitionConfig (PreviousEra (MaryEra c)))
L.tcPreviousEraConfigL
transitionConfigMary :: TransitionConfig (MaryEra c)
transitionConfigMary = TransitionConfig (AlonzoEra c)
transitionConfigAlonzo TransitionConfig (AlonzoEra c)
-> Getting
(TransitionConfig (MaryEra c))
(TransitionConfig (AlonzoEra c))
(TransitionConfig (MaryEra c))
-> TransitionConfig (MaryEra c)
forall s a. s -> Getting a s a -> a
^. (TransitionConfig (PreviousEra (AlonzoEra c))
-> Const
(TransitionConfig (MaryEra c))
(TransitionConfig (PreviousEra (AlonzoEra c))))
-> TransitionConfig (AlonzoEra c)
-> Const
(TransitionConfig (MaryEra c)) (TransitionConfig (AlonzoEra c))
Getting
(TransitionConfig (MaryEra c))
(TransitionConfig (AlonzoEra c))
(TransitionConfig (MaryEra c))
forall era.
(EraTransition era, EraTransition (PreviousEra era)) =>
Lens' (TransitionConfig era) (TransitionConfig (PreviousEra era))
Lens'
(TransitionConfig (AlonzoEra c))
(TransitionConfig (PreviousEra (AlonzoEra c)))
L.tcPreviousEraConfigL
transitionConfigAlonzo :: TransitionConfig (AlonzoEra c)
transitionConfigAlonzo = TransitionConfig (BabbageEra c)
transitionConfigBabbage TransitionConfig (BabbageEra c)
-> Getting
(TransitionConfig (AlonzoEra c))
(TransitionConfig (BabbageEra c))
(TransitionConfig (AlonzoEra c))
-> TransitionConfig (AlonzoEra c)
forall s a. s -> Getting a s a -> a
^. (TransitionConfig (PreviousEra (BabbageEra c))
-> Const
(TransitionConfig (AlonzoEra c))
(TransitionConfig (PreviousEra (BabbageEra c))))
-> TransitionConfig (BabbageEra c)
-> Const
(TransitionConfig (AlonzoEra c)) (TransitionConfig (BabbageEra c))
Getting
(TransitionConfig (AlonzoEra c))
(TransitionConfig (BabbageEra c))
(TransitionConfig (AlonzoEra c))
forall era.
(EraTransition era, EraTransition (PreviousEra era)) =>
Lens' (TransitionConfig era) (TransitionConfig (PreviousEra era))
Lens'
(TransitionConfig (BabbageEra c))
(TransitionConfig (PreviousEra (BabbageEra c)))
L.tcPreviousEraConfigL
transitionConfigBabbage :: TransitionConfig (BabbageEra c)
transitionConfigBabbage = TransitionConfig (LatestKnownEra c)
transitionConfigConway TransitionConfig (LatestKnownEra c)
-> Getting
(TransitionConfig (BabbageEra c))
(TransitionConfig (LatestKnownEra c))
(TransitionConfig (BabbageEra c))
-> TransitionConfig (BabbageEra c)
forall s a. s -> Getting a s a -> a
^. (TransitionConfig (PreviousEra (LatestKnownEra c))
-> Const
(TransitionConfig (BabbageEra c))
(TransitionConfig (PreviousEra (LatestKnownEra c))))
-> TransitionConfig (LatestKnownEra c)
-> Const
(TransitionConfig (BabbageEra c))
(TransitionConfig (LatestKnownEra c))
Getting
(TransitionConfig (BabbageEra c))
(TransitionConfig (LatestKnownEra c))
(TransitionConfig (BabbageEra c))
forall era.
(EraTransition era, EraTransition (PreviousEra era)) =>
Lens' (TransitionConfig era) (TransitionConfig (PreviousEra era))
Lens'
(TransitionConfig (LatestKnownEra c))
(TransitionConfig (PreviousEra (LatestKnownEra c)))
L.tcPreviousEraConfigL
transitionConfigConway :: TransitionConfig (LatestKnownEra c)
transitionConfigConway = TransitionConfig (LatestKnownEra c)
cardanoLedgerTransitionConfig
maxMajorProtVer :: MaxMajorProtVer
maxMajorProtVer :: MaxMajorProtVer
maxMajorProtVer = Version -> MaxMajorProtVer
MaxMajorProtVer (Version -> MaxMajorProtVer) -> Version -> MaxMajorProtVer
forall a b. (a -> b) -> a -> b
$ ProtVer -> Version
pvMajor ProtVer
cardanoProtocolVersion
ProtocolInfo {
pInfoConfig :: forall b. ProtocolInfo b -> TopLevelConfig b
pInfoConfig = topLevelConfigByron :: TopLevelConfig ByronBlock
topLevelConfigByron@TopLevelConfig {
topLevelConfigProtocol :: forall blk.
TopLevelConfig blk -> ConsensusConfig (BlockProtocol blk)
topLevelConfigProtocol = ConsensusConfig (BlockProtocol ByronBlock)
consensusConfigByron
, topLevelConfigLedger :: forall blk. TopLevelConfig blk -> LedgerConfig blk
topLevelConfigLedger = LedgerConfig ByronBlock
ledgerConfigByron
, topLevelConfigBlock :: forall blk. TopLevelConfig blk -> BlockConfig blk
topLevelConfigBlock = BlockConfig ByronBlock
blockConfigByron
}
, pInfoInitLedger :: forall b. ProtocolInfo b -> ExtLedgerState b
pInfoInitLedger = ExtLedgerState ByronBlock
initExtLedgerStateByron
} = ProtocolParamsByron -> ProtocolInfo ByronBlock
protocolInfoByron ProtocolParamsByron
byronProtocolParams
partialConsensusConfigByron :: PartialConsensusConfig (BlockProtocol ByronBlock)
partialConsensusConfigByron :: PartialConsensusConfig (BlockProtocol ByronBlock)
partialConsensusConfigByron = ConsensusConfig (BlockProtocol ByronBlock)
PartialConsensusConfig (BlockProtocol ByronBlock)
consensusConfigByron
partialLedgerConfigByron :: PartialLedgerConfig ByronBlock
partialLedgerConfigByron :: PartialLedgerConfig ByronBlock
partialLedgerConfigByron = ByronPartialLedgerConfig {
byronLedgerConfig :: LedgerConfig ByronBlock
byronLedgerConfig = LedgerConfig ByronBlock
ledgerConfigByron
, byronTriggerHardFork :: TriggerHardFork
byronTriggerHardFork = CardanoHardForkTrigger
(ShelleyBlock (TPraos StandardCrypto) (ShelleyEra StandardCrypto))
-> TriggerHardFork
forall blk.
Era (ShelleyBlockLedgerEra blk) =>
CardanoHardForkTrigger blk -> TriggerHardFork
toTriggerHardFork CardanoHardForkTrigger
(ShelleyBlock (TPraos StandardCrypto) (ShelleyEra StandardCrypto))
triggerHardForkShelley
}
kByron :: SecurityParam
kByron :: SecurityParam
kByron = Config -> SecurityParam
Byron.genesisSecurityParam Config
genesisByron
tpraosParams :: TPraosParams
tpraosParams :: TPraosParams
tpraosParams =
MaxMajorProtVer -> Nonce -> ShelleyGenesis c -> TPraosParams
forall era.
MaxMajorProtVer -> Nonce -> ShelleyGenesis era -> TPraosParams
Shelley.mkTPraosParams
MaxMajorProtVer
maxMajorProtVer
Nonce
initialNonceShelley
ShelleyGenesis c
genesisShelley
TPraosParams { Word64
tpraosSlotsPerKESPeriod :: Word64
tpraosSlotsPerKESPeriod :: TPraosParams -> Word64
tpraosSlotsPerKESPeriod, Word64
tpraosMaxKESEvo :: Word64
tpraosMaxKESEvo :: TPraosParams -> Word64
tpraosMaxKESEvo } = TPraosParams
tpraosParams
praosParams :: PraosParams
praosParams :: PraosParams
praosParams = PraosParams
{ praosSlotsPerKESPeriod :: Word64
praosSlotsPerKESPeriod = ShelleyGenesis c -> Word64
forall c. ShelleyGenesis c -> Word64
SL.sgSlotsPerKESPeriod ShelleyGenesis c
genesisShelley,
praosLeaderF :: ActiveSlotCoeff
praosLeaderF = PositiveUnitInterval -> ActiveSlotCoeff
SL.mkActiveSlotCoeff (PositiveUnitInterval -> ActiveSlotCoeff)
-> PositiveUnitInterval -> ActiveSlotCoeff
forall a b. (a -> b) -> a -> b
$ ShelleyGenesis c -> PositiveUnitInterval
forall c. ShelleyGenesis c -> PositiveUnitInterval
SL.sgActiveSlotsCoeff ShelleyGenesis c
genesisShelley,
praosSecurityParam :: SecurityParam
praosSecurityParam = Word64 -> SecurityParam
SecurityParam (Word64 -> SecurityParam) -> Word64 -> SecurityParam
forall a b. (a -> b) -> a -> b
$ ShelleyGenesis c -> Word64
forall c. ShelleyGenesis c -> Word64
SL.sgSecurityParam ShelleyGenesis c
genesisShelley,
praosMaxKESEvo :: Word64
praosMaxKESEvo = ShelleyGenesis c -> Word64
forall c. ShelleyGenesis c -> Word64
SL.sgMaxKESEvolutions ShelleyGenesis c
genesisShelley,
praosMaxMajorPV :: MaxMajorProtVer
praosMaxMajorPV = MaxMajorProtVer
maxMajorProtVer,
praosRandomnessStabilisationWindow :: Word64
praosRandomnessStabilisationWindow =
Word64 -> ActiveSlotCoeff -> Word64
SL.computeRandomnessStabilisationWindow
(ShelleyGenesis c -> Word64
forall c. ShelleyGenesis c -> Word64
SL.sgSecurityParam ShelleyGenesis c
genesisShelley)
(PositiveUnitInterval -> ActiveSlotCoeff
SL.mkActiveSlotCoeff (PositiveUnitInterval -> ActiveSlotCoeff)
-> PositiveUnitInterval -> ActiveSlotCoeff
forall a b. (a -> b) -> a -> b
$ ShelleyGenesis c -> PositiveUnitInterval
forall c. ShelleyGenesis c -> PositiveUnitInterval
SL.sgActiveSlotsCoeff ShelleyGenesis c
genesisShelley)
}
PraosParams { Word64
praosSlotsPerKESPeriod :: PraosParams -> Word64
praosSlotsPerKESPeriod :: Word64
praosSlotsPerKESPeriod, Word64
praosMaxKESEvo :: PraosParams -> Word64
praosMaxKESEvo :: Word64
praosMaxKESEvo } = PraosParams
praosParams
blockConfigShelley :: BlockConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
blockConfigShelley :: BlockConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
blockConfigShelley =
ProtVer
-> ShelleyGenesis (EraCrypto (ShelleyEra c))
-> [VKey 'BlockIssuer (EraCrypto (ShelleyEra c))]
-> BlockConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
forall proto era.
ShelleyBasedEra era =>
ProtVer
-> ShelleyGenesis (EraCrypto era)
-> [VKey 'BlockIssuer (EraCrypto era)]
-> BlockConfig (ShelleyBlock proto era)
Shelley.mkShelleyBlockConfig
ProtVer
cardanoProtocolVersion
ShelleyGenesis c
ShelleyGenesis (EraCrypto (ShelleyEra c))
genesisShelley
(ShelleyLeaderCredentials c -> VKey 'BlockIssuer c
forall c. ShelleyLeaderCredentials c -> VKey 'BlockIssuer c
shelleyBlockIssuerVKey (ShelleyLeaderCredentials c -> VKey 'BlockIssuer c)
-> [ShelleyLeaderCredentials c] -> [VKey 'BlockIssuer c]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ShelleyLeaderCredentials c]
credssShelleyBased)
partialConsensusConfigShelley ::
PartialConsensusConfig (BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c)))
partialConsensusConfigShelley :: PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c)))
partialConsensusConfigShelley = PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c)))
TPraosParams
tpraosParams
partialLedgerConfigShelley :: PartialLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
partialLedgerConfigShelley :: PartialLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
partialLedgerConfigShelley =
TransitionConfig (ShelleyEra c)
-> TriggerHardFork
-> PartialLedgerConfig (ShelleyBlock Any (ShelleyEra c))
forall era proto.
EraTransition era =>
TransitionConfig era
-> TriggerHardFork -> PartialLedgerConfig (ShelleyBlock proto era)
mkPartialLedgerConfigShelley
TransitionConfig (ShelleyEra c)
transitionConfigShelley
(CardanoHardForkTrigger
(ShelleyBlock (TPraos StandardCrypto) (AllegraEra StandardCrypto))
-> TriggerHardFork
forall blk.
Era (ShelleyBlockLedgerEra blk) =>
CardanoHardForkTrigger blk -> TriggerHardFork
toTriggerHardFork CardanoHardForkTrigger
(ShelleyBlock (TPraos StandardCrypto) (AllegraEra StandardCrypto))
triggerHardForkAllegra)
kShelley :: SecurityParam
kShelley :: SecurityParam
kShelley = Word64 -> SecurityParam
SecurityParam (Word64 -> SecurityParam) -> Word64 -> SecurityParam
forall a b. (a -> b) -> a -> b
$ ShelleyGenesis c -> Word64
forall c. ShelleyGenesis c -> Word64
sgSecurityParam ShelleyGenesis c
genesisShelley
blockConfigAllegra :: BlockConfig (ShelleyBlock (TPraos c) (AllegraEra c))
blockConfigAllegra :: BlockConfig (ShelleyBlock (TPraos c) (AllegraEra c))
blockConfigAllegra =
ProtVer
-> ShelleyGenesis (EraCrypto (AllegraEra c))
-> [VKey 'BlockIssuer (EraCrypto (AllegraEra c))]
-> BlockConfig (ShelleyBlock (TPraos c) (AllegraEra c))
forall proto era.
ShelleyBasedEra era =>
ProtVer
-> ShelleyGenesis (EraCrypto era)
-> [VKey 'BlockIssuer (EraCrypto era)]
-> BlockConfig (ShelleyBlock proto era)
Shelley.mkShelleyBlockConfig
ProtVer
cardanoProtocolVersion
ShelleyGenesis c
ShelleyGenesis (EraCrypto (AllegraEra c))
genesisShelley
(ShelleyLeaderCredentials c -> VKey 'BlockIssuer c
forall c. ShelleyLeaderCredentials c -> VKey 'BlockIssuer c
shelleyBlockIssuerVKey (ShelleyLeaderCredentials c -> VKey 'BlockIssuer c)
-> [ShelleyLeaderCredentials c] -> [VKey 'BlockIssuer c]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ShelleyLeaderCredentials c]
credssShelleyBased)
partialConsensusConfigAllegra ::
PartialConsensusConfig (BlockProtocol (ShelleyBlock (TPraos c) (AllegraEra c)))
partialConsensusConfigAllegra :: PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) (AllegraEra c)))
partialConsensusConfigAllegra = PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) (AllegraEra c)))
TPraosParams
tpraosParams
partialLedgerConfigAllegra :: PartialLedgerConfig (ShelleyBlock (TPraos c) (AllegraEra c))
partialLedgerConfigAllegra :: PartialLedgerConfig (ShelleyBlock (TPraos c) (AllegraEra c))
partialLedgerConfigAllegra =
TransitionConfig (AllegraEra c)
-> TriggerHardFork
-> PartialLedgerConfig (ShelleyBlock Any (AllegraEra c))
forall era proto.
EraTransition era =>
TransitionConfig era
-> TriggerHardFork -> PartialLedgerConfig (ShelleyBlock proto era)
mkPartialLedgerConfigShelley
TransitionConfig (AllegraEra c)
transitionConfigAllegra
(CardanoHardForkTrigger
(ShelleyBlock (TPraos StandardCrypto) (MaryEra StandardCrypto))
-> TriggerHardFork
forall blk.
Era (ShelleyBlockLedgerEra blk) =>
CardanoHardForkTrigger blk -> TriggerHardFork
toTriggerHardFork CardanoHardForkTrigger
(ShelleyBlock (TPraos StandardCrypto) (MaryEra StandardCrypto))
triggerHardForkMary)
blockConfigMary :: BlockConfig (ShelleyBlock (TPraos c) (MaryEra c))
blockConfigMary :: BlockConfig (ShelleyBlock (TPraos c) (MaryEra c))
blockConfigMary =
ProtVer
-> ShelleyGenesis (EraCrypto (MaryEra c))
-> [VKey 'BlockIssuer (EraCrypto (MaryEra c))]
-> BlockConfig (ShelleyBlock (TPraos c) (MaryEra c))
forall proto era.
ShelleyBasedEra era =>
ProtVer
-> ShelleyGenesis (EraCrypto era)
-> [VKey 'BlockIssuer (EraCrypto era)]
-> BlockConfig (ShelleyBlock proto era)
Shelley.mkShelleyBlockConfig
ProtVer
cardanoProtocolVersion
ShelleyGenesis c
ShelleyGenesis (EraCrypto (MaryEra c))
genesisShelley
(ShelleyLeaderCredentials c -> VKey 'BlockIssuer c
forall c. ShelleyLeaderCredentials c -> VKey 'BlockIssuer c
shelleyBlockIssuerVKey (ShelleyLeaderCredentials c -> VKey 'BlockIssuer c)
-> [ShelleyLeaderCredentials c] -> [VKey 'BlockIssuer c]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ShelleyLeaderCredentials c]
credssShelleyBased)
partialConsensusConfigMary ::
PartialConsensusConfig (BlockProtocol (ShelleyBlock (TPraos c) (MaryEra c)))
partialConsensusConfigMary :: PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) (MaryEra c)))
partialConsensusConfigMary = PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) (MaryEra c)))
TPraosParams
tpraosParams
partialLedgerConfigMary :: PartialLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
partialLedgerConfigMary :: PartialLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
partialLedgerConfigMary =
TransitionConfig (MaryEra c)
-> TriggerHardFork
-> PartialLedgerConfig (ShelleyBlock Any (MaryEra c))
forall era proto.
EraTransition era =>
TransitionConfig era
-> TriggerHardFork -> PartialLedgerConfig (ShelleyBlock proto era)
mkPartialLedgerConfigShelley
TransitionConfig (MaryEra c)
transitionConfigMary
(CardanoHardForkTrigger
(ShelleyBlock (TPraos StandardCrypto) (AlonzoEra StandardCrypto))
-> TriggerHardFork
forall blk.
Era (ShelleyBlockLedgerEra blk) =>
CardanoHardForkTrigger blk -> TriggerHardFork
toTriggerHardFork CardanoHardForkTrigger
(ShelleyBlock (TPraos StandardCrypto) (AlonzoEra StandardCrypto))
triggerHardForkAlonzo)
blockConfigAlonzo :: BlockConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
blockConfigAlonzo :: BlockConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
blockConfigAlonzo =
ProtVer
-> ShelleyGenesis (EraCrypto (AlonzoEra c))
-> [VKey 'BlockIssuer (EraCrypto (AlonzoEra c))]
-> BlockConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
forall proto era.
ShelleyBasedEra era =>
ProtVer
-> ShelleyGenesis (EraCrypto era)
-> [VKey 'BlockIssuer (EraCrypto era)]
-> BlockConfig (ShelleyBlock proto era)
Shelley.mkShelleyBlockConfig
ProtVer
cardanoProtocolVersion
ShelleyGenesis c
ShelleyGenesis (EraCrypto (AlonzoEra c))
genesisShelley
(ShelleyLeaderCredentials c -> VKey 'BlockIssuer c
forall c. ShelleyLeaderCredentials c -> VKey 'BlockIssuer c
shelleyBlockIssuerVKey (ShelleyLeaderCredentials c -> VKey 'BlockIssuer c)
-> [ShelleyLeaderCredentials c] -> [VKey 'BlockIssuer c]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ShelleyLeaderCredentials c]
credssShelleyBased)
partialConsensusConfigAlonzo ::
PartialConsensusConfig (BlockProtocol (ShelleyBlock (TPraos c) (AlonzoEra c)))
partialConsensusConfigAlonzo :: PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) (AlonzoEra c)))
partialConsensusConfigAlonzo = PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) (AlonzoEra c)))
TPraosParams
tpraosParams
partialLedgerConfigAlonzo :: PartialLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
partialLedgerConfigAlonzo :: PartialLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
partialLedgerConfigAlonzo =
TransitionConfig (AlonzoEra c)
-> TriggerHardFork
-> PartialLedgerConfig (ShelleyBlock Any (AlonzoEra c))
forall era proto.
EraTransition era =>
TransitionConfig era
-> TriggerHardFork -> PartialLedgerConfig (ShelleyBlock proto era)
mkPartialLedgerConfigShelley
TransitionConfig (AlonzoEra c)
transitionConfigAlonzo
(CardanoHardForkTrigger
(ShelleyBlock (Praos StandardCrypto) (BabbageEra StandardCrypto))
-> TriggerHardFork
forall blk.
Era (ShelleyBlockLedgerEra blk) =>
CardanoHardForkTrigger blk -> TriggerHardFork
toTriggerHardFork CardanoHardForkTrigger
(ShelleyBlock (Praos StandardCrypto) (BabbageEra StandardCrypto))
triggerHardForkBabbage)
blockConfigBabbage :: BlockConfig (ShelleyBlock (Praos c) (BabbageEra c))
blockConfigBabbage :: BlockConfig (ShelleyBlock (Praos c) (BabbageEra c))
blockConfigBabbage =
ProtVer
-> ShelleyGenesis (EraCrypto (BabbageEra c))
-> [VKey 'BlockIssuer (EraCrypto (BabbageEra c))]
-> BlockConfig (ShelleyBlock (Praos c) (BabbageEra c))
forall proto era.
ShelleyBasedEra era =>
ProtVer
-> ShelleyGenesis (EraCrypto era)
-> [VKey 'BlockIssuer (EraCrypto era)]
-> BlockConfig (ShelleyBlock proto era)
Shelley.mkShelleyBlockConfig
ProtVer
cardanoProtocolVersion
ShelleyGenesis c
ShelleyGenesis (EraCrypto (BabbageEra c))
genesisShelley
(ShelleyLeaderCredentials c -> VKey 'BlockIssuer c
forall c. ShelleyLeaderCredentials c -> VKey 'BlockIssuer c
shelleyBlockIssuerVKey (ShelleyLeaderCredentials c -> VKey 'BlockIssuer c)
-> [ShelleyLeaderCredentials c] -> [VKey 'BlockIssuer c]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ShelleyLeaderCredentials c]
credssShelleyBased)
partialConsensusConfigBabbage ::
PartialConsensusConfig (BlockProtocol (ShelleyBlock (Praos c) (BabbageEra c)))
partialConsensusConfigBabbage :: PartialConsensusConfig
(BlockProtocol (ShelleyBlock (Praos c) (BabbageEra c)))
partialConsensusConfigBabbage = PraosParams
praosParams {
praosRandomnessStabilisationWindow =
SL.computeStabilityWindow
(SL.sgSecurityParam genesisShelley)
(SL.mkActiveSlotCoeff $ SL.sgActiveSlotsCoeff genesisShelley)
}
partialLedgerConfigBabbage :: PartialLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
partialLedgerConfigBabbage :: PartialLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
partialLedgerConfigBabbage =
TransitionConfig (BabbageEra c)
-> TriggerHardFork
-> PartialLedgerConfig (ShelleyBlock Any (BabbageEra c))
forall era proto.
EraTransition era =>
TransitionConfig era
-> TriggerHardFork -> PartialLedgerConfig (ShelleyBlock proto era)
mkPartialLedgerConfigShelley
TransitionConfig (BabbageEra c)
transitionConfigBabbage
(CardanoHardForkTrigger
(ShelleyBlock (Praos StandardCrypto) (ConwayEra StandardCrypto))
-> TriggerHardFork
forall blk.
Era (ShelleyBlockLedgerEra blk) =>
CardanoHardForkTrigger blk -> TriggerHardFork
toTriggerHardFork CardanoHardForkTrigger
(ShelleyBlock (Praos StandardCrypto) (ConwayEra StandardCrypto))
triggerHardForkConway)
blockConfigConway :: BlockConfig (ShelleyBlock (Praos c) (ConwayEra c))
blockConfigConway :: BlockConfig (ShelleyBlock (Praos c) (LatestKnownEra c))
blockConfigConway =
ProtVer
-> ShelleyGenesis (EraCrypto (LatestKnownEra c))
-> [VKey 'BlockIssuer (EraCrypto (LatestKnownEra c))]
-> BlockConfig (ShelleyBlock (Praos c) (LatestKnownEra c))
forall proto era.
ShelleyBasedEra era =>
ProtVer
-> ShelleyGenesis (EraCrypto era)
-> [VKey 'BlockIssuer (EraCrypto era)]
-> BlockConfig (ShelleyBlock proto era)
Shelley.mkShelleyBlockConfig
ProtVer
cardanoProtocolVersion
ShelleyGenesis c
ShelleyGenesis (EraCrypto (LatestKnownEra c))
genesisShelley
(ShelleyLeaderCredentials c -> VKey 'BlockIssuer c
forall c. ShelleyLeaderCredentials c -> VKey 'BlockIssuer c
shelleyBlockIssuerVKey (ShelleyLeaderCredentials c -> VKey 'BlockIssuer c)
-> [ShelleyLeaderCredentials c] -> [VKey 'BlockIssuer c]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ShelleyLeaderCredentials c]
credssShelleyBased)
partialConsensusConfigConway ::
PartialConsensusConfig (BlockProtocol (ShelleyBlock (Praos c) (ConwayEra c)))
partialConsensusConfigConway :: PartialConsensusConfig
(BlockProtocol (ShelleyBlock (Praos c) (LatestKnownEra c)))
partialConsensusConfigConway = PartialConsensusConfig
(BlockProtocol (ShelleyBlock (Praos c) (LatestKnownEra c)))
PraosParams
praosParams
partialLedgerConfigConway :: PartialLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
partialLedgerConfigConway :: PartialLedgerConfig (ShelleyBlock (Praos c) (LatestKnownEra c))
partialLedgerConfigConway =
TransitionConfig (LatestKnownEra c)
-> TriggerHardFork
-> PartialLedgerConfig (ShelleyBlock Any (LatestKnownEra c))
forall era proto.
EraTransition era =>
TransitionConfig era
-> TriggerHardFork -> PartialLedgerConfig (ShelleyBlock proto era)
mkPartialLedgerConfigShelley
TransitionConfig (LatestKnownEra c)
transitionConfigConway
TriggerHardFork
TriggerHardForkNotDuringThisExecution
k :: SecurityParam
k :: SecurityParam
k = Bool -> SecurityParam -> SecurityParam
forall a. HasCallStack => Bool -> a -> a
assert (SecurityParam
kByron SecurityParam -> SecurityParam -> Bool
forall a. Eq a => a -> a -> Bool
== SecurityParam
kShelley) SecurityParam
kByron
shape :: History.Shape (CardanoEras c)
shape :: Shape (CardanoEras c)
shape = Exactly (CardanoEras c) EraParams -> Shape (CardanoEras c)
forall (xs :: [*]). Exactly xs EraParams -> Shape xs
History.Shape (Exactly (CardanoEras c) EraParams -> Shape (CardanoEras c))
-> Exactly (CardanoEras c) EraParams -> Shape (CardanoEras c)
forall a b. (a -> b) -> a -> b
$ NP (K EraParams) (CardanoEras c)
-> Exactly (CardanoEras c) EraParams
forall (xs :: [*]) a. NP (K a) xs -> Exactly xs a
Exactly (NP (K EraParams) (CardanoEras c)
-> Exactly (CardanoEras c) EraParams)
-> NP (K EraParams) (CardanoEras c)
-> Exactly (CardanoEras c) EraParams
forall a b. (a -> b) -> a -> b
$
EraParams -> K EraParams ByronBlock
forall k a (b :: k). a -> K a b
K (Config -> EraParams
Byron.byronEraParams Config
genesisByron)
K EraParams ByronBlock
-> NP (K EraParams) (CardanoShelleyEras c)
-> NP (K EraParams) (CardanoEras c)
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* EraParams -> K EraParams (ShelleyBlock (TPraos c) (ShelleyEra c))
forall k a (b :: k). a -> K a b
K (ShelleyGenesis c -> EraParams
forall c. ShelleyGenesis c -> EraParams
Shelley.shelleyEraParams ShelleyGenesis c
genesisShelley)
K EraParams (ShelleyBlock (TPraos c) (ShelleyEra c))
-> NP
(K EraParams)
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP (K EraParams) (CardanoShelleyEras c)
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* EraParams -> K EraParams (ShelleyBlock (TPraos c) (AllegraEra c))
forall k a (b :: k). a -> K a b
K (ShelleyGenesis c -> EraParams
forall c. ShelleyGenesis c -> EraParams
Shelley.shelleyEraParams ShelleyGenesis c
genesisShelley)
K EraParams (ShelleyBlock (TPraos c) (AllegraEra c))
-> NP
(K EraParams)
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP
(K EraParams)
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* EraParams -> K EraParams (ShelleyBlock (TPraos c) (MaryEra c))
forall k a (b :: k). a -> K a b
K (ShelleyGenesis c -> EraParams
forall c. ShelleyGenesis c -> EraParams
Shelley.shelleyEraParams ShelleyGenesis c
genesisShelley)
K EraParams (ShelleyBlock (TPraos c) (MaryEra c))
-> NP
(K EraParams)
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP
(K EraParams)
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* EraParams -> K EraParams (ShelleyBlock (TPraos c) (AlonzoEra c))
forall k a (b :: k). a -> K a b
K (ShelleyGenesis c -> EraParams
forall c. ShelleyGenesis c -> EraParams
Shelley.shelleyEraParams ShelleyGenesis c
genesisShelley)
K EraParams (ShelleyBlock (TPraos c) (AlonzoEra c))
-> NP
(K EraParams)
'[ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP
(K EraParams)
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* EraParams -> K EraParams (ShelleyBlock (Praos c) (BabbageEra c))
forall k a (b :: k). a -> K a b
K (ShelleyGenesis c -> EraParams
forall c. ShelleyGenesis c -> EraParams
Shelley.shelleyEraParams ShelleyGenesis c
genesisShelley)
K EraParams (ShelleyBlock (Praos c) (BabbageEra c))
-> NP (K EraParams) '[ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP
(K EraParams)
'[ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* EraParams
-> K EraParams (ShelleyBlock (Praos c) (LatestKnownEra c))
forall k a (b :: k). a -> K a b
K (ShelleyGenesis c -> EraParams
forall c. ShelleyGenesis c -> EraParams
Shelley.shelleyEraParams ShelleyGenesis c
genesisShelley)
K EraParams (ShelleyBlock (Praos c) (LatestKnownEra c))
-> NP (K EraParams) '[]
-> NP (K EraParams) '[ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* NP (K EraParams) '[]
forall {k} (f :: k -> *). NP f '[]
Nil
cfg :: TopLevelConfig (CardanoBlock c)
cfg :: TopLevelConfig (CardanoBlock c)
cfg = TopLevelConfig {
topLevelConfigProtocol :: ConsensusConfig (BlockProtocol (CardanoBlock c))
topLevelConfigProtocol = HardForkConsensusConfig {
hardForkConsensusConfigK :: SecurityParam
hardForkConsensusConfigK = SecurityParam
k
, hardForkConsensusConfigShape :: Shape (CardanoEras c)
hardForkConsensusConfigShape = Shape (CardanoEras c)
shape
, hardForkConsensusConfigPerEra :: PerEraConsensusConfig (CardanoEras c)
hardForkConsensusConfigPerEra = NP WrapPartialConsensusConfig (CardanoEras c)
-> PerEraConsensusConfig (CardanoEras c)
forall (xs :: [*]).
NP WrapPartialConsensusConfig xs -> PerEraConsensusConfig xs
PerEraConsensusConfig
( PartialConsensusConfig (BlockProtocol ByronBlock)
-> WrapPartialConsensusConfig ByronBlock
forall blk.
PartialConsensusConfig (BlockProtocol blk)
-> WrapPartialConsensusConfig blk
WrapPartialConsensusConfig PartialConsensusConfig (BlockProtocol ByronBlock)
partialConsensusConfigByron
WrapPartialConsensusConfig ByronBlock
-> NP WrapPartialConsensusConfig (CardanoShelleyEras c)
-> NP WrapPartialConsensusConfig (CardanoEras c)
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> WrapPartialConsensusConfig
(ShelleyBlock (TPraos c) (ShelleyEra c))
forall blk.
PartialConsensusConfig (BlockProtocol blk)
-> WrapPartialConsensusConfig blk
WrapPartialConsensusConfig PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c)))
partialConsensusConfigShelley
WrapPartialConsensusConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> NP
WrapPartialConsensusConfig
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP WrapPartialConsensusConfig (CardanoShelleyEras c)
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) (AllegraEra c)))
-> WrapPartialConsensusConfig
(ShelleyBlock (TPraos c) (AllegraEra c))
forall blk.
PartialConsensusConfig (BlockProtocol blk)
-> WrapPartialConsensusConfig blk
WrapPartialConsensusConfig PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) (AllegraEra c)))
partialConsensusConfigAllegra
WrapPartialConsensusConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> NP
WrapPartialConsensusConfig
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP
WrapPartialConsensusConfig
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) (MaryEra c)))
-> WrapPartialConsensusConfig (ShelleyBlock (TPraos c) (MaryEra c))
forall blk.
PartialConsensusConfig (BlockProtocol blk)
-> WrapPartialConsensusConfig blk
WrapPartialConsensusConfig PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) (MaryEra c)))
partialConsensusConfigMary
WrapPartialConsensusConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> NP
WrapPartialConsensusConfig
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP
WrapPartialConsensusConfig
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> WrapPartialConsensusConfig
(ShelleyBlock (TPraos c) (AlonzoEra c))
forall blk.
PartialConsensusConfig (BlockProtocol blk)
-> WrapPartialConsensusConfig blk
WrapPartialConsensusConfig PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) (AlonzoEra c)))
partialConsensusConfigAlonzo
WrapPartialConsensusConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> NP
WrapPartialConsensusConfig
'[ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP
WrapPartialConsensusConfig
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* PartialConsensusConfig
(BlockProtocol (ShelleyBlock (Praos c) (BabbageEra c)))
-> WrapPartialConsensusConfig
(ShelleyBlock (Praos c) (BabbageEra c))
forall blk.
PartialConsensusConfig (BlockProtocol blk)
-> WrapPartialConsensusConfig blk
WrapPartialConsensusConfig PartialConsensusConfig
(BlockProtocol (ShelleyBlock (Praos c) (BabbageEra c)))
partialConsensusConfigBabbage
WrapPartialConsensusConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> NP
WrapPartialConsensusConfig
'[ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP
WrapPartialConsensusConfig
'[ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* PartialConsensusConfig
(BlockProtocol (ShelleyBlock (Praos c) (LatestKnownEra c)))
-> WrapPartialConsensusConfig
(ShelleyBlock (Praos c) (LatestKnownEra c))
forall blk.
PartialConsensusConfig (BlockProtocol blk)
-> WrapPartialConsensusConfig blk
WrapPartialConsensusConfig PartialConsensusConfig
(BlockProtocol (ShelleyBlock (Praos c) (LatestKnownEra c)))
partialConsensusConfigConway
WrapPartialConsensusConfig
(ShelleyBlock (Praos c) (LatestKnownEra c))
-> NP WrapPartialConsensusConfig '[]
-> NP
WrapPartialConsensusConfig
'[ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* NP WrapPartialConsensusConfig '[]
forall {k} (f :: k -> *). NP f '[]
Nil
)
}
, topLevelConfigLedger :: LedgerConfig (CardanoBlock c)
topLevelConfigLedger = HardForkLedgerConfig {
hardForkLedgerConfigShape :: Shape (CardanoEras c)
hardForkLedgerConfigShape = Shape (CardanoEras c)
shape
, hardForkLedgerConfigPerEra :: PerEraLedgerConfig (CardanoEras c)
hardForkLedgerConfigPerEra = NP WrapPartialLedgerConfig (CardanoEras c)
-> PerEraLedgerConfig (CardanoEras c)
forall (xs :: [*]).
NP WrapPartialLedgerConfig xs -> PerEraLedgerConfig xs
PerEraLedgerConfig
( PartialLedgerConfig ByronBlock
-> WrapPartialLedgerConfig ByronBlock
forall blk. PartialLedgerConfig blk -> WrapPartialLedgerConfig blk
WrapPartialLedgerConfig PartialLedgerConfig ByronBlock
partialLedgerConfigByron
WrapPartialLedgerConfig ByronBlock
-> NP WrapPartialLedgerConfig (CardanoShelleyEras c)
-> NP WrapPartialLedgerConfig (CardanoEras c)
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* PartialLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> WrapPartialLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
forall blk. PartialLedgerConfig blk -> WrapPartialLedgerConfig blk
WrapPartialLedgerConfig PartialLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
partialLedgerConfigShelley
WrapPartialLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> NP
WrapPartialLedgerConfig
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP WrapPartialLedgerConfig (CardanoShelleyEras c)
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* PartialLedgerConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> WrapPartialLedgerConfig (ShelleyBlock (TPraos c) (AllegraEra c))
forall blk. PartialLedgerConfig blk -> WrapPartialLedgerConfig blk
WrapPartialLedgerConfig PartialLedgerConfig (ShelleyBlock (TPraos c) (AllegraEra c))
partialLedgerConfigAllegra
WrapPartialLedgerConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> NP
WrapPartialLedgerConfig
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP
WrapPartialLedgerConfig
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* PartialLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> WrapPartialLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
forall blk. PartialLedgerConfig blk -> WrapPartialLedgerConfig blk
WrapPartialLedgerConfig PartialLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
partialLedgerConfigMary
WrapPartialLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> NP
WrapPartialLedgerConfig
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP
WrapPartialLedgerConfig
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* PartialLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> WrapPartialLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
forall blk. PartialLedgerConfig blk -> WrapPartialLedgerConfig blk
WrapPartialLedgerConfig PartialLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
partialLedgerConfigAlonzo
WrapPartialLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> NP
WrapPartialLedgerConfig
'[ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP
WrapPartialLedgerConfig
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* PartialLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> WrapPartialLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
forall blk. PartialLedgerConfig blk -> WrapPartialLedgerConfig blk
WrapPartialLedgerConfig PartialLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
partialLedgerConfigBabbage
WrapPartialLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> NP
WrapPartialLedgerConfig
'[ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP
WrapPartialLedgerConfig
'[ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* PartialLedgerConfig (ShelleyBlock (Praos c) (LatestKnownEra c))
-> WrapPartialLedgerConfig
(ShelleyBlock (Praos c) (LatestKnownEra c))
forall blk. PartialLedgerConfig blk -> WrapPartialLedgerConfig blk
WrapPartialLedgerConfig PartialLedgerConfig (ShelleyBlock (Praos c) (LatestKnownEra c))
partialLedgerConfigConway
WrapPartialLedgerConfig (ShelleyBlock (Praos c) (LatestKnownEra c))
-> NP WrapPartialLedgerConfig '[]
-> NP
WrapPartialLedgerConfig
'[ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* NP WrapPartialLedgerConfig '[]
forall {k} (f :: k -> *). NP f '[]
Nil
)
}
, topLevelConfigBlock :: BlockConfig (CardanoBlock c)
topLevelConfigBlock =
BlockConfig ByronBlock
-> BlockConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> BlockConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> BlockConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> BlockConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> BlockConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> BlockConfig (ShelleyBlock (Praos c) (LatestKnownEra c))
-> BlockConfig (CardanoBlock c)
forall c.
BlockConfig ByronBlock
-> BlockConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> BlockConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> BlockConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> BlockConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> BlockConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> BlockConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> CardanoBlockConfig c
CardanoBlockConfig
BlockConfig ByronBlock
blockConfigByron
BlockConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
blockConfigShelley
BlockConfig (ShelleyBlock (TPraos c) (AllegraEra c))
blockConfigAllegra
BlockConfig (ShelleyBlock (TPraos c) (MaryEra c))
blockConfigMary
BlockConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
blockConfigAlonzo
BlockConfig (ShelleyBlock (Praos c) (BabbageEra c))
blockConfigBabbage
BlockConfig (ShelleyBlock (Praos c) (LatestKnownEra c))
blockConfigConway
, topLevelConfigCodec :: CodecConfig (CardanoBlock c)
topLevelConfigCodec =
CodecConfig ByronBlock
-> CodecConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> CodecConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> CodecConfig (ShelleyBlock (Praos c) (LatestKnownEra c))
-> CodecConfig (CardanoBlock c)
forall c.
CodecConfig ByronBlock
-> CodecConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> CodecConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> CodecConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> CardanoCodecConfig c
CardanoCodecConfig
(TopLevelConfig ByronBlock -> CodecConfig ByronBlock
forall blk. TopLevelConfig blk -> CodecConfig blk
configCodec TopLevelConfig ByronBlock
topLevelConfigByron)
CodecConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
forall proto era. CodecConfig (ShelleyBlock proto era)
Shelley.ShelleyCodecConfig
CodecConfig (ShelleyBlock (TPraos c) (AllegraEra c))
forall proto era. CodecConfig (ShelleyBlock proto era)
Shelley.ShelleyCodecConfig
CodecConfig (ShelleyBlock (TPraos c) (MaryEra c))
forall proto era. CodecConfig (ShelleyBlock proto era)
Shelley.ShelleyCodecConfig
CodecConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
forall proto era. CodecConfig (ShelleyBlock proto era)
Shelley.ShelleyCodecConfig
CodecConfig (ShelleyBlock (Praos c) (BabbageEra c))
forall proto era. CodecConfig (ShelleyBlock proto era)
Shelley.ShelleyCodecConfig
CodecConfig (ShelleyBlock (Praos c) (LatestKnownEra c))
forall proto era. CodecConfig (ShelleyBlock proto era)
Shelley.ShelleyCodecConfig
, topLevelConfigStorage :: StorageConfig (CardanoBlock c)
topLevelConfigStorage =
StorageConfig ByronBlock
-> StorageConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> StorageConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> StorageConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> StorageConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> StorageConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> StorageConfig (ShelleyBlock (Praos c) (LatestKnownEra c))
-> StorageConfig (CardanoBlock c)
forall c.
StorageConfig ByronBlock
-> StorageConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> StorageConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> StorageConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> StorageConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> StorageConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> StorageConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> CardanoStorageConfig c
CardanoStorageConfig
(TopLevelConfig ByronBlock -> StorageConfig ByronBlock
forall blk. TopLevelConfig blk -> StorageConfig blk
configStorage TopLevelConfig ByronBlock
topLevelConfigByron)
(Word64
-> SecurityParam
-> StorageConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
forall proto era.
Word64 -> SecurityParam -> StorageConfig (ShelleyBlock proto era)
Shelley.ShelleyStorageConfig Word64
tpraosSlotsPerKESPeriod SecurityParam
k)
(Word64
-> SecurityParam
-> StorageConfig (ShelleyBlock (TPraos c) (AllegraEra c))
forall proto era.
Word64 -> SecurityParam -> StorageConfig (ShelleyBlock proto era)
Shelley.ShelleyStorageConfig Word64
tpraosSlotsPerKESPeriod SecurityParam
k)
(Word64
-> SecurityParam
-> StorageConfig (ShelleyBlock (TPraos c) (MaryEra c))
forall proto era.
Word64 -> SecurityParam -> StorageConfig (ShelleyBlock proto era)
Shelley.ShelleyStorageConfig Word64
tpraosSlotsPerKESPeriod SecurityParam
k)
(Word64
-> SecurityParam
-> StorageConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
forall proto era.
Word64 -> SecurityParam -> StorageConfig (ShelleyBlock proto era)
Shelley.ShelleyStorageConfig Word64
tpraosSlotsPerKESPeriod SecurityParam
k)
(Word64
-> SecurityParam
-> StorageConfig (ShelleyBlock (Praos c) (BabbageEra c))
forall proto era.
Word64 -> SecurityParam -> StorageConfig (ShelleyBlock proto era)
Shelley.ShelleyStorageConfig Word64
tpraosSlotsPerKESPeriod SecurityParam
k)
(Word64
-> SecurityParam
-> StorageConfig (ShelleyBlock (Praos c) (LatestKnownEra c))
forall proto era.
Word64 -> SecurityParam -> StorageConfig (ShelleyBlock proto era)
Shelley.ShelleyStorageConfig Word64
tpraosSlotsPerKESPeriod SecurityParam
k)
, topLevelConfigCheckpoints :: CheckpointsMap (CardanoBlock c)
topLevelConfigCheckpoints = CheckpointsMap (CardanoBlock c)
cardanoCheckpoints
}
initExtLedgerStateCardano :: ExtLedgerState (CardanoBlock c)
initExtLedgerStateCardano :: ExtLedgerState (CardanoBlock c)
initExtLedgerStateCardano = ExtLedgerState {
headerState :: HeaderState (CardanoBlock c)
headerState = HeaderState (CardanoBlock c)
initHeaderState
, ledgerState :: LedgerState (CardanoBlock c)
ledgerState =
HardForkState LedgerState (CardanoEras c)
-> LedgerState (CardanoBlock c)
forall (xs :: [*]).
HardForkState LedgerState xs -> LedgerState (HardForkBlock xs)
HardForkLedgerState
(HardForkState LedgerState (CardanoEras c)
-> LedgerState (CardanoBlock c))
-> (HardForkState LedgerState (CardanoEras c)
-> HardForkState LedgerState (CardanoEras c))
-> HardForkState LedgerState (CardanoEras c)
-> LedgerState (CardanoBlock c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Prod HardForkState (LedgerState -.-> LedgerState) (CardanoEras c)
-> HardForkState LedgerState (CardanoEras c)
-> HardForkState LedgerState (CardanoEras c)
forall k l (h :: (k -> *) -> l -> *) (f :: k -> *) (g :: k -> *)
(xs :: l).
HAp h =>
Prod h (f -.-> g) xs -> h f xs -> h g xs
forall (f :: * -> *) (g :: * -> *) (xs :: [*]).
Prod HardForkState (f -.-> g) xs
-> HardForkState f xs -> HardForkState g xs
hap ((LedgerState ByronBlock -> LedgerState ByronBlock)
-> (-.->) LedgerState LedgerState ByronBlock
forall {k} (f :: k -> *) (a :: k) (f' :: k -> *).
(f a -> f' a) -> (-.->) f f' a
fn LedgerState ByronBlock -> LedgerState ByronBlock
forall a. a -> a
id (-.->) LedgerState LedgerState ByronBlock
-> NP (LedgerState -.-> LedgerState) (CardanoShelleyEras c)
-> NP (LedgerState -.-> LedgerState) (CardanoEras c)
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* NP (LedgerState -.-> LedgerState) (CardanoShelleyEras c)
registerAny)
(HardForkState LedgerState (CardanoEras c)
-> LedgerState (CardanoBlock c))
-> HardForkState LedgerState (CardanoEras c)
-> LedgerState (CardanoBlock c)
forall a b. (a -> b) -> a -> b
$ LedgerState (CardanoBlock c)
-> HardForkState LedgerState (CardanoEras c)
forall (xs :: [*]).
LedgerState (HardForkBlock xs) -> HardForkState LedgerState xs
hardForkLedgerStatePerEra LedgerState (CardanoBlock c)
initLedgerState
}
where
initHeaderState :: HeaderState (CardanoBlock c)
initLedgerState :: LedgerState (CardanoBlock c)
ExtLedgerState LedgerState (CardanoBlock c)
initLedgerState HeaderState (CardanoBlock c)
initHeaderState =
TopLevelConfig (CardanoBlock c)
-> ExtLedgerState ByronBlock -> ExtLedgerState (CardanoBlock c)
forall x (xs :: [*]).
CanHardFork (x : xs) =>
TopLevelConfig (HardForkBlock (x : xs))
-> ExtLedgerState x -> ExtLedgerState (HardForkBlock (x : xs))
injectInitialExtLedgerState TopLevelConfig (CardanoBlock c)
cfg ExtLedgerState ByronBlock
initExtLedgerStateByron
registerAny :: NP (LedgerState -.-> LedgerState) (CardanoShelleyEras c)
registerAny :: NP (LedgerState -.-> LedgerState) (CardanoShelleyEras c)
registerAny =
Proxy IsShelleyBlock
-> (forall a.
IsShelleyBlock a =>
WrapTransitionConfig a -> (-.->) LedgerState LedgerState a)
-> NP WrapTransitionConfig (CardanoShelleyEras c)
-> NP (LedgerState -.-> LedgerState) (CardanoShelleyEras c)
forall {k} {l} (h :: (k -> *) -> l -> *) (c :: k -> Constraint)
(xs :: l) (proxy :: (k -> Constraint) -> *) (f :: k -> *)
(f' :: k -> *).
(AllN (Prod h) c xs, HAp h) =>
proxy c
-> (forall (a :: k). c a => f a -> f' a) -> h f xs -> h f' xs
hcmap (forall {k} (t :: k). Proxy t
forall (t :: * -> Constraint). Proxy t
Proxy @IsShelleyBlock) WrapTransitionConfig a -> (-.->) LedgerState LedgerState a
WrapTransitionConfig
(ShelleyBlock (BlockProtocol a) (ShelleyBlockLedgerEra a))
-> (-.->)
LedgerState
LedgerState
(ShelleyBlock (BlockProtocol a) (ShelleyBlockLedgerEra a))
forall a.
IsShelleyBlock a =>
WrapTransitionConfig a -> (-.->) LedgerState LedgerState a
forall era proto.
EraTransition era =>
WrapTransitionConfig (ShelleyBlock proto era)
-> (-.->) LedgerState LedgerState (ShelleyBlock proto era)
injectIntoTestState (NP WrapTransitionConfig (CardanoShelleyEras c)
-> NP (LedgerState -.-> LedgerState) (CardanoShelleyEras c))
-> NP WrapTransitionConfig (CardanoShelleyEras c)
-> NP (LedgerState -.-> LedgerState) (CardanoShelleyEras c)
forall a b. (a -> b) -> a -> b
$
TransitionConfig
(ShelleyBlockLedgerEra (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> WrapTransitionConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
forall blk.
TransitionConfig (ShelleyBlockLedgerEra blk)
-> WrapTransitionConfig blk
WrapTransitionConfig TransitionConfig (ShelleyEra c)
TransitionConfig
(ShelleyBlockLedgerEra (ShelleyBlock (TPraos c) (ShelleyEra c)))
transitionConfigShelley
WrapTransitionConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> NP
WrapTransitionConfig
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP WrapTransitionConfig (CardanoShelleyEras c)
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* TransitionConfig
(ShelleyBlockLedgerEra (ShelleyBlock (TPraos c) (AllegraEra c)))
-> WrapTransitionConfig (ShelleyBlock (TPraos c) (AllegraEra c))
forall blk.
TransitionConfig (ShelleyBlockLedgerEra blk)
-> WrapTransitionConfig blk
WrapTransitionConfig TransitionConfig (AllegraEra c)
TransitionConfig
(ShelleyBlockLedgerEra (ShelleyBlock (TPraos c) (AllegraEra c)))
transitionConfigAllegra
WrapTransitionConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> NP
WrapTransitionConfig
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP
WrapTransitionConfig
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* TransitionConfig
(ShelleyBlockLedgerEra (ShelleyBlock (TPraos c) (MaryEra c)))
-> WrapTransitionConfig (ShelleyBlock (TPraos c) (MaryEra c))
forall blk.
TransitionConfig (ShelleyBlockLedgerEra blk)
-> WrapTransitionConfig blk
WrapTransitionConfig TransitionConfig (MaryEra c)
TransitionConfig
(ShelleyBlockLedgerEra (ShelleyBlock (TPraos c) (MaryEra c)))
transitionConfigMary
WrapTransitionConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> NP
WrapTransitionConfig
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP
WrapTransitionConfig
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* TransitionConfig
(ShelleyBlockLedgerEra (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> WrapTransitionConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
forall blk.
TransitionConfig (ShelleyBlockLedgerEra blk)
-> WrapTransitionConfig blk
WrapTransitionConfig TransitionConfig (AlonzoEra c)
TransitionConfig
(ShelleyBlockLedgerEra (ShelleyBlock (TPraos c) (AlonzoEra c)))
transitionConfigAlonzo
WrapTransitionConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> NP
WrapTransitionConfig
'[ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP
WrapTransitionConfig
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* TransitionConfig
(ShelleyBlockLedgerEra (ShelleyBlock (Praos c) (BabbageEra c)))
-> WrapTransitionConfig (ShelleyBlock (Praos c) (BabbageEra c))
forall blk.
TransitionConfig (ShelleyBlockLedgerEra blk)
-> WrapTransitionConfig blk
WrapTransitionConfig TransitionConfig (BabbageEra c)
TransitionConfig
(ShelleyBlockLedgerEra (ShelleyBlock (Praos c) (BabbageEra c)))
transitionConfigBabbage
WrapTransitionConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> NP
WrapTransitionConfig '[ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP
WrapTransitionConfig
'[ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* TransitionConfig
(ShelleyBlockLedgerEra (ShelleyBlock (Praos c) (LatestKnownEra c)))
-> WrapTransitionConfig (ShelleyBlock (Praos c) (LatestKnownEra c))
forall blk.
TransitionConfig (ShelleyBlockLedgerEra blk)
-> WrapTransitionConfig blk
WrapTransitionConfig TransitionConfig (LatestKnownEra c)
TransitionConfig
(ShelleyBlockLedgerEra (ShelleyBlock (Praos c) (LatestKnownEra c)))
transitionConfigConway
WrapTransitionConfig (ShelleyBlock (Praos c) (LatestKnownEra c))
-> NP WrapTransitionConfig '[]
-> NP
WrapTransitionConfig '[ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:* NP WrapTransitionConfig '[]
forall {k} (f :: k -> *). NP f '[]
Nil
injectIntoTestState ::
L.EraTransition era
=> WrapTransitionConfig (ShelleyBlock proto era)
-> (LedgerState -.-> LedgerState) (ShelleyBlock proto era)
injectIntoTestState :: forall era proto.
EraTransition era =>
WrapTransitionConfig (ShelleyBlock proto era)
-> (-.->) LedgerState LedgerState (ShelleyBlock proto era)
injectIntoTestState (WrapTransitionConfig TransitionConfig (ShelleyBlockLedgerEra (ShelleyBlock proto era))
cfg) = (LedgerState (ShelleyBlock proto era)
-> LedgerState (ShelleyBlock proto era))
-> (-.->) LedgerState LedgerState (ShelleyBlock proto era)
forall {k} (f :: k -> *) (a :: k) (f' :: k -> *).
(f a -> f' a) -> (-.->) f f' a
fn ((LedgerState (ShelleyBlock proto era)
-> LedgerState (ShelleyBlock proto era))
-> (-.->) LedgerState LedgerState (ShelleyBlock proto era))
-> (LedgerState (ShelleyBlock proto era)
-> LedgerState (ShelleyBlock proto era))
-> (-.->) LedgerState LedgerState (ShelleyBlock proto era)
forall a b. (a -> b) -> a -> b
$ \LedgerState (ShelleyBlock proto era)
st -> LedgerState (ShelleyBlock proto era)
st {
Shelley.shelleyLedgerState = L.injectIntoTestState cfg (Shelley.shelleyLedgerState st)
}
blockForging :: m [BlockForging m (CardanoBlock c)]
blockForging :: m [BlockForging m (CardanoBlock c)]
blockForging = do
[NonEmptyOptNP (BlockForging m) (CardanoEras c)]
shelleyBased <- (ShelleyLeaderCredentials c
-> m (NonEmptyOptNP (BlockForging m) (CardanoEras c)))
-> [ShelleyLeaderCredentials c]
-> m [NonEmptyOptNP (BlockForging m) (CardanoEras c)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse ShelleyLeaderCredentials c
-> m (NonEmptyOptNP (BlockForging m) (CardanoEras c))
blockForgingShelleyBased [ShelleyLeaderCredentials c]
credssShelleyBased
let blockForgings :: [NonEmptyOptNP (BlockForging m) (CardanoEras c)]
blockForgings :: [NonEmptyOptNP (BlockForging m) (CardanoEras c)]
blockForgings = case (Maybe (NonEmptyOptNP (BlockForging m) (CardanoEras c))
mBlockForgingByron, [NonEmptyOptNP (BlockForging m) (CardanoEras c)]
shelleyBased) of
(Maybe (NonEmptyOptNP (BlockForging m) (CardanoEras c))
Nothing, [NonEmptyOptNP (BlockForging m) (CardanoEras c)]
shelleys) -> [NonEmptyOptNP (BlockForging m) (CardanoEras c)]
shelleys
(Just NonEmptyOptNP (BlockForging m) (CardanoEras c)
byron, []) -> [NonEmptyOptNP (BlockForging m) (CardanoEras c)
byron]
(Just NonEmptyOptNP (BlockForging m) (CardanoEras c)
byron, NonEmptyOptNP (BlockForging m) (CardanoEras c)
shelley:[NonEmptyOptNP (BlockForging m) (CardanoEras c)]
shelleys) ->
(forall a.
These1 (BlockForging m) (BlockForging m) a -> BlockForging m a)
-> NonEmptyOptNP (BlockForging m) (CardanoEras c)
-> NonEmptyOptNP (BlockForging m) (CardanoEras c)
-> NonEmptyOptNP (BlockForging m) (CardanoEras c)
forall (f :: * -> *) (g :: * -> *) (h :: * -> *) (xs :: [*]).
(forall a. These1 f g a -> h a)
-> NonEmptyOptNP f xs -> NonEmptyOptNP g xs -> NonEmptyOptNP h xs
OptNP.zipWith These1 (BlockForging m) (BlockForging m) a -> BlockForging m a
forall a.
These1 (BlockForging m) (BlockForging m) a -> BlockForging m a
forall {f :: * -> *} {a}. These1 f f a -> f a
merge NonEmptyOptNP (BlockForging m) (CardanoEras c)
byron NonEmptyOptNP (BlockForging m) (CardanoEras c)
shelley NonEmptyOptNP (BlockForging m) (CardanoEras c)
-> [NonEmptyOptNP (BlockForging m) (CardanoEras c)]
-> [NonEmptyOptNP (BlockForging m) (CardanoEras c)]
forall a. a -> [a] -> [a]
: [NonEmptyOptNP (BlockForging m) (CardanoEras c)]
shelleys
where
merge :: These1 f f a -> f a
merge (These1 f a
_ f a
_) = [Char] -> f a
forall a. HasCallStack => [Char] -> a
error [Char]
"forgings of the same era"
merge (This1 f a
x) = f a
x
merge (That1 f a
y) = f a
y
[BlockForging m (CardanoBlock c)]
-> m [BlockForging m (CardanoBlock c)]
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return ([BlockForging m (CardanoBlock c)]
-> m [BlockForging m (CardanoBlock c)])
-> [BlockForging m (CardanoBlock c)]
-> m [BlockForging m (CardanoBlock c)]
forall a b. (a -> b) -> a -> b
$ Text
-> NonEmptyOptNP (BlockForging m) (CardanoEras c)
-> BlockForging m (CardanoBlock c)
forall (m :: * -> *) (xs :: [*]).
(CanHardFork xs, Monad m) =>
Text
-> NonEmptyOptNP (BlockForging m) xs
-> BlockForging m (HardForkBlock xs)
hardForkBlockForging Text
"Cardano" (NonEmptyOptNP (BlockForging m) (CardanoEras c)
-> BlockForging m (CardanoBlock c))
-> [NonEmptyOptNP (BlockForging m) (CardanoEras c)]
-> [BlockForging m (CardanoBlock c)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [NonEmptyOptNP (BlockForging m) (CardanoEras c)]
blockForgings
mBlockForgingByron :: Maybe (NonEmptyOptNP (BlockForging m) (CardanoEras c))
mBlockForgingByron :: Maybe (NonEmptyOptNP (BlockForging m) (CardanoEras c))
mBlockForgingByron = do
ByronLeaderCredentials
creds <- Maybe ByronLeaderCredentials
mCredsByron
NonEmptyOptNP (BlockForging m) (CardanoEras c)
-> Maybe (NonEmptyOptNP (BlockForging m) (CardanoEras c))
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (NonEmptyOptNP (BlockForging m) (CardanoEras c)
-> Maybe (NonEmptyOptNP (BlockForging m) (CardanoEras c)))
-> NonEmptyOptNP (BlockForging m) (CardanoEras c)
-> Maybe (NonEmptyOptNP (BlockForging m) (CardanoEras c))
forall a b. (a -> b) -> a -> b
$ ByronLeaderCredentials -> BlockForging m ByronBlock
forall (m :: * -> *).
Monad m =>
ByronLeaderCredentials -> BlockForging m ByronBlock
byronBlockForging ByronLeaderCredentials
creds BlockForging m ByronBlock
-> Index (CardanoEras c) ByronBlock
-> NonEmptyOptNP (BlockForging m) (CardanoEras c)
forall {k} (xs :: [k]) (f :: k -> *) (x :: k).
SListI xs =>
f x -> Index xs x -> NonEmptyOptNP f xs
`OptNP.at` Index (CardanoEras c) ByronBlock
forall {k} (x :: k) (xs1 :: [k]). Index (x : xs1) x
IZ
blockForgingShelleyBased ::
ShelleyLeaderCredentials c
-> m (NonEmptyOptNP (BlockForging m) (CardanoEras c))
blockForgingShelleyBased :: ShelleyLeaderCredentials c
-> m (NonEmptyOptNP (BlockForging m) (CardanoEras c))
blockForgingShelleyBased ShelleyLeaderCredentials c
credentials = do
let ShelleyLeaderCredentials
{ shelleyLeaderCredentialsInitSignKey :: forall c. ShelleyLeaderCredentials c -> SignKeyKES c
shelleyLeaderCredentialsInitSignKey = SignKeyKES c
initSignKey
, shelleyLeaderCredentialsCanBeLeader :: forall c. ShelleyLeaderCredentials c -> PraosCanBeLeader c
shelleyLeaderCredentialsCanBeLeader = PraosCanBeLeader c
canBeLeader
} = ShelleyLeaderCredentials c
credentials
HotKey c m
hotKey <- do
let maxKESEvo :: Word64
maxKESEvo :: Word64
maxKESEvo = Bool -> Word64 -> Word64
forall a. HasCallStack => Bool -> a -> a
assert (Word64
tpraosMaxKESEvo Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
== Word64
praosMaxKESEvo) Word64
praosMaxKESEvo
startPeriod :: Absolute.KESPeriod
startPeriod :: KESPeriod
startPeriod = OCert c -> KESPeriod
forall c. OCert c -> KESPeriod
Absolute.ocertKESPeriod (OCert c -> KESPeriod) -> OCert c -> KESPeriod
forall a b. (a -> b) -> a -> b
$ PraosCanBeLeader c -> OCert c
forall c. PraosCanBeLeader c -> OCert c
praosCanBeLeaderOpCert PraosCanBeLeader c
canBeLeader
forall (m :: * -> *) c.
(Crypto c, IOLike m) =>
SignKeyKES c -> KESPeriod -> Word64 -> m (HotKey c m)
HotKey.mkHotKey @m @c SignKeyKES c
initSignKey KESPeriod
startPeriod Word64
maxKESEvo
let slotToPeriod :: SlotNo -> Absolute.KESPeriod
slotToPeriod :: SlotNo -> KESPeriod
slotToPeriod (SlotNo Word64
slot) = Bool -> KESPeriod -> KESPeriod
forall a. HasCallStack => Bool -> a -> a
assert (Word64
tpraosSlotsPerKESPeriod Word64 -> Word64 -> Bool
forall a. Eq a => a -> a -> Bool
== Word64
praosSlotsPerKESPeriod) (KESPeriod -> KESPeriod) -> KESPeriod -> KESPeriod
forall a b. (a -> b) -> a -> b
$
Word -> KESPeriod
Absolute.KESPeriod (Word -> KESPeriod) -> Word -> KESPeriod
forall a b. (a -> b) -> a -> b
$ Word64 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Word) -> Word64 -> Word
forall a b. (a -> b) -> a -> b
$ Word64
slot Word64 -> Word64 -> Word64
forall a. Integral a => a -> a -> a
`div` Word64
praosSlotsPerKESPeriod
let tpraos :: forall era.
ShelleyEraWithCrypto c (TPraos c) era
=> BlockForging m (ShelleyBlock (TPraos c) era)
tpraos :: forall era.
ShelleyEraWithCrypto c (TPraos c) era =>
BlockForging m (ShelleyBlock (TPraos c) era)
tpraos =
HotKey c m
-> (SlotNo -> KESPeriod)
-> ShelleyLeaderCredentials c
-> BlockForging m (ShelleyBlock (TPraos c) era)
forall (m :: * -> *) c era.
(PraosCrypto c, ShelleyEraWithCrypto c (TPraos c) era, IOLike m) =>
HotKey c m
-> (SlotNo -> KESPeriod)
-> ShelleyLeaderCredentials c
-> BlockForging m (ShelleyBlock (TPraos c) era)
TPraos.shelleySharedBlockForging HotKey c m
hotKey SlotNo -> KESPeriod
slotToPeriod ShelleyLeaderCredentials c
credentials
let praos :: forall era.
ShelleyEraWithCrypto c (Praos c) era
=> BlockForging m (ShelleyBlock (Praos c) era)
praos :: forall era.
ShelleyEraWithCrypto c (Praos c) era =>
BlockForging m (ShelleyBlock (Praos c) era)
praos =
HotKey c m
-> (SlotNo -> KESPeriod)
-> ShelleyLeaderCredentials c
-> BlockForging m (ShelleyBlock (Praos c) era)
forall (m :: * -> *) c era.
(ShelleyEraWithCrypto c (Praos c) era, IOLike m) =>
HotKey c m
-> (SlotNo -> KESPeriod)
-> ShelleyLeaderCredentials c
-> BlockForging m (ShelleyBlock (Praos c) era)
Praos.praosSharedBlockForging HotKey c m
hotKey SlotNo -> KESPeriod
slotToPeriod ShelleyLeaderCredentials c
credentials
NonEmptyOptNP (BlockForging m) (CardanoEras c)
-> m (NonEmptyOptNP (BlockForging m) (CardanoEras c))
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(NonEmptyOptNP (BlockForging m) (CardanoEras c)
-> m (NonEmptyOptNP (BlockForging m) (CardanoEras c)))
-> NonEmptyOptNP (BlockForging m) (CardanoEras c)
-> m (NonEmptyOptNP (BlockForging m) (CardanoEras c))
forall a b. (a -> b) -> a -> b
$ OptNP 'False (BlockForging m) (CardanoShelleyEras c)
-> NonEmptyOptNP (BlockForging m) (CardanoEras c)
forall {k} (empty :: Bool) (f :: k -> *) (xs1 :: [k]) (x :: k).
OptNP empty f xs1 -> OptNP empty f (x : xs1)
OptSkip
(OptNP 'False (BlockForging m) (CardanoShelleyEras c)
-> NonEmptyOptNP (BlockForging m) (CardanoEras c))
-> OptNP 'False (BlockForging m) (CardanoShelleyEras c)
-> NonEmptyOptNP (BlockForging m) (CardanoEras c)
forall a b. (a -> b) -> a -> b
$ NP (BlockForging m) (CardanoShelleyEras c)
-> OptNP 'False (BlockForging m) (CardanoShelleyEras c)
forall {k} (f :: k -> *) (xs :: [k]).
IsNonEmpty xs =>
NP f xs -> NonEmptyOptNP f xs
OptNP.fromNonEmptyNP (NP (BlockForging m) (CardanoShelleyEras c)
-> OptNP 'False (BlockForging m) (CardanoShelleyEras c))
-> NP (BlockForging m) (CardanoShelleyEras c)
-> OptNP 'False (BlockForging m) (CardanoShelleyEras c)
forall a b. (a -> b) -> a -> b
$
BlockForging m (ShelleyBlock (TPraos c) (ShelleyEra c))
forall era.
ShelleyEraWithCrypto c (TPraos c) era =>
BlockForging m (ShelleyBlock (TPraos c) era)
tpraos BlockForging m (ShelleyBlock (TPraos c) (ShelleyEra c))
-> NP
(BlockForging m)
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP (BlockForging m) (CardanoShelleyEras c)
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:*
BlockForging m (ShelleyBlock (TPraos c) (AllegraEra c))
forall era.
ShelleyEraWithCrypto c (TPraos c) era =>
BlockForging m (ShelleyBlock (TPraos c) era)
tpraos BlockForging m (ShelleyBlock (TPraos c) (AllegraEra c))
-> NP
(BlockForging m)
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP
(BlockForging m)
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:*
BlockForging m (ShelleyBlock (TPraos c) (MaryEra c))
forall era.
ShelleyEraWithCrypto c (TPraos c) era =>
BlockForging m (ShelleyBlock (TPraos c) era)
tpraos BlockForging m (ShelleyBlock (TPraos c) (MaryEra c))
-> NP
(BlockForging m)
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP
(BlockForging m)
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:*
BlockForging m (ShelleyBlock (TPraos c) (AlonzoEra c))
forall era.
ShelleyEraWithCrypto c (TPraos c) era =>
BlockForging m (ShelleyBlock (TPraos c) era)
tpraos BlockForging m (ShelleyBlock (TPraos c) (AlonzoEra c))
-> NP
(BlockForging m)
'[ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP
(BlockForging m)
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:*
BlockForging m (ShelleyBlock (Praos c) (BabbageEra c))
forall era.
ShelleyEraWithCrypto c (Praos c) era =>
BlockForging m (ShelleyBlock (Praos c) era)
praos BlockForging m (ShelleyBlock (Praos c) (BabbageEra c))
-> NP (BlockForging m) '[ShelleyBlock (Praos c) (LatestKnownEra c)]
-> NP
(BlockForging m)
'[ShelleyBlock (Praos c) (BabbageEra c),
ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:*
BlockForging m (ShelleyBlock (Praos c) (LatestKnownEra c))
forall era.
ShelleyEraWithCrypto c (Praos c) era =>
BlockForging m (ShelleyBlock (Praos c) era)
praos BlockForging m (ShelleyBlock (Praos c) (LatestKnownEra c))
-> NP (BlockForging m) '[]
-> NP (BlockForging m) '[ShelleyBlock (Praos c) (LatestKnownEra c)]
forall {k} (f :: k -> *) (x :: k) (xs1 :: [k]).
f x -> NP f xs1 -> NP f (x : xs1)
:*
NP (BlockForging m) '[]
forall {k} (f :: k -> *). NP f '[]
Nil
protocolClientInfoCardano ::
forall c.
EpochSlots
-> ProtocolClientInfo (CardanoBlock c)
protocolClientInfoCardano :: forall c. EpochSlots -> ProtocolClientInfo (CardanoBlock c)
protocolClientInfoCardano EpochSlots
epochSlots = ProtocolClientInfo {
pClientInfoCodecConfig :: CodecConfig (CardanoBlock c)
pClientInfoCodecConfig =
CodecConfig ByronBlock
-> CodecConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> CodecConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> CodecConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> CodecConfig (CardanoBlock c)
forall c.
CodecConfig ByronBlock
-> CodecConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> CodecConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> CodecConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> CardanoCodecConfig c
CardanoCodecConfig
(ProtocolClientInfo ByronBlock -> CodecConfig ByronBlock
forall b. ProtocolClientInfo b -> CodecConfig b
pClientInfoCodecConfig (EpochSlots -> ProtocolClientInfo ByronBlock
protocolClientInfoByron EpochSlots
epochSlots))
(ProtocolClientInfo (ShelleyBlock (TPraos c) (ShelleyEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
forall b. ProtocolClientInfo b -> CodecConfig b
pClientInfoCodecConfig ProtocolClientInfo (ShelleyBlock (TPraos c) (ShelleyEra c))
forall proto era. ProtocolClientInfo (ShelleyBlock proto era)
protocolClientInfoShelley)
(ProtocolClientInfo (ShelleyBlock (TPraos c) (AllegraEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (AllegraEra c))
forall b. ProtocolClientInfo b -> CodecConfig b
pClientInfoCodecConfig ProtocolClientInfo (ShelleyBlock (TPraos c) (AllegraEra c))
forall proto era. ProtocolClientInfo (ShelleyBlock proto era)
protocolClientInfoShelley)
(ProtocolClientInfo (ShelleyBlock (TPraos c) (MaryEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (MaryEra c))
forall b. ProtocolClientInfo b -> CodecConfig b
pClientInfoCodecConfig ProtocolClientInfo (ShelleyBlock (TPraos c) (MaryEra c))
forall proto era. ProtocolClientInfo (ShelleyBlock proto era)
protocolClientInfoShelley)
(ProtocolClientInfo (ShelleyBlock (TPraos c) (AlonzoEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
forall b. ProtocolClientInfo b -> CodecConfig b
pClientInfoCodecConfig ProtocolClientInfo (ShelleyBlock (TPraos c) (AlonzoEra c))
forall proto era. ProtocolClientInfo (ShelleyBlock proto era)
protocolClientInfoShelley)
(ProtocolClientInfo (ShelleyBlock (Praos c) (BabbageEra c))
-> CodecConfig (ShelleyBlock (Praos c) (BabbageEra c))
forall b. ProtocolClientInfo b -> CodecConfig b
pClientInfoCodecConfig ProtocolClientInfo (ShelleyBlock (Praos c) (BabbageEra c))
forall proto era. ProtocolClientInfo (ShelleyBlock proto era)
protocolClientInfoShelley)
(ProtocolClientInfo (ShelleyBlock (Praos c) (ConwayEra c))
-> CodecConfig (ShelleyBlock (Praos c) (ConwayEra c))
forall b. ProtocolClientInfo b -> CodecConfig b
pClientInfoCodecConfig ProtocolClientInfo (ShelleyBlock (Praos c) (ConwayEra c))
forall proto era. ProtocolClientInfo (ShelleyBlock proto era)
protocolClientInfoShelley)
}
mkPartialLedgerConfigShelley ::
L.EraTransition era
=> L.TransitionConfig era
-> TriggerHardFork
-> PartialLedgerConfig (ShelleyBlock proto era)
mkPartialLedgerConfigShelley :: forall era proto.
EraTransition era =>
TransitionConfig era
-> TriggerHardFork -> PartialLedgerConfig (ShelleyBlock proto era)
mkPartialLedgerConfigShelley TransitionConfig era
transitionConfig TriggerHardFork
shelleyTriggerHardFork =
ShelleyPartialLedgerConfig {
shelleyLedgerConfig :: ShelleyLedgerConfig era
shelleyLedgerConfig =
ShelleyGenesis (EraCrypto era)
-> TranslationContext era
-> EpochInfo (Except PastHorizonException)
-> ShelleyLedgerConfig era
forall era.
ShelleyGenesis (EraCrypto era)
-> TranslationContext era
-> EpochInfo (Except PastHorizonException)
-> ShelleyLedgerConfig era
Shelley.mkShelleyLedgerConfig
(TransitionConfig era
transitionConfig TransitionConfig era
-> Getting
(ShelleyGenesis (EraCrypto era))
(TransitionConfig era)
(ShelleyGenesis (EraCrypto era))
-> ShelleyGenesis (EraCrypto era)
forall s a. s -> Getting a s a -> a
^. Getting
(ShelleyGenesis (EraCrypto era))
(TransitionConfig era)
(ShelleyGenesis (EraCrypto era))
forall era.
EraTransition era =>
Lens' (TransitionConfig era) (ShelleyGenesis (EraCrypto era))
Lens' (TransitionConfig era) (ShelleyGenesis (EraCrypto era))
L.tcShelleyGenesisL)
(TransitionConfig era
transitionConfig TransitionConfig era
-> Getting
(TranslationContext era)
(TransitionConfig era)
(TranslationContext era)
-> TranslationContext era
forall s a. s -> Getting a s a -> a
^. Getting
(TranslationContext era)
(TransitionConfig era)
(TranslationContext era)
forall era.
EraTransition era =>
Lens' (TransitionConfig era) (TranslationContext era)
Lens' (TransitionConfig era) (TranslationContext era)
L.tcTranslationContextL)
EpochInfo (Except PastHorizonException)
History.dummyEpochInfo
, shelleyTriggerHardFork :: TriggerHardFork
shelleyTriggerHardFork = TriggerHardFork
shelleyTriggerHardFork
}
newtype WrapTransitionConfig blk =
WrapTransitionConfig (L.TransitionConfig (ShelleyBlockLedgerEra blk))