{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE EmptyCase #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}

{-# OPTIONS_GHC -Wno-orphans #-}

module Ouroboros.Consensus.Cardano.CanHardFork (
    ByronPartialLedgerConfig (..)
  , CardanoHardForkConstraints
  , TriggerHardFork (..)
    -- * Re-exports of Shelley code
  , ShelleyPartialLedgerConfig (..)
  , crossEraForecastAcrossShelley
  , translateChainDepStateAcrossShelley
  ) where

import qualified Cardano.Chain.Common as CC
import qualified Cardano.Chain.Genesis as CC.Genesis
import qualified Cardano.Chain.Update as CC.Update
import           Cardano.Crypto.DSIGN (Ed25519DSIGN)
import           Cardano.Crypto.Hash.Blake2b (Blake2b_224, Blake2b_256)
import           Cardano.Ledger.Crypto (ADDRHASH, Crypto, DSIGN, HASH)
import qualified Cardano.Ledger.Era as SL
import qualified Cardano.Ledger.Genesis as SL
import           Cardano.Ledger.Hashes (EraIndependentTxBody)
import           Cardano.Ledger.Keys (DSignable, Hash)
import qualified Cardano.Ledger.Shelley.API as SL
import           Cardano.Ledger.Shelley.Translation
                     (toFromByronTranslationContext)
import qualified Cardano.Protocol.TPraos.API as SL
import qualified Cardano.Protocol.TPraos.Rules.Prtcl as SL
import qualified Cardano.Protocol.TPraos.Rules.Tickn as SL
import           Control.Monad
import           Control.Monad.Except (runExcept, throwError)
import           Data.Coerce (coerce)
import qualified Data.Map.Strict as Map
import           Data.Maybe (listToMaybe, mapMaybe)
import           Data.Proxy
import           Data.SOP.BasicFunctors
import           Data.SOP.InPairs (RequiringBoth (..), ignoringBoth)
import qualified Data.SOP.Strict as SOP
import           Data.SOP.Tails (Tails (..))
import qualified Data.SOP.Tails as Tails
import           Data.Word
import           GHC.Generics (Generic)
import           NoThunks.Class (NoThunks)
import           Ouroboros.Consensus.Block
import           Ouroboros.Consensus.Byron.Ledger
import qualified Ouroboros.Consensus.Byron.Ledger.Inspect as Byron.Inspect
import           Ouroboros.Consensus.Byron.Node ()
import           Ouroboros.Consensus.Cardano.Block
import           Ouroboros.Consensus.Forecast
import           Ouroboros.Consensus.HardFork.Combinator
import           Ouroboros.Consensus.HardFork.Combinator.State.Types
import           Ouroboros.Consensus.HardFork.History (Bound (boundSlot),
                     addSlots)
import           Ouroboros.Consensus.HardFork.Simple
import           Ouroboros.Consensus.Ledger.Abstract
import           Ouroboros.Consensus.Ledger.SupportsMempool (ByteSize32,
                     IgnoringOverflow, TxMeasure)
import           Ouroboros.Consensus.Ledger.SupportsProtocol
                     (LedgerSupportsProtocol)
import           Ouroboros.Consensus.Protocol.Abstract
import           Ouroboros.Consensus.Protocol.PBFT (PBft, PBftCrypto)
import           Ouroboros.Consensus.Protocol.PBFT.State (PBftState)
import qualified Ouroboros.Consensus.Protocol.PBFT.State as PBftState
import           Ouroboros.Consensus.Protocol.Praos (Praos)
import qualified Ouroboros.Consensus.Protocol.Praos as Praos
import           Ouroboros.Consensus.Protocol.TPraos
import qualified Ouroboros.Consensus.Protocol.TPraos as TPraos
import           Ouroboros.Consensus.Shelley.Ledger
import           Ouroboros.Consensus.Shelley.Node ()
import           Ouroboros.Consensus.Shelley.Protocol.Praos ()
import           Ouroboros.Consensus.Shelley.ShelleyHFC
import           Ouroboros.Consensus.TypeFamilyWrappers
import           Ouroboros.Consensus.Util (eitherToMaybe)
import           Ouroboros.Consensus.Util.RedundantConstraints

{-------------------------------------------------------------------------------
  Figure out the transition point for Byron

  The Byron ledger defines the update 'State' in
  "Cardano.Chain.Update.Validation.Interface". The critical piece of state we
  need is

  > candidateProtocolUpdates :: ![CandidateProtocolUpdate]

  which are the update proposals that have been voted on, accepted, and
  endorsed, and now need to become stable. In `tryBumpVersion`
  ("Cardano.Chain.Update.Validation.Interface.ProtocolVersionBump") we
  find the candidates that are at least 'kUpdateStabilityParam' (@== 4k@) deep,
  and then construct

  > State
  > { nextProtocolVersion    = cpuProtocolVersion
  > , nextProtocolParameters = cpuProtocolParameters
  > }

  (with 'State' from "Cardano.Chain.Update.Validation.Interface.ProtocolVersionBump")
  where 'cpuProtocolVersion'/'cpuProtocolParameters' are the version and
  parameters from the update. This then ends up in the following callstack

  > applyChainTick
  > |
  > \-- epochTransition
  >     |
  >     \-- registerEpoch
  >         |
  >         \-- tryBumpVersion

  Now, if this is changing the major version of the protocol, then this actually
  indicates the transition to Shelley, and the Byron 'applyChainTick' won't
  actually happen. Instead, in 'singleEraTransition' we will report the
  'EpochNo' of the transition as soon as it's @2k@ (not @4k@!) deep: in other
  words, as soon as it is stable; at this point, the HFC will do the rest.

  A slightly subtle point is that the Byron ledger does not record any
  information about /past/ updates to the protocol parameters, and so if we
  /were/ to ask the Byron ledger /after/ the update when the transition is
  going to take place (did take place), it will say 'Nothing': transition not
  yet known. In practice this won't matter, as it will have been translated to
  a Shelley ledger at that point.
-------------------------------------------------------------------------------}

byronTransition :: PartialLedgerConfig ByronBlock
                -> Word16   -- ^ Shelley major protocol version
                -> LedgerState ByronBlock
                -> Maybe EpochNo
byronTransition :: PartialLedgerConfig ByronBlock
-> Word16 -> LedgerState ByronBlock -> Maybe EpochNo
byronTransition ByronPartialLedgerConfig{TriggerHardFork
LedgerConfig ByronBlock
byronLedgerConfig :: LedgerConfig ByronBlock
byronTriggerHardFork :: TriggerHardFork
byronLedgerConfig :: ByronPartialLedgerConfig -> LedgerConfig ByronBlock
byronTriggerHardFork :: ByronPartialLedgerConfig -> TriggerHardFork
..} Word16
shelleyMajorVersion LedgerState ByronBlock
state =
      [EpochNo] -> Maybe EpochNo
forall a. [a] -> Maybe a
takeAny
    ([EpochNo] -> Maybe EpochNo)
-> (LedgerState ByronBlock -> [EpochNo])
-> LedgerState ByronBlock
-> Maybe EpochNo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ProtocolUpdate -> Maybe EpochNo) -> [ProtocolUpdate] -> [EpochNo]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe ProtocolUpdate -> Maybe EpochNo
isTransitionToShelley
    ([ProtocolUpdate] -> [EpochNo])
-> (LedgerState ByronBlock -> [ProtocolUpdate])
-> LedgerState ByronBlock
-> [EpochNo]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerConfig ByronBlock
-> LedgerState ByronBlock -> [ProtocolUpdate]
Byron.Inspect.protocolUpdates LedgerConfig ByronBlock
byronLedgerConfig
    (LedgerState ByronBlock -> Maybe EpochNo)
-> LedgerState ByronBlock -> Maybe EpochNo
forall a b. (a -> b) -> a -> b
$ LedgerState ByronBlock
state
  where
    ByronTransitionInfo Map ProtocolVersion BlockNo
transitionInfo = LedgerState ByronBlock -> ByronTransition
byronLedgerTransition LedgerState ByronBlock
state

    genesis :: LedgerConfig ByronBlock
genesis = LedgerConfig ByronBlock
byronLedgerConfig
    k :: BlockCount
k       = GenesisData -> BlockCount
CC.Genesis.gdK (GenesisData -> BlockCount) -> GenesisData -> BlockCount
forall a b. (a -> b) -> a -> b
$ Config -> GenesisData
CC.Genesis.configGenesisData Config
LedgerConfig ByronBlock
genesis

    isTransitionToShelley :: Byron.Inspect.ProtocolUpdate -> Maybe EpochNo
    isTransitionToShelley :: ProtocolUpdate -> Maybe EpochNo
isTransitionToShelley ProtocolUpdate
update = do
        Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> Bool -> Maybe ()
forall a b. (a -> b) -> a -> b
$ ProtocolVersion -> Word16
CC.Update.pvMajor ProtocolVersion
version Word16 -> Word16 -> Bool
forall a. Eq a => a -> a -> Bool
== Word16
shelleyMajorVersion
        case ProtocolUpdate -> UpdateState
Byron.Inspect.protocolUpdateState ProtocolUpdate
update of
          Byron.Inspect.UpdateCandidate SlotNo
_becameCandidateSlotNo EpochNo
adoptedIn -> do
            BlockNo
becameCandidateBlockNo <- ProtocolVersion -> Map ProtocolVersion BlockNo -> Maybe BlockNo
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup ProtocolVersion
version Map ProtocolVersion BlockNo
transitionInfo
            Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> Bool -> Maybe ()
forall a b. (a -> b) -> a -> b
$ BlockNo -> Bool
isReallyStable BlockNo
becameCandidateBlockNo
            EpochNo -> Maybe EpochNo
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return EpochNo
adoptedIn
          Byron.Inspect.UpdateStableCandidate EpochNo
adoptedIn ->
            -- If the Byron ledger thinks it's stable, it's _definitely_ stable
            EpochNo -> Maybe EpochNo
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return EpochNo
adoptedIn
          UpdateState
_otherwise ->
            -- The proposal isn't yet a candidate, never mind a stable one
            Maybe EpochNo
forall a. Maybe a
forall (m :: * -> *) a. MonadPlus m => m a
mzero
      where
        version :: CC.Update.ProtocolVersion
        version :: ProtocolVersion
version = ProtocolUpdate -> ProtocolVersion
Byron.Inspect.protocolUpdateVersion ProtocolUpdate
update

    -- Normally, stability in the ledger is defined in terms of slots, not
    -- blocks. Byron considers the proposal to be stable after the slot is more
    -- than @2k@ old. That is not wrong: after @2k@, the block indeed is stable.
    --
    -- Unfortunately, this means that the /conclusion about stability itself/
    -- is /not/ stable: if we were to switch to a denser fork, we might change
    -- our mind (on the sparse chain we thought the block was already stable,
    -- but on the dense chain we conclude it is it not yet stable).
    --
    -- It is unclear at the moment if this presents a problem; the HFC assumes
    -- monotonicity of timing info, in the sense that that any slot/time
    -- conversions are either unknown or else not subject to rollback.
    -- The problem sketched above might mean that we can go from "conversion
    -- known" to "conversion unknown", but then when we go back again to
    -- "conversion known", we /are/ guaranteed that we'd get the same answer.
    --
    -- Rather than trying to analyse this subtle problem, we instead base
    -- stability on block numbers; after the block is `k` deep, we know for sure
    -- that it is stable, and moreover, no matter which chain we switch to, that
    -- will remain to be the case.
    --
    -- The Byron 'UpdateState' records the 'SlotNo' of the block in which the
    -- proposal became a candidate (i.e., when the last required endorsement
    -- came in). That doesn't tell us very much, we need to know the block
    -- number; that's precisely what the 'ByronTransition' part of the Byron
    -- state tells us.
    isReallyStable :: BlockNo -> Bool
    isReallyStable :: BlockNo -> Bool
isReallyStable (BlockNo Word64
bno) = Word64
distance Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
>= BlockCount -> Word64
CC.unBlockCount BlockCount
k
      where
        distance :: Word64
        distance :: Word64
distance = case LedgerState ByronBlock -> WithOrigin BlockNo
byronLedgerTipBlockNo LedgerState ByronBlock
state of
                     WithOrigin BlockNo
Origin                  -> Word64
bno Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
1
                     NotOrigin (BlockNo Word64
tip) -> Word64
tip Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
- Word64
bno

    -- We only expect a single proposal that updates to Shelley, but in case
    -- there are multiple, any one will do
    takeAny :: [a] -> Maybe a
    takeAny :: forall a. [a] -> Maybe a
takeAny = [a] -> Maybe a
forall a. [a] -> Maybe a
listToMaybe

{-------------------------------------------------------------------------------
  SingleEraBlock Byron
-------------------------------------------------------------------------------}

instance SingleEraBlock ByronBlock where
  singleEraTransition :: PartialLedgerConfig ByronBlock
-> EraParams -> Bound -> LedgerState ByronBlock -> Maybe EpochNo
singleEraTransition PartialLedgerConfig ByronBlock
pcfg EraParams
_eraParams Bound
_eraStart LedgerState ByronBlock
ledgerState =
      case ByronPartialLedgerConfig -> TriggerHardFork
byronTriggerHardFork PartialLedgerConfig ByronBlock
ByronPartialLedgerConfig
pcfg of
        TriggerHardFork
TriggerHardForkNotDuringThisExecution        -> Maybe EpochNo
forall a. Maybe a
Nothing
        TriggerHardForkAtEpoch   EpochNo
epoch               -> EpochNo -> Maybe EpochNo
forall a. a -> Maybe a
Just EpochNo
epoch
        TriggerHardForkAtVersion Word16
shelleyMajorVersion ->
            PartialLedgerConfig ByronBlock
-> Word16 -> LedgerState ByronBlock -> Maybe EpochNo
byronTransition
              PartialLedgerConfig ByronBlock
pcfg
              Word16
shelleyMajorVersion
              LedgerState ByronBlock
ledgerState

  singleEraInfo :: forall (proxy :: * -> *).
proxy ByronBlock -> SingleEraInfo ByronBlock
singleEraInfo proxy ByronBlock
_ = SingleEraInfo {
      singleEraName :: Text
singleEraName = Text
"Byron"
    }

instance PBftCrypto bc => HasPartialConsensusConfig (PBft bc)
  -- Use defaults

-- | When Byron is part of the hard-fork combinator, we use the partial ledger
-- config. Standalone Byron uses the regular ledger config. This means that
-- the partial ledger config is the perfect place to store the trigger
-- condition for the hard fork to Shelley, as we don't have to modify the
-- ledger config for standalone Byron.
data ByronPartialLedgerConfig = ByronPartialLedgerConfig {
      ByronPartialLedgerConfig -> LedgerConfig ByronBlock
byronLedgerConfig    :: !(LedgerConfig ByronBlock)
    , ByronPartialLedgerConfig -> TriggerHardFork
byronTriggerHardFork :: !TriggerHardFork
    }
  deriving ((forall x.
 ByronPartialLedgerConfig -> Rep ByronPartialLedgerConfig x)
-> (forall x.
    Rep ByronPartialLedgerConfig x -> ByronPartialLedgerConfig)
-> Generic ByronPartialLedgerConfig
forall x.
Rep ByronPartialLedgerConfig x -> ByronPartialLedgerConfig
forall x.
ByronPartialLedgerConfig -> Rep ByronPartialLedgerConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
ByronPartialLedgerConfig -> Rep ByronPartialLedgerConfig x
from :: forall x.
ByronPartialLedgerConfig -> Rep ByronPartialLedgerConfig x
$cto :: forall x.
Rep ByronPartialLedgerConfig x -> ByronPartialLedgerConfig
to :: forall x.
Rep ByronPartialLedgerConfig x -> ByronPartialLedgerConfig
Generic, Context -> ByronPartialLedgerConfig -> IO (Maybe ThunkInfo)
Proxy ByronPartialLedgerConfig -> String
(Context -> ByronPartialLedgerConfig -> IO (Maybe ThunkInfo))
-> (Context -> ByronPartialLedgerConfig -> IO (Maybe ThunkInfo))
-> (Proxy ByronPartialLedgerConfig -> String)
-> NoThunks ByronPartialLedgerConfig
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: Context -> ByronPartialLedgerConfig -> IO (Maybe ThunkInfo)
noThunks :: Context -> ByronPartialLedgerConfig -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> ByronPartialLedgerConfig -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> ByronPartialLedgerConfig -> IO (Maybe ThunkInfo)
$cshowTypeOf :: Proxy ByronPartialLedgerConfig -> String
showTypeOf :: Proxy ByronPartialLedgerConfig -> String
NoThunks)

instance HasPartialLedgerConfig ByronBlock where

  type PartialLedgerConfig ByronBlock = ByronPartialLedgerConfig

  completeLedgerConfig :: forall (proxy :: * -> *).
proxy ByronBlock
-> EpochInfo (Except PastHorizonException)
-> PartialLedgerConfig ByronBlock
-> LedgerConfig ByronBlock
completeLedgerConfig proxy ByronBlock
_ EpochInfo (Except PastHorizonException)
_ = PartialLedgerConfig ByronBlock -> LedgerConfig ByronBlock
ByronPartialLedgerConfig -> LedgerConfig ByronBlock
byronLedgerConfig

{-------------------------------------------------------------------------------
  CanHardFork
-------------------------------------------------------------------------------}

type CardanoHardForkConstraints c =
  ( TPraos.PraosCrypto c
  , Praos.PraosCrypto c
  , TranslateProto (TPraos c) (Praos c)
  , ShelleyCompatible (TPraos c) (ShelleyEra c)
  , LedgerSupportsProtocol (ShelleyBlock (TPraos c) (ShelleyEra c))
  , ShelleyCompatible (TPraos c) (AllegraEra c)
  , LedgerSupportsProtocol (ShelleyBlock (TPraos c) (AllegraEra c))
  , ShelleyCompatible (TPraos c) (MaryEra    c)
  , LedgerSupportsProtocol (ShelleyBlock (TPraos c) (MaryEra c))
  , ShelleyCompatible (TPraos c) (AlonzoEra  c)
  , LedgerSupportsProtocol (ShelleyBlock (TPraos c) (AlonzoEra c))
  , ShelleyCompatible (Praos c) (BabbageEra  c)
  , LedgerSupportsProtocol (ShelleyBlock (Praos c) (BabbageEra c))
  , ShelleyCompatible (Praos c) (ConwayEra  c)
  , LedgerSupportsProtocol (ShelleyBlock (Praos c) (ConwayEra c))
    -- These equalities allow the transition from Byron to Shelley, since
    -- @cardano-ledger-shelley@ requires Ed25519 for Byron bootstrap addresses and
    -- the current Byron-to-Shelley translation requires a 224-bit hash for
    -- address and a 256-bit hash for header hashes.
  , HASH     c ~ Blake2b_256
  , ADDRHASH c ~ Blake2b_224
  , DSIGN    c ~ Ed25519DSIGN
  )

instance CardanoHardForkConstraints c => CanHardFork (CardanoEras c) where
  type HardForkTxMeasure (CardanoEras c) = ConwayMeasure

  hardForkEraTranslation :: EraTranslation (CardanoEras c)
hardForkEraTranslation = EraTranslation {
      translateLedgerState :: InPairs
  (RequiringBoth WrapLedgerConfig (Translate LedgerState))
  (CardanoEras c)
translateLedgerState   =
          RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  ByronBlock
  (ShelleyBlock (TPraos c) (ShelleyEra c))
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     '[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)]
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     (CardanoEras c)
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  ByronBlock
  (ShelleyBlock (TPraos c) (ShelleyEra c))
forall c.
(ShelleyCompatible (TPraos c) (ShelleyEra c), HASH c ~ Blake2b_256,
 ADDRHASH c ~ Blake2b_224) =>
RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  ByronBlock
  (ShelleyBlock (TPraos c) (ShelleyEra c))
translateLedgerStateByronToShelleyWrapper
        (InPairs
   (RequiringBoth WrapLedgerConfig (Translate LedgerState))
   '[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)]
 -> InPairs
      (RequiringBoth WrapLedgerConfig (Translate LedgerState))
      (CardanoEras c))
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     '[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)]
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     (CardanoEras c)
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  (ShelleyBlock (TPraos c) (ShelleyEra c))
  (ShelleyBlock (TPraos c) (AllegraEra c))
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     '[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)]
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     '[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)]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  (ShelleyBlock (TPraos c) (ShelleyEra c))
  (ShelleyBlock (TPraos c) (AllegraEra c))
forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  (ShelleyBlock (TPraos c) (ShelleyEra c))
  (ShelleyBlock (TPraos c) (AllegraEra c))
translateLedgerStateShelleyToAllegraWrapper
        (InPairs
   (RequiringBoth WrapLedgerConfig (Translate LedgerState))
   '[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)]
 -> InPairs
      (RequiringBoth WrapLedgerConfig (Translate LedgerState))
      '[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)])
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     '[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)]
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     '[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)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  (ShelleyBlock (TPraos c) (AllegraEra c))
  (ShelleyBlock (TPraos c) (MaryEra c))
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     '[ShelleyBlock (TPraos c) (MaryEra c),
       ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     '[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)]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  (ShelleyBlock (TPraos c) (AllegraEra c))
  (ShelleyBlock (TPraos c) (MaryEra c))
forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  (ShelleyBlock (TPraos c) (AllegraEra c))
  (ShelleyBlock (TPraos c) (MaryEra c))
translateLedgerStateAllegraToMaryWrapper
        (InPairs
   (RequiringBoth WrapLedgerConfig (Translate LedgerState))
   '[ShelleyBlock (TPraos c) (MaryEra c),
     ShelleyBlock (TPraos c) (AlonzoEra c),
     ShelleyBlock (Praos c) (BabbageEra c),
     ShelleyBlock (Praos c) (ConwayEra c)]
 -> InPairs
      (RequiringBoth WrapLedgerConfig (Translate LedgerState))
      '[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)])
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     '[ShelleyBlock (TPraos c) (MaryEra c),
       ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     '[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)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  (ShelleyBlock (TPraos c) (MaryEra c))
  (ShelleyBlock (TPraos c) (AlonzoEra c))
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     '[ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     '[ShelleyBlock (TPraos c) (MaryEra c),
       ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  (ShelleyBlock (TPraos c) (MaryEra c))
  (ShelleyBlock (TPraos c) (AlonzoEra c))
forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  (ShelleyBlock (TPraos c) (MaryEra c))
  (ShelleyBlock (TPraos c) (AlonzoEra c))
translateLedgerStateMaryToAlonzoWrapper
        (InPairs
   (RequiringBoth WrapLedgerConfig (Translate LedgerState))
   '[ShelleyBlock (TPraos c) (AlonzoEra c),
     ShelleyBlock (Praos c) (BabbageEra c),
     ShelleyBlock (Praos c) (ConwayEra c)]
 -> InPairs
      (RequiringBoth WrapLedgerConfig (Translate LedgerState))
      '[ShelleyBlock (TPraos c) (MaryEra c),
        ShelleyBlock (TPraos c) (AlonzoEra c),
        ShelleyBlock (Praos c) (BabbageEra c),
        ShelleyBlock (Praos c) (ConwayEra c)])
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     '[ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     '[ShelleyBlock (TPraos c) (MaryEra c),
       ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  (ShelleyBlock (TPraos c) (AlonzoEra c))
  (ShelleyBlock (Praos c) (BabbageEra c))
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     '[ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     '[ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  (ShelleyBlock (TPraos c) (AlonzoEra c))
  (ShelleyBlock (Praos c) (BabbageEra c))
forall c.
(PraosCrypto c, PraosCrypto c) =>
RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  (ShelleyBlock (TPraos c) (AlonzoEra c))
  (ShelleyBlock (Praos c) (BabbageEra c))
translateLedgerStateAlonzoToBabbageWrapper
        (InPairs
   (RequiringBoth WrapLedgerConfig (Translate LedgerState))
   '[ShelleyBlock (Praos c) (BabbageEra c),
     ShelleyBlock (Praos c) (ConwayEra c)]
 -> InPairs
      (RequiringBoth WrapLedgerConfig (Translate LedgerState))
      '[ShelleyBlock (TPraos c) (AlonzoEra c),
        ShelleyBlock (Praos c) (BabbageEra c),
        ShelleyBlock (Praos c) (ConwayEra c)])
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     '[ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     '[ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  (ShelleyBlock (Praos c) (BabbageEra c))
  (ShelleyBlock (Praos c) (ConwayEra c))
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     '[ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     '[ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  (ShelleyBlock (Praos c) (BabbageEra c))
  (ShelleyBlock (Praos c) (ConwayEra c))
forall c.
PraosCrypto c =>
RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  (ShelleyBlock (Praos c) (BabbageEra c))
  (ShelleyBlock (Praos c) (ConwayEra c))
translateLedgerStateBabbageToConwayWrapper
        (InPairs
   (RequiringBoth WrapLedgerConfig (Translate LedgerState))
   '[ShelleyBlock (Praos c) (ConwayEra c)]
 -> InPairs
      (RequiringBoth WrapLedgerConfig (Translate LedgerState))
      '[ShelleyBlock (Praos c) (BabbageEra c),
        ShelleyBlock (Praos c) (ConwayEra c)])
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     '[ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth WrapLedgerConfig (Translate LedgerState))
     '[ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall a b. (a -> b) -> a -> b
$ InPairs
  (RequiringBoth WrapLedgerConfig (Translate LedgerState))
  '[ShelleyBlock (Praos c) (ConwayEra c)]
forall {k} (f :: k -> k -> *) (x :: k). InPairs f '[x]
PNil
    , translateChainDepState :: InPairs
  (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
  (CardanoEras c)
translateChainDepState =
          RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  ByronBlock
  (ShelleyBlock (TPraos c) (ShelleyEra c))
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[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)]
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     (CardanoEras c)
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  ByronBlock
  (ShelleyBlock (TPraos c) (ShelleyEra c))
forall c.
RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  ByronBlock
  (ShelleyBlock (TPraos c) (ShelleyEra c))
translateChainDepStateByronToShelleyWrapper
        (InPairs
   (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
   '[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)]
 -> InPairs
      (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
      (CardanoEras c))
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[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)]
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     (CardanoEras c)
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  (ShelleyBlock (TPraos c) (ShelleyEra c))
  (ShelleyBlock (TPraos c) (AllegraEra c))
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[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)]
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[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)]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  (ShelleyBlock (TPraos c) (ShelleyEra c))
  (ShelleyBlock (TPraos c) (AllegraEra c))
forall eraFrom eraTo protoFrom protoTo.
TranslateProto protoFrom protoTo =>
RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  (ShelleyBlock protoFrom eraFrom)
  (ShelleyBlock protoTo eraTo)
translateChainDepStateAcrossShelley
        (InPairs
   (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
   '[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)]
 -> InPairs
      (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
      '[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)])
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[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)]
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[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)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  (ShelleyBlock (TPraos c) (AllegraEra c))
  (ShelleyBlock (TPraos c) (MaryEra c))
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) (MaryEra c),
       ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[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)]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  (ShelleyBlock (TPraos c) (AllegraEra c))
  (ShelleyBlock (TPraos c) (MaryEra c))
forall eraFrom eraTo protoFrom protoTo.
TranslateProto protoFrom protoTo =>
RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  (ShelleyBlock protoFrom eraFrom)
  (ShelleyBlock protoTo eraTo)
translateChainDepStateAcrossShelley
        (InPairs
   (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
   '[ShelleyBlock (TPraos c) (MaryEra c),
     ShelleyBlock (TPraos c) (AlonzoEra c),
     ShelleyBlock (Praos c) (BabbageEra c),
     ShelleyBlock (Praos c) (ConwayEra c)]
 -> InPairs
      (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
      '[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)])
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) (MaryEra c),
       ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[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)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  (ShelleyBlock (TPraos c) (MaryEra c))
  (ShelleyBlock (TPraos c) (AlonzoEra c))
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) (MaryEra c),
       ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  (ShelleyBlock (TPraos c) (MaryEra c))
  (ShelleyBlock (TPraos c) (AlonzoEra c))
forall eraFrom eraTo protoFrom protoTo.
TranslateProto protoFrom protoTo =>
RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  (ShelleyBlock protoFrom eraFrom)
  (ShelleyBlock protoTo eraTo)
translateChainDepStateAcrossShelley
        (InPairs
   (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
   '[ShelleyBlock (TPraos c) (AlonzoEra c),
     ShelleyBlock (Praos c) (BabbageEra c),
     ShelleyBlock (Praos c) (ConwayEra c)]
 -> InPairs
      (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
      '[ShelleyBlock (TPraos c) (MaryEra c),
        ShelleyBlock (TPraos c) (AlonzoEra c),
        ShelleyBlock (Praos c) (BabbageEra c),
        ShelleyBlock (Praos c) (ConwayEra c)])
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) (MaryEra c),
       ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  (ShelleyBlock (TPraos c) (AlonzoEra c))
  (ShelleyBlock (Praos c) (BabbageEra c))
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  (ShelleyBlock (TPraos c) (AlonzoEra c))
  (ShelleyBlock (Praos c) (BabbageEra c))
forall eraFrom eraTo protoFrom protoTo.
TranslateProto protoFrom protoTo =>
RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  (ShelleyBlock protoFrom eraFrom)
  (ShelleyBlock protoTo eraTo)
translateChainDepStateAcrossShelley
        (InPairs
   (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
   '[ShelleyBlock (Praos c) (BabbageEra c),
     ShelleyBlock (Praos c) (ConwayEra c)]
 -> InPairs
      (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
      '[ShelleyBlock (TPraos c) (AlonzoEra c),
        ShelleyBlock (Praos c) (BabbageEra c),
        ShelleyBlock (Praos c) (ConwayEra c)])
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  (ShelleyBlock (Praos c) (BabbageEra c))
  (ShelleyBlock (Praos c) (ConwayEra c))
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  (ShelleyBlock (Praos c) (BabbageEra c))
  (ShelleyBlock (Praos c) (ConwayEra c))
forall eraFrom eraTo protoFrom protoTo.
TranslateProto protoFrom protoTo =>
RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  (ShelleyBlock protoFrom eraFrom)
  (ShelleyBlock protoTo eraTo)
translateChainDepStateAcrossShelley
        (InPairs
   (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
   '[ShelleyBlock (Praos c) (ConwayEra c)]
 -> InPairs
      (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
      '[ShelleyBlock (Praos c) (BabbageEra c),
        ShelleyBlock (Praos c) (ConwayEra c)])
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall a b. (a -> b) -> a -> b
$ InPairs
  (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
  '[ShelleyBlock (Praos c) (ConwayEra c)]
forall {k} (f :: k -> k -> *) (x :: k). InPairs f '[x]
PNil
    , crossEraForecast :: InPairs
  (RequiringBoth
     WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
  (CardanoEras c)
crossEraForecast       =
          RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  ByronBlock
  (ShelleyBlock (TPraos c) (ShelleyEra c))
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[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)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     (CardanoEras c)
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  ByronBlock
  (ShelleyBlock (TPraos c) (ShelleyEra c))
forall c.
Crypto c =>
RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  ByronBlock
  (ShelleyBlock (TPraos c) (ShelleyEra c))
crossEraForecastByronToShelleyWrapper
        (InPairs
   (RequiringBoth
      WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
   '[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)]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
      (CardanoEras c))
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[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)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     (CardanoEras c)
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  (ShelleyBlock (TPraos c) (ShelleyEra c))
  (ShelleyBlock (TPraos c) (AllegraEra c))
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[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)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[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)]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  (ShelleyBlock (TPraos c) (ShelleyEra c))
  (ShelleyBlock (TPraos c) (AllegraEra c))
forall eraFrom eraTo protoFrom protoTo.
(TranslateProto protoFrom protoTo,
 LedgerSupportsProtocol (ShelleyBlock protoFrom eraFrom)) =>
RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  (ShelleyBlock protoFrom eraFrom)
  (ShelleyBlock protoTo eraTo)
crossEraForecastAcrossShelley
        (InPairs
   (RequiringBoth
      WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
   '[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)]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
      '[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)])
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[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)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[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)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  (ShelleyBlock (TPraos c) (AllegraEra c))
  (ShelleyBlock (TPraos c) (MaryEra c))
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) (MaryEra c),
       ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[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)]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  (ShelleyBlock (TPraos c) (AllegraEra c))
  (ShelleyBlock (TPraos c) (MaryEra c))
forall eraFrom eraTo protoFrom protoTo.
(TranslateProto protoFrom protoTo,
 LedgerSupportsProtocol (ShelleyBlock protoFrom eraFrom)) =>
RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  (ShelleyBlock protoFrom eraFrom)
  (ShelleyBlock protoTo eraTo)
crossEraForecastAcrossShelley
        (InPairs
   (RequiringBoth
      WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
   '[ShelleyBlock (TPraos c) (MaryEra c),
     ShelleyBlock (TPraos c) (AlonzoEra c),
     ShelleyBlock (Praos c) (BabbageEra c),
     ShelleyBlock (Praos c) (ConwayEra c)]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
      '[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)])
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) (MaryEra c),
       ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[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)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  (ShelleyBlock (TPraos c) (MaryEra c))
  (ShelleyBlock (TPraos c) (AlonzoEra c))
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) (MaryEra c),
       ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  (ShelleyBlock (TPraos c) (MaryEra c))
  (ShelleyBlock (TPraos c) (AlonzoEra c))
forall eraFrom eraTo protoFrom protoTo.
(TranslateProto protoFrom protoTo,
 LedgerSupportsProtocol (ShelleyBlock protoFrom eraFrom)) =>
RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  (ShelleyBlock protoFrom eraFrom)
  (ShelleyBlock protoTo eraTo)
crossEraForecastAcrossShelley
        (InPairs
   (RequiringBoth
      WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
   '[ShelleyBlock (TPraos c) (AlonzoEra c),
     ShelleyBlock (Praos c) (BabbageEra c),
     ShelleyBlock (Praos c) (ConwayEra c)]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
      '[ShelleyBlock (TPraos c) (MaryEra c),
        ShelleyBlock (TPraos c) (AlonzoEra c),
        ShelleyBlock (Praos c) (BabbageEra c),
        ShelleyBlock (Praos c) (ConwayEra c)])
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) (MaryEra c),
       ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  (ShelleyBlock (TPraos c) (AlonzoEra c))
  (ShelleyBlock (Praos c) (BabbageEra c))
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  (ShelleyBlock (TPraos c) (AlonzoEra c))
  (ShelleyBlock (Praos c) (BabbageEra c))
forall eraFrom eraTo protoFrom protoTo.
(TranslateProto protoFrom protoTo,
 LedgerSupportsProtocol (ShelleyBlock protoFrom eraFrom)) =>
RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  (ShelleyBlock protoFrom eraFrom)
  (ShelleyBlock protoTo eraTo)
crossEraForecastAcrossShelley
        (InPairs
   (RequiringBoth
      WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
   '[ShelleyBlock (Praos c) (BabbageEra c),
     ShelleyBlock (Praos c) (ConwayEra c)]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
      '[ShelleyBlock (TPraos c) (AlonzoEra c),
        ShelleyBlock (Praos c) (BabbageEra c),
        ShelleyBlock (Praos c) (ConwayEra c)])
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  (ShelleyBlock (Praos c) (BabbageEra c))
  (ShelleyBlock (Praos c) (ConwayEra c))
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  (ShelleyBlock (Praos c) (BabbageEra c))
  (ShelleyBlock (Praos c) (ConwayEra c))
forall eraFrom eraTo protoFrom protoTo.
(TranslateProto protoFrom protoTo,
 LedgerSupportsProtocol (ShelleyBlock protoFrom eraFrom)) =>
RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  (ShelleyBlock protoFrom eraFrom)
  (ShelleyBlock protoTo eraTo)
crossEraForecastAcrossShelley
        (InPairs
   (RequiringBoth
      WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
   '[ShelleyBlock (Praos c) (ConwayEra c)]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
      '[ShelleyBlock (Praos c) (BabbageEra c),
        ShelleyBlock (Praos c) (ConwayEra c)])
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall a b. (a -> b) -> a -> b
$ InPairs
  (RequiringBoth
     WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
  '[ShelleyBlock (Praos c) (ConwayEra c)]
forall {k} (f :: k -> k -> *) (x :: k). InPairs f '[x]
PNil
    }
  hardForkChainSel :: Tails AcrossEraSelection (CardanoEras c)
hardForkChainSel =
        -- Byron <-> Shelley, ...
        NP
  (AcrossEraSelection ByronBlock)
  '[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)]
-> Tails
     AcrossEraSelection
     '[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)]
-> Tails AcrossEraSelection (CardanoEras c)
forall {k} (f :: k -> k -> *) (x :: k) (xs1 :: [k]).
NP (f x) xs1 -> Tails f xs1 -> Tails f (x : xs1)
TCons ((forall a. AcrossEraSelection ByronBlock a)
-> NP
     (AcrossEraSelection ByronBlock)
     '[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)]
forall (xs :: [*]) (f :: * -> *).
SListIN NP xs =>
(forall a. f a) -> NP f xs
forall k l (h :: (k -> *) -> l -> *) (xs :: l) (f :: k -> *).
(HPure h, SListIN h xs) =>
(forall (a :: k). f a) -> h f xs
SOP.hpure AcrossEraSelection ByronBlock a
forall a. AcrossEraSelection ByronBlock a
forall a b. AcrossEraSelection a b
CompareBlockNo)
        -- Inter-Shelley-based
      (Tails
   AcrossEraSelection
   '[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)]
 -> Tails AcrossEraSelection (CardanoEras c))
-> Tails
     AcrossEraSelection
     '[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)]
-> Tails AcrossEraSelection (CardanoEras c)
forall a b. (a -> b) -> a -> b
$ Proxy (HasPraosSelectView c)
-> (forall x y.
    (HasPraosSelectView c x, HasPraosSelectView c y) =>
    AcrossEraSelection x y)
-> Tails
     AcrossEraSelection
     '[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)]
forall {k} (proxy :: (k -> Constraint) -> *) (f :: k -> k -> *)
       (c :: k -> Constraint) (xs :: [k]).
All c xs =>
proxy c
-> (forall (x :: k) (y :: k). (c x, c y) => f x y) -> Tails f xs
Tails.hcpure (forall {k} (t :: k). Proxy t
forall (t :: * -> Constraint). Proxy t
Proxy @(HasPraosSelectView c)) AcrossEraSelection x y
forall a b.
(SelectView (BlockProtocol a) ~ SelectView (BlockProtocol b)) =>
AcrossEraSelection a b
forall x y.
(HasPraosSelectView c x, HasPraosSelectView c y) =>
AcrossEraSelection x y
CompareSameSelectView
  hardForkInjectTxs :: InPairs
  (RequiringBoth
     WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
  (CardanoEras c)
hardForkInjectTxs =
        RequiringBoth
  WrapLedgerConfig
  (Product2 InjectTx InjectValidatedTx)
  ByronBlock
  (ShelleyBlock (TPraos c) (ShelleyEra c))
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[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)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     (CardanoEras c)
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons (Product2
  InjectTx
  InjectValidatedTx
  ByronBlock
  (ShelleyBlock (TPraos c) (ShelleyEra c))
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     ByronBlock
     (ShelleyBlock (TPraos c) (ShelleyEra c))
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (h :: k -> *).
f x y -> RequiringBoth h f x y
ignoringBoth (Product2
   InjectTx
   InjectValidatedTx
   ByronBlock
   (ShelleyBlock (TPraos c) (ShelleyEra c))
 -> RequiringBoth
      WrapLedgerConfig
      (Product2 InjectTx InjectValidatedTx)
      ByronBlock
      (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> Product2
     InjectTx
     InjectValidatedTx
     ByronBlock
     (ShelleyBlock (TPraos c) (ShelleyEra c))
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     ByronBlock
     (ShelleyBlock (TPraos c) (ShelleyEra c))
forall a b. (a -> b) -> a -> b
$ InjectTx ByronBlock (ShelleyBlock (TPraos c) (ShelleyEra c))
-> InjectValidatedTx
     ByronBlock (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Product2
     InjectTx
     InjectValidatedTx
     ByronBlock
     (ShelleyBlock (TPraos c) (ShelleyEra c))
forall (f :: * -> * -> *) (g :: * -> * -> *) x y.
f x y -> g x y -> Product2 f g x y
Pair2 InjectTx ByronBlock (ShelleyBlock (TPraos c) (ShelleyEra c))
forall blk blk'. InjectTx blk blk'
cannotInjectTx InjectValidatedTx
  ByronBlock (ShelleyBlock (TPraos c) (ShelleyEra c))
forall blk blk'. InjectValidatedTx blk blk'
cannotInjectValidatedTx)
      (InPairs
   (RequiringBoth
      WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
   '[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)]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
      (CardanoEras c))
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[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)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     (CardanoEras c)
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapLedgerConfig
  (Product2 InjectTx InjectValidatedTx)
  (ShelleyBlock (TPraos c) (ShelleyEra c))
  (ShelleyBlock (TPraos c) (AllegraEra c))
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[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)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[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)]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons (   Product2
  InjectTx
  InjectValidatedTx
  (ShelleyBlock (TPraos c) (ShelleyEra c))
  (ShelleyBlock (TPraos c) (AllegraEra c))
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     (ShelleyBlock (TPraos c) (ShelleyEra c))
     (ShelleyBlock (TPraos c) (AllegraEra c))
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (h :: k -> *).
f x y -> RequiringBoth h f x y
ignoringBoth
                (Product2
   InjectTx
   InjectValidatedTx
   (ShelleyBlock (TPraos c) (ShelleyEra c))
   (ShelleyBlock (TPraos c) (AllegraEra c))
 -> RequiringBoth
      WrapLedgerConfig
      (Product2 InjectTx InjectValidatedTx)
      (ShelleyBlock (TPraos c) (ShelleyEra c))
      (ShelleyBlock (TPraos c) (AllegraEra c)))
-> Product2
     InjectTx
     InjectValidatedTx
     (ShelleyBlock (TPraos c) (ShelleyEra c))
     (ShelleyBlock (TPraos c) (AllegraEra c))
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     (ShelleyBlock (TPraos c) (ShelleyEra c))
     (ShelleyBlock (TPraos c) (AllegraEra c))
forall a b. (a -> b) -> a -> b
$ InjectTx
  (ShelleyBlock (TPraos c) (ShelleyEra c))
  (ShelleyBlock (TPraos c) (AllegraEra c))
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) (ShelleyEra c))
     (ShelleyBlock (TPraos c) (AllegraEra c))
-> Product2
     InjectTx
     InjectValidatedTx
     (ShelleyBlock (TPraos c) (ShelleyEra c))
     (ShelleyBlock (TPraos c) (AllegraEra c))
forall (f :: * -> * -> *) (g :: * -> * -> *) x y.
f x y -> g x y -> Product2 f g x y
Pair2
                    InjectTx
  (ShelleyBlock (TPraos c) (ShelleyEra c))
  (ShelleyBlock (TPraos c) (AllegraEra c))
forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
InjectTx
  (ShelleyBlock (TPraos c) (ShelleyEra c))
  (ShelleyBlock (TPraos c) (AllegraEra c))
translateTxShelleyToAllegraWrapper
                    InjectValidatedTx
  (ShelleyBlock (TPraos c) (ShelleyEra c))
  (ShelleyBlock (TPraos c) (AllegraEra c))
forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
InjectValidatedTx
  (ShelleyBlock (TPraos c) (ShelleyEra c))
  (ShelleyBlock (TPraos c) (AllegraEra c))
translateValidatedTxShelleyToAllegraWrapper
              )
      (InPairs
   (RequiringBoth
      WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
   '[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)]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
      '[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)])
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[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)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[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)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapLedgerConfig
  (Product2 InjectTx InjectValidatedTx)
  (ShelleyBlock (TPraos c) (AllegraEra c))
  (ShelleyBlock (TPraos c) (MaryEra c))
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) (MaryEra c),
       ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[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)]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons (   Product2
  InjectTx
  InjectValidatedTx
  (ShelleyBlock (TPraos c) (AllegraEra c))
  (ShelleyBlock (TPraos c) (MaryEra c))
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     (ShelleyBlock (TPraos c) (AllegraEra c))
     (ShelleyBlock (TPraos c) (MaryEra c))
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (h :: k -> *).
f x y -> RequiringBoth h f x y
ignoringBoth
                (Product2
   InjectTx
   InjectValidatedTx
   (ShelleyBlock (TPraos c) (AllegraEra c))
   (ShelleyBlock (TPraos c) (MaryEra c))
 -> RequiringBoth
      WrapLedgerConfig
      (Product2 InjectTx InjectValidatedTx)
      (ShelleyBlock (TPraos c) (AllegraEra c))
      (ShelleyBlock (TPraos c) (MaryEra c)))
-> Product2
     InjectTx
     InjectValidatedTx
     (ShelleyBlock (TPraos c) (AllegraEra c))
     (ShelleyBlock (TPraos c) (MaryEra c))
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     (ShelleyBlock (TPraos c) (AllegraEra c))
     (ShelleyBlock (TPraos c) (MaryEra c))
forall a b. (a -> b) -> a -> b
$ InjectTx
  (ShelleyBlock (TPraos c) (AllegraEra c))
  (ShelleyBlock (TPraos c) (MaryEra c))
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) (AllegraEra c))
     (ShelleyBlock (TPraos c) (MaryEra c))
-> Product2
     InjectTx
     InjectValidatedTx
     (ShelleyBlock (TPraos c) (AllegraEra c))
     (ShelleyBlock (TPraos c) (MaryEra c))
forall (f :: * -> * -> *) (g :: * -> * -> *) x y.
f x y -> g x y -> Product2 f g x y
Pair2
                    InjectTx
  (ShelleyBlock (TPraos c) (AllegraEra c))
  (ShelleyBlock (TPraos c) (MaryEra c))
forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
InjectTx
  (ShelleyBlock (TPraos c) (AllegraEra c))
  (ShelleyBlock (TPraos c) (MaryEra c))
translateTxAllegraToMaryWrapper
                    InjectValidatedTx
  (ShelleyBlock (TPraos c) (AllegraEra c))
  (ShelleyBlock (TPraos c) (MaryEra c))
forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
InjectValidatedTx
  (ShelleyBlock (TPraos c) (AllegraEra c))
  (ShelleyBlock (TPraos c) (MaryEra c))
translateValidatedTxAllegraToMaryWrapper
              )
      (InPairs
   (RequiringBoth
      WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
   '[ShelleyBlock (TPraos c) (MaryEra c),
     ShelleyBlock (TPraos c) (AlonzoEra c),
     ShelleyBlock (Praos c) (BabbageEra c),
     ShelleyBlock (Praos c) (ConwayEra c)]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
      '[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)])
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) (MaryEra c),
       ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[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)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapLedgerConfig
  (Product2 InjectTx InjectValidatedTx)
  (ShelleyBlock (TPraos c) (MaryEra c))
  (ShelleyBlock (TPraos c) (AlonzoEra c))
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) (MaryEra c),
       ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons ((WrapLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
 -> WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
 -> Product2
      InjectTx
      InjectValidatedTx
      (ShelleyBlock (TPraos c) (MaryEra c))
      (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     (ShelleyBlock (TPraos c) (MaryEra c))
     (ShelleyBlock (TPraos c) (AlonzoEra c))
forall {k} (h :: k -> *) (f :: k -> k -> *) (x :: k) (y :: k).
(h x -> h y -> f x y) -> RequiringBoth h f x y
RequireBoth ((WrapLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
  -> WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
  -> Product2
       InjectTx
       InjectValidatedTx
       (ShelleyBlock (TPraos c) (MaryEra c))
       (ShelleyBlock (TPraos c) (AlonzoEra c)))
 -> RequiringBoth
      WrapLedgerConfig
      (Product2 InjectTx InjectValidatedTx)
      (ShelleyBlock (TPraos c) (MaryEra c))
      (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> (WrapLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
    -> WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
    -> Product2
         InjectTx
         InjectValidatedTx
         (ShelleyBlock (TPraos c) (MaryEra c))
         (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     (ShelleyBlock (TPraos c) (MaryEra c))
     (ShelleyBlock (TPraos c) (AlonzoEra c))
forall a b. (a -> b) -> a -> b
$ \WrapLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
_cfgMary WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
cfgAlonzo ->
                let ctxt :: TranslationContext (AlonzoEra c)
ctxt = WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> TranslationContext (AlonzoEra c)
forall c.
WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> TranslationContext (AlonzoEra c)
getAlonzoTranslationContext WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
cfgAlonzo
                in
                InjectTx
  (ShelleyBlock (TPraos c) (MaryEra c))
  (ShelleyBlock (TPraos c) (AlonzoEra c))
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) (MaryEra c))
     (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Product2
     InjectTx
     InjectValidatedTx
     (ShelleyBlock (TPraos c) (MaryEra c))
     (ShelleyBlock (TPraos c) (AlonzoEra c))
forall (f :: * -> * -> *) (g :: * -> * -> *) x y.
f x y -> g x y -> Product2 f g x y
Pair2
                  (TranslationContext (AlonzoEra c)
-> InjectTx
     (ShelleyBlock (TPraos c) (MaryEra c))
     (ShelleyBlock (TPraos c) (AlonzoEra c))
forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
TranslationContext (AlonzoEra c)
-> InjectTx
     (ShelleyBlock (TPraos c) (MaryEra c))
     (ShelleyBlock (TPraos c) (AlonzoEra c))
translateTxMaryToAlonzoWrapper          TranslationContext (AlonzoEra c)
ctxt)
                  (TranslationContext (AlonzoEra c)
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) (MaryEra c))
     (ShelleyBlock (TPraos c) (AlonzoEra c))
forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
TranslationContext (AlonzoEra c)
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) (MaryEra c))
     (ShelleyBlock (TPraos c) (AlonzoEra c))
translateValidatedTxMaryToAlonzoWrapper TranslationContext (AlonzoEra c)
ctxt)
              )
      (InPairs
   (RequiringBoth
      WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
   '[ShelleyBlock (TPraos c) (AlonzoEra c),
     ShelleyBlock (Praos c) (BabbageEra c),
     ShelleyBlock (Praos c) (ConwayEra c)]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
      '[ShelleyBlock (TPraos c) (MaryEra c),
        ShelleyBlock (TPraos c) (AlonzoEra c),
        ShelleyBlock (Praos c) (BabbageEra c),
        ShelleyBlock (Praos c) (ConwayEra c)])
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) (MaryEra c),
       ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapLedgerConfig
  (Product2 InjectTx InjectValidatedTx)
  (ShelleyBlock (TPraos c) (AlonzoEra c))
  (ShelleyBlock (Praos c) (BabbageEra c))
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons ((WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
 -> WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
 -> Product2
      InjectTx
      InjectValidatedTx
      (ShelleyBlock (TPraos c) (AlonzoEra c))
      (ShelleyBlock (Praos c) (BabbageEra c)))
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     (ShelleyBlock (TPraos c) (AlonzoEra c))
     (ShelleyBlock (Praos c) (BabbageEra c))
forall {k} (h :: k -> *) (f :: k -> k -> *) (x :: k) (y :: k).
(h x -> h y -> f x y) -> RequiringBoth h f x y
RequireBoth ((WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
  -> WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
  -> Product2
       InjectTx
       InjectValidatedTx
       (ShelleyBlock (TPraos c) (AlonzoEra c))
       (ShelleyBlock (Praos c) (BabbageEra c)))
 -> RequiringBoth
      WrapLedgerConfig
      (Product2 InjectTx InjectValidatedTx)
      (ShelleyBlock (TPraos c) (AlonzoEra c))
      (ShelleyBlock (Praos c) (BabbageEra c)))
-> (WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
    -> WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
    -> Product2
         InjectTx
         InjectValidatedTx
         (ShelleyBlock (TPraos c) (AlonzoEra c))
         (ShelleyBlock (Praos c) (BabbageEra c)))
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     (ShelleyBlock (TPraos c) (AlonzoEra c))
     (ShelleyBlock (Praos c) (BabbageEra c))
forall a b. (a -> b) -> a -> b
$ \WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
_cfgAlonzo WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
_cfgBabbage ->
                let ctxt :: NoGenesis era
ctxt = NoGenesis era
forall era. NoGenesis era
SL.NoGenesis
                in
                InjectTx
  (ShelleyBlock (TPraos c) (AlonzoEra c))
  (ShelleyBlock (Praos c) (BabbageEra c))
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) (AlonzoEra c))
     (ShelleyBlock (Praos c) (BabbageEra c))
-> Product2
     InjectTx
     InjectValidatedTx
     (ShelleyBlock (TPraos c) (AlonzoEra c))
     (ShelleyBlock (Praos c) (BabbageEra c))
forall (f :: * -> * -> *) (g :: * -> * -> *) x y.
f x y -> g x y -> Product2 f g x y
Pair2
                  (TranslationContext (BabbageEra c)
-> InjectTx
     (ShelleyBlock (TPraos c) (AlonzoEra c))
     (ShelleyBlock (Praos c) (BabbageEra c))
forall c.
PraosCrypto c =>
TranslationContext (BabbageEra c)
-> InjectTx
     (ShelleyBlock (TPraos c) (AlonzoEra c))
     (ShelleyBlock (Praos c) (BabbageEra c))
translateTxAlonzoToBabbageWrapper          TranslationContext (BabbageEra c)
NoGenesis (BabbageEra c)
forall era. NoGenesis era
ctxt)
                  (TranslationContext (BabbageEra c)
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) (AlonzoEra c))
     (ShelleyBlock (Praos c) (BabbageEra c))
forall c.
PraosCrypto c =>
TranslationContext (BabbageEra c)
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) (AlonzoEra c))
     (ShelleyBlock (Praos c) (BabbageEra c))
translateValidatedTxAlonzoToBabbageWrapper TranslationContext (BabbageEra c)
NoGenesis (BabbageEra c)
forall era. NoGenesis era
ctxt)
              )
      (InPairs
   (RequiringBoth
      WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
   '[ShelleyBlock (Praos c) (BabbageEra c),
     ShelleyBlock (Praos c) (ConwayEra c)]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
      '[ShelleyBlock (TPraos c) (AlonzoEra c),
        ShelleyBlock (Praos c) (BabbageEra c),
        ShelleyBlock (Praos c) (ConwayEra c)])
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapLedgerConfig
  (Product2 InjectTx InjectValidatedTx)
  (ShelleyBlock (Praos c) (BabbageEra c))
  (ShelleyBlock (Praos c) (ConwayEra c))
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons ((WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
 -> WrapLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
 -> Product2
      InjectTx
      InjectValidatedTx
      (ShelleyBlock (Praos c) (BabbageEra c))
      (ShelleyBlock (Praos c) (ConwayEra c)))
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     (ShelleyBlock (Praos c) (BabbageEra c))
     (ShelleyBlock (Praos c) (ConwayEra c))
forall {k} (h :: k -> *) (f :: k -> k -> *) (x :: k) (y :: k).
(h x -> h y -> f x y) -> RequiringBoth h f x y
RequireBoth ((WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
  -> WrapLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
  -> Product2
       InjectTx
       InjectValidatedTx
       (ShelleyBlock (Praos c) (BabbageEra c))
       (ShelleyBlock (Praos c) (ConwayEra c)))
 -> RequiringBoth
      WrapLedgerConfig
      (Product2 InjectTx InjectValidatedTx)
      (ShelleyBlock (Praos c) (BabbageEra c))
      (ShelleyBlock (Praos c) (ConwayEra c)))
-> (WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
    -> WrapLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
    -> Product2
         InjectTx
         InjectValidatedTx
         (ShelleyBlock (Praos c) (BabbageEra c))
         (ShelleyBlock (Praos c) (ConwayEra c)))
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     (ShelleyBlock (Praos c) (BabbageEra c))
     (ShelleyBlock (Praos c) (ConwayEra c))
forall a b. (a -> b) -> a -> b
$ \WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
_cfgBabbage WrapLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
cfgConway ->
                let ctxt :: TranslationContext (ConwayEra c)
ctxt = WrapLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> TranslationContext (ConwayEra c)
forall c.
WrapLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> TranslationContext (ConwayEra c)
getConwayTranslationContext WrapLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
cfgConway
                in
                InjectTx
  (ShelleyBlock (Praos c) (BabbageEra c))
  (ShelleyBlock (Praos c) (ConwayEra c))
-> InjectValidatedTx
     (ShelleyBlock (Praos c) (BabbageEra c))
     (ShelleyBlock (Praos c) (ConwayEra c))
-> Product2
     InjectTx
     InjectValidatedTx
     (ShelleyBlock (Praos c) (BabbageEra c))
     (ShelleyBlock (Praos c) (ConwayEra c))
forall (f :: * -> * -> *) (g :: * -> * -> *) x y.
f x y -> g x y -> Product2 f g x y
Pair2
                  (TranslationContext (ConwayEra c)
-> InjectTx
     (ShelleyBlock (Praos c) (BabbageEra c))
     (ShelleyBlock (Praos c) (ConwayEra c))
forall c.
PraosCrypto c =>
TranslationContext (ConwayEra c)
-> InjectTx
     (ShelleyBlock (Praos c) (BabbageEra c))
     (ShelleyBlock (Praos c) (ConwayEra c))
translateTxBabbageToConwayWrapper          TranslationContext (ConwayEra c)
ctxt)
                  (TranslationContext (ConwayEra c)
-> InjectValidatedTx
     (ShelleyBlock (Praos c) (BabbageEra c))
     (ShelleyBlock (Praos c) (ConwayEra c))
forall c.
PraosCrypto c =>
TranslationContext (ConwayEra c)
-> InjectValidatedTx
     (ShelleyBlock (Praos c) (BabbageEra c))
     (ShelleyBlock (Praos c) (ConwayEra c))
translateValidatedTxBabbageToConwayWrapper TranslationContext (ConwayEra c)
ctxt)
              )
      (InPairs
   (RequiringBoth
      WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
   '[ShelleyBlock (Praos c) (ConwayEra c)]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
      '[ShelleyBlock (Praos c) (BabbageEra c),
        ShelleyBlock (Praos c) (ConwayEra c)])
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (Praos c) (ConwayEra c)]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
forall a b. (a -> b) -> a -> b
$ InPairs
  (RequiringBoth
     WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
  '[ShelleyBlock (Praos c) (ConwayEra c)]
forall {k} (f :: k -> k -> *) (x :: k). InPairs f '[x]
PNil

  hardForkInjTxMeasure :: NS WrapTxMeasure (CardanoEras c)
-> HardForkTxMeasure (CardanoEras c)
hardForkInjTxMeasure =
    IgnoringOverflow ByteSize32 -> ConwayMeasure
TxMeasure ByronBlock -> ConwayMeasure
fromByteSize (TxMeasure ByronBlock -> ConwayMeasure)
-> (NS
      WrapTxMeasure
      '[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)]
    -> ConwayMeasure)
-> NS WrapTxMeasure (CardanoEras c)
-> ConwayMeasure
forall x a (xs :: [*]).
(TxMeasure x -> a)
-> (NS WrapTxMeasure xs -> a) -> NS WrapTxMeasure (x : xs) -> a
`o`
    IgnoringOverflow ByteSize32 -> ConwayMeasure
TxMeasure (ShelleyBlock (TPraos c) (ShelleyEra c)) -> ConwayMeasure
fromByteSize (TxMeasure (ShelleyBlock (TPraos c) (ShelleyEra c))
 -> ConwayMeasure)
-> (NS
      WrapTxMeasure
      '[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)]
    -> ConwayMeasure)
-> NS
     WrapTxMeasure
     '[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)]
-> ConwayMeasure
forall x a (xs :: [*]).
(TxMeasure x -> a)
-> (NS WrapTxMeasure xs -> a) -> NS WrapTxMeasure (x : xs) -> a
`o`
    IgnoringOverflow ByteSize32 -> ConwayMeasure
TxMeasure (ShelleyBlock (TPraos c) (AllegraEra c)) -> ConwayMeasure
fromByteSize (TxMeasure (ShelleyBlock (TPraos c) (AllegraEra c))
 -> ConwayMeasure)
-> (NS
      WrapTxMeasure
      '[ShelleyBlock (TPraos c) (MaryEra c),
        ShelleyBlock (TPraos c) (AlonzoEra c),
        ShelleyBlock (Praos c) (BabbageEra c),
        ShelleyBlock (Praos c) (ConwayEra c)]
    -> ConwayMeasure)
-> NS
     WrapTxMeasure
     '[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)]
-> ConwayMeasure
forall x a (xs :: [*]).
(TxMeasure x -> a)
-> (NS WrapTxMeasure xs -> a) -> NS WrapTxMeasure (x : xs) -> a
`o`
    IgnoringOverflow ByteSize32 -> ConwayMeasure
TxMeasure (ShelleyBlock (TPraos c) (MaryEra c)) -> ConwayMeasure
fromByteSize (TxMeasure (ShelleyBlock (TPraos c) (MaryEra c)) -> ConwayMeasure)
-> (NS
      WrapTxMeasure
      '[ShelleyBlock (TPraos c) (AlonzoEra c),
        ShelleyBlock (Praos c) (BabbageEra c),
        ShelleyBlock (Praos c) (ConwayEra c)]
    -> ConwayMeasure)
-> NS
     WrapTxMeasure
     '[ShelleyBlock (TPraos c) (MaryEra c),
       ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> ConwayMeasure
forall x a (xs :: [*]).
(TxMeasure x -> a)
-> (NS WrapTxMeasure xs -> a) -> NS WrapTxMeasure (x : xs) -> a
`o`
    TxMeasure (ShelleyBlock (TPraos c) (AlonzoEra c)) -> ConwayMeasure
AlonzoMeasure -> ConwayMeasure
fromAlonzo   (TxMeasure (ShelleyBlock (TPraos c) (AlonzoEra c))
 -> ConwayMeasure)
-> (NS
      WrapTxMeasure
      '[ShelleyBlock (Praos c) (BabbageEra c),
        ShelleyBlock (Praos c) (ConwayEra c)]
    -> ConwayMeasure)
-> NS
     WrapTxMeasure
     '[ShelleyBlock (TPraos c) (AlonzoEra c),
       ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> ConwayMeasure
forall x a (xs :: [*]).
(TxMeasure x -> a)
-> (NS WrapTxMeasure xs -> a) -> NS WrapTxMeasure (x : xs) -> a
`o`
    TxMeasure (ShelleyBlock (Praos c) (BabbageEra c)) -> ConwayMeasure
ConwayMeasure -> ConwayMeasure
forall {p}. p -> p
fromConway   (TxMeasure (ShelleyBlock (Praos c) (BabbageEra c))
 -> ConwayMeasure)
-> (NS WrapTxMeasure '[ShelleyBlock (Praos c) (ConwayEra c)]
    -> ConwayMeasure)
-> NS
     WrapTxMeasure
     '[ShelleyBlock (Praos c) (BabbageEra c),
       ShelleyBlock (Praos c) (ConwayEra c)]
-> ConwayMeasure
forall x a (xs :: [*]).
(TxMeasure x -> a)
-> (NS WrapTxMeasure xs -> a) -> NS WrapTxMeasure (x : xs) -> a
`o`
    TxMeasure (ShelleyBlock (Praos c) (ConwayEra c)) -> ConwayMeasure
ConwayMeasure -> ConwayMeasure
forall {p}. p -> p
fromConway   (TxMeasure (ShelleyBlock (Praos c) (ConwayEra c)) -> ConwayMeasure)
-> (NS WrapTxMeasure '[] -> ConwayMeasure)
-> NS WrapTxMeasure '[ShelleyBlock (Praos c) (ConwayEra c)]
-> ConwayMeasure
forall x a (xs :: [*]).
(TxMeasure x -> a)
-> (NS WrapTxMeasure xs -> a) -> NS WrapTxMeasure (x : xs) -> a
`o`
    NS WrapTxMeasure '[] -> ConwayMeasure
forall (f :: * -> *) a. NS f '[] -> a
nil
    where
      nil :: SOP.NS f '[] -> a
      nil :: forall (f :: * -> *) a. NS f '[] -> a
nil = \case {}

      infixr `o`
      o ::
           (TxMeasure x -> a)
        -> (SOP.NS WrapTxMeasure xs -> a)
        -> SOP.NS WrapTxMeasure (x : xs)
        -> a
      o :: forall x a (xs :: [*]).
(TxMeasure x -> a)
-> (NS WrapTxMeasure xs -> a) -> NS WrapTxMeasure (x : xs) -> a
o TxMeasure x -> a
f NS WrapTxMeasure xs -> a
g = \case
        SOP.Z (WrapTxMeasure TxMeasure x
x) -> TxMeasure x -> a
f TxMeasure x
TxMeasure x
x
        SOP.S NS WrapTxMeasure xs1
y                 -> NS WrapTxMeasure xs -> a
g NS WrapTxMeasure xs
NS WrapTxMeasure xs1
y

      fromByteSize :: IgnoringOverflow ByteSize32 -> ConwayMeasure
      fromByteSize :: IgnoringOverflow ByteSize32 -> ConwayMeasure
fromByteSize IgnoringOverflow ByteSize32
x = AlonzoMeasure -> ConwayMeasure
fromAlonzo (AlonzoMeasure -> ConwayMeasure) -> AlonzoMeasure -> ConwayMeasure
forall a b. (a -> b) -> a -> b
$ IgnoringOverflow ByteSize32 -> ExUnits' Natural -> AlonzoMeasure
AlonzoMeasure IgnoringOverflow ByteSize32
x ExUnits' Natural
forall a. Monoid a => a
mempty
      fromAlonzo :: AlonzoMeasure -> ConwayMeasure
fromAlonzo   AlonzoMeasure
x = ConwayMeasure -> ConwayMeasure
forall {p}. p -> p
fromConway (ConwayMeasure -> ConwayMeasure) -> ConwayMeasure -> ConwayMeasure
forall a b. (a -> b) -> a -> b
$ AlonzoMeasure -> IgnoringOverflow ByteSize32 -> ConwayMeasure
ConwayMeasure AlonzoMeasure
x IgnoringOverflow ByteSize32
forall a. Monoid a => a
mempty
      fromConway :: p -> p
fromConway   p
x = p
x

class    (SelectView (BlockProtocol blk) ~ PraosChainSelectView c) => HasPraosSelectView c blk
instance (SelectView (BlockProtocol blk) ~ PraosChainSelectView c) => HasPraosSelectView c blk

{-------------------------------------------------------------------------------
  Translation from Byron to Shelley
-------------------------------------------------------------------------------}

translateHeaderHashByronToShelley ::
     forall c.
     ( ShelleyCompatible (TPraos c) (ShelleyEra c)
     , HASH c ~ Blake2b_256
     )
  => HeaderHash ByronBlock
  -> HeaderHash (ShelleyBlock (TPraos c) (ShelleyEra c))
translateHeaderHashByronToShelley :: forall c.
(ShelleyCompatible (TPraos c) (ShelleyEra c),
 HASH c ~ Blake2b_256) =>
HeaderHash ByronBlock
-> HeaderHash (ShelleyBlock (TPraos c) (ShelleyEra c))
translateHeaderHashByronToShelley =
      Proxy (ShelleyBlock (TPraos c) (ShelleyEra c))
-> ShortByteString
-> HeaderHash (ShelleyBlock (TPraos c) (ShelleyEra c))
forall blk (proxy :: * -> *).
ConvertRawHash blk =>
proxy blk -> ShortByteString -> HeaderHash blk
forall (proxy :: * -> *).
proxy (ShelleyBlock (TPraos c) (ShelleyEra c))
-> ShortByteString
-> HeaderHash (ShelleyBlock (TPraos c) (ShelleyEra c))
fromShortRawHash (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @(ShelleyBlock (TPraos c) (ShelleyEra c)))
    (ShortByteString -> ShelleyHash c)
-> (ByronHash -> ShortByteString) -> ByronHash -> ShelleyHash c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy ByronBlock -> HeaderHash ByronBlock -> ShortByteString
forall blk (proxy :: * -> *).
ConvertRawHash blk =>
proxy blk -> HeaderHash blk -> ShortByteString
forall (proxy :: * -> *).
proxy ByronBlock -> HeaderHash ByronBlock -> ShortByteString
toShortRawHash   (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @ByronBlock)
  where
    -- Byron uses 'Blake2b_256' for header hashes
    ()
_ = Proxy (HASH c ~ Blake2b_256) -> ()
forall (c :: Constraint) (proxy :: Constraint -> *).
c =>
proxy c -> ()
keepRedundantConstraint (forall {k} (t :: k). Proxy t
forall (t :: Constraint). Proxy t
Proxy @(HASH c ~ Blake2b_256))

translatePointByronToShelley ::
     ( ShelleyCompatible (TPraos c) (ShelleyEra c)
     , HASH c ~ Blake2b_256
     )
  => Point ByronBlock
  -> WithOrigin BlockNo
  -> WithOrigin (ShelleyTip (TPraos c) (ShelleyEra c))
translatePointByronToShelley :: forall c.
(ShelleyCompatible (TPraos c) (ShelleyEra c),
 HASH c ~ Blake2b_256) =>
Point ByronBlock
-> WithOrigin BlockNo
-> WithOrigin (ShelleyTip (TPraos c) (ShelleyEra c))
translatePointByronToShelley Point ByronBlock
point WithOrigin BlockNo
bNo =
    case (Point ByronBlock
point, WithOrigin BlockNo
bNo) of
      (Point ByronBlock
GenesisPoint, WithOrigin BlockNo
Origin) ->
        WithOrigin (ShelleyTip (TPraos c) (ShelleyEra c))
forall t. WithOrigin t
Origin
      (BlockPoint SlotNo
s HeaderHash ByronBlock
h, NotOrigin BlockNo
n) -> ShelleyTip (TPraos c) (ShelleyEra c)
-> WithOrigin (ShelleyTip (TPraos c) (ShelleyEra c))
forall t. t -> WithOrigin t
NotOrigin ShelleyTip {
          shelleyTipSlotNo :: SlotNo
shelleyTipSlotNo  = SlotNo
s
        , shelleyTipBlockNo :: BlockNo
shelleyTipBlockNo = BlockNo
n
        , shelleyTipHash :: HeaderHash (ShelleyBlock (TPraos c) (ShelleyEra c))
shelleyTipHash    = HeaderHash ByronBlock
-> HeaderHash (ShelleyBlock (TPraos c) (ShelleyEra c))
forall c.
(ShelleyCompatible (TPraos c) (ShelleyEra c),
 HASH c ~ Blake2b_256) =>
HeaderHash ByronBlock
-> HeaderHash (ShelleyBlock (TPraos c) (ShelleyEra c))
translateHeaderHashByronToShelley HeaderHash ByronBlock
h
        }
      (Point ByronBlock, WithOrigin BlockNo)
_otherwise ->
        String -> WithOrigin (ShelleyTip (TPraos c) (ShelleyEra c))
forall a. HasCallStack => String -> a
error String
"translatePointByronToShelley: invalid Byron state"

translateLedgerStateByronToShelleyWrapper ::
     ( ShelleyCompatible (TPraos c) (ShelleyEra c)
     , HASH     c ~ Blake2b_256
     , ADDRHASH c ~ Blake2b_224
     )
  => RequiringBoth
       WrapLedgerConfig
       (Translate LedgerState)
       ByronBlock
       (ShelleyBlock (TPraos c) (ShelleyEra c))
translateLedgerStateByronToShelleyWrapper :: forall c.
(ShelleyCompatible (TPraos c) (ShelleyEra c), HASH c ~ Blake2b_256,
 ADDRHASH c ~ Blake2b_224) =>
RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  ByronBlock
  (ShelleyBlock (TPraos c) (ShelleyEra c))
translateLedgerStateByronToShelleyWrapper =
    (WrapLedgerConfig ByronBlock
 -> WrapLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
 -> Translate
      LedgerState ByronBlock (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> RequiringBoth
     WrapLedgerConfig
     (Translate LedgerState)
     ByronBlock
     (ShelleyBlock (TPraos c) (ShelleyEra c))
forall {k} (h :: k -> *) (f :: k -> k -> *) (x :: k) (y :: k).
(h x -> h y -> f x y) -> RequiringBoth h f x y
RequireBoth ((WrapLedgerConfig ByronBlock
  -> WrapLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
  -> Translate
       LedgerState ByronBlock (ShelleyBlock (TPraos c) (ShelleyEra c)))
 -> RequiringBoth
      WrapLedgerConfig
      (Translate LedgerState)
      ByronBlock
      (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> (WrapLedgerConfig ByronBlock
    -> WrapLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
    -> Translate
         LedgerState ByronBlock (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> RequiringBoth
     WrapLedgerConfig
     (Translate LedgerState)
     ByronBlock
     (ShelleyBlock (TPraos c) (ShelleyEra c))
forall a b. (a -> b) -> a -> b
$ \WrapLedgerConfig ByronBlock
_ (WrapLedgerConfig LedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
cfgShelley) ->
    (EpochNo
 -> LedgerState ByronBlock
 -> LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> Translate
     LedgerState ByronBlock (ShelleyBlock (TPraos c) (ShelleyEra c))
forall (f :: * -> *) x y.
(EpochNo -> f x -> f y) -> Translate f x y
Translate   ((EpochNo
  -> LedgerState ByronBlock
  -> LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c)))
 -> Translate
      LedgerState ByronBlock (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> (EpochNo
    -> LedgerState ByronBlock
    -> LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> Translate
     LedgerState ByronBlock (ShelleyBlock (TPraos c) (ShelleyEra c))
forall a b. (a -> b) -> a -> b
$ \EpochNo
epochNo LedgerState ByronBlock
ledgerByron ->
      ShelleyLedgerState {
        shelleyLedgerTip :: WithOrigin (ShelleyTip (TPraos c) (ShelleyEra c))
shelleyLedgerTip =
          Point ByronBlock
-> WithOrigin BlockNo
-> WithOrigin (ShelleyTip (TPraos c) (ShelleyEra c))
forall c.
(ShelleyCompatible (TPraos c) (ShelleyEra c),
 HASH c ~ Blake2b_256) =>
Point ByronBlock
-> WithOrigin BlockNo
-> WithOrigin (ShelleyTip (TPraos c) (ShelleyEra c))
translatePointByronToShelley
            (LedgerState ByronBlock -> Point ByronBlock
forall blk. UpdateLedger blk => LedgerState blk -> Point blk
ledgerTipPoint LedgerState ByronBlock
ledgerByron)
            (LedgerState ByronBlock -> WithOrigin BlockNo
byronLedgerTipBlockNo LedgerState ByronBlock
ledgerByron)
      , shelleyLedgerState :: NewEpochState (ShelleyEra c)
shelleyLedgerState =
          FromByronTranslationContext c
-> EpochNo -> ChainValidationState -> NewEpochState (ShelleyEra c)
forall c.
(Crypto c, ADDRHASH c ~ Blake2b_224) =>
FromByronTranslationContext c
-> EpochNo -> ChainValidationState -> NewEpochState (ShelleyEra c)
SL.translateToShelleyLedgerState
            (ShelleyGenesis c -> FromByronTranslationContext c
forall c. ShelleyGenesis c -> FromByronTranslationContext c
toFromByronTranslationContext (ShelleyLedgerConfig (ShelleyEra c)
-> ShelleyGenesis (EraCrypto (ShelleyEra c))
forall era.
ShelleyLedgerConfig era -> ShelleyGenesis (EraCrypto era)
shelleyLedgerGenesis LedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
ShelleyLedgerConfig (ShelleyEra c)
cfgShelley))
            EpochNo
epochNo
            (LedgerState ByronBlock -> ChainValidationState
byronLedgerState LedgerState ByronBlock
ledgerByron)
      , shelleyLedgerTransition :: ShelleyTransition
shelleyLedgerTransition =
          ShelleyTransitionInfo{shelleyAfterVoting :: Word32
shelleyAfterVoting = Word32
0}
      }

translateChainDepStateByronToShelleyWrapper ::
     RequiringBoth
       WrapConsensusConfig
       (Translate WrapChainDepState)
       ByronBlock
       (ShelleyBlock (TPraos c) (ShelleyEra c))
translateChainDepStateByronToShelleyWrapper :: forall c.
RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  ByronBlock
  (ShelleyBlock (TPraos c) (ShelleyEra c))
translateChainDepStateByronToShelleyWrapper =
    (WrapConsensusConfig ByronBlock
 -> WrapConsensusConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
 -> Translate
      WrapChainDepState
      ByronBlock
      (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> RequiringBoth
     WrapConsensusConfig
     (Translate WrapChainDepState)
     ByronBlock
     (ShelleyBlock (TPraos c) (ShelleyEra c))
forall {k} (h :: k -> *) (f :: k -> k -> *) (x :: k) (y :: k).
(h x -> h y -> f x y) -> RequiringBoth h f x y
RequireBoth ((WrapConsensusConfig ByronBlock
  -> WrapConsensusConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
  -> Translate
       WrapChainDepState
       ByronBlock
       (ShelleyBlock (TPraos c) (ShelleyEra c)))
 -> RequiringBoth
      WrapConsensusConfig
      (Translate WrapChainDepState)
      ByronBlock
      (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> (WrapConsensusConfig ByronBlock
    -> WrapConsensusConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
    -> Translate
         WrapChainDepState
         ByronBlock
         (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> RequiringBoth
     WrapConsensusConfig
     (Translate WrapChainDepState)
     ByronBlock
     (ShelleyBlock (TPraos c) (ShelleyEra c))
forall a b. (a -> b) -> a -> b
$ \WrapConsensusConfig ByronBlock
_ (WrapConsensusConfig ConsensusConfig
  (BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c)))
cfgShelley) ->
      (EpochNo
 -> WrapChainDepState ByronBlock
 -> WrapChainDepState (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> Translate
     WrapChainDepState
     ByronBlock
     (ShelleyBlock (TPraos c) (ShelleyEra c))
forall (f :: * -> *) x y.
(EpochNo -> f x -> f y) -> Translate f x y
Translate ((EpochNo
  -> WrapChainDepState ByronBlock
  -> WrapChainDepState (ShelleyBlock (TPraos c) (ShelleyEra c)))
 -> Translate
      WrapChainDepState
      ByronBlock
      (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> (EpochNo
    -> WrapChainDepState ByronBlock
    -> WrapChainDepState (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> Translate
     WrapChainDepState
     ByronBlock
     (ShelleyBlock (TPraos c) (ShelleyEra c))
forall a b. (a -> b) -> a -> b
$ \EpochNo
_ (WrapChainDepState ChainDepState (BlockProtocol ByronBlock)
pbftState) ->
        ChainDepState
  (BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> WrapChainDepState (ShelleyBlock (TPraos c) (ShelleyEra c))
forall blk.
ChainDepState (BlockProtocol blk) -> WrapChainDepState blk
WrapChainDepState (ChainDepState
   (BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c)))
 -> WrapChainDepState (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> ChainDepState
     (BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> WrapChainDepState (ShelleyBlock (TPraos c) (ShelleyEra c))
forall a b. (a -> b) -> a -> b
$
          ConsensusConfig (TPraos c)
-> PBftState PBftByronCrypto -> TPraosState c
forall bc c.
ConsensusConfig (TPraos c) -> PBftState bc -> TPraosState c
translateChainDepStateByronToShelley ConsensusConfig
  (BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c)))
ConsensusConfig (TPraos c)
cfgShelley ChainDepState (BlockProtocol ByronBlock)
PBftState PBftByronCrypto
pbftState

translateChainDepStateByronToShelley ::
     forall bc c.
     ConsensusConfig (TPraos c)
  -> PBftState bc
  -> TPraosState c
translateChainDepStateByronToShelley :: forall bc c.
ConsensusConfig (TPraos c) -> PBftState bc -> TPraosState c
translateChainDepStateByronToShelley TPraosConfig { TPraosParams
tpraosParams :: TPraosParams
tpraosParams :: forall c. ConsensusConfig (TPraos c) -> TPraosParams
tpraosParams } PBftState bc
pbftState =
    -- Note that the 'PBftState' doesn't know about EBBs. So if the last slot of
    -- the Byron era were occupied by an EBB (and no regular block in that same
    -- slot), we would pick the wrong slot here, i.e., the slot of the regular
    -- block before the EBB.
    --
    -- Fortunately, this is impossible for two reasons:
    --
    -- 1. On mainnet we stopped producing EBBs a while before the transition.
    -- 2. The transition happens at the start of an epoch, so if the last slot
    --    were occupied by an EBB, it must have been the EBB at the start of the
    --    previous epoch. This means the previous epoch must have been empty,
    --    which is a violation of the "@k@ blocks per @2k@ slots" property.
    WithOrigin SlotNo -> ChainDepState c -> TPraosState c
forall c. WithOrigin SlotNo -> ChainDepState c -> TPraosState c
TPraosState (PBftState bc -> WithOrigin SlotNo
forall c. PBftState c -> WithOrigin SlotNo
PBftState.lastSignedSlot PBftState bc
pbftState) (ChainDepState c -> TPraosState c)
-> ChainDepState c -> TPraosState c
forall a b. (a -> b) -> a -> b
$
      SL.ChainDepState
        { csProtocol :: PrtclState c
SL.csProtocol = Map (KeyHash 'BlockIssuer c) Word64
-> Nonce -> Nonce -> PrtclState c
forall c.
Map (KeyHash 'BlockIssuer c) Word64
-> Nonce -> Nonce -> PrtclState c
SL.PrtclState Map (KeyHash 'BlockIssuer c) Word64
forall k a. Map k a
Map.empty Nonce
nonce Nonce
nonce
        , csTickn :: TicknState
SL.csTickn    = SL.TicknState {
              ticknStateEpochNonce :: Nonce
ticknStateEpochNonce    = Nonce
nonce
            , ticknStatePrevHashNonce :: Nonce
ticknStatePrevHashNonce = Nonce
SL.NeutralNonce
            }
          -- Overridden before used
        , csLabNonce :: Nonce
SL.csLabNonce = Nonce
SL.NeutralNonce
        }
  where
    nonce :: Nonce
nonce = TPraosParams -> Nonce
tpraosInitialNonce TPraosParams
tpraosParams

crossEraForecastByronToShelleyWrapper ::
     forall c. Crypto c =>
     RequiringBoth
       WrapLedgerConfig
       (CrossEraForecaster LedgerState WrapLedgerView)
       ByronBlock
       (ShelleyBlock (TPraos c) (ShelleyEra c))
crossEraForecastByronToShelleyWrapper :: forall c.
Crypto c =>
RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  ByronBlock
  (ShelleyBlock (TPraos c) (ShelleyEra c))
crossEraForecastByronToShelleyWrapper =
    (WrapLedgerConfig ByronBlock
 -> WrapLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
 -> CrossEraForecaster
      LedgerState
      WrapLedgerView
      ByronBlock
      (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> RequiringBoth
     WrapLedgerConfig
     (CrossEraForecaster LedgerState WrapLedgerView)
     ByronBlock
     (ShelleyBlock (TPraos c) (ShelleyEra c))
forall {k} (h :: k -> *) (f :: k -> k -> *) (x :: k) (y :: k).
(h x -> h y -> f x y) -> RequiringBoth h f x y
RequireBoth ((WrapLedgerConfig ByronBlock
  -> WrapLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
  -> CrossEraForecaster
       LedgerState
       WrapLedgerView
       ByronBlock
       (ShelleyBlock (TPraos c) (ShelleyEra c)))
 -> RequiringBoth
      WrapLedgerConfig
      (CrossEraForecaster LedgerState WrapLedgerView)
      ByronBlock
      (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> (WrapLedgerConfig ByronBlock
    -> WrapLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
    -> CrossEraForecaster
         LedgerState
         WrapLedgerView
         ByronBlock
         (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> RequiringBoth
     WrapLedgerConfig
     (CrossEraForecaster LedgerState WrapLedgerView)
     ByronBlock
     (ShelleyBlock (TPraos c) (ShelleyEra c))
forall a b. (a -> b) -> a -> b
$ \WrapLedgerConfig ByronBlock
_ (WrapLedgerConfig LedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
cfgShelley) ->
      (Bound
 -> SlotNo
 -> LedgerState ByronBlock
 -> Except
      OutsideForecastRange
      (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c))))
-> CrossEraForecaster
     LedgerState
     WrapLedgerView
     ByronBlock
     (ShelleyBlock (TPraos c) (ShelleyEra c))
forall (state :: * -> *) (view :: * -> *) x y.
(Bound
 -> SlotNo -> state x -> Except OutsideForecastRange (view y))
-> CrossEraForecaster state view x y
CrossEraForecaster (ShelleyLedgerConfig (ShelleyEra c)
-> Bound
-> SlotNo
-> LedgerState ByronBlock
-> Except
     OutsideForecastRange
     (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c)))
forecast LedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
ShelleyLedgerConfig (ShelleyEra c)
cfgShelley)
  where
    -- We ignore the Byron ledger view and create a new Shelley.
    --
    -- The full Shelley forecast range (stability window) starts from the first
    -- slot of the Shelley era, no matter how many slots there are between the
    -- Byron ledger and the first Shelley slot. Note that this number of slots
    -- is still guaranteed to be less than the forecast range of the HFC in the
    -- Byron era.
    forecast ::
         ShelleyLedgerConfig (ShelleyEra c)
      -> Bound
      -> SlotNo
      -> LedgerState ByronBlock
      -> Except
           OutsideForecastRange
           (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c)))
    forecast :: ShelleyLedgerConfig (ShelleyEra c)
-> Bound
-> SlotNo
-> LedgerState ByronBlock
-> Except
     OutsideForecastRange
     (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c)))
forecast ShelleyLedgerConfig (ShelleyEra c)
cfgShelley Bound
bound SlotNo
forecastFor LedgerState ByronBlock
currentByronState
        | SlotNo
forecastFor SlotNo -> SlotNo -> Bool
forall a. Ord a => a -> a -> Bool
< SlotNo
maxFor
        = WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Except
     OutsideForecastRange
     (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c)))
forall a. a -> ExceptT OutsideForecastRange Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c))
 -> Except
      OutsideForecastRange
      (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c))))
-> WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Except
     OutsideForecastRange
     (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c)))
forall a b. (a -> b) -> a -> b
$
            LedgerView (BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c))
forall blk. LedgerView (BlockProtocol blk) -> WrapLedgerView blk
WrapLedgerView (LedgerView
   (BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c)))
 -> WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> LedgerView
     (BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c))
forall a b. (a -> b) -> a -> b
$
              FromByronTranslationContext c -> LedgerView c
forall c. Crypto c => FromByronTranslationContext c -> LedgerView c
SL.mkInitialShelleyLedgerView
                (ShelleyGenesis c -> FromByronTranslationContext c
forall c. ShelleyGenesis c -> FromByronTranslationContext c
toFromByronTranslationContext (ShelleyLedgerConfig (ShelleyEra c)
-> ShelleyGenesis (EraCrypto (ShelleyEra c))
forall era.
ShelleyLedgerConfig era -> ShelleyGenesis (EraCrypto era)
shelleyLedgerGenesis ShelleyLedgerConfig (ShelleyEra c)
cfgShelley))
        | Bool
otherwise
        = OutsideForecastRange
-> Except
     OutsideForecastRange
     (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c)))
forall a.
OutsideForecastRange -> ExceptT OutsideForecastRange Identity a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (OutsideForecastRange
 -> Except
      OutsideForecastRange
      (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c))))
-> OutsideForecastRange
-> Except
     OutsideForecastRange
     (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c)))
forall a b. (a -> b) -> a -> b
$ OutsideForecastRange {
              outsideForecastAt :: WithOrigin SlotNo
outsideForecastAt     = LedgerState ByronBlock -> WithOrigin SlotNo
forall blk.
UpdateLedger blk =>
LedgerState blk -> WithOrigin SlotNo
ledgerTipSlot LedgerState ByronBlock
currentByronState
            , outsideForecastMaxFor :: SlotNo
outsideForecastMaxFor = SlotNo
maxFor
            , outsideForecastFor :: SlotNo
outsideForecastFor    = SlotNo
forecastFor
            }
      where
        globals :: Globals
globals = ShelleyLedgerConfig (ShelleyEra c) -> Globals
forall era. ShelleyLedgerConfig era -> Globals
shelleyLedgerGlobals ShelleyLedgerConfig (ShelleyEra c)
cfgShelley
        swindow :: Word64
swindow = Globals -> Word64
SL.stabilityWindow Globals
globals

        -- This is the exclusive upper bound of the forecast range
        --
        -- If Shelley's stability window is 0, it means we can't forecast /at
        -- all/ in the Shelley era. Not even to the first slot in the Shelley
        -- era! Remember that forecasting to slot @S@ means forecasting the
        -- ledger view obtained from the ledger state /after/ applying the block
        -- with slot @S@. If the stability window is 0, we can't even forecast
        -- after the very first "virtual" Shelley block, meaning we can't
        -- forecast into the Shelley era when still in the Byron era.
        maxFor :: SlotNo
        maxFor :: SlotNo
maxFor = Word64 -> SlotNo -> SlotNo
addSlots Word64
swindow (Bound -> SlotNo
boundSlot Bound
bound)

{-------------------------------------------------------------------------------
  Translation from Shelley to Allegra
-------------------------------------------------------------------------------}

translateLedgerStateShelleyToAllegraWrapper ::
     (PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
  => RequiringBoth
       WrapLedgerConfig
       (Translate LedgerState)
       (ShelleyBlock (TPraos c) (ShelleyEra c))
       (ShelleyBlock (TPraos c) (AllegraEra c))
translateLedgerStateShelleyToAllegraWrapper :: forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  (ShelleyBlock (TPraos c) (ShelleyEra c))
  (ShelleyBlock (TPraos c) (AllegraEra c))
translateLedgerStateShelleyToAllegraWrapper =
    Translate
  LedgerState
  (ShelleyBlock (TPraos c) (ShelleyEra c))
  (ShelleyBlock (TPraos c) (AllegraEra c))
-> RequiringBoth
     WrapLedgerConfig
     (Translate LedgerState)
     (ShelleyBlock (TPraos c) (ShelleyEra c))
     (ShelleyBlock (TPraos c) (AllegraEra c))
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (h :: k -> *).
f x y -> RequiringBoth h f x y
ignoringBoth (Translate
   LedgerState
   (ShelleyBlock (TPraos c) (ShelleyEra c))
   (ShelleyBlock (TPraos c) (AllegraEra c))
 -> RequiringBoth
      WrapLedgerConfig
      (Translate LedgerState)
      (ShelleyBlock (TPraos c) (ShelleyEra c))
      (ShelleyBlock (TPraos c) (AllegraEra c)))
-> Translate
     LedgerState
     (ShelleyBlock (TPraos c) (ShelleyEra c))
     (ShelleyBlock (TPraos c) (AllegraEra c))
-> RequiringBoth
     WrapLedgerConfig
     (Translate LedgerState)
     (ShelleyBlock (TPraos c) (ShelleyEra c))
     (ShelleyBlock (TPraos c) (AllegraEra c))
forall a b. (a -> b) -> a -> b
$
      (EpochNo
 -> LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c))
 -> LedgerState (ShelleyBlock (TPraos c) (AllegraEra c)))
-> Translate
     LedgerState
     (ShelleyBlock (TPraos c) (ShelleyEra c))
     (ShelleyBlock (TPraos c) (AllegraEra c))
forall (f :: * -> *) x y.
(EpochNo -> f x -> f y) -> Translate f x y
Translate ((EpochNo
  -> LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c))
  -> LedgerState (ShelleyBlock (TPraos c) (AllegraEra c)))
 -> Translate
      LedgerState
      (ShelleyBlock (TPraos c) (ShelleyEra c))
      (ShelleyBlock (TPraos c) (AllegraEra c)))
-> (EpochNo
    -> LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c))
    -> LedgerState (ShelleyBlock (TPraos c) (AllegraEra c)))
-> Translate
     LedgerState
     (ShelleyBlock (TPraos c) (ShelleyEra c))
     (ShelleyBlock (TPraos c) (AllegraEra c))
forall a b. (a -> b) -> a -> b
$ \EpochNo
_epochNo ->
        (:.:) LedgerState (ShelleyBlock (TPraos c)) (AllegraEra c)
-> LedgerState (ShelleyBlock (TPraos c) (AllegraEra c))
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp ((:.:) LedgerState (ShelleyBlock (TPraos c)) (AllegraEra c)
 -> LedgerState (ShelleyBlock (TPraos c) (AllegraEra c)))
-> (LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c))
    -> (:.:) LedgerState (ShelleyBlock (TPraos c)) (AllegraEra c))
-> LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c))
-> LedgerState (ShelleyBlock (TPraos c) (AllegraEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (AllegraEra c)
-> (:.:)
     LedgerState (ShelleyBlock (TPraos c)) (PreviousEra (AllegraEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (AllegraEra c)
forall era (f :: * -> *).
(TranslateEra era f, TranslationError era f ~ Void) =>
TranslationContext era -> f (PreviousEra era) -> f era
SL.translateEra' TranslationContext (AllegraEra c)
NoGenesis (AllegraEra c)
forall era. NoGenesis era
SL.NoGenesis ((:.:) LedgerState (ShelleyBlock (TPraos c)) (ShelleyEra c)
 -> (:.:) LedgerState (ShelleyBlock (TPraos c)) (AllegraEra c))
-> (LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c))
    -> (:.:) LedgerState (ShelleyBlock (TPraos c)) (ShelleyEra c))
-> LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (AllegraEra c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (ShelleyEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp

translateTxShelleyToAllegraWrapper ::
     (PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
  => InjectTx
       (ShelleyBlock (TPraos c) (ShelleyEra c))
       (ShelleyBlock (TPraos c) (AllegraEra c))
translateTxShelleyToAllegraWrapper :: forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
InjectTx
  (ShelleyBlock (TPraos c) (ShelleyEra c))
  (ShelleyBlock (TPraos c) (AllegraEra c))
translateTxShelleyToAllegraWrapper = (GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
 -> Maybe (GenTx (ShelleyBlock (TPraos c) (AllegraEra c))))
-> InjectTx
     (ShelleyBlock (TPraos c) (ShelleyEra c))
     (ShelleyBlock (TPraos c) (AllegraEra c))
forall blk blk'.
(GenTx blk -> Maybe (GenTx blk')) -> InjectTx blk blk'
InjectTx ((GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
  -> Maybe (GenTx (ShelleyBlock (TPraos c) (AllegraEra c))))
 -> InjectTx
      (ShelleyBlock (TPraos c) (ShelleyEra c))
      (ShelleyBlock (TPraos c) (AllegraEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
    -> Maybe (GenTx (ShelleyBlock (TPraos c) (AllegraEra c))))
-> InjectTx
     (ShelleyBlock (TPraos c) (ShelleyEra c))
     (ShelleyBlock (TPraos c) (AllegraEra c))
forall a b. (a -> b) -> a -> b
$
    ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c)
 -> GenTx (ShelleyBlock (TPraos c) (AllegraEra c)))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (AllegraEra c)))
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c)
-> GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp (Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
 -> Maybe (GenTx (ShelleyBlock (TPraos c) (AllegraEra c))))
-> (GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
    -> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (AllegraEra c)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
  DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall a b. Either a b -> Maybe b
eitherToMaybe (Either
   DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
 -> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
    -> Either
         DecoderError
         ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except
  DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
-> Either
     DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall e a. Except e a -> Either e a
runExcept (Except
   DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
 -> Either
      DecoderError
      ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
    -> Except
         DecoderError
         ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Either
     DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (AllegraEra c)
-> (:.:)
     GenTx (ShelleyBlock (TPraos c)) (PreviousEra (AllegraEra c))
-> Except
     (TranslationError
        (AllegraEra c) (GenTx :.: ShelleyBlock (TPraos c)))
     ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra TranslationContext (AllegraEra c)
NoGenesis (AllegraEra c)
forall era. NoGenesis era
SL.NoGenesis ((:.:) GenTx (ShelleyBlock (TPraos c)) (ShelleyEra c)
 -> Except
      DecoderError
      ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
    -> (:.:) GenTx (ShelleyBlock (TPraos c)) (ShelleyEra c))
-> GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Except
     DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> (:.:) GenTx (ShelleyBlock (TPraos c)) (ShelleyEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp

translateValidatedTxShelleyToAllegraWrapper ::
     (PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
  => InjectValidatedTx
       (ShelleyBlock (TPraos c) (ShelleyEra c))
       (ShelleyBlock (TPraos c) (AllegraEra c))
translateValidatedTxShelleyToAllegraWrapper :: forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
InjectValidatedTx
  (ShelleyBlock (TPraos c) (ShelleyEra c))
  (ShelleyBlock (TPraos c) (AllegraEra c))
translateValidatedTxShelleyToAllegraWrapper = (WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
 -> Maybe
      (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))))
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) (ShelleyEra c))
     (ShelleyBlock (TPraos c) (AllegraEra c))
forall blk blk'.
(WrapValidatedGenTx blk -> Maybe (WrapValidatedGenTx blk'))
-> InjectValidatedTx blk blk'
InjectValidatedTx ((WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
  -> Maybe
       (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))))
 -> InjectValidatedTx
      (ShelleyBlock (TPraos c) (ShelleyEra c))
      (ShelleyBlock (TPraos c) (AllegraEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
    -> Maybe
         (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))))
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) (ShelleyEra c))
     (ShelleyBlock (TPraos c) (AllegraEra c))
forall a b. (a -> b) -> a -> b
$
    ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c)
 -> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c)))
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
-> Maybe
     (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c)))
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c)
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp (Maybe
   ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
 -> Maybe
      (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
    -> Maybe
         ((:.:)
            WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Maybe
     (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
  DecoderError
  ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall a b. Either a b -> Maybe b
eitherToMaybe (Either
   DecoderError
   ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
 -> Maybe
      ((:.:)
         WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
    -> Either
         DecoderError
         ((:.:)
            WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except
  DecoderError
  ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
-> Either
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall e a. Except e a -> Either e a
runExcept (Except
   DecoderError
   ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
 -> Either
      DecoderError
      ((:.:)
         WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
    -> Except
         DecoderError
         ((:.:)
            WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Either
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (AllegraEra c)
-> (:.:)
     WrapValidatedGenTx
     (ShelleyBlock (TPraos c))
     (PreviousEra (AllegraEra c))
-> Except
     (TranslationError
        (AllegraEra c) (WrapValidatedGenTx :.: ShelleyBlock (TPraos c)))
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra TranslationContext (AllegraEra c)
NoGenesis (AllegraEra c)
forall era. NoGenesis era
SL.NoGenesis ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (ShelleyEra c)
 -> Except
      DecoderError
      ((:.:)
         WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
    -> (:.:)
         WrapValidatedGenTx (ShelleyBlock (TPraos c)) (ShelleyEra c))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Except
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> (:.:)
     WrapValidatedGenTx (ShelleyBlock (TPraos c)) (ShelleyEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp

{-------------------------------------------------------------------------------
  Translation from Allegra to Mary
-------------------------------------------------------------------------------}

translateLedgerStateAllegraToMaryWrapper ::
     (PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
  => RequiringBoth
       WrapLedgerConfig
       (Translate LedgerState)
       (ShelleyBlock (TPraos c) (AllegraEra c))
       (ShelleyBlock (TPraos c) (MaryEra c))
translateLedgerStateAllegraToMaryWrapper :: forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  (ShelleyBlock (TPraos c) (AllegraEra c))
  (ShelleyBlock (TPraos c) (MaryEra c))
translateLedgerStateAllegraToMaryWrapper =
    Translate
  LedgerState
  (ShelleyBlock (TPraos c) (AllegraEra c))
  (ShelleyBlock (TPraos c) (MaryEra c))
-> RequiringBoth
     WrapLedgerConfig
     (Translate LedgerState)
     (ShelleyBlock (TPraos c) (AllegraEra c))
     (ShelleyBlock (TPraos c) (MaryEra c))
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (h :: k -> *).
f x y -> RequiringBoth h f x y
ignoringBoth (Translate
   LedgerState
   (ShelleyBlock (TPraos c) (AllegraEra c))
   (ShelleyBlock (TPraos c) (MaryEra c))
 -> RequiringBoth
      WrapLedgerConfig
      (Translate LedgerState)
      (ShelleyBlock (TPraos c) (AllegraEra c))
      (ShelleyBlock (TPraos c) (MaryEra c)))
-> Translate
     LedgerState
     (ShelleyBlock (TPraos c) (AllegraEra c))
     (ShelleyBlock (TPraos c) (MaryEra c))
-> RequiringBoth
     WrapLedgerConfig
     (Translate LedgerState)
     (ShelleyBlock (TPraos c) (AllegraEra c))
     (ShelleyBlock (TPraos c) (MaryEra c))
forall a b. (a -> b) -> a -> b
$
      (EpochNo
 -> LedgerState (ShelleyBlock (TPraos c) (AllegraEra c))
 -> LedgerState (ShelleyBlock (TPraos c) (MaryEra c)))
-> Translate
     LedgerState
     (ShelleyBlock (TPraos c) (AllegraEra c))
     (ShelleyBlock (TPraos c) (MaryEra c))
forall (f :: * -> *) x y.
(EpochNo -> f x -> f y) -> Translate f x y
Translate ((EpochNo
  -> LedgerState (ShelleyBlock (TPraos c) (AllegraEra c))
  -> LedgerState (ShelleyBlock (TPraos c) (MaryEra c)))
 -> Translate
      LedgerState
      (ShelleyBlock (TPraos c) (AllegraEra c))
      (ShelleyBlock (TPraos c) (MaryEra c)))
-> (EpochNo
    -> LedgerState (ShelleyBlock (TPraos c) (AllegraEra c))
    -> LedgerState (ShelleyBlock (TPraos c) (MaryEra c)))
-> Translate
     LedgerState
     (ShelleyBlock (TPraos c) (AllegraEra c))
     (ShelleyBlock (TPraos c) (MaryEra c))
forall a b. (a -> b) -> a -> b
$ \EpochNo
_epochNo ->
        (:.:) LedgerState (ShelleyBlock (TPraos c)) (MaryEra c)
-> LedgerState (ShelleyBlock (TPraos c) (MaryEra c))
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp ((:.:) LedgerState (ShelleyBlock (TPraos c)) (MaryEra c)
 -> LedgerState (ShelleyBlock (TPraos c) (MaryEra c)))
-> (LedgerState (ShelleyBlock (TPraos c) (AllegraEra c))
    -> (:.:) LedgerState (ShelleyBlock (TPraos c)) (MaryEra c))
-> LedgerState (ShelleyBlock (TPraos c) (AllegraEra c))
-> LedgerState (ShelleyBlock (TPraos c) (MaryEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (MaryEra c)
-> (:.:)
     LedgerState (ShelleyBlock (TPraos c)) (PreviousEra (MaryEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (MaryEra c)
forall era (f :: * -> *).
(TranslateEra era f, TranslationError era f ~ Void) =>
TranslationContext era -> f (PreviousEra era) -> f era
SL.translateEra' TranslationContext (MaryEra c)
NoGenesis (MaryEra c)
forall era. NoGenesis era
SL.NoGenesis ((:.:) LedgerState (ShelleyBlock (TPraos c)) (AllegraEra c)
 -> (:.:) LedgerState (ShelleyBlock (TPraos c)) (MaryEra c))
-> (LedgerState (ShelleyBlock (TPraos c) (AllegraEra c))
    -> (:.:) LedgerState (ShelleyBlock (TPraos c)) (AllegraEra c))
-> LedgerState (ShelleyBlock (TPraos c) (AllegraEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (MaryEra c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (TPraos c) (AllegraEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (AllegraEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp

translateTxAllegraToMaryWrapper ::
     (PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
  => InjectTx
       (ShelleyBlock (TPraos c) (AllegraEra c))
       (ShelleyBlock (TPraos c) (MaryEra c))
translateTxAllegraToMaryWrapper :: forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
InjectTx
  (ShelleyBlock (TPraos c) (AllegraEra c))
  (ShelleyBlock (TPraos c) (MaryEra c))
translateTxAllegraToMaryWrapper = (GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
 -> Maybe (GenTx (ShelleyBlock (TPraos c) (MaryEra c))))
-> InjectTx
     (ShelleyBlock (TPraos c) (AllegraEra c))
     (ShelleyBlock (TPraos c) (MaryEra c))
forall blk blk'.
(GenTx blk -> Maybe (GenTx blk')) -> InjectTx blk blk'
InjectTx ((GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
  -> Maybe (GenTx (ShelleyBlock (TPraos c) (MaryEra c))))
 -> InjectTx
      (ShelleyBlock (TPraos c) (AllegraEra c))
      (ShelleyBlock (TPraos c) (MaryEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
    -> Maybe (GenTx (ShelleyBlock (TPraos c) (MaryEra c))))
-> InjectTx
     (ShelleyBlock (TPraos c) (AllegraEra c))
     (ShelleyBlock (TPraos c) (MaryEra c))
forall a b. (a -> b) -> a -> b
$
    ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c)
 -> GenTx (ShelleyBlock (TPraos c) (MaryEra c)))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (MaryEra c)))
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c)
-> GenTx (ShelleyBlock (TPraos c) (MaryEra c))
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp (Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
 -> Maybe (GenTx (ShelleyBlock (TPraos c) (MaryEra c))))
-> (GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
    -> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (MaryEra c)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
  DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall a b. Either a b -> Maybe b
eitherToMaybe (Either
   DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
 -> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
    -> Either
         DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except
  DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
-> Either
     DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall e a. Except e a -> Either e a
runExcept (Except
   DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
 -> Either
      DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
    -> Except
         DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Either
     DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (MaryEra c)
-> (:.:) GenTx (ShelleyBlock (TPraos c)) (PreviousEra (MaryEra c))
-> Except
     (TranslationError (MaryEra c) (GenTx :.: ShelleyBlock (TPraos c)))
     ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra TranslationContext (MaryEra c)
NoGenesis (MaryEra c)
forall era. NoGenesis era
SL.NoGenesis ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c)
 -> Except
      DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
    -> (:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
-> GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Except
     DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> (:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp

translateValidatedTxAllegraToMaryWrapper ::
     (PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
  => InjectValidatedTx
       (ShelleyBlock (TPraos c) (AllegraEra c))
       (ShelleyBlock (TPraos c) (MaryEra c))
translateValidatedTxAllegraToMaryWrapper :: forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
InjectValidatedTx
  (ShelleyBlock (TPraos c) (AllegraEra c))
  (ShelleyBlock (TPraos c) (MaryEra c))
translateValidatedTxAllegraToMaryWrapper = (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
 -> Maybe
      (WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))))
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) (AllegraEra c))
     (ShelleyBlock (TPraos c) (MaryEra c))
forall blk blk'.
(WrapValidatedGenTx blk -> Maybe (WrapValidatedGenTx blk'))
-> InjectValidatedTx blk blk'
InjectValidatedTx ((WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
  -> Maybe
       (WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))))
 -> InjectValidatedTx
      (ShelleyBlock (TPraos c) (AllegraEra c))
      (ShelleyBlock (TPraos c) (MaryEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
    -> Maybe
         (WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))))
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) (AllegraEra c))
     (ShelleyBlock (TPraos c) (MaryEra c))
forall a b. (a -> b) -> a -> b
$
    ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c)
 -> WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c)))
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
-> Maybe (WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c)))
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c)
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp (Maybe
   ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
 -> Maybe
      (WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
    -> Maybe
         ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Maybe (WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
  DecoderError
  ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall a b. Either a b -> Maybe b
eitherToMaybe (Either
   DecoderError
   ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
 -> Maybe
      ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
    -> Either
         DecoderError
         ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except
  DecoderError
  ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
-> Either
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall e a. Except e a -> Either e a
runExcept (Except
   DecoderError
   ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
 -> Either
      DecoderError
      ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
    -> Except
         DecoderError
         ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Either
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (MaryEra c)
-> (:.:)
     WrapValidatedGenTx
     (ShelleyBlock (TPraos c))
     (PreviousEra (MaryEra c))
-> Except
     (TranslationError
        (MaryEra c) (WrapValidatedGenTx :.: ShelleyBlock (TPraos c)))
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra TranslationContext (MaryEra c)
NoGenesis (MaryEra c)
forall era. NoGenesis era
SL.NoGenesis ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c)
 -> Except
      DecoderError
      ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
    -> (:.:)
         WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Except
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> (:.:)
     WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp

{-------------------------------------------------------------------------------
  Translation from Mary to Alonzo
-------------------------------------------------------------------------------}

translateLedgerStateMaryToAlonzoWrapper ::
     (PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
  => RequiringBoth
       WrapLedgerConfig
       (Translate LedgerState)
       (ShelleyBlock (TPraos c) (MaryEra c))
       (ShelleyBlock (TPraos c) (AlonzoEra c))
translateLedgerStateMaryToAlonzoWrapper :: forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  (ShelleyBlock (TPraos c) (MaryEra c))
  (ShelleyBlock (TPraos c) (AlonzoEra c))
translateLedgerStateMaryToAlonzoWrapper =
    (WrapLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
 -> WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
 -> Translate
      LedgerState
      (ShelleyBlock (TPraos c) (MaryEra c))
      (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> RequiringBoth
     WrapLedgerConfig
     (Translate LedgerState)
     (ShelleyBlock (TPraos c) (MaryEra c))
     (ShelleyBlock (TPraos c) (AlonzoEra c))
forall {k} (h :: k -> *) (f :: k -> k -> *) (x :: k) (y :: k).
(h x -> h y -> f x y) -> RequiringBoth h f x y
RequireBoth ((WrapLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
  -> WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
  -> Translate
       LedgerState
       (ShelleyBlock (TPraos c) (MaryEra c))
       (ShelleyBlock (TPraos c) (AlonzoEra c)))
 -> RequiringBoth
      WrapLedgerConfig
      (Translate LedgerState)
      (ShelleyBlock (TPraos c) (MaryEra c))
      (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> (WrapLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
    -> WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
    -> Translate
         LedgerState
         (ShelleyBlock (TPraos c) (MaryEra c))
         (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> RequiringBoth
     WrapLedgerConfig
     (Translate LedgerState)
     (ShelleyBlock (TPraos c) (MaryEra c))
     (ShelleyBlock (TPraos c) (AlonzoEra c))
forall a b. (a -> b) -> a -> b
$ \WrapLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
_cfgMary WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
cfgAlonzo ->
      (EpochNo
 -> LedgerState (ShelleyBlock (TPraos c) (MaryEra c))
 -> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> Translate
     LedgerState
     (ShelleyBlock (TPraos c) (MaryEra c))
     (ShelleyBlock (TPraos c) (AlonzoEra c))
forall (f :: * -> *) x y.
(EpochNo -> f x -> f y) -> Translate f x y
Translate ((EpochNo
  -> LedgerState (ShelleyBlock (TPraos c) (MaryEra c))
  -> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c)))
 -> Translate
      LedgerState
      (ShelleyBlock (TPraos c) (MaryEra c))
      (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> (EpochNo
    -> LedgerState (ShelleyBlock (TPraos c) (MaryEra c))
    -> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> Translate
     LedgerState
     (ShelleyBlock (TPraos c) (MaryEra c))
     (ShelleyBlock (TPraos c) (AlonzoEra c))
forall a b. (a -> b) -> a -> b
$ \EpochNo
_epochNo ->
        (:.:) LedgerState (ShelleyBlock (TPraos c)) (AlonzoEra c)
-> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp ((:.:) LedgerState (ShelleyBlock (TPraos c)) (AlonzoEra c)
 -> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> (LedgerState (ShelleyBlock (TPraos c) (MaryEra c))
    -> (:.:) LedgerState (ShelleyBlock (TPraos c)) (AlonzoEra c))
-> LedgerState (ShelleyBlock (TPraos c) (MaryEra c))
-> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (AlonzoEra c)
-> (:.:)
     LedgerState (ShelleyBlock (TPraos c)) (PreviousEra (AlonzoEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (AlonzoEra c)
forall era (f :: * -> *).
(TranslateEra era f, TranslationError era f ~ Void) =>
TranslationContext era -> f (PreviousEra era) -> f era
SL.translateEra' (WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> TranslationContext (AlonzoEra c)
forall c.
WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> TranslationContext (AlonzoEra c)
getAlonzoTranslationContext WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
cfgAlonzo) ((:.:) LedgerState (ShelleyBlock (TPraos c)) (MaryEra c)
 -> (:.:) LedgerState (ShelleyBlock (TPraos c)) (AlonzoEra c))
-> (LedgerState (ShelleyBlock (TPraos c) (MaryEra c))
    -> (:.:) LedgerState (ShelleyBlock (TPraos c)) (MaryEra c))
-> LedgerState (ShelleyBlock (TPraos c) (MaryEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (AlonzoEra c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (TPraos c) (MaryEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (MaryEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp

getAlonzoTranslationContext ::
     WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
  -> SL.TranslationContext (AlonzoEra c)
getAlonzoTranslationContext :: forall c.
WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> TranslationContext (AlonzoEra c)
getAlonzoTranslationContext =
    ShelleyLedgerConfig (AlonzoEra c)
-> TranslationContext (AlonzoEra c)
ShelleyLedgerConfig (AlonzoEra c) -> AlonzoGenesis
forall era. ShelleyLedgerConfig era -> TranslationContext era
shelleyLedgerTranslationContext (ShelleyLedgerConfig (AlonzoEra c) -> AlonzoGenesis)
-> (WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
    -> ShelleyLedgerConfig (AlonzoEra c))
-> WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> AlonzoGenesis
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> LedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> ShelleyLedgerConfig (AlonzoEra c)
forall blk. WrapLedgerConfig blk -> LedgerConfig blk
unwrapLedgerConfig

translateTxMaryToAlonzoWrapper ::
     (PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
  => SL.TranslationContext (AlonzoEra c)
  -> InjectTx
       (ShelleyBlock (TPraos c) (MaryEra c))
       (ShelleyBlock (TPraos c) (AlonzoEra c))
translateTxMaryToAlonzoWrapper :: forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
TranslationContext (AlonzoEra c)
-> InjectTx
     (ShelleyBlock (TPraos c) (MaryEra c))
     (ShelleyBlock (TPraos c) (AlonzoEra c))
translateTxMaryToAlonzoWrapper TranslationContext (AlonzoEra c)
ctxt = (GenTx (ShelleyBlock (TPraos c) (MaryEra c))
 -> Maybe (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))))
-> InjectTx
     (ShelleyBlock (TPraos c) (MaryEra c))
     (ShelleyBlock (TPraos c) (AlonzoEra c))
forall blk blk'.
(GenTx blk -> Maybe (GenTx blk')) -> InjectTx blk blk'
InjectTx ((GenTx (ShelleyBlock (TPraos c) (MaryEra c))
  -> Maybe (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))))
 -> InjectTx
      (ShelleyBlock (TPraos c) (MaryEra c))
      (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (MaryEra c))
    -> Maybe (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))))
-> InjectTx
     (ShelleyBlock (TPraos c) (MaryEra c))
     (ShelleyBlock (TPraos c) (AlonzoEra c))
forall a b. (a -> b) -> a -> b
$
    ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)
 -> GenTx (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c)))
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)
-> GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp (Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
 -> Maybe (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))))
-> (GenTx (ShelleyBlock (TPraos c) (MaryEra c))
    -> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> GenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
  DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall a b. Either a b -> Maybe b
eitherToMaybe (Either
   DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
 -> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (MaryEra c))
    -> Either
         DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> GenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except
  DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
-> Either
     DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall e a. Except e a -> Either e a
runExcept (Except
   DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
 -> Either
      DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (MaryEra c))
    -> Except
         DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> GenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Either
     DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (AlonzoEra c)
-> (:.:)
     GenTx (ShelleyBlock (TPraos c)) (PreviousEra (AlonzoEra c))
-> Except
     (TranslationError
        (AlonzoEra c) (GenTx :.: ShelleyBlock (TPraos c)))
     ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra TranslationContext (AlonzoEra c)
ctxt ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c)
 -> Except
      DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (MaryEra c))
    -> (:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
-> GenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Except
     DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> (:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp

translateValidatedTxMaryToAlonzoWrapper ::
     forall c.
     (PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
  => SL.TranslationContext (AlonzoEra c)
  -> InjectValidatedTx
       (ShelleyBlock (TPraos c) (MaryEra c))
       (ShelleyBlock (TPraos c) (AlonzoEra c))
translateValidatedTxMaryToAlonzoWrapper :: forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
TranslationContext (AlonzoEra c)
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) (MaryEra c))
     (ShelleyBlock (TPraos c) (AlonzoEra c))
translateValidatedTxMaryToAlonzoWrapper TranslationContext (AlonzoEra c)
ctxt = (WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
 -> Maybe
      (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))))
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) (MaryEra c))
     (ShelleyBlock (TPraos c) (AlonzoEra c))
forall blk blk'.
(WrapValidatedGenTx blk -> Maybe (WrapValidatedGenTx blk'))
-> InjectValidatedTx blk blk'
InjectValidatedTx ((WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
  -> Maybe
       (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))))
 -> InjectValidatedTx
      (ShelleyBlock (TPraos c) (MaryEra c))
      (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
    -> Maybe
         (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))))
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) (MaryEra c))
     (ShelleyBlock (TPraos c) (AlonzoEra c))
forall a b. (a -> b) -> a -> b
$
    ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)
 -> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
-> Maybe
     (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c)))
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp (Maybe
   ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
 -> Maybe
      (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
    -> Maybe
         ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Maybe
     (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
  DecoderError
  ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall a b. Either a b -> Maybe b
eitherToMaybe (Either
   DecoderError
   ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
 -> Maybe
      ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
    -> Either
         DecoderError
         ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except
  DecoderError
  ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
-> Either
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall e a. Except e a -> Either e a
runExcept (Except
   DecoderError
   ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
 -> Either
      DecoderError
      ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
    -> Except
         DecoderError
         ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Either
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (AlonzoEra c)
-> (:.:)
     WrapValidatedGenTx
     (ShelleyBlock (TPraos c))
     (PreviousEra (AlonzoEra c))
-> Except
     (TranslationError
        (AlonzoEra c) (WrapValidatedGenTx :.: ShelleyBlock (TPraos c)))
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra TranslationContext (AlonzoEra c)
ctxt ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c)
 -> Except
      DecoderError
      ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
    -> (:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Except
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> (:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp

{-------------------------------------------------------------------------------
  Translation from Alonzo to Babbage
-------------------------------------------------------------------------------}

translateLedgerStateAlonzoToBabbageWrapper ::
     (Praos.PraosCrypto c, TPraos.PraosCrypto c)
  => RequiringBoth
       WrapLedgerConfig
       (Translate LedgerState)
       (ShelleyBlock (TPraos c) (AlonzoEra c))
       (ShelleyBlock (Praos c) (BabbageEra c))
translateLedgerStateAlonzoToBabbageWrapper :: forall c.
(PraosCrypto c, PraosCrypto c) =>
RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  (ShelleyBlock (TPraos c) (AlonzoEra c))
  (ShelleyBlock (Praos c) (BabbageEra c))
translateLedgerStateAlonzoToBabbageWrapper =
    (WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
 -> WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
 -> Translate
      LedgerState
      (ShelleyBlock (TPraos c) (AlonzoEra c))
      (ShelleyBlock (Praos c) (BabbageEra c)))
-> RequiringBoth
     WrapLedgerConfig
     (Translate LedgerState)
     (ShelleyBlock (TPraos c) (AlonzoEra c))
     (ShelleyBlock (Praos c) (BabbageEra c))
forall {k} (h :: k -> *) (f :: k -> k -> *) (x :: k) (y :: k).
(h x -> h y -> f x y) -> RequiringBoth h f x y
RequireBoth ((WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
  -> WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
  -> Translate
       LedgerState
       (ShelleyBlock (TPraos c) (AlonzoEra c))
       (ShelleyBlock (Praos c) (BabbageEra c)))
 -> RequiringBoth
      WrapLedgerConfig
      (Translate LedgerState)
      (ShelleyBlock (TPraos c) (AlonzoEra c))
      (ShelleyBlock (Praos c) (BabbageEra c)))
-> (WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
    -> WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
    -> Translate
         LedgerState
         (ShelleyBlock (TPraos c) (AlonzoEra c))
         (ShelleyBlock (Praos c) (BabbageEra c)))
-> RequiringBoth
     WrapLedgerConfig
     (Translate LedgerState)
     (ShelleyBlock (TPraos c) (AlonzoEra c))
     (ShelleyBlock (Praos c) (BabbageEra c))
forall a b. (a -> b) -> a -> b
$ \WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
_cfgAlonzo WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
_cfgBabbage ->
      (EpochNo
 -> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
 -> LedgerState (ShelleyBlock (Praos c) (BabbageEra c)))
-> Translate
     LedgerState
     (ShelleyBlock (TPraos c) (AlonzoEra c))
     (ShelleyBlock (Praos c) (BabbageEra c))
forall (f :: * -> *) x y.
(EpochNo -> f x -> f y) -> Translate f x y
Translate ((EpochNo
  -> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
  -> LedgerState (ShelleyBlock (Praos c) (BabbageEra c)))
 -> Translate
      LedgerState
      (ShelleyBlock (TPraos c) (AlonzoEra c))
      (ShelleyBlock (Praos c) (BabbageEra c)))
-> (EpochNo
    -> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
    -> LedgerState (ShelleyBlock (Praos c) (BabbageEra c)))
-> Translate
     LedgerState
     (ShelleyBlock (TPraos c) (AlonzoEra c))
     (ShelleyBlock (Praos c) (BabbageEra c))
forall a b. (a -> b) -> a -> b
$ \EpochNo
_epochNo ->
        (:.:) LedgerState (ShelleyBlock (Praos c)) (BabbageEra c)
-> LedgerState (ShelleyBlock (Praos c) (BabbageEra c))
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp ((:.:) LedgerState (ShelleyBlock (Praos c)) (BabbageEra c)
 -> LedgerState (ShelleyBlock (Praos c) (BabbageEra c)))
-> (LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
    -> (:.:) LedgerState (ShelleyBlock (Praos c)) (BabbageEra c))
-> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
-> LedgerState (ShelleyBlock (Praos c) (BabbageEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (BabbageEra c)
-> (:.:)
     LedgerState (ShelleyBlock (Praos c)) (PreviousEra (BabbageEra c))
-> (:.:) LedgerState (ShelleyBlock (Praos c)) (BabbageEra c)
forall era (f :: * -> *).
(TranslateEra era f, TranslationError era f ~ Void) =>
TranslationContext era -> f (PreviousEra era) -> f era
SL.translateEra' TranslationContext (BabbageEra c)
NoGenesis (BabbageEra c)
forall era. NoGenesis era
SL.NoGenesis ((:.:) LedgerState (ShelleyBlock (Praos c)) (AlonzoEra c)
 -> (:.:) LedgerState (ShelleyBlock (Praos c)) (BabbageEra c))
-> (LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
    -> (:.:) LedgerState (ShelleyBlock (Praos c)) (AlonzoEra c))
-> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
-> (:.:) LedgerState (ShelleyBlock (Praos c)) (BabbageEra c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (Praos c) (AlonzoEra c))
-> (:.:) LedgerState (ShelleyBlock (Praos c)) (AlonzoEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp (LedgerState (ShelleyBlock (Praos c) (AlonzoEra c))
 -> (:.:) LedgerState (ShelleyBlock (Praos c)) (AlonzoEra c))
-> (LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
    -> LedgerState (ShelleyBlock (Praos c) (AlonzoEra c)))
-> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
-> (:.:) LedgerState (ShelleyBlock (Praos c)) (AlonzoEra c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
-> LedgerState (ShelleyBlock (Praos c) (AlonzoEra c))
forall c.
LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
-> LedgerState (ShelleyBlock (Praos c) (AlonzoEra c))
transPraosLS
  where
    transPraosLS ::
      LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c)) ->
      LedgerState (ShelleyBlock (Praos c)  (AlonzoEra c))
    transPraosLS :: forall c.
LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
-> LedgerState (ShelleyBlock (Praos c) (AlonzoEra c))
transPraosLS (ShelleyLedgerState WithOrigin (ShelleyTip (TPraos c) (AlonzoEra c))
wo NewEpochState (AlonzoEra c)
nes ShelleyTransition
st) =
      ShelleyLedgerState
        { shelleyLedgerTip :: WithOrigin (ShelleyTip (Praos c) (AlonzoEra c))
shelleyLedgerTip        = (ShelleyTip (TPraos c) (AlonzoEra c)
 -> ShelleyTip (Praos c) (AlonzoEra c))
-> WithOrigin (ShelleyTip (TPraos c) (AlonzoEra c))
-> WithOrigin (ShelleyTip (Praos c) (AlonzoEra c))
forall a b. (a -> b) -> WithOrigin a -> WithOrigin b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShelleyTip (TPraos c) (AlonzoEra c)
-> ShelleyTip (Praos c) (AlonzoEra c)
forall proto era proto' era'.
(HeaderHash (ShelleyBlock proto era)
 ~ HeaderHash (ShelleyBlock proto' era')) =>
ShelleyTip proto era -> ShelleyTip proto' era'
castShelleyTip WithOrigin (ShelleyTip (TPraos c) (AlonzoEra c))
wo
        , shelleyLedgerState :: NewEpochState (AlonzoEra c)
shelleyLedgerState      = NewEpochState (AlonzoEra c)
nes
        , shelleyLedgerTransition :: ShelleyTransition
shelleyLedgerTransition = ShelleyTransition
st
        }

translateTxAlonzoToBabbageWrapper ::
     (Praos.PraosCrypto c)
  => SL.TranslationContext (BabbageEra c)
  -> InjectTx
       (ShelleyBlock (TPraos c) (AlonzoEra c))
       (ShelleyBlock (Praos c) (BabbageEra c))
translateTxAlonzoToBabbageWrapper :: forall c.
PraosCrypto c =>
TranslationContext (BabbageEra c)
-> InjectTx
     (ShelleyBlock (TPraos c) (AlonzoEra c))
     (ShelleyBlock (Praos c) (BabbageEra c))
translateTxAlonzoToBabbageWrapper TranslationContext (BabbageEra c)
ctxt = (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
 -> Maybe (GenTx (ShelleyBlock (Praos c) (BabbageEra c))))
-> InjectTx
     (ShelleyBlock (TPraos c) (AlonzoEra c))
     (ShelleyBlock (Praos c) (BabbageEra c))
forall blk blk'.
(GenTx blk -> Maybe (GenTx blk')) -> InjectTx blk blk'
InjectTx ((GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
  -> Maybe (GenTx (ShelleyBlock (Praos c) (BabbageEra c))))
 -> InjectTx
      (ShelleyBlock (TPraos c) (AlonzoEra c))
      (ShelleyBlock (Praos c) (BabbageEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
    -> Maybe (GenTx (ShelleyBlock (Praos c) (BabbageEra c))))
-> InjectTx
     (ShelleyBlock (TPraos c) (AlonzoEra c))
     (ShelleyBlock (Praos c) (BabbageEra c))
forall a b. (a -> b) -> a -> b
$
    ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c)
 -> GenTx (ShelleyBlock (Praos c) (BabbageEra c)))
-> Maybe ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
-> Maybe (GenTx (ShelleyBlock (Praos c) (BabbageEra c)))
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c)
-> GenTx (ShelleyBlock (Praos c) (BabbageEra c))
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp (Maybe ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
 -> Maybe (GenTx (ShelleyBlock (Praos c) (BabbageEra c))))
-> (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
    -> Maybe ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Maybe (GenTx (ShelleyBlock (Praos c) (BabbageEra c)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
  DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall a b. Either a b -> Maybe b
eitherToMaybe (Either
   DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
 -> Maybe ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
    -> Either
         DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except
  DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
-> Either
     DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall e a. Except e a -> Either e a
runExcept (Except
   DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
 -> Either
      DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
    -> Except
         DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Either
     DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (BabbageEra c)
-> (:.:)
     GenTx (ShelleyBlock (Praos c)) (PreviousEra (BabbageEra c))
-> Except
     (TranslationError
        (BabbageEra c) (GenTx :.: ShelleyBlock (Praos c)))
     ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra TranslationContext (BabbageEra c)
ctxt ((:.:) GenTx (ShelleyBlock (Praos c)) (AlonzoEra c)
 -> Except
      DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
    -> (:.:) GenTx (ShelleyBlock (Praos c)) (AlonzoEra c))
-> GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Except
     DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenTx (ShelleyBlock (Praos c) (AlonzoEra c))
-> (:.:) GenTx (ShelleyBlock (Praos c)) (AlonzoEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp (GenTx (ShelleyBlock (Praos c) (AlonzoEra c))
 -> (:.:) GenTx (ShelleyBlock (Praos c)) (AlonzoEra c))
-> (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
    -> GenTx (ShelleyBlock (Praos c) (AlonzoEra c)))
-> GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> (:.:) GenTx (ShelleyBlock (Praos c)) (AlonzoEra c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> GenTx (ShelleyBlock (Praos c) (AlonzoEra c))
forall c.
GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> GenTx (ShelleyBlock (Praos c) (AlonzoEra c))
transPraosTx
  where
    transPraosTx
      :: GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
      -> GenTx (ShelleyBlock (Praos c) (AlonzoEra c))
    transPraosTx :: forall c.
GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> GenTx (ShelleyBlock (Praos c) (AlonzoEra c))
transPraosTx (ShelleyTx TxId (EraCrypto (AlonzoEra c))
ti Tx (AlonzoEra c)
tx) = TxId (EraCrypto (AlonzoEra c))
-> Tx (AlonzoEra c) -> GenTx (ShelleyBlock (Praos c) (AlonzoEra c))
forall proto era.
TxId (EraCrypto era) -> Tx era -> GenTx (ShelleyBlock proto era)
ShelleyTx TxId (EraCrypto (AlonzoEra c))
ti (AlonzoTx (AlonzoEra c) -> AlonzoTx (AlonzoEra c)
forall a b. Coercible a b => a -> b
coerce Tx (AlonzoEra c)
AlonzoTx (AlonzoEra c)
tx)

translateValidatedTxAlonzoToBabbageWrapper ::
     forall c.
     (Praos.PraosCrypto c)
  => SL.TranslationContext (BabbageEra c)
  -> InjectValidatedTx
       (ShelleyBlock (TPraos c) (AlonzoEra c))
       (ShelleyBlock (Praos c) (BabbageEra c))
translateValidatedTxAlonzoToBabbageWrapper :: forall c.
PraosCrypto c =>
TranslationContext (BabbageEra c)
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) (AlonzoEra c))
     (ShelleyBlock (Praos c) (BabbageEra c))
translateValidatedTxAlonzoToBabbageWrapper TranslationContext (BabbageEra c)
ctxt = (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
 -> Maybe
      (WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c))))
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) (AlonzoEra c))
     (ShelleyBlock (Praos c) (BabbageEra c))
forall blk blk'.
(WrapValidatedGenTx blk -> Maybe (WrapValidatedGenTx blk'))
-> InjectValidatedTx blk blk'
InjectValidatedTx ((WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
  -> Maybe
       (WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c))))
 -> InjectValidatedTx
      (ShelleyBlock (TPraos c) (AlonzoEra c))
      (ShelleyBlock (Praos c) (BabbageEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
    -> Maybe
         (WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c))))
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) (AlonzoEra c))
     (ShelleyBlock (Praos c) (BabbageEra c))
forall a b. (a -> b) -> a -> b
$
  ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c)
 -> WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c)))
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
-> Maybe
     (WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c)))
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c)
-> WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c))
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp
    (Maybe
   ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
 -> Maybe
      (WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c))))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
    -> Maybe
         ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Maybe
     (WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
  DecoderError
  ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall a b. Either a b -> Maybe b
eitherToMaybe
    (Either
   DecoderError
   ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
 -> Maybe
      ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
    -> Either
         DecoderError
         ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except
  DecoderError
  ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
-> Either
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall e a. Except e a -> Either e a
runExcept
    (Except
   DecoderError
   ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
 -> Either
      DecoderError
      ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
    -> Except
         DecoderError
         ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Either
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (BabbageEra c)
-> (:.:)
     WrapValidatedGenTx
     (ShelleyBlock (Praos c))
     (PreviousEra (BabbageEra c))
-> Except
     (TranslationError
        (BabbageEra c) (WrapValidatedGenTx :.: ShelleyBlock (Praos c)))
     ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra TranslationContext (BabbageEra c)
ctxt
    ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (AlonzoEra c)
 -> Except
      DecoderError
      ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
    -> (:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (AlonzoEra c))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Except
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapValidatedGenTx (ShelleyBlock (Praos c) (AlonzoEra c))
-> (:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (AlonzoEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp
    (WrapValidatedGenTx (ShelleyBlock (Praos c) (AlonzoEra c))
 -> (:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (AlonzoEra c))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
    -> WrapValidatedGenTx (ShelleyBlock (Praos c) (AlonzoEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> (:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (AlonzoEra c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> WrapValidatedGenTx (ShelleyBlock (Praos c) (AlonzoEra c))
transPraosValidatedTx
 where
  transPraosValidatedTx
    :: WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
    -> WrapValidatedGenTx (ShelleyBlock (Praos c) (AlonzoEra c))
  transPraosValidatedTx :: WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> WrapValidatedGenTx (ShelleyBlock (Praos c) (AlonzoEra c))
transPraosValidatedTx (WrapValidatedGenTx Validated (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c)))
x) = case Validated (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c)))
x of
    ShelleyValidatedTx TxId (EraCrypto (AlonzoEra c))
txid Validated (Tx (AlonzoEra c))
vtx -> Validated (GenTx (ShelleyBlock (Praos c) (AlonzoEra c)))
-> WrapValidatedGenTx (ShelleyBlock (Praos c) (AlonzoEra c))
forall blk. Validated (GenTx blk) -> WrapValidatedGenTx blk
WrapValidatedGenTx (Validated (GenTx (ShelleyBlock (Praos c) (AlonzoEra c)))
 -> WrapValidatedGenTx (ShelleyBlock (Praos c) (AlonzoEra c)))
-> Validated (GenTx (ShelleyBlock (Praos c) (AlonzoEra c)))
-> WrapValidatedGenTx (ShelleyBlock (Praos c) (AlonzoEra c))
forall a b. (a -> b) -> a -> b
$
      TxId (EraCrypto (AlonzoEra c))
-> Validated (Tx (AlonzoEra c))
-> Validated (GenTx (ShelleyBlock (Praos c) (AlonzoEra c)))
forall proto era.
TxId (EraCrypto era)
-> Validated (Tx era) -> Validated (GenTx (ShelleyBlock proto era))
ShelleyValidatedTx TxId (EraCrypto (AlonzoEra c))
txid (Validated (AlonzoTx (AlonzoEra c))
-> Validated (AlonzoTx (AlonzoEra c))
forall a b. Coercible a b => Validated a -> Validated b
SL.coerceValidated Validated (Tx (AlonzoEra c))
Validated (AlonzoTx (AlonzoEra c))
vtx)

{-------------------------------------------------------------------------------
  Translation from Babbage to Conway
-------------------------------------------------------------------------------}

translateLedgerStateBabbageToConwayWrapper ::
     (Praos.PraosCrypto c)
  => RequiringBoth
       WrapLedgerConfig
       (Translate LedgerState)
       (ShelleyBlock (Praos c) (BabbageEra c))
       (ShelleyBlock (Praos c) (ConwayEra c))
translateLedgerStateBabbageToConwayWrapper :: forall c.
PraosCrypto c =>
RequiringBoth
  WrapLedgerConfig
  (Translate LedgerState)
  (ShelleyBlock (Praos c) (BabbageEra c))
  (ShelleyBlock (Praos c) (ConwayEra c))
translateLedgerStateBabbageToConwayWrapper =
    (WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
 -> WrapLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
 -> Translate
      LedgerState
      (ShelleyBlock (Praos c) (BabbageEra c))
      (ShelleyBlock (Praos c) (ConwayEra c)))
-> RequiringBoth
     WrapLedgerConfig
     (Translate LedgerState)
     (ShelleyBlock (Praos c) (BabbageEra c))
     (ShelleyBlock (Praos c) (ConwayEra c))
forall {k} (h :: k -> *) (f :: k -> k -> *) (x :: k) (y :: k).
(h x -> h y -> f x y) -> RequiringBoth h f x y
RequireBoth ((WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
  -> WrapLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
  -> Translate
       LedgerState
       (ShelleyBlock (Praos c) (BabbageEra c))
       (ShelleyBlock (Praos c) (ConwayEra c)))
 -> RequiringBoth
      WrapLedgerConfig
      (Translate LedgerState)
      (ShelleyBlock (Praos c) (BabbageEra c))
      (ShelleyBlock (Praos c) (ConwayEra c)))
-> (WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
    -> WrapLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
    -> Translate
         LedgerState
         (ShelleyBlock (Praos c) (BabbageEra c))
         (ShelleyBlock (Praos c) (ConwayEra c)))
-> RequiringBoth
     WrapLedgerConfig
     (Translate LedgerState)
     (ShelleyBlock (Praos c) (BabbageEra c))
     (ShelleyBlock (Praos c) (ConwayEra c))
forall a b. (a -> b) -> a -> b
$ \WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
_cfgBabbage WrapLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
cfgConway ->
      (EpochNo
 -> LedgerState (ShelleyBlock (Praos c) (BabbageEra c))
 -> LedgerState (ShelleyBlock (Praos c) (ConwayEra c)))
-> Translate
     LedgerState
     (ShelleyBlock (Praos c) (BabbageEra c))
     (ShelleyBlock (Praos c) (ConwayEra c))
forall (f :: * -> *) x y.
(EpochNo -> f x -> f y) -> Translate f x y
Translate ((EpochNo
  -> LedgerState (ShelleyBlock (Praos c) (BabbageEra c))
  -> LedgerState (ShelleyBlock (Praos c) (ConwayEra c)))
 -> Translate
      LedgerState
      (ShelleyBlock (Praos c) (BabbageEra c))
      (ShelleyBlock (Praos c) (ConwayEra c)))
-> (EpochNo
    -> LedgerState (ShelleyBlock (Praos c) (BabbageEra c))
    -> LedgerState (ShelleyBlock (Praos c) (ConwayEra c)))
-> Translate
     LedgerState
     (ShelleyBlock (Praos c) (BabbageEra c))
     (ShelleyBlock (Praos c) (ConwayEra c))
forall a b. (a -> b) -> a -> b
$ \EpochNo
_epochNo ->
        (:.:) LedgerState (ShelleyBlock (Praos c)) (ConwayEra c)
-> LedgerState (ShelleyBlock (Praos c) (ConwayEra c))
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp ((:.:) LedgerState (ShelleyBlock (Praos c)) (ConwayEra c)
 -> LedgerState (ShelleyBlock (Praos c) (ConwayEra c)))
-> (LedgerState (ShelleyBlock (Praos c) (BabbageEra c))
    -> (:.:) LedgerState (ShelleyBlock (Praos c)) (ConwayEra c))
-> LedgerState (ShelleyBlock (Praos c) (BabbageEra c))
-> LedgerState (ShelleyBlock (Praos c) (ConwayEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (ConwayEra c)
-> (:.:)
     LedgerState (ShelleyBlock (Praos c)) (PreviousEra (ConwayEra c))
-> (:.:) LedgerState (ShelleyBlock (Praos c)) (ConwayEra c)
forall era (f :: * -> *).
(TranslateEra era f, TranslationError era f ~ Void) =>
TranslationContext era -> f (PreviousEra era) -> f era
SL.translateEra' (WrapLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> TranslationContext (ConwayEra c)
forall c.
WrapLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> TranslationContext (ConwayEra c)
getConwayTranslationContext WrapLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
cfgConway) ((:.:) LedgerState (ShelleyBlock (Praos c)) (BabbageEra c)
 -> (:.:) LedgerState (ShelleyBlock (Praos c)) (ConwayEra c))
-> (LedgerState (ShelleyBlock (Praos c) (BabbageEra c))
    -> (:.:) LedgerState (ShelleyBlock (Praos c)) (BabbageEra c))
-> LedgerState (ShelleyBlock (Praos c) (BabbageEra c))
-> (:.:) LedgerState (ShelleyBlock (Praos c)) (ConwayEra c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (Praos c) (BabbageEra c))
-> (:.:) LedgerState (ShelleyBlock (Praos c)) (BabbageEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp

getConwayTranslationContext ::
     WrapLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
  -> SL.TranslationContext (ConwayEra c)
getConwayTranslationContext :: forall c.
WrapLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> TranslationContext (ConwayEra c)
getConwayTranslationContext =
    ShelleyLedgerConfig (ConwayEra c)
-> TranslationContext (ConwayEra c)
ShelleyLedgerConfig (ConwayEra c) -> ConwayGenesis c
forall era. ShelleyLedgerConfig era -> TranslationContext era
shelleyLedgerTranslationContext (ShelleyLedgerConfig (ConwayEra c) -> ConwayGenesis c)
-> (WrapLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
    -> ShelleyLedgerConfig (ConwayEra c))
-> WrapLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> ConwayGenesis c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> LedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
WrapLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> ShelleyLedgerConfig (ConwayEra c)
forall blk. WrapLedgerConfig blk -> LedgerConfig blk
unwrapLedgerConfig

translateTxBabbageToConwayWrapper ::
     (Praos.PraosCrypto c)
  => SL.TranslationContext (ConwayEra c)
  -> InjectTx
       (ShelleyBlock (Praos c) (BabbageEra c))
       (ShelleyBlock (Praos c) (ConwayEra c))
translateTxBabbageToConwayWrapper :: forall c.
PraosCrypto c =>
TranslationContext (ConwayEra c)
-> InjectTx
     (ShelleyBlock (Praos c) (BabbageEra c))
     (ShelleyBlock (Praos c) (ConwayEra c))
translateTxBabbageToConwayWrapper TranslationContext (ConwayEra c)
ctxt = (GenTx (ShelleyBlock (Praos c) (BabbageEra c))
 -> Maybe (GenTx (ShelleyBlock (Praos c) (ConwayEra c))))
-> InjectTx
     (ShelleyBlock (Praos c) (BabbageEra c))
     (ShelleyBlock (Praos c) (ConwayEra c))
forall blk blk'.
(GenTx blk -> Maybe (GenTx blk')) -> InjectTx blk blk'
InjectTx ((GenTx (ShelleyBlock (Praos c) (BabbageEra c))
  -> Maybe (GenTx (ShelleyBlock (Praos c) (ConwayEra c))))
 -> InjectTx
      (ShelleyBlock (Praos c) (BabbageEra c))
      (ShelleyBlock (Praos c) (ConwayEra c)))
-> (GenTx (ShelleyBlock (Praos c) (BabbageEra c))
    -> Maybe (GenTx (ShelleyBlock (Praos c) (ConwayEra c))))
-> InjectTx
     (ShelleyBlock (Praos c) (BabbageEra c))
     (ShelleyBlock (Praos c) (ConwayEra c))
forall a b. (a -> b) -> a -> b
$
    ((:.:) GenTx (ShelleyBlock (Praos c)) (ConwayEra c)
 -> GenTx (ShelleyBlock (Praos c) (ConwayEra c)))
-> Maybe ((:.:) GenTx (ShelleyBlock (Praos c)) (ConwayEra c))
-> Maybe (GenTx (ShelleyBlock (Praos c) (ConwayEra c)))
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (:.:) GenTx (ShelleyBlock (Praos c)) (ConwayEra c)
-> GenTx (ShelleyBlock (Praos c) (ConwayEra c))
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp (Maybe ((:.:) GenTx (ShelleyBlock (Praos c)) (ConwayEra c))
 -> Maybe (GenTx (ShelleyBlock (Praos c) (ConwayEra c))))
-> (GenTx (ShelleyBlock (Praos c) (BabbageEra c))
    -> Maybe ((:.:) GenTx (ShelleyBlock (Praos c)) (ConwayEra c)))
-> GenTx (ShelleyBlock (Praos c) (BabbageEra c))
-> Maybe (GenTx (ShelleyBlock (Praos c) (ConwayEra c)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
  DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (ConwayEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (Praos c)) (ConwayEra c))
forall a b. Either a b -> Maybe b
eitherToMaybe (Either
   DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (ConwayEra c))
 -> Maybe ((:.:) GenTx (ShelleyBlock (Praos c)) (ConwayEra c)))
-> (GenTx (ShelleyBlock (Praos c) (BabbageEra c))
    -> Either
         DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (ConwayEra c)))
-> GenTx (ShelleyBlock (Praos c) (BabbageEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (Praos c)) (ConwayEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except
  DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (ConwayEra c))
-> Either
     DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (ConwayEra c))
forall e a. Except e a -> Either e a
runExcept (Except
   DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (ConwayEra c))
 -> Either
      DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (ConwayEra c)))
-> (GenTx (ShelleyBlock (Praos c) (BabbageEra c))
    -> Except
         DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (ConwayEra c)))
-> GenTx (ShelleyBlock (Praos c) (BabbageEra c))
-> Either
     DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (ConwayEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (ConwayEra c)
-> (:.:) GenTx (ShelleyBlock (Praos c)) (PreviousEra (ConwayEra c))
-> Except
     (TranslationError (ConwayEra c) (GenTx :.: ShelleyBlock (Praos c)))
     ((:.:) GenTx (ShelleyBlock (Praos c)) (ConwayEra c))
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra TranslationContext (ConwayEra c)
ctxt ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c)
 -> Except
      DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (ConwayEra c)))
-> (GenTx (ShelleyBlock (Praos c) (BabbageEra c))
    -> (:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
-> GenTx (ShelleyBlock (Praos c) (BabbageEra c))
-> Except
     DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (ConwayEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenTx (ShelleyBlock (Praos c) (BabbageEra c))
-> (:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp

translateValidatedTxBabbageToConwayWrapper ::
     forall c.
     (Praos.PraosCrypto c)
  => SL.TranslationContext (ConwayEra c)
  -> InjectValidatedTx
       (ShelleyBlock (Praos c) (BabbageEra c))
       (ShelleyBlock (Praos c) (ConwayEra c))
translateValidatedTxBabbageToConwayWrapper :: forall c.
PraosCrypto c =>
TranslationContext (ConwayEra c)
-> InjectValidatedTx
     (ShelleyBlock (Praos c) (BabbageEra c))
     (ShelleyBlock (Praos c) (ConwayEra c))
translateValidatedTxBabbageToConwayWrapper TranslationContext (ConwayEra c)
ctxt = (WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c))
 -> Maybe
      (WrapValidatedGenTx (ShelleyBlock (Praos c) (ConwayEra c))))
-> InjectValidatedTx
     (ShelleyBlock (Praos c) (BabbageEra c))
     (ShelleyBlock (Praos c) (ConwayEra c))
forall blk blk'.
(WrapValidatedGenTx blk -> Maybe (WrapValidatedGenTx blk'))
-> InjectValidatedTx blk blk'
InjectValidatedTx ((WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c))
  -> Maybe
       (WrapValidatedGenTx (ShelleyBlock (Praos c) (ConwayEra c))))
 -> InjectValidatedTx
      (ShelleyBlock (Praos c) (BabbageEra c))
      (ShelleyBlock (Praos c) (ConwayEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c))
    -> Maybe
         (WrapValidatedGenTx (ShelleyBlock (Praos c) (ConwayEra c))))
-> InjectValidatedTx
     (ShelleyBlock (Praos c) (BabbageEra c))
     (ShelleyBlock (Praos c) (ConwayEra c))
forall a b. (a -> b) -> a -> b
$
    ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (ConwayEra c)
 -> WrapValidatedGenTx (ShelleyBlock (Praos c) (ConwayEra c)))
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (ConwayEra c))
-> Maybe
     (WrapValidatedGenTx (ShelleyBlock (Praos c) (ConwayEra c)))
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (ConwayEra c)
-> WrapValidatedGenTx (ShelleyBlock (Praos c) (ConwayEra c))
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp (Maybe
   ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (ConwayEra c))
 -> Maybe
      (WrapValidatedGenTx (ShelleyBlock (Praos c) (ConwayEra c))))
-> (WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c))
    -> Maybe
         ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (ConwayEra c)))
-> WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c))
-> Maybe
     (WrapValidatedGenTx (ShelleyBlock (Praos c) (ConwayEra c)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
  DecoderError
  ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (ConwayEra c))
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (ConwayEra c))
forall a b. Either a b -> Maybe b
eitherToMaybe (Either
   DecoderError
   ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (ConwayEra c))
 -> Maybe
      ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (ConwayEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c))
    -> Either
         DecoderError
         ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (ConwayEra c)))
-> WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c))
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (ConwayEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except
  DecoderError
  ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (ConwayEra c))
-> Either
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (ConwayEra c))
forall e a. Except e a -> Either e a
runExcept (Except
   DecoderError
   ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (ConwayEra c))
 -> Either
      DecoderError
      ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (ConwayEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c))
    -> Except
         DecoderError
         ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (ConwayEra c)))
-> WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c))
-> Either
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (ConwayEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (ConwayEra c)
-> (:.:)
     WrapValidatedGenTx
     (ShelleyBlock (Praos c))
     (PreviousEra (ConwayEra c))
-> Except
     (TranslationError
        (ConwayEra c) (WrapValidatedGenTx :.: ShelleyBlock (Praos c)))
     ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (ConwayEra c))
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra TranslationContext (ConwayEra c)
ctxt ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c)
 -> Except
      DecoderError
      ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (ConwayEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c))
    -> (:.:)
         WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
-> WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c))
-> Except
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (ConwayEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c))
-> (:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp