{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE EmptyCase #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}

module Ouroboros.Consensus.Cardano.CanHardFork
  ( CardanoHardForkConstraints
  , TriggerHardFork (..)

    -- * Re-exports of Shelley code
  , ShelleyPartialLedgerConfig (..)
  , crossEraForecastAcrossShelley
  , translateChainDepStateAcrossShelley

    -- * Exposed for testing
  , getConwayTranslationContext
  ) where

import Cardano.Ledger.Allegra.Translation
  ( shelleyToAllegraAVVMsToDelete
  )
import qualified Cardano.Ledger.BaseTypes as SL
import qualified Cardano.Ledger.Core as SL
import qualified Cardano.Ledger.Genesis as SL
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.Except (runExcept, throwError)
import Data.Coerce (coerce)
import qualified Data.Map.Strict as Map
import Data.Proxy
import Data.SOP.BasicFunctors
import Data.SOP.Functors (Flip (..))
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.Void
import Ouroboros.Consensus.Block
import Ouroboros.Consensus.Byron.ByronHFC ()
import Ouroboros.Consensus.Byron.Ledger
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 qualified Ouroboros.Consensus.Ledger.Tables.Diff as Diff
import Ouroboros.Consensus.Ledger.Tables.Utils
import Ouroboros.Consensus.Protocol.Abstract hiding
  ( translateChainDepState
  )
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.HFEras ()
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)

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

type CardanoHardForkConstraints c =
  ( TPraos.PraosCrypto c
  , Praos.PraosCrypto c
  , TranslateProto (TPraos c) (Praos c)
  , ShelleyCompatible (TPraos c) ShelleyEra
  , LedgerSupportsProtocol (ShelleyBlock (TPraos c) ShelleyEra)
  , ShelleyCompatible (TPraos c) AllegraEra
  , LedgerSupportsProtocol (ShelleyBlock (TPraos c) AllegraEra)
  , ShelleyCompatible (TPraos c) MaryEra
  , LedgerSupportsProtocol (ShelleyBlock (TPraos c) MaryEra)
  , ShelleyCompatible (TPraos c) AlonzoEra
  , LedgerSupportsProtocol (ShelleyBlock (TPraos c) AlonzoEra)
  , ShelleyCompatible (Praos c) BabbageEra
  , LedgerSupportsProtocol (ShelleyBlock (Praos c) BabbageEra)
  , ShelleyCompatible (Praos c) ConwayEra
  , LedgerSupportsProtocol (ShelleyBlock (Praos c) ConwayEra)
  )

-- | When performing era translations, two eras have special behaviours on the
-- ledger tables:
--
-- * Byron to Shelley: as Byron has no tables, the whole UTxO set is computed as
--     insertions, note that it uses 'valuesAsDiffs'
--
-- * Shelley to Allegra: some special addresses (the so called /AVVM/
--     addresses), were deleted in this transition, which influenced things like
--     the calculation of later rewards. In this transition, we consume the
--     'shelleyToAllegraAVVMsToDelete' as deletions in the ledger tables.
instance CardanoHardForkConstraints c => CanHardFork (CardanoEras c) where
  type HardForkTxMeasure (CardanoEras c) = ConwayMeasure

  hardForkEraTranslation :: EraTranslation (CardanoEras c)
hardForkEraTranslation =
    EraTranslation
      { translateLedgerState :: InPairs
  (RequiringBoth WrapLedgerConfig TranslateLedgerState)
  (CardanoEras c)
translateLedgerState =
          RequiringBoth
  WrapLedgerConfig
  TranslateLedgerState
  ByronBlock
  (ShelleyBlock (TPraos c) ShelleyEra)
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     '[ShelleyBlock (TPraos c) ShelleyEra,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     (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
  TranslateLedgerState
  ByronBlock
  (ShelleyBlock (TPraos c) ShelleyEra)
forall c.
ShelleyCompatible (TPraos c) ShelleyEra =>
RequiringBoth
  WrapLedgerConfig
  TranslateLedgerState
  ByronBlock
  (ShelleyBlock (TPraos c) ShelleyEra)
translateLedgerStateByronToShelleyWrapper (InPairs
   (RequiringBoth WrapLedgerConfig TranslateLedgerState)
   '[ShelleyBlock (TPraos c) ShelleyEra,
     ShelleyBlock (TPraos c) AllegraEra,
     ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
     ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      (RequiringBoth WrapLedgerConfig TranslateLedgerState)
      (CardanoEras c))
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     '[ShelleyBlock (TPraos c) ShelleyEra,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     (CardanoEras c)
forall a b. (a -> b) -> a -> b
$
            RequiringBoth
  WrapLedgerConfig
  TranslateLedgerState
  (ShelleyBlock (TPraos c) ShelleyEra)
  (ShelleyBlock (TPraos c) AllegraEra)
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     '[ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     '[ShelleyBlock (TPraos c) ShelleyEra,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
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
  TranslateLedgerState
  (ShelleyBlock (TPraos c) ShelleyEra)
  (ShelleyBlock (TPraos c) AllegraEra)
forall c.
RequiringBoth
  WrapLedgerConfig
  TranslateLedgerState
  (ShelleyBlock (TPraos c) ShelleyEra)
  (ShelleyBlock (TPraos c) AllegraEra)
translateLedgerStateShelleyToAllegraWrapper (InPairs
   (RequiringBoth WrapLedgerConfig TranslateLedgerState)
   '[ShelleyBlock (TPraos c) AllegraEra,
     ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
     ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      (RequiringBoth WrapLedgerConfig TranslateLedgerState)
      '[ShelleyBlock (TPraos c) ShelleyEra,
        ShelleyBlock (TPraos c) AllegraEra,
        ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     '[ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     '[ShelleyBlock (TPraos c) ShelleyEra,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$
              RequiringBoth
  WrapLedgerConfig
  TranslateLedgerState
  (ShelleyBlock (TPraos c) AllegraEra)
  (ShelleyBlock (TPraos c) MaryEra)
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     '[ShelleyBlock (TPraos c) MaryEra,
       ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     '[ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
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
  TranslateLedgerState
  (ShelleyBlock (TPraos c) AllegraEra)
  (ShelleyBlock (TPraos c) MaryEra)
forall c.
RequiringBoth
  WrapLedgerConfig
  TranslateLedgerState
  (ShelleyBlock (TPraos c) AllegraEra)
  (ShelleyBlock (TPraos c) MaryEra)
translateLedgerStateAllegraToMaryWrapper (InPairs
   (RequiringBoth WrapLedgerConfig TranslateLedgerState)
   '[ShelleyBlock (TPraos c) MaryEra,
     ShelleyBlock (TPraos c) AlonzoEra,
     ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      (RequiringBoth WrapLedgerConfig TranslateLedgerState)
      '[ShelleyBlock (TPraos c) AllegraEra,
        ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     '[ShelleyBlock (TPraos c) MaryEra,
       ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     '[ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$
                RequiringBoth
  WrapLedgerConfig
  TranslateLedgerState
  (ShelleyBlock (TPraos c) MaryEra)
  (ShelleyBlock (TPraos c) AlonzoEra)
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     '[ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     '[ShelleyBlock (TPraos c) MaryEra,
       ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
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
  TranslateLedgerState
  (ShelleyBlock (TPraos c) MaryEra)
  (ShelleyBlock (TPraos c) AlonzoEra)
forall c.
RequiringBoth
  WrapLedgerConfig
  TranslateLedgerState
  (ShelleyBlock (TPraos c) MaryEra)
  (ShelleyBlock (TPraos c) AlonzoEra)
translateLedgerStateMaryToAlonzoWrapper (InPairs
   (RequiringBoth WrapLedgerConfig TranslateLedgerState)
   '[ShelleyBlock (TPraos c) AlonzoEra,
     ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      (RequiringBoth WrapLedgerConfig TranslateLedgerState)
      '[ShelleyBlock (TPraos c) MaryEra,
        ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     '[ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     '[ShelleyBlock (TPraos c) MaryEra,
       ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$
                  RequiringBoth
  WrapLedgerConfig
  TranslateLedgerState
  (ShelleyBlock (TPraos c) AlonzoEra)
  (ShelleyBlock (Praos c) BabbageEra)
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     '[ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     '[ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
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
  TranslateLedgerState
  (ShelleyBlock (TPraos c) AlonzoEra)
  (ShelleyBlock (Praos c) BabbageEra)
forall c.
RequiringBoth
  WrapLedgerConfig
  TranslateLedgerState
  (ShelleyBlock (TPraos c) AlonzoEra)
  (ShelleyBlock (Praos c) BabbageEra)
translateLedgerStateAlonzoToBabbageWrapper (InPairs
   (RequiringBoth WrapLedgerConfig TranslateLedgerState)
   '[ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      (RequiringBoth WrapLedgerConfig TranslateLedgerState)
      '[ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     '[ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     '[ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$
                    RequiringBoth
  WrapLedgerConfig
  TranslateLedgerState
  (ShelleyBlock (Praos c) BabbageEra)
  (ShelleyBlock (Praos c) ConwayEra)
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     '[ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     '[ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
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
  TranslateLedgerState
  (ShelleyBlock (Praos c) BabbageEra)
  (ShelleyBlock (Praos c) ConwayEra)
forall c.
RequiringBoth
  WrapLedgerConfig
  TranslateLedgerState
  (ShelleyBlock (Praos c) BabbageEra)
  (ShelleyBlock (Praos c) ConwayEra)
translateLedgerStateBabbageToConwayWrapper (InPairs
   (RequiringBoth WrapLedgerConfig TranslateLedgerState)
   '[ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      (RequiringBoth WrapLedgerConfig TranslateLedgerState)
      '[ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     '[ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth WrapLedgerConfig TranslateLedgerState)
     '[ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$
                      InPairs
  (RequiringBoth WrapLedgerConfig TranslateLedgerState)
  '[ShelleyBlock (Praos c) ConwayEra]
forall {k} (f :: k -> k -> *) (x :: k). InPairs f '[x]
PNil
      , translateLedgerTables :: InPairs TranslateLedgerTables (CardanoEras c)
translateLedgerTables =
          TranslateLedgerTables
  ByronBlock (ShelleyBlock (TPraos c) ShelleyEra)
-> InPairs
     TranslateLedgerTables
     '[ShelleyBlock (TPraos c) ShelleyEra,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs TranslateLedgerTables (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 TranslateLedgerTables
  ByronBlock (ShelleyBlock (TPraos c) ShelleyEra)
forall c.
TranslateLedgerTables
  ByronBlock (ShelleyBlock (TPraos c) ShelleyEra)
translateLedgerTablesByronToShelleyWrapper (InPairs
   TranslateLedgerTables
   '[ShelleyBlock (TPraos c) ShelleyEra,
     ShelleyBlock (TPraos c) AllegraEra,
     ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
     ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs TranslateLedgerTables (CardanoEras c))
-> InPairs
     TranslateLedgerTables
     '[ShelleyBlock (TPraos c) ShelleyEra,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs TranslateLedgerTables (CardanoEras c)
forall a b. (a -> b) -> a -> b
$
            TranslateLedgerTables
  (ShelleyBlock (TPraos c) ShelleyEra)
  (ShelleyBlock (TPraos c) AllegraEra)
-> InPairs
     TranslateLedgerTables
     '[ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     TranslateLedgerTables
     '[ShelleyBlock (TPraos c) ShelleyEra,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons TranslateLedgerTables
  (ShelleyBlock (TPraos c) ShelleyEra)
  (ShelleyBlock (TPraos c) AllegraEra)
forall c.
TranslateLedgerTables
  (ShelleyBlock (TPraos c) ShelleyEra)
  (ShelleyBlock (TPraos c) AllegraEra)
translateLedgerTablesShelleyToAllegraWrapper (InPairs
   TranslateLedgerTables
   '[ShelleyBlock (TPraos c) AllegraEra,
     ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
     ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      TranslateLedgerTables
      '[ShelleyBlock (TPraos c) ShelleyEra,
        ShelleyBlock (TPraos c) AllegraEra,
        ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     TranslateLedgerTables
     '[ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     TranslateLedgerTables
     '[ShelleyBlock (TPraos c) ShelleyEra,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$
              TranslateLedgerTables
  (ShelleyBlock (TPraos c) AllegraEra)
  (ShelleyBlock (TPraos c) MaryEra)
-> InPairs
     TranslateLedgerTables
     '[ShelleyBlock (TPraos c) MaryEra,
       ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     TranslateLedgerTables
     '[ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons TranslateLedgerTables
  (ShelleyBlock (TPraos c) AllegraEra)
  (ShelleyBlock (TPraos c) MaryEra)
forall c.
TranslateLedgerTables
  (ShelleyBlock (TPraos c) AllegraEra)
  (ShelleyBlock (TPraos c) MaryEra)
translateLedgerTablesAllegraToMaryWrapper (InPairs
   TranslateLedgerTables
   '[ShelleyBlock (TPraos c) MaryEra,
     ShelleyBlock (TPraos c) AlonzoEra,
     ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      TranslateLedgerTables
      '[ShelleyBlock (TPraos c) AllegraEra,
        ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     TranslateLedgerTables
     '[ShelleyBlock (TPraos c) MaryEra,
       ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     TranslateLedgerTables
     '[ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$
                TranslateLedgerTables
  (ShelleyBlock (TPraos c) MaryEra)
  (ShelleyBlock (TPraos c) AlonzoEra)
-> InPairs
     TranslateLedgerTables
     '[ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     TranslateLedgerTables
     '[ShelleyBlock (TPraos c) MaryEra,
       ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons TranslateLedgerTables
  (ShelleyBlock (TPraos c) MaryEra)
  (ShelleyBlock (TPraos c) AlonzoEra)
forall c.
TranslateLedgerTables
  (ShelleyBlock (TPraos c) MaryEra)
  (ShelleyBlock (TPraos c) AlonzoEra)
translateLedgerTablesMaryToAlonzoWrapper (InPairs
   TranslateLedgerTables
   '[ShelleyBlock (TPraos c) AlonzoEra,
     ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      TranslateLedgerTables
      '[ShelleyBlock (TPraos c) MaryEra,
        ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     TranslateLedgerTables
     '[ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     TranslateLedgerTables
     '[ShelleyBlock (TPraos c) MaryEra,
       ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$
                  TranslateLedgerTables
  (ShelleyBlock (TPraos c) AlonzoEra)
  (ShelleyBlock (Praos c) BabbageEra)
-> InPairs
     TranslateLedgerTables
     '[ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     TranslateLedgerTables
     '[ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons TranslateLedgerTables
  (ShelleyBlock (TPraos c) AlonzoEra)
  (ShelleyBlock (Praos c) BabbageEra)
forall c.
TranslateLedgerTables
  (ShelleyBlock (TPraos c) AlonzoEra)
  (ShelleyBlock (Praos c) BabbageEra)
translateLedgerTablesAlonzoToBabbageWrapper (InPairs
   TranslateLedgerTables
   '[ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      TranslateLedgerTables
      '[ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     TranslateLedgerTables
     '[ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     TranslateLedgerTables
     '[ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$
                    TranslateLedgerTables
  (ShelleyBlock (Praos c) BabbageEra)
  (ShelleyBlock (Praos c) ConwayEra)
-> InPairs
     TranslateLedgerTables '[ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     TranslateLedgerTables
     '[ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons TranslateLedgerTables
  (ShelleyBlock (Praos c) BabbageEra)
  (ShelleyBlock (Praos c) ConwayEra)
forall c.
TranslateLedgerTables
  (ShelleyBlock (Praos c) BabbageEra)
  (ShelleyBlock (Praos c) ConwayEra)
translateLedgerTablesBabbageToConwayWrapper (InPairs TranslateLedgerTables '[ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      TranslateLedgerTables
      '[ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     TranslateLedgerTables '[ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     TranslateLedgerTables
     '[ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$
                      InPairs TranslateLedgerTables '[ShelleyBlock (Praos c) ConwayEra]
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)
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) ShelleyEra,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> 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)
forall c.
RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  ByronBlock
  (ShelleyBlock (TPraos c) ShelleyEra)
translateChainDepStateByronToShelleyWrapper (InPairs
   (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
   '[ShelleyBlock (TPraos c) ShelleyEra,
     ShelleyBlock (TPraos c) AllegraEra,
     ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
     ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
      (CardanoEras c))
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) ShelleyEra,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     (CardanoEras c)
forall a b. (a -> b) -> a -> b
$
            RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  (ShelleyBlock (TPraos c) ShelleyEra)
  (ShelleyBlock (TPraos c) AllegraEra)
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) ShelleyEra,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
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)
  (ShelleyBlock (TPraos c) AllegraEra)
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,
     ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
     ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
      '[ShelleyBlock (TPraos c) ShelleyEra,
        ShelleyBlock (TPraos c) AllegraEra,
        ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) ShelleyEra,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$
              RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  (ShelleyBlock (TPraos c) AllegraEra)
  (ShelleyBlock (TPraos c) MaryEra)
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) MaryEra,
       ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
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)
  (ShelleyBlock (TPraos c) MaryEra)
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,
     ShelleyBlock (TPraos c) AlonzoEra,
     ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
      '[ShelleyBlock (TPraos c) AllegraEra,
        ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) MaryEra,
       ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$
                RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  (ShelleyBlock (TPraos c) MaryEra)
  (ShelleyBlock (TPraos c) AlonzoEra)
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) MaryEra,
       ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
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)
  (ShelleyBlock (TPraos c) AlonzoEra)
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,
     ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
      '[ShelleyBlock (TPraos c) MaryEra,
        ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) MaryEra,
       ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$
                  RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  (ShelleyBlock (TPraos c) AlonzoEra)
  (ShelleyBlock (Praos c) BabbageEra)
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
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)
  (ShelleyBlock (Praos c) BabbageEra)
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,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
      '[ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$
                    RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  (ShelleyBlock (Praos c) BabbageEra)
  (ShelleyBlock (Praos c) ConwayEra)
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
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)
  (ShelleyBlock (Praos c) ConwayEra)
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]
 -> InPairs
      (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
      '[ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
     '[ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$
                      InPairs
  (RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
  '[ShelleyBlock (Praos c) ConwayEra]
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)
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) ShelleyEra,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> 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)
forall c.
RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  ByronBlock
  (ShelleyBlock (TPraos c) ShelleyEra)
crossEraForecastByronToShelleyWrapper (InPairs
   (RequiringBoth
      WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
   '[ShelleyBlock (TPraos c) ShelleyEra,
     ShelleyBlock (TPraos c) AllegraEra,
     ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
     ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
      (CardanoEras c))
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) ShelleyEra,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     (CardanoEras c)
forall a b. (a -> b) -> a -> b
$
            RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  (ShelleyBlock (TPraos c) ShelleyEra)
  (ShelleyBlock (TPraos c) AllegraEra)
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) ShelleyEra,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
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)
  (ShelleyBlock (TPraos c) AllegraEra)
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,
     ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
     ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
      '[ShelleyBlock (TPraos c) ShelleyEra,
        ShelleyBlock (TPraos c) AllegraEra,
        ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) ShelleyEra,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$
              RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  (ShelleyBlock (TPraos c) AllegraEra)
  (ShelleyBlock (TPraos c) MaryEra)
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) MaryEra,
       ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
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)
  (ShelleyBlock (TPraos c) MaryEra)
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,
     ShelleyBlock (TPraos c) AlonzoEra,
     ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
      '[ShelleyBlock (TPraos c) AllegraEra,
        ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) MaryEra,
       ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$
                RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  (ShelleyBlock (TPraos c) MaryEra)
  (ShelleyBlock (TPraos c) AlonzoEra)
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) MaryEra,
       ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
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)
  (ShelleyBlock (TPraos c) AlonzoEra)
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,
     ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
      '[ShelleyBlock (TPraos c) MaryEra,
        ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) MaryEra,
       ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$
                  RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  (ShelleyBlock (TPraos c) AlonzoEra)
  (ShelleyBlock (Praos c) BabbageEra)
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
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)
  (ShelleyBlock (Praos c) BabbageEra)
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,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
      '[ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$
                    RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  (ShelleyBlock (Praos c) BabbageEra)
  (ShelleyBlock (Praos c) ConwayEra)
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
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)
  (ShelleyBlock (Praos c) ConwayEra)
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]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
      '[ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
     '[ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$
                      InPairs
  (RequiringBoth
     WrapLedgerConfig (CrossEraForecaster LedgerState WrapLedgerView))
  '[ShelleyBlock (Praos c) ConwayEra]
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,
    ShelleyBlock (TPraos c) AllegraEra,
    ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
    ShelleyBlock (Praos c) BabbageEra,
    ShelleyBlock (Praos c) ConwayEra]
-> Tails
     AcrossEraSelection
     '[ShelleyBlock (TPraos c) ShelleyEra,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> 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,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
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,
     ShelleyBlock (TPraos c) AllegraEra,
     ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
     ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> Tails AcrossEraSelection (CardanoEras c))
-> Tails
     AcrossEraSelection
     '[ShelleyBlock (TPraos c) ShelleyEra,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> 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,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
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)
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) ShelleyEra,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> 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)
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     ByronBlock
     (ShelleyBlock (TPraos c) ShelleyEra)
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)
 -> RequiringBoth
      WrapLedgerConfig
      (Product2 InjectTx InjectValidatedTx)
      ByronBlock
      (ShelleyBlock (TPraos c) ShelleyEra))
-> Product2
     InjectTx
     InjectValidatedTx
     ByronBlock
     (ShelleyBlock (TPraos c) ShelleyEra)
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     ByronBlock
     (ShelleyBlock (TPraos c) ShelleyEra)
forall a b. (a -> b) -> a -> b
$ InjectTx ByronBlock (ShelleyBlock (TPraos c) ShelleyEra)
-> InjectValidatedTx
     ByronBlock (ShelleyBlock (TPraos c) ShelleyEra)
-> Product2
     InjectTx
     InjectValidatedTx
     ByronBlock
     (ShelleyBlock (TPraos c) ShelleyEra)
forall (f :: * -> * -> *) (g :: * -> * -> *) x y.
f x y -> g x y -> Product2 f g x y
Pair2 InjectTx ByronBlock (ShelleyBlock (TPraos c) ShelleyEra)
forall blk blk'. InjectTx blk blk'
cannotInjectTx InjectValidatedTx ByronBlock (ShelleyBlock (TPraos c) ShelleyEra)
forall blk blk'. InjectValidatedTx blk blk'
cannotInjectValidatedTx)
      (InPairs
   (RequiringBoth
      WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
   '[ShelleyBlock (TPraos c) ShelleyEra,
     ShelleyBlock (TPraos c) AllegraEra,
     ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
     ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
      (CardanoEras c))
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) ShelleyEra,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     (CardanoEras c)
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapLedgerConfig
  (Product2 InjectTx InjectValidatedTx)
  (ShelleyBlock (TPraos c) ShelleyEra)
  (ShelleyBlock (TPraos c) AllegraEra)
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) ShelleyEra,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
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)
  (ShelleyBlock (TPraos c) AllegraEra)
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     (ShelleyBlock (TPraos c) ShelleyEra)
     (ShelleyBlock (TPraos c) AllegraEra)
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)
   (ShelleyBlock (TPraos c) AllegraEra)
 -> RequiringBoth
      WrapLedgerConfig
      (Product2 InjectTx InjectValidatedTx)
      (ShelleyBlock (TPraos c) ShelleyEra)
      (ShelleyBlock (TPraos c) AllegraEra))
-> Product2
     InjectTx
     InjectValidatedTx
     (ShelleyBlock (TPraos c) ShelleyEra)
     (ShelleyBlock (TPraos c) AllegraEra)
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     (ShelleyBlock (TPraos c) ShelleyEra)
     (ShelleyBlock (TPraos c) AllegraEra)
forall a b. (a -> b) -> a -> b
$
            InjectTx
  (ShelleyBlock (TPraos c) ShelleyEra)
  (ShelleyBlock (TPraos c) AllegraEra)
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) ShelleyEra)
     (ShelleyBlock (TPraos c) AllegraEra)
-> Product2
     InjectTx
     InjectValidatedTx
     (ShelleyBlock (TPraos c) ShelleyEra)
     (ShelleyBlock (TPraos c) AllegraEra)
forall (f :: * -> * -> *) (g :: * -> * -> *) x y.
f x y -> g x y -> Product2 f g x y
Pair2
              InjectTx
  (ShelleyBlock (TPraos c) ShelleyEra)
  (ShelleyBlock (TPraos c) AllegraEra)
forall c.
InjectTx
  (ShelleyBlock (TPraos c) ShelleyEra)
  (ShelleyBlock (TPraos c) AllegraEra)
translateTxShelleyToAllegraWrapper
              InjectValidatedTx
  (ShelleyBlock (TPraos c) ShelleyEra)
  (ShelleyBlock (TPraos c) AllegraEra)
forall c.
InjectValidatedTx
  (ShelleyBlock (TPraos c) ShelleyEra)
  (ShelleyBlock (TPraos c) AllegraEra)
translateValidatedTxShelleyToAllegraWrapper
        )
      (InPairs
   (RequiringBoth
      WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
   '[ShelleyBlock (TPraos c) AllegraEra,
     ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
     ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
      '[ShelleyBlock (TPraos c) ShelleyEra,
        ShelleyBlock (TPraos c) AllegraEra,
        ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) ShelleyEra,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapLedgerConfig
  (Product2 InjectTx InjectValidatedTx)
  (ShelleyBlock (TPraos c) AllegraEra)
  (ShelleyBlock (TPraos c) MaryEra)
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) MaryEra,
       ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
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)
  (ShelleyBlock (TPraos c) MaryEra)
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     (ShelleyBlock (TPraos c) AllegraEra)
     (ShelleyBlock (TPraos c) MaryEra)
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)
   (ShelleyBlock (TPraos c) MaryEra)
 -> RequiringBoth
      WrapLedgerConfig
      (Product2 InjectTx InjectValidatedTx)
      (ShelleyBlock (TPraos c) AllegraEra)
      (ShelleyBlock (TPraos c) MaryEra))
-> Product2
     InjectTx
     InjectValidatedTx
     (ShelleyBlock (TPraos c) AllegraEra)
     (ShelleyBlock (TPraos c) MaryEra)
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     (ShelleyBlock (TPraos c) AllegraEra)
     (ShelleyBlock (TPraos c) MaryEra)
forall a b. (a -> b) -> a -> b
$
            InjectTx
  (ShelleyBlock (TPraos c) AllegraEra)
  (ShelleyBlock (TPraos c) MaryEra)
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) AllegraEra)
     (ShelleyBlock (TPraos c) MaryEra)
-> Product2
     InjectTx
     InjectValidatedTx
     (ShelleyBlock (TPraos c) AllegraEra)
     (ShelleyBlock (TPraos c) MaryEra)
forall (f :: * -> * -> *) (g :: * -> * -> *) x y.
f x y -> g x y -> Product2 f g x y
Pair2
              InjectTx
  (ShelleyBlock (TPraos c) AllegraEra)
  (ShelleyBlock (TPraos c) MaryEra)
forall c.
InjectTx
  (ShelleyBlock (TPraos c) AllegraEra)
  (ShelleyBlock (TPraos c) MaryEra)
translateTxAllegraToMaryWrapper
              InjectValidatedTx
  (ShelleyBlock (TPraos c) AllegraEra)
  (ShelleyBlock (TPraos c) MaryEra)
forall c.
InjectValidatedTx
  (ShelleyBlock (TPraos c) AllegraEra)
  (ShelleyBlock (TPraos c) MaryEra)
translateValidatedTxAllegraToMaryWrapper
        )
      (InPairs
   (RequiringBoth
      WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
   '[ShelleyBlock (TPraos c) MaryEra,
     ShelleyBlock (TPraos c) AlonzoEra,
     ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
      '[ShelleyBlock (TPraos c) AllegraEra,
        ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) MaryEra,
       ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapLedgerConfig
  (Product2 InjectTx InjectValidatedTx)
  (ShelleyBlock (TPraos c) MaryEra)
  (ShelleyBlock (TPraos c) AlonzoEra)
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) MaryEra,
       ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
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)
 -> WrapLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
 -> Product2
      InjectTx
      InjectValidatedTx
      (ShelleyBlock (TPraos c) MaryEra)
      (ShelleyBlock (TPraos c) AlonzoEra))
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     (ShelleyBlock (TPraos c) MaryEra)
     (ShelleyBlock (TPraos c) AlonzoEra)
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)
  -> WrapLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
  -> Product2
       InjectTx
       InjectValidatedTx
       (ShelleyBlock (TPraos c) MaryEra)
       (ShelleyBlock (TPraos c) AlonzoEra))
 -> RequiringBoth
      WrapLedgerConfig
      (Product2 InjectTx InjectValidatedTx)
      (ShelleyBlock (TPraos c) MaryEra)
      (ShelleyBlock (TPraos c) AlonzoEra))
-> (WrapLedgerConfig (ShelleyBlock (TPraos c) MaryEra)
    -> WrapLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
    -> Product2
         InjectTx
         InjectValidatedTx
         (ShelleyBlock (TPraos c) MaryEra)
         (ShelleyBlock (TPraos c) AlonzoEra))
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     (ShelleyBlock (TPraos c) MaryEra)
     (ShelleyBlock (TPraos c) AlonzoEra)
forall a b. (a -> b) -> a -> b
$ \WrapLedgerConfig (ShelleyBlock (TPraos c) MaryEra)
_cfgMary WrapLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
cfgAlonzo ->
            let ctxt :: TranslationContext AlonzoEra
ctxt = WrapLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
-> TranslationContext AlonzoEra
forall c.
WrapLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
-> TranslationContext AlonzoEra
getAlonzoTranslationContext WrapLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
cfgAlonzo
             in InjectTx
  (ShelleyBlock (TPraos c) MaryEra)
  (ShelleyBlock (TPraos c) AlonzoEra)
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) MaryEra)
     (ShelleyBlock (TPraos c) AlonzoEra)
-> Product2
     InjectTx
     InjectValidatedTx
     (ShelleyBlock (TPraos c) MaryEra)
     (ShelleyBlock (TPraos c) AlonzoEra)
forall (f :: * -> * -> *) (g :: * -> * -> *) x y.
f x y -> g x y -> Product2 f g x y
Pair2
                  (TranslationContext AlonzoEra
-> InjectTx
     (ShelleyBlock (TPraos c) MaryEra)
     (ShelleyBlock (TPraos c) AlonzoEra)
forall c.
TranslationContext AlonzoEra
-> InjectTx
     (ShelleyBlock (TPraos c) MaryEra)
     (ShelleyBlock (TPraos c) AlonzoEra)
translateTxMaryToAlonzoWrapper TranslationContext AlonzoEra
ctxt)
                  (TranslationContext AlonzoEra
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) MaryEra)
     (ShelleyBlock (TPraos c) AlonzoEra)
forall c.
TranslationContext AlonzoEra
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) MaryEra)
     (ShelleyBlock (TPraos c) AlonzoEra)
translateValidatedTxMaryToAlonzoWrapper TranslationContext AlonzoEra
ctxt)
        )
      (InPairs
   (RequiringBoth
      WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
   '[ShelleyBlock (TPraos c) AlonzoEra,
     ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
      '[ShelleyBlock (TPraos c) MaryEra,
        ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) MaryEra,
       ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapLedgerConfig
  (Product2 InjectTx InjectValidatedTx)
  (ShelleyBlock (TPraos c) AlonzoEra)
  (ShelleyBlock (Praos c) BabbageEra)
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
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)
 -> WrapLedgerConfig (ShelleyBlock (Praos c) BabbageEra)
 -> Product2
      InjectTx
      InjectValidatedTx
      (ShelleyBlock (TPraos c) AlonzoEra)
      (ShelleyBlock (Praos c) BabbageEra))
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     (ShelleyBlock (TPraos c) AlonzoEra)
     (ShelleyBlock (Praos c) BabbageEra)
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)
  -> WrapLedgerConfig (ShelleyBlock (Praos c) BabbageEra)
  -> Product2
       InjectTx
       InjectValidatedTx
       (ShelleyBlock (TPraos c) AlonzoEra)
       (ShelleyBlock (Praos c) BabbageEra))
 -> RequiringBoth
      WrapLedgerConfig
      (Product2 InjectTx InjectValidatedTx)
      (ShelleyBlock (TPraos c) AlonzoEra)
      (ShelleyBlock (Praos c) BabbageEra))
-> (WrapLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
    -> WrapLedgerConfig (ShelleyBlock (Praos c) BabbageEra)
    -> Product2
         InjectTx
         InjectValidatedTx
         (ShelleyBlock (TPraos c) AlonzoEra)
         (ShelleyBlock (Praos c) BabbageEra))
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     (ShelleyBlock (TPraos c) AlonzoEra)
     (ShelleyBlock (Praos c) BabbageEra)
forall a b. (a -> b) -> a -> b
$ \WrapLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
_cfgAlonzo WrapLedgerConfig (ShelleyBlock (Praos c) BabbageEra)
_cfgBabbage ->
            let ctxt :: NoGenesis era
ctxt = NoGenesis era
forall era. NoGenesis era
SL.NoGenesis
             in InjectTx
  (ShelleyBlock (TPraos c) AlonzoEra)
  (ShelleyBlock (Praos c) BabbageEra)
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) AlonzoEra)
     (ShelleyBlock (Praos c) BabbageEra)
-> Product2
     InjectTx
     InjectValidatedTx
     (ShelleyBlock (TPraos c) AlonzoEra)
     (ShelleyBlock (Praos c) BabbageEra)
forall (f :: * -> * -> *) (g :: * -> * -> *) x y.
f x y -> g x y -> Product2 f g x y
Pair2
                  (TranslationContext BabbageEra
-> InjectTx
     (ShelleyBlock (TPraos c) AlonzoEra)
     (ShelleyBlock (Praos c) BabbageEra)
forall c.
TranslationContext BabbageEra
-> InjectTx
     (ShelleyBlock (TPraos c) AlonzoEra)
     (ShelleyBlock (Praos c) BabbageEra)
translateTxAlonzoToBabbageWrapper TranslationContext BabbageEra
NoGenesis BabbageEra
forall era. NoGenesis era
ctxt)
                  (TranslationContext BabbageEra
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) AlonzoEra)
     (ShelleyBlock (Praos c) BabbageEra)
forall c.
TranslationContext BabbageEra
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) AlonzoEra)
     (ShelleyBlock (Praos c) BabbageEra)
translateValidatedTxAlonzoToBabbageWrapper TranslationContext BabbageEra
NoGenesis BabbageEra
forall era. NoGenesis era
ctxt)
        )
      (InPairs
   (RequiringBoth
      WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
   '[ShelleyBlock (Praos c) BabbageEra,
     ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
      '[ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
  WrapLedgerConfig
  (Product2 InjectTx InjectValidatedTx)
  (ShelleyBlock (Praos c) BabbageEra)
  (ShelleyBlock (Praos c) ConwayEra)
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
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)
 -> WrapLedgerConfig (ShelleyBlock (Praos c) ConwayEra)
 -> Product2
      InjectTx
      InjectValidatedTx
      (ShelleyBlock (Praos c) BabbageEra)
      (ShelleyBlock (Praos c) ConwayEra))
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     (ShelleyBlock (Praos c) BabbageEra)
     (ShelleyBlock (Praos c) ConwayEra)
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)
  -> WrapLedgerConfig (ShelleyBlock (Praos c) ConwayEra)
  -> Product2
       InjectTx
       InjectValidatedTx
       (ShelleyBlock (Praos c) BabbageEra)
       (ShelleyBlock (Praos c) ConwayEra))
 -> RequiringBoth
      WrapLedgerConfig
      (Product2 InjectTx InjectValidatedTx)
      (ShelleyBlock (Praos c) BabbageEra)
      (ShelleyBlock (Praos c) ConwayEra))
-> (WrapLedgerConfig (ShelleyBlock (Praos c) BabbageEra)
    -> WrapLedgerConfig (ShelleyBlock (Praos c) ConwayEra)
    -> Product2
         InjectTx
         InjectValidatedTx
         (ShelleyBlock (Praos c) BabbageEra)
         (ShelleyBlock (Praos c) ConwayEra))
-> RequiringBoth
     WrapLedgerConfig
     (Product2 InjectTx InjectValidatedTx)
     (ShelleyBlock (Praos c) BabbageEra)
     (ShelleyBlock (Praos c) ConwayEra)
forall a b. (a -> b) -> a -> b
$ \WrapLedgerConfig (ShelleyBlock (Praos c) BabbageEra)
_cfgBabbage WrapLedgerConfig (ShelleyBlock (Praos c) ConwayEra)
cfgConway ->
            let ctxt :: TranslationContext ConwayEra
ctxt = WrapLedgerConfig (ShelleyBlock (Praos c) ConwayEra)
-> TranslationContext ConwayEra
forall c.
WrapLedgerConfig (ShelleyBlock (Praos c) ConwayEra)
-> TranslationContext ConwayEra
getConwayTranslationContext WrapLedgerConfig (ShelleyBlock (Praos c) ConwayEra)
cfgConway
             in InjectTx
  (ShelleyBlock (Praos c) BabbageEra)
  (ShelleyBlock (Praos c) ConwayEra)
-> InjectValidatedTx
     (ShelleyBlock (Praos c) BabbageEra)
     (ShelleyBlock (Praos c) ConwayEra)
-> Product2
     InjectTx
     InjectValidatedTx
     (ShelleyBlock (Praos c) BabbageEra)
     (ShelleyBlock (Praos c) ConwayEra)
forall (f :: * -> * -> *) (g :: * -> * -> *) x y.
f x y -> g x y -> Product2 f g x y
Pair2
                  (TranslationContext ConwayEra
-> InjectTx
     (ShelleyBlock (Praos c) BabbageEra)
     (ShelleyBlock (Praos c) ConwayEra)
forall c.
TranslationContext ConwayEra
-> InjectTx
     (ShelleyBlock (Praos c) BabbageEra)
     (ShelleyBlock (Praos c) ConwayEra)
translateTxBabbageToConwayWrapper TranslationContext ConwayEra
ctxt)
                  (TranslationContext ConwayEra
-> InjectValidatedTx
     (ShelleyBlock (Praos c) BabbageEra)
     (ShelleyBlock (Praos c) ConwayEra)
forall c.
TranslationContext ConwayEra
-> InjectValidatedTx
     (ShelleyBlock (Praos c) BabbageEra)
     (ShelleyBlock (Praos c) ConwayEra)
translateValidatedTxBabbageToConwayWrapper TranslationContext ConwayEra
ctxt)
        )
      (InPairs
   (RequiringBoth
      WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
   '[ShelleyBlock (Praos c) ConwayEra]
 -> InPairs
      (RequiringBoth
         WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
      '[ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra])
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (Praos c) ConwayEra]
-> InPairs
     (RequiringBoth
        WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
     '[ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$ InPairs
  (RequiringBoth
     WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
  '[ShelleyBlock (Praos c) ConwayEra]
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,
        ShelleyBlock (TPraos c) AllegraEra,
        ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra]
    -> 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) -> ConwayMeasure
fromByteSize
      (TxMeasure (ShelleyBlock (TPraos c) ShelleyEra) -> ConwayMeasure)
-> (NS
      WrapTxMeasure
      '[ShelleyBlock (TPraos c) AllegraEra,
        ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra]
    -> ConwayMeasure)
-> NS
     WrapTxMeasure
     '[ShelleyBlock (TPraos c) ShelleyEra,
       ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> 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) -> ConwayMeasure
fromByteSize
      (TxMeasure (ShelleyBlock (TPraos c) AllegraEra) -> ConwayMeasure)
-> (NS
      WrapTxMeasure
      '[ShelleyBlock (TPraos c) MaryEra,
        ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra]
    -> ConwayMeasure)
-> NS
     WrapTxMeasure
     '[ShelleyBlock (TPraos c) AllegraEra,
       ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> 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) -> ConwayMeasure
fromByteSize
      (TxMeasure (ShelleyBlock (TPraos c) MaryEra) -> ConwayMeasure)
-> (NS
      WrapTxMeasure
      '[ShelleyBlock (TPraos c) AlonzoEra,
        ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra]
    -> ConwayMeasure)
-> NS
     WrapTxMeasure
     '[ShelleyBlock (TPraos c) MaryEra,
       ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> ConwayMeasure
forall x a (xs :: [*]).
(TxMeasure x -> a)
-> (NS WrapTxMeasure xs -> a) -> NS WrapTxMeasure (x : xs) -> a
`o` TxMeasure (ShelleyBlock (TPraos c) AlonzoEra) -> ConwayMeasure
AlonzoMeasure -> ConwayMeasure
fromAlonzo
      (TxMeasure (ShelleyBlock (TPraos c) AlonzoEra) -> ConwayMeasure)
-> (NS
      WrapTxMeasure
      '[ShelleyBlock (Praos c) BabbageEra,
        ShelleyBlock (Praos c) ConwayEra]
    -> ConwayMeasure)
-> NS
     WrapTxMeasure
     '[ShelleyBlock (TPraos c) AlonzoEra,
       ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> ConwayMeasure
forall x a (xs :: [*]).
(TxMeasure x -> a)
-> (NS WrapTxMeasure xs -> a) -> NS WrapTxMeasure (x : xs) -> a
`o` TxMeasure (ShelleyBlock (Praos c) BabbageEra) -> ConwayMeasure
ConwayMeasure -> ConwayMeasure
forall {p}. p -> p
fromConway
      (TxMeasure (ShelleyBlock (Praos c) BabbageEra) -> ConwayMeasure)
-> (NS WrapTxMeasure '[ShelleyBlock (Praos c) ConwayEra]
    -> ConwayMeasure)
-> NS
     WrapTxMeasure
     '[ShelleyBlock (Praos c) BabbageEra,
       ShelleyBlock (Praos c) ConwayEra]
-> ConwayMeasure
forall x a (xs :: [*]).
(TxMeasure x -> a)
-> (NS WrapTxMeasure xs -> a) -> NS WrapTxMeasure (x : xs) -> a
`o` TxMeasure (ShelleyBlock (Praos c) ConwayEra) -> ConwayMeasure
ConwayMeasure -> ConwayMeasure
forall {p}. p -> p
fromConway
      (TxMeasure (ShelleyBlock (Praos c) ConwayEra) -> ConwayMeasure)
-> (NS WrapTxMeasure '[] -> ConwayMeasure)
-> NS WrapTxMeasure '[ShelleyBlock (Praos c) ConwayEra]
-> 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 9 `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 =>
  Proxy c ->
  HeaderHash ByronBlock ->
  HeaderHash (ShelleyBlock (TPraos c) ShelleyEra)
translateHeaderHashByronToShelley :: forall c.
ShelleyCompatible (TPraos c) ShelleyEra =>
Proxy c
-> HeaderHash ByronBlock
-> HeaderHash (ShelleyBlock (TPraos c) ShelleyEra)
translateHeaderHashByronToShelley Proxy c
_ =
  Proxy (ShelleyBlock (TPraos c) ShelleyEra)
-> ShortByteString
-> HeaderHash (ShelleyBlock (TPraos c) ShelleyEra)
forall blk (proxy :: * -> *).
ConvertRawHash blk =>
proxy blk -> ShortByteString -> HeaderHash blk
forall (proxy :: * -> *).
proxy (ShelleyBlock (TPraos c) ShelleyEra)
-> ShortByteString
-> HeaderHash (ShelleyBlock (TPraos c) ShelleyEra)
fromShortRawHash (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @(ShelleyBlock (TPraos c) ShelleyEra))
    (ShortByteString -> ShelleyHash)
-> (ByronHash -> ShortByteString) -> ByronHash -> ShelleyHash
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)

translatePointByronToShelley ::
  forall c.
  ShelleyCompatible (TPraos c) ShelleyEra =>
  Point ByronBlock ->
  WithOrigin BlockNo ->
  WithOrigin (ShelleyTip (TPraos c) ShelleyEra)
translatePointByronToShelley :: forall c.
ShelleyCompatible (TPraos c) ShelleyEra =>
Point ByronBlock
-> WithOrigin BlockNo
-> WithOrigin (ShelleyTip (TPraos c) ShelleyEra)
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)
forall t. WithOrigin t
Origin
    (BlockPoint SlotNo
s HeaderHash ByronBlock
h, NotOrigin BlockNo
n) ->
      ShelleyTip (TPraos c) ShelleyEra
-> WithOrigin (ShelleyTip (TPraos c) ShelleyEra)
forall t. t -> WithOrigin t
NotOrigin
        ShelleyTip
          { shelleyTipSlotNo :: SlotNo
shelleyTipSlotNo = SlotNo
s
          , shelleyTipBlockNo :: BlockNo
shelleyTipBlockNo = BlockNo
n
          , shelleyTipHash :: HeaderHash (ShelleyBlock (TPraos c) ShelleyEra)
shelleyTipHash = Proxy c
-> HeaderHash ByronBlock
-> HeaderHash (ShelleyBlock (TPraos c) ShelleyEra)
forall c.
ShelleyCompatible (TPraos c) ShelleyEra =>
Proxy c
-> HeaderHash ByronBlock
-> HeaderHash (ShelleyBlock (TPraos c) ShelleyEra)
translateHeaderHashByronToShelley (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @c) HeaderHash ByronBlock
h
          }
    (Point ByronBlock, WithOrigin BlockNo)
_otherwise ->
      [Char] -> WithOrigin (ShelleyTip (TPraos c) ShelleyEra)
forall a. HasCallStack => [Char] -> a
error [Char]
"translatePointByronToShelley: invalid Byron state"

translateLedgerStateByronToShelleyWrapper ::
  ShelleyCompatible (TPraos c) ShelleyEra =>
  RequiringBoth
    WrapLedgerConfig
    TranslateLedgerState
    ByronBlock
    (ShelleyBlock (TPraos c) ShelleyEra)
translateLedgerStateByronToShelleyWrapper :: forall c.
ShelleyCompatible (TPraos c) ShelleyEra =>
RequiringBoth
  WrapLedgerConfig
  TranslateLedgerState
  ByronBlock
  (ShelleyBlock (TPraos c) ShelleyEra)
translateLedgerStateByronToShelleyWrapper =
  (WrapLedgerConfig ByronBlock
 -> WrapLedgerConfig (ShelleyBlock (TPraos c) ShelleyEra)
 -> TranslateLedgerState
      ByronBlock (ShelleyBlock (TPraos c) ShelleyEra))
-> RequiringBoth
     WrapLedgerConfig
     TranslateLedgerState
     ByronBlock
     (ShelleyBlock (TPraos c) ShelleyEra)
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)
  -> TranslateLedgerState
       ByronBlock (ShelleyBlock (TPraos c) ShelleyEra))
 -> RequiringBoth
      WrapLedgerConfig
      TranslateLedgerState
      ByronBlock
      (ShelleyBlock (TPraos c) ShelleyEra))
-> (WrapLedgerConfig ByronBlock
    -> WrapLedgerConfig (ShelleyBlock (TPraos c) ShelleyEra)
    -> TranslateLedgerState
         ByronBlock (ShelleyBlock (TPraos c) ShelleyEra))
-> RequiringBoth
     WrapLedgerConfig
     TranslateLedgerState
     ByronBlock
     (ShelleyBlock (TPraos c) ShelleyEra)
forall a b. (a -> b) -> a -> b
$
    \WrapLedgerConfig ByronBlock
_ (WrapLedgerConfig LedgerConfig (ShelleyBlock (TPraos c) ShelleyEra)
cfgShelley) ->
      TranslateLedgerState
        { translateLedgerStateWith :: EpochNo
-> LedgerState ByronBlock EmptyMK
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) DiffMK
translateLedgerStateWith = \EpochNo
epochNo LedgerState ByronBlock EmptyMK
ledgerByron ->
            LedgerState (ShelleyBlock (TPraos c) ShelleyEra) ValuesMK
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) DiffMK
forall (l :: LedgerStateKind).
(LedgerTableConstraints l, HasLedgerTables l) =>
l ValuesMK -> l DiffMK
valuesAsDiffs
              (LedgerState (ShelleyBlock (TPraos c) ShelleyEra) ValuesMK
 -> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) DiffMK)
-> (LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
    -> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) ValuesMK)
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) DiffMK
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) ValuesMK
forall (l :: LedgerStateKind).
CanStowLedgerTables l =>
l EmptyMK -> l ValuesMK
unstowLedgerTables
              (LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
 -> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) DiffMK)
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) DiffMK
forall a b. (a -> b) -> a -> b
$ ShelleyLedgerState
                { shelleyLedgerTip :: WithOrigin (ShelleyTip (TPraos c) ShelleyEra)
shelleyLedgerTip =
                    Point ByronBlock
-> WithOrigin BlockNo
-> WithOrigin (ShelleyTip (TPraos c) ShelleyEra)
forall c.
ShelleyCompatible (TPraos c) ShelleyEra =>
Point ByronBlock
-> WithOrigin BlockNo
-> WithOrigin (ShelleyTip (TPraos c) ShelleyEra)
translatePointByronToShelley
                      (LedgerState ByronBlock EmptyMK -> Point ByronBlock
forall blk (mk :: * -> * -> *).
UpdateLedger blk =>
LedgerState blk mk -> Point blk
ledgerTipPoint LedgerState ByronBlock EmptyMK
ledgerByron)
                      (LedgerState ByronBlock EmptyMK -> WithOrigin BlockNo
forall (mk :: * -> * -> *).
LedgerState ByronBlock mk -> WithOrigin BlockNo
byronLedgerTipBlockNo LedgerState ByronBlock EmptyMK
ledgerByron)
                , shelleyLedgerState :: NewEpochState ShelleyEra
shelleyLedgerState =
                    FromByronTranslationContext
-> EpochNo -> ChainValidationState -> NewEpochState ShelleyEra
SL.translateToShelleyLedgerState
                      (ShelleyGenesis -> FromByronTranslationContext
toFromByronTranslationContext (ShelleyLedgerConfig ShelleyEra -> ShelleyGenesis
forall era. ShelleyLedgerConfig era -> ShelleyGenesis
shelleyLedgerGenesis LedgerConfig (ShelleyBlock (TPraos c) ShelleyEra)
ShelleyLedgerConfig ShelleyEra
cfgShelley))
                      EpochNo
epochNo
                      (LedgerState ByronBlock EmptyMK -> ChainValidationState
forall (mk :: * -> * -> *).
LedgerState ByronBlock mk -> ChainValidationState
byronLedgerState LedgerState ByronBlock EmptyMK
ledgerByron)
                , shelleyLedgerTransition :: ShelleyTransition
shelleyLedgerTransition =
                    ShelleyTransitionInfo{shelleyAfterVoting :: Word32
shelleyAfterVoting = Word32
0}
                , shelleyLedgerTables :: LedgerTables
  (LedgerState (ShelleyBlock (TPraos c) ShelleyEra)) EmptyMK
shelleyLedgerTables = LedgerTables
  (LedgerState (ShelleyBlock (TPraos c) ShelleyEra)) EmptyMK
forall (mk :: * -> * -> *) (l :: LedgerStateKind).
(ZeroableMK mk, LedgerTableConstraints l) =>
LedgerTables l mk
emptyLedgerTables
                }
        }

translateLedgerTablesByronToShelleyWrapper ::
  TranslateLedgerTables ByronBlock (ShelleyBlock (TPraos c) ShelleyEra)
translateLedgerTablesByronToShelleyWrapper :: forall c.
TranslateLedgerTables
  ByronBlock (ShelleyBlock (TPraos c) ShelleyEra)
translateLedgerTablesByronToShelleyWrapper =
  TranslateLedgerTables
    { translateTxInWith :: TxIn (LedgerState ByronBlock)
-> TxIn (LedgerState (ShelleyBlock (TPraos c) ShelleyEra))
translateTxInWith = Void -> TxIn
TxIn (LedgerState ByronBlock)
-> TxIn (LedgerState (ShelleyBlock (TPraos c) ShelleyEra))
forall a. Void -> a
absurd
    , translateTxOutWith :: TxOut (LedgerState ByronBlock)
-> TxOut (LedgerState (ShelleyBlock (TPraos c) ShelleyEra))
translateTxOutWith = Void -> ShelleyTxOut ShelleyEra
TxOut (LedgerState ByronBlock)
-> TxOut (LedgerState (ShelleyBlock (TPraos c) ShelleyEra))
forall a. Void -> a
absurd
    }

translateChainDepStateByronToShelleyWrapper ::
  RequiringBoth
    WrapConsensusConfig
    (Translate WrapChainDepState)
    ByronBlock
    (ShelleyBlock (TPraos c) ShelleyEra)
translateChainDepStateByronToShelleyWrapper :: forall c.
RequiringBoth
  WrapConsensusConfig
  (Translate WrapChainDepState)
  ByronBlock
  (ShelleyBlock (TPraos c) ShelleyEra)
translateChainDepStateByronToShelleyWrapper =
  (WrapConsensusConfig ByronBlock
 -> WrapConsensusConfig (ShelleyBlock (TPraos c) ShelleyEra)
 -> Translate
      WrapChainDepState ByronBlock (ShelleyBlock (TPraos c) ShelleyEra))
-> RequiringBoth
     WrapConsensusConfig
     (Translate WrapChainDepState)
     ByronBlock
     (ShelleyBlock (TPraos c) ShelleyEra)
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)
  -> Translate
       WrapChainDepState ByronBlock (ShelleyBlock (TPraos c) ShelleyEra))
 -> RequiringBoth
      WrapConsensusConfig
      (Translate WrapChainDepState)
      ByronBlock
      (ShelleyBlock (TPraos c) ShelleyEra))
-> (WrapConsensusConfig ByronBlock
    -> WrapConsensusConfig (ShelleyBlock (TPraos c) ShelleyEra)
    -> Translate
         WrapChainDepState ByronBlock (ShelleyBlock (TPraos c) ShelleyEra))
-> RequiringBoth
     WrapConsensusConfig
     (Translate WrapChainDepState)
     ByronBlock
     (ShelleyBlock (TPraos c) ShelleyEra)
forall a b. (a -> b) -> a -> b
$ \WrapConsensusConfig ByronBlock
_ (WrapConsensusConfig ConsensusConfig
  (BlockProtocol (ShelleyBlock (TPraos c) ShelleyEra))
cfgShelley) ->
    (EpochNo
 -> WrapChainDepState ByronBlock
 -> WrapChainDepState (ShelleyBlock (TPraos c) ShelleyEra))
-> Translate
     WrapChainDepState ByronBlock (ShelleyBlock (TPraos c) ShelleyEra)
forall (f :: * -> *) x y.
(EpochNo -> f x -> f y) -> Translate f x y
Translate ((EpochNo
  -> WrapChainDepState ByronBlock
  -> WrapChainDepState (ShelleyBlock (TPraos c) ShelleyEra))
 -> Translate
      WrapChainDepState ByronBlock (ShelleyBlock (TPraos c) ShelleyEra))
-> (EpochNo
    -> WrapChainDepState ByronBlock
    -> WrapChainDepState (ShelleyBlock (TPraos c) ShelleyEra))
-> Translate
     WrapChainDepState ByronBlock (ShelleyBlock (TPraos c) ShelleyEra)
forall a b. (a -> b) -> a -> b
$ \EpochNo
_ (WrapChainDepState ChainDepState (BlockProtocol ByronBlock)
pbftState) ->
      ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) ShelleyEra))
-> WrapChainDepState (ShelleyBlock (TPraos c) ShelleyEra)
forall blk.
ChainDepState (BlockProtocol blk) -> WrapChainDepState blk
WrapChainDepState (ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) ShelleyEra))
 -> WrapChainDepState (ShelleyBlock (TPraos c) ShelleyEra))
-> ChainDepState
     (BlockProtocol (ShelleyBlock (TPraos c) ShelleyEra))
-> WrapChainDepState (ShelleyBlock (TPraos c) ShelleyEra)
forall a b. (a -> b) -> a -> b
$
        ConsensusConfig (TPraos c)
-> PBftState PBftByronCrypto -> TPraosState
forall bc c.
ConsensusConfig (TPraos c) -> PBftState bc -> TPraosState
translateChainDepStateByronToShelley ConsensusConfig
  (BlockProtocol (ShelleyBlock (TPraos c) ShelleyEra))
ConsensusConfig (TPraos c)
cfgShelley ChainDepState (BlockProtocol ByronBlock)
PBftState PBftByronCrypto
pbftState

translateChainDepStateByronToShelley ::
  forall bc c.
  ConsensusConfig (TPraos c) ->
  PBftState bc ->
  TPraosState
translateChainDepStateByronToShelley :: forall bc c.
ConsensusConfig (TPraos c) -> PBftState bc -> TPraosState
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 -> TPraosState
TPraosState (PBftState bc -> WithOrigin SlotNo
forall c. PBftState c -> WithOrigin SlotNo
PBftState.lastSignedSlot PBftState bc
pbftState) (ChainDepState -> TPraosState) -> ChainDepState -> TPraosState
forall a b. (a -> b) -> a -> b
$
    SL.ChainDepState
      { csProtocol :: PrtclState
SL.csProtocol = Map (KeyHash 'BlockIssuer) Word64 -> Nonce -> Nonce -> PrtclState
SL.PrtclState Map (KeyHash 'BlockIssuer) Word64
forall k a. Map k a
Map.empty Nonce
nonce Nonce
nonce
      , csTickn :: TicknState
SL.csTickn =
          SL.TicknState
            { ticknStateEpochNonce :: Nonce
SL.ticknStateEpochNonce = Nonce
nonce
            , ticknStatePrevHashNonce :: Nonce
SL.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.
  RequiringBoth
    WrapLedgerConfig
    (CrossEraForecaster LedgerState WrapLedgerView)
    ByronBlock
    (ShelleyBlock (TPraos c) ShelleyEra)
crossEraForecastByronToShelleyWrapper :: forall c.
RequiringBoth
  WrapLedgerConfig
  (CrossEraForecaster LedgerState WrapLedgerView)
  ByronBlock
  (ShelleyBlock (TPraos c) ShelleyEra)
crossEraForecastByronToShelleyWrapper =
  (WrapLedgerConfig ByronBlock
 -> WrapLedgerConfig (ShelleyBlock (TPraos c) ShelleyEra)
 -> CrossEraForecaster
      LedgerState
      WrapLedgerView
      ByronBlock
      (ShelleyBlock (TPraos c) ShelleyEra))
-> RequiringBoth
     WrapLedgerConfig
     (CrossEraForecaster LedgerState WrapLedgerView)
     ByronBlock
     (ShelleyBlock (TPraos c) ShelleyEra)
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)
  -> CrossEraForecaster
       LedgerState
       WrapLedgerView
       ByronBlock
       (ShelleyBlock (TPraos c) ShelleyEra))
 -> RequiringBoth
      WrapLedgerConfig
      (CrossEraForecaster LedgerState WrapLedgerView)
      ByronBlock
      (ShelleyBlock (TPraos c) ShelleyEra))
-> (WrapLedgerConfig ByronBlock
    -> WrapLedgerConfig (ShelleyBlock (TPraos c) ShelleyEra)
    -> CrossEraForecaster
         LedgerState
         WrapLedgerView
         ByronBlock
         (ShelleyBlock (TPraos c) ShelleyEra))
-> RequiringBoth
     WrapLedgerConfig
     (CrossEraForecaster LedgerState WrapLedgerView)
     ByronBlock
     (ShelleyBlock (TPraos c) ShelleyEra)
forall a b. (a -> b) -> a -> b
$ \WrapLedgerConfig ByronBlock
_ (WrapLedgerConfig LedgerConfig (ShelleyBlock (TPraos c) ShelleyEra)
cfgShelley) ->
    (Bound
 -> SlotNo
 -> LedgerState ByronBlock EmptyMK
 -> Except
      OutsideForecastRange
      (WrapLedgerView (ShelleyBlock (TPraos c) ShelleyEra)))
-> CrossEraForecaster
     LedgerState
     WrapLedgerView
     ByronBlock
     (ShelleyBlock (TPraos c) ShelleyEra)
forall (state :: * -> LedgerStateKind) (view :: * -> *) x y.
(Bound
 -> SlotNo
 -> state x EmptyMK
 -> Except OutsideForecastRange (view y))
-> CrossEraForecaster state view x y
CrossEraForecaster (ShelleyLedgerConfig ShelleyEra
-> Bound
-> SlotNo
-> LedgerState ByronBlock EmptyMK
-> Except
     OutsideForecastRange
     (WrapLedgerView (ShelleyBlock (TPraos c) ShelleyEra))
forall (mk :: * -> * -> *).
ShelleyLedgerConfig ShelleyEra
-> Bound
-> SlotNo
-> LedgerState ByronBlock mk
-> Except
     OutsideForecastRange
     (WrapLedgerView (ShelleyBlock (TPraos c) ShelleyEra))
forecast LedgerConfig (ShelleyBlock (TPraos c) ShelleyEra)
ShelleyLedgerConfig ShelleyEra
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 ->
    Bound ->
    SlotNo ->
    LedgerState ByronBlock mk ->
    Except
      OutsideForecastRange
      (WrapLedgerView (ShelleyBlock (TPraos c) ShelleyEra))
  forecast :: forall (mk :: * -> * -> *).
ShelleyLedgerConfig ShelleyEra
-> Bound
-> SlotNo
-> LedgerState ByronBlock mk
-> Except
     OutsideForecastRange
     (WrapLedgerView (ShelleyBlock (TPraos c) ShelleyEra))
forecast ShelleyLedgerConfig ShelleyEra
cfgShelley Bound
bound SlotNo
forecastFor LedgerState ByronBlock mk
currentByronState
    | SlotNo
forecastFor SlotNo -> SlotNo -> Bool
forall a. Ord a => a -> a -> Bool
< SlotNo
maxFor =
        WrapLedgerView (ShelleyBlock (TPraos c) ShelleyEra)
-> Except
     OutsideForecastRange
     (WrapLedgerView (ShelleyBlock (TPraos c) ShelleyEra))
forall a. a -> ExceptT OutsideForecastRange Identity a
forall (m :: * -> *) a. Monad m => a -> m a
return (WrapLedgerView (ShelleyBlock (TPraos c) ShelleyEra)
 -> Except
      OutsideForecastRange
      (WrapLedgerView (ShelleyBlock (TPraos c) ShelleyEra)))
-> WrapLedgerView (ShelleyBlock (TPraos c) ShelleyEra)
-> Except
     OutsideForecastRange
     (WrapLedgerView (ShelleyBlock (TPraos c) ShelleyEra))
forall a b. (a -> b) -> a -> b
$
          LedgerView (BlockProtocol (ShelleyBlock (TPraos c) ShelleyEra))
-> WrapLedgerView (ShelleyBlock (TPraos c) ShelleyEra)
forall blk. LedgerView (BlockProtocol blk) -> WrapLedgerView blk
WrapLedgerView (LedgerView (BlockProtocol (ShelleyBlock (TPraos c) ShelleyEra))
 -> WrapLedgerView (ShelleyBlock (TPraos c) ShelleyEra))
-> LedgerView (BlockProtocol (ShelleyBlock (TPraos c) ShelleyEra))
-> WrapLedgerView (ShelleyBlock (TPraos c) ShelleyEra)
forall a b. (a -> b) -> a -> b
$
            FromByronTranslationContext -> LedgerView
SL.mkInitialShelleyLedgerView
              (ShelleyGenesis -> FromByronTranslationContext
toFromByronTranslationContext (ShelleyLedgerConfig ShelleyEra -> ShelleyGenesis
forall era. ShelleyLedgerConfig era -> ShelleyGenesis
shelleyLedgerGenesis ShelleyLedgerConfig ShelleyEra
cfgShelley))
    | Bool
otherwise =
        OutsideForecastRange
-> Except
     OutsideForecastRange
     (WrapLedgerView (ShelleyBlock (TPraos c) ShelleyEra))
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)))
-> OutsideForecastRange
-> Except
     OutsideForecastRange
     (WrapLedgerView (ShelleyBlock (TPraos c) ShelleyEra))
forall a b. (a -> b) -> a -> b
$
          OutsideForecastRange
            { outsideForecastAt :: WithOrigin SlotNo
outsideForecastAt = LedgerState ByronBlock mk -> WithOrigin SlotNo
forall blk (mk :: * -> * -> *).
UpdateLedger blk =>
LedgerState blk mk -> WithOrigin SlotNo
ledgerTipSlot LedgerState ByronBlock mk
currentByronState
            , outsideForecastMaxFor :: SlotNo
outsideForecastMaxFor = SlotNo
maxFor
            , outsideForecastFor :: SlotNo
outsideForecastFor = SlotNo
forecastFor
            }
   where
    globals :: Globals
globals = ShelleyLedgerConfig ShelleyEra -> Globals
forall era. ShelleyLedgerConfig era -> Globals
shelleyLedgerGlobals ShelleyLedgerConfig ShelleyEra
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 ::
  RequiringBoth
    WrapLedgerConfig
    TranslateLedgerState
    (ShelleyBlock (TPraos c) ShelleyEra)
    (ShelleyBlock (TPraos c) AllegraEra)
translateLedgerStateShelleyToAllegraWrapper :: forall c.
RequiringBoth
  WrapLedgerConfig
  TranslateLedgerState
  (ShelleyBlock (TPraos c) ShelleyEra)
  (ShelleyBlock (TPraos c) AllegraEra)
translateLedgerStateShelleyToAllegraWrapper =
  TranslateLedgerState
  (ShelleyBlock (TPraos c) ShelleyEra)
  (ShelleyBlock (TPraos c) AllegraEra)
-> RequiringBoth
     WrapLedgerConfig
     TranslateLedgerState
     (ShelleyBlock (TPraos c) ShelleyEra)
     (ShelleyBlock (TPraos c) AllegraEra)
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (h :: k -> *).
f x y -> RequiringBoth h f x y
ignoringBoth (TranslateLedgerState
   (ShelleyBlock (TPraos c) ShelleyEra)
   (ShelleyBlock (TPraos c) AllegraEra)
 -> RequiringBoth
      WrapLedgerConfig
      TranslateLedgerState
      (ShelleyBlock (TPraos c) ShelleyEra)
      (ShelleyBlock (TPraos c) AllegraEra))
-> TranslateLedgerState
     (ShelleyBlock (TPraos c) ShelleyEra)
     (ShelleyBlock (TPraos c) AllegraEra)
-> RequiringBoth
     WrapLedgerConfig
     TranslateLedgerState
     (ShelleyBlock (TPraos c) ShelleyEra)
     (ShelleyBlock (TPraos c) AllegraEra)
forall a b. (a -> b) -> a -> b
$
    TranslateLedgerState
      { translateLedgerStateWith :: EpochNo
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
-> LedgerState (ShelleyBlock (TPraos c) AllegraEra) DiffMK
translateLedgerStateWith = \EpochNo
_epochNo LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
ls ->
          -- In the Shelley to Allegra transition, the AVVM addresses have
          -- to be deleted, and their balance has to be moved to the
          -- reserves. For this matter, the Ledger keeps track of these
          -- small set of entries since the Byron to Shelley transition and
          -- provides them to us through 'shelleyToAllegraAVVMsToDelete'.
          --
          -- In the long run, the ledger will already use ledger states
          -- parametrized by the map kind and therefore will already provide
          -- the differences in this translation.
          let avvms :: Map TxIn (TxOut ShelleyEra)
avvms =
                UTxO ShelleyEra -> Map TxIn (TxOut ShelleyEra)
forall era. UTxO era -> Map TxIn (TxOut era)
SL.unUTxO (UTxO ShelleyEra -> Map TxIn (TxOut ShelleyEra))
-> UTxO ShelleyEra -> Map TxIn (TxOut ShelleyEra)
forall a b. (a -> b) -> a -> b
$
                  NewEpochState ShelleyEra -> UTxO ShelleyEra
shelleyToAllegraAVVMsToDelete (NewEpochState ShelleyEra -> UTxO ShelleyEra)
-> NewEpochState ShelleyEra -> UTxO ShelleyEra
forall a b. (a -> b) -> a -> b
$
                    LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
-> NewEpochState ShelleyEra
forall proto era (mk :: * -> * -> *).
LedgerState (ShelleyBlock proto era) mk -> NewEpochState era
shelleyLedgerState LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
ls

              -- While techically we can diff the LedgerTables, it becomes
              -- complex doing so, as we cannot perform operations with
              -- 'LedgerTables l1 mk' and 'LedgerTables l2 mk'. Because of
              -- this, for now we choose to generate the differences out of
              -- thin air as we know that in this era translation these are
              -- the only differences produced.
              --
              -- When adding more tables, this decision might need to be
              -- revisited, as there might be other diffs produced in the
              -- translation.
              avvmsAsDeletions :: LedgerTables
  (LedgerState (ShelleyBlock (TPraos c) AllegraEra)) DiffMK
avvmsAsDeletions =
                DiffMK TxIn (ShelleyTxOut AllegraEra)
-> LedgerTables
     (LedgerState (ShelleyBlock (TPraos c) AllegraEra)) DiffMK
DiffMK
  (TxIn (LedgerState (ShelleyBlock (TPraos c) AllegraEra)))
  (TxOut (LedgerState (ShelleyBlock (TPraos c) AllegraEra)))
-> LedgerTables
     (LedgerState (ShelleyBlock (TPraos c) AllegraEra)) DiffMK
forall (l :: LedgerStateKind) (mk :: * -> * -> *).
mk (TxIn l) (TxOut l) -> LedgerTables l mk
LedgerTables
                  (DiffMK TxIn (ShelleyTxOut AllegraEra)
 -> LedgerTables
      (LedgerState (ShelleyBlock (TPraos c) AllegraEra)) DiffMK)
-> (Map TxIn (TxOut ShelleyEra)
    -> DiffMK TxIn (ShelleyTxOut AllegraEra))
-> Map TxIn (TxOut ShelleyEra)
-> LedgerTables
     (LedgerState (ShelleyBlock (TPraos c) AllegraEra)) DiffMK
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Diff TxIn (ShelleyTxOut AllegraEra)
-> DiffMK TxIn (ShelleyTxOut AllegraEra)
forall k v. Diff k v -> DiffMK k v
DiffMK
                  (Diff TxIn (ShelleyTxOut AllegraEra)
 -> DiffMK TxIn (ShelleyTxOut AllegraEra))
-> (Map TxIn (ShelleyTxOut ShelleyEra)
    -> Diff TxIn (ShelleyTxOut AllegraEra))
-> Map TxIn (ShelleyTxOut ShelleyEra)
-> DiffMK TxIn (ShelleyTxOut AllegraEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map TxIn (ShelleyTxOut AllegraEra)
-> Diff TxIn (ShelleyTxOut AllegraEra)
forall k v. Map k v -> Diff k v
Diff.fromMapDeletes
                  (Map TxIn (ShelleyTxOut AllegraEra)
 -> Diff TxIn (ShelleyTxOut AllegraEra))
-> (Map TxIn (ShelleyTxOut ShelleyEra)
    -> Map TxIn (ShelleyTxOut AllegraEra))
-> Map TxIn (ShelleyTxOut ShelleyEra)
-> Diff TxIn (ShelleyTxOut AllegraEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ShelleyTxOut ShelleyEra -> ShelleyTxOut AllegraEra)
-> Map TxIn (ShelleyTxOut ShelleyEra)
-> Map TxIn (ShelleyTxOut AllegraEra)
forall a b k. (a -> b) -> Map k a -> Map k b
Map.map TxOut (PreviousEra AllegraEra) -> TxOut AllegraEra
ShelleyTxOut ShelleyEra -> ShelleyTxOut AllegraEra
forall era.
(EraTxOut era, EraTxOut (PreviousEra era)) =>
TxOut (PreviousEra era) -> TxOut era
SL.upgradeTxOut
                  (Map TxIn (TxOut ShelleyEra)
 -> LedgerTables
      (LedgerState (ShelleyBlock (TPraos c) AllegraEra)) DiffMK)
-> Map TxIn (TxOut ShelleyEra)
-> LedgerTables
     (LedgerState (ShelleyBlock (TPraos c) AllegraEra)) DiffMK
forall a b. (a -> b) -> a -> b
$ Map TxIn (TxOut ShelleyEra)
avvms

              -- This 'stowLedgerTables' + 'withLedgerTables' injects the
              -- values provided by the Ledger so that the translation
              -- operation finds those entries in the UTxO and destroys
              -- them, modifying the reserves accordingly.
              stowedState :: LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
stowedState =
                LedgerState (ShelleyBlock (TPraos c) ShelleyEra) ValuesMK
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
forall (l :: LedgerStateKind).
CanStowLedgerTables l =>
l ValuesMK -> l EmptyMK
stowLedgerTables
                  (LedgerState (ShelleyBlock (TPraos c) ShelleyEra) ValuesMK
 -> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK)
-> (Map TxIn (TxOut ShelleyEra)
    -> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) ValuesMK)
-> Map TxIn (TxOut ShelleyEra)
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
-> LedgerTables
     (LedgerState (ShelleyBlock (TPraos c) ShelleyEra)) ValuesMK
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) ValuesMK
forall (mk :: * -> * -> *) (any :: * -> * -> *).
(CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) =>
LedgerState (ShelleyBlock (TPraos c) ShelleyEra) any
-> LedgerTables
     (LedgerState (ShelleyBlock (TPraos c) ShelleyEra)) mk
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) mk
forall (l :: LedgerStateKind) (mk :: * -> * -> *)
       (any :: * -> * -> *).
(HasLedgerTables l, CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) =>
l any -> LedgerTables l mk -> l mk
withLedgerTables LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
ls
                  (LedgerTables
   (LedgerState (ShelleyBlock (TPraos c) ShelleyEra)) ValuesMK
 -> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) ValuesMK)
-> (Map TxIn (ShelleyTxOut ShelleyEra)
    -> LedgerTables
         (LedgerState (ShelleyBlock (TPraos c) ShelleyEra)) ValuesMK)
-> Map TxIn (ShelleyTxOut ShelleyEra)
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) ValuesMK
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValuesMK TxIn (ShelleyTxOut ShelleyEra)
-> LedgerTables
     (LedgerState (ShelleyBlock (TPraos c) ShelleyEra)) ValuesMK
ValuesMK
  (TxIn (LedgerState (ShelleyBlock (TPraos c) ShelleyEra)))
  (TxOut (LedgerState (ShelleyBlock (TPraos c) ShelleyEra)))
-> LedgerTables
     (LedgerState (ShelleyBlock (TPraos c) ShelleyEra)) ValuesMK
forall (l :: LedgerStateKind) (mk :: * -> * -> *).
mk (TxIn l) (TxOut l) -> LedgerTables l mk
LedgerTables
                  (ValuesMK TxIn (ShelleyTxOut ShelleyEra)
 -> LedgerTables
      (LedgerState (ShelleyBlock (TPraos c) ShelleyEra)) ValuesMK)
-> (Map TxIn (ShelleyTxOut ShelleyEra)
    -> ValuesMK TxIn (ShelleyTxOut ShelleyEra))
-> Map TxIn (ShelleyTxOut ShelleyEra)
-> LedgerTables
     (LedgerState (ShelleyBlock (TPraos c) ShelleyEra)) ValuesMK
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map TxIn (ShelleyTxOut ShelleyEra)
-> ValuesMK TxIn (ShelleyTxOut ShelleyEra)
forall k v. Map k v -> ValuesMK k v
ValuesMK
                  (Map TxIn (TxOut ShelleyEra)
 -> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK)
-> Map TxIn (TxOut ShelleyEra)
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
forall a b. (a -> b) -> a -> b
$ Map TxIn (TxOut ShelleyEra)
avvms

              resultingState :: LedgerState (ShelleyBlock (TPraos c) AllegraEra) EmptyMK
resultingState =
                Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) AllegraEra)
-> LedgerState (ShelleyBlock (TPraos c) AllegraEra) EmptyMK
forall x1 y1 (f :: x1 -> y1 -> *) (x2 :: y1) (y2 :: x1).
Flip f x2 y2 -> f y2 x2
unFlip
                  (Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) AllegraEra)
 -> LedgerState (ShelleyBlock (TPraos c) AllegraEra) EmptyMK)
-> (LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
    -> Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) AllegraEra))
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
-> LedgerState (ShelleyBlock (TPraos c) AllegraEra) EmptyMK
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:.:)
  (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) AllegraEra
-> Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) AllegraEra)
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp
                  ((:.:)
   (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) AllegraEra
 -> Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) AllegraEra))
-> (LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
    -> (:.:)
         (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) AllegraEra)
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
-> Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) AllegraEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext AllegraEra
-> (:.:)
     (Flip LedgerState EmptyMK)
     (ShelleyBlock (TPraos c))
     (PreviousEra AllegraEra)
-> (:.:)
     (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) AllegraEra
forall era (f :: * -> *).
(TranslateEra era f, TranslationError era f ~ Void) =>
TranslationContext era -> f (PreviousEra era) -> f era
SL.translateEra' TranslationContext AllegraEra
NoGenesis AllegraEra
forall era. NoGenesis era
SL.NoGenesis
                  ((:.:)
   (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) ShelleyEra
 -> (:.:)
      (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) AllegraEra)
-> (LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
    -> (:.:)
         (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) ShelleyEra)
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
-> (:.:)
     (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) AllegraEra
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) ShelleyEra)
-> (:.:)
     (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) ShelleyEra
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp
                  (Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) ShelleyEra)
 -> (:.:)
      (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) ShelleyEra)
-> (LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
    -> Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) ShelleyEra))
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
-> (:.:)
     (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) ShelleyEra
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
-> Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) ShelleyEra)
forall x y (f :: x -> y -> *) (x1 :: y) (y1 :: x).
f y1 x1 -> Flip f x1 y1
Flip
                  (LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
 -> LedgerState (ShelleyBlock (TPraos c) AllegraEra) EmptyMK)
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
-> LedgerState (ShelleyBlock (TPraos c) AllegraEra) EmptyMK
forall a b. (a -> b) -> a -> b
$ LedgerState (ShelleyBlock (TPraos c) ShelleyEra) EmptyMK
stowedState
           in LedgerState (ShelleyBlock (TPraos c) AllegraEra) EmptyMK
resultingState LedgerState (ShelleyBlock (TPraos c) AllegraEra) EmptyMK
-> LedgerTables
     (LedgerState (ShelleyBlock (TPraos c) AllegraEra)) DiffMK
-> LedgerState (ShelleyBlock (TPraos c) AllegraEra) DiffMK
forall (mk :: * -> * -> *) (any :: * -> * -> *).
(CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) =>
LedgerState (ShelleyBlock (TPraos c) AllegraEra) any
-> LedgerTables
     (LedgerState (ShelleyBlock (TPraos c) AllegraEra)) mk
-> LedgerState (ShelleyBlock (TPraos c) AllegraEra) mk
forall (l :: LedgerStateKind) (mk :: * -> * -> *)
       (any :: * -> * -> *).
(HasLedgerTables l, CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) =>
l any -> LedgerTables l mk -> l mk
`withLedgerTables` LedgerTables
  (LedgerState (ShelleyBlock (TPraos c) AllegraEra)) DiffMK
avvmsAsDeletions
      }

translateLedgerTablesShelleyToAllegraWrapper ::
  TranslateLedgerTables
    (ShelleyBlock (TPraos c) ShelleyEra)
    (ShelleyBlock (TPraos c) AllegraEra)
translateLedgerTablesShelleyToAllegraWrapper :: forall c.
TranslateLedgerTables
  (ShelleyBlock (TPraos c) ShelleyEra)
  (ShelleyBlock (TPraos c) AllegraEra)
translateLedgerTablesShelleyToAllegraWrapper =
  TranslateLedgerTables
    { translateTxInWith :: TxIn (LedgerState (ShelleyBlock (TPraos c) ShelleyEra))
-> TxIn (LedgerState (ShelleyBlock (TPraos c) AllegraEra))
translateTxInWith = TxIn -> TxIn
TxIn (LedgerState (ShelleyBlock (TPraos c) ShelleyEra))
-> TxIn (LedgerState (ShelleyBlock (TPraos c) AllegraEra))
forall a b. Coercible a b => a -> b
coerce
    , translateTxOutWith :: TxOut (LedgerState (ShelleyBlock (TPraos c) ShelleyEra))
-> TxOut (LedgerState (ShelleyBlock (TPraos c) AllegraEra))
translateTxOutWith = TxOut (PreviousEra AllegraEra) -> TxOut AllegraEra
TxOut (LedgerState (ShelleyBlock (TPraos c) ShelleyEra))
-> TxOut (LedgerState (ShelleyBlock (TPraos c) AllegraEra))
forall era.
(EraTxOut era, EraTxOut (PreviousEra era)) =>
TxOut (PreviousEra era) -> TxOut era
SL.upgradeTxOut
    }

translateTxShelleyToAllegraWrapper ::
  InjectTx
    (ShelleyBlock (TPraos c) ShelleyEra)
    (ShelleyBlock (TPraos c) AllegraEra)
translateTxShelleyToAllegraWrapper :: forall c.
InjectTx
  (ShelleyBlock (TPraos c) ShelleyEra)
  (ShelleyBlock (TPraos c) AllegraEra)
translateTxShelleyToAllegraWrapper =
  (GenTx (ShelleyBlock (TPraos c) ShelleyEra)
 -> Maybe (GenTx (ShelleyBlock (TPraos c) AllegraEra)))
-> InjectTx
     (ShelleyBlock (TPraos c) ShelleyEra)
     (ShelleyBlock (TPraos c) AllegraEra)
forall blk blk'.
(GenTx blk -> Maybe (GenTx blk')) -> InjectTx blk blk'
InjectTx ((GenTx (ShelleyBlock (TPraos c) ShelleyEra)
  -> Maybe (GenTx (ShelleyBlock (TPraos c) AllegraEra)))
 -> InjectTx
      (ShelleyBlock (TPraos c) ShelleyEra)
      (ShelleyBlock (TPraos c) AllegraEra))
-> (GenTx (ShelleyBlock (TPraos c) ShelleyEra)
    -> Maybe (GenTx (ShelleyBlock (TPraos c) AllegraEra)))
-> InjectTx
     (ShelleyBlock (TPraos c) ShelleyEra)
     (ShelleyBlock (TPraos c) AllegraEra)
forall a b. (a -> b) -> a -> b
$
    ((:.:) GenTx (ShelleyBlock (TPraos c)) AllegraEra
 -> GenTx (ShelleyBlock (TPraos c) AllegraEra))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) AllegraEra)
-> Maybe (GenTx (ShelleyBlock (TPraos c) AllegraEra))
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
-> GenTx (ShelleyBlock (TPraos c) AllegraEra)
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp (Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) AllegraEra)
 -> Maybe (GenTx (ShelleyBlock (TPraos c) AllegraEra)))
-> (GenTx (ShelleyBlock (TPraos c) ShelleyEra)
    -> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) AllegraEra))
-> GenTx (ShelleyBlock (TPraos c) ShelleyEra)
-> Maybe (GenTx (ShelleyBlock (TPraos c) AllegraEra))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
  DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) AllegraEra)
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) AllegraEra)
forall a b. Either a b -> Maybe b
eitherToMaybe (Either
   DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) AllegraEra)
 -> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) AllegraEra))
-> (GenTx (ShelleyBlock (TPraos c) ShelleyEra)
    -> Either
         DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) AllegraEra))
-> GenTx (ShelleyBlock (TPraos c) ShelleyEra)
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) AllegraEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except
  DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) AllegraEra)
-> Either
     DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) AllegraEra)
forall e a. Except e a -> Either e a
runExcept (Except
   DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) AllegraEra)
 -> Either
      DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) AllegraEra))
-> (GenTx (ShelleyBlock (TPraos c) ShelleyEra)
    -> Except
         DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) AllegraEra))
-> GenTx (ShelleyBlock (TPraos c) ShelleyEra)
-> Either
     DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) AllegraEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext AllegraEra
-> (:.:) GenTx (ShelleyBlock (TPraos c)) (PreviousEra AllegraEra)
-> Except
     (TranslationError AllegraEra (GenTx :.: ShelleyBlock (TPraos c)))
     ((:.:) GenTx (ShelleyBlock (TPraos c)) AllegraEra)
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra TranslationContext AllegraEra
NoGenesis AllegraEra
forall era. NoGenesis era
SL.NoGenesis ((:.:) GenTx (ShelleyBlock (TPraos c)) ShelleyEra
 -> Except
      DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) AllegraEra))
-> (GenTx (ShelleyBlock (TPraos c) ShelleyEra)
    -> (:.:) GenTx (ShelleyBlock (TPraos c)) ShelleyEra)
-> GenTx (ShelleyBlock (TPraos c) ShelleyEra)
-> Except
     DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) AllegraEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenTx (ShelleyBlock (TPraos c) ShelleyEra)
-> (:.:) GenTx (ShelleyBlock (TPraos c)) ShelleyEra
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp

translateValidatedTxShelleyToAllegraWrapper ::
  InjectValidatedTx
    (ShelleyBlock (TPraos c) ShelleyEra)
    (ShelleyBlock (TPraos c) AllegraEra)
translateValidatedTxShelleyToAllegraWrapper :: forall c.
InjectValidatedTx
  (ShelleyBlock (TPraos c) ShelleyEra)
  (ShelleyBlock (TPraos c) AllegraEra)
translateValidatedTxShelleyToAllegraWrapper =
  (WrapValidatedGenTx (ShelleyBlock (TPraos c) ShelleyEra)
 -> Maybe (WrapValidatedGenTx (ShelleyBlock (TPraos c) AllegraEra)))
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) ShelleyEra)
     (ShelleyBlock (TPraos c) AllegraEra)
forall blk blk'.
(WrapValidatedGenTx blk -> Maybe (WrapValidatedGenTx blk'))
-> InjectValidatedTx blk blk'
InjectValidatedTx ((WrapValidatedGenTx (ShelleyBlock (TPraos c) ShelleyEra)
  -> Maybe (WrapValidatedGenTx (ShelleyBlock (TPraos c) AllegraEra)))
 -> InjectValidatedTx
      (ShelleyBlock (TPraos c) ShelleyEra)
      (ShelleyBlock (TPraos c) AllegraEra))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) ShelleyEra)
    -> Maybe (WrapValidatedGenTx (ShelleyBlock (TPraos c) AllegraEra)))
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) ShelleyEra)
     (ShelleyBlock (TPraos c) AllegraEra)
forall a b. (a -> b) -> a -> b
$
    ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AllegraEra
 -> WrapValidatedGenTx (ShelleyBlock (TPraos c) AllegraEra))
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AllegraEra)
-> Maybe (WrapValidatedGenTx (ShelleyBlock (TPraos c) AllegraEra))
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
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) AllegraEra)
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp (Maybe
   ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AllegraEra)
 -> Maybe (WrapValidatedGenTx (ShelleyBlock (TPraos c) AllegraEra)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) ShelleyEra)
    -> Maybe
         ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AllegraEra))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) ShelleyEra)
-> Maybe (WrapValidatedGenTx (ShelleyBlock (TPraos c) AllegraEra))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
  DecoderError
  ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AllegraEra)
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AllegraEra)
forall a b. Either a b -> Maybe b
eitherToMaybe (Either
   DecoderError
   ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AllegraEra)
 -> Maybe
      ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AllegraEra))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) ShelleyEra)
    -> Either
         DecoderError
         ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AllegraEra))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) ShelleyEra)
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AllegraEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except
  DecoderError
  ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AllegraEra)
-> Either
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AllegraEra)
forall e a. Except e a -> Either e a
runExcept (Except
   DecoderError
   ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AllegraEra)
 -> Either
      DecoderError
      ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AllegraEra))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) ShelleyEra)
    -> Except
         DecoderError
         ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AllegraEra))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) ShelleyEra)
-> Either
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AllegraEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext AllegraEra
-> (:.:)
     WrapValidatedGenTx
     (ShelleyBlock (TPraos c))
     (PreviousEra AllegraEra)
-> Except
     (TranslationError
        AllegraEra (WrapValidatedGenTx :.: ShelleyBlock (TPraos c)))
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AllegraEra)
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra TranslationContext AllegraEra
NoGenesis AllegraEra
forall era. NoGenesis era
SL.NoGenesis ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) ShelleyEra
 -> Except
      DecoderError
      ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AllegraEra))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) ShelleyEra)
    -> (:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) ShelleyEra)
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) ShelleyEra)
-> Except
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AllegraEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapValidatedGenTx (ShelleyBlock (TPraos c) ShelleyEra)
-> (:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) ShelleyEra
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp

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

translateLedgerStateAllegraToMaryWrapper ::
  RequiringBoth
    WrapLedgerConfig
    TranslateLedgerState
    (ShelleyBlock (TPraos c) AllegraEra)
    (ShelleyBlock (TPraos c) MaryEra)
translateLedgerStateAllegraToMaryWrapper :: forall c.
RequiringBoth
  WrapLedgerConfig
  TranslateLedgerState
  (ShelleyBlock (TPraos c) AllegraEra)
  (ShelleyBlock (TPraos c) MaryEra)
translateLedgerStateAllegraToMaryWrapper =
  TranslateLedgerState
  (ShelleyBlock (TPraos c) AllegraEra)
  (ShelleyBlock (TPraos c) MaryEra)
-> RequiringBoth
     WrapLedgerConfig
     TranslateLedgerState
     (ShelleyBlock (TPraos c) AllegraEra)
     (ShelleyBlock (TPraos c) MaryEra)
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (h :: k -> *).
f x y -> RequiringBoth h f x y
ignoringBoth (TranslateLedgerState
   (ShelleyBlock (TPraos c) AllegraEra)
   (ShelleyBlock (TPraos c) MaryEra)
 -> RequiringBoth
      WrapLedgerConfig
      TranslateLedgerState
      (ShelleyBlock (TPraos c) AllegraEra)
      (ShelleyBlock (TPraos c) MaryEra))
-> TranslateLedgerState
     (ShelleyBlock (TPraos c) AllegraEra)
     (ShelleyBlock (TPraos c) MaryEra)
-> RequiringBoth
     WrapLedgerConfig
     TranslateLedgerState
     (ShelleyBlock (TPraos c) AllegraEra)
     (ShelleyBlock (TPraos c) MaryEra)
forall a b. (a -> b) -> a -> b
$
    TranslateLedgerState
      { translateLedgerStateWith :: EpochNo
-> LedgerState (ShelleyBlock (TPraos c) AllegraEra) EmptyMK
-> LedgerState (ShelleyBlock (TPraos c) MaryEra) DiffMK
translateLedgerStateWith = \EpochNo
_epochNo ->
          LedgerState (ShelleyBlock (TPraos c) MaryEra) EmptyMK
-> LedgerState (ShelleyBlock (TPraos c) MaryEra) DiffMK
forall (l :: LedgerStateKind) (any :: * -> * -> *).
HasLedgerTables l =>
l any -> l DiffMK
noNewTickingDiffs
            (LedgerState (ShelleyBlock (TPraos c) MaryEra) EmptyMK
 -> LedgerState (ShelleyBlock (TPraos c) MaryEra) DiffMK)
-> (LedgerState (ShelleyBlock (TPraos c) AllegraEra) EmptyMK
    -> LedgerState (ShelleyBlock (TPraos c) MaryEra) EmptyMK)
-> LedgerState (ShelleyBlock (TPraos c) AllegraEra) EmptyMK
-> LedgerState (ShelleyBlock (TPraos c) MaryEra) DiffMK
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) MaryEra)
-> LedgerState (ShelleyBlock (TPraos c) MaryEra) EmptyMK
forall x1 y1 (f :: x1 -> y1 -> *) (x2 :: y1) (y2 :: x1).
Flip f x2 y2 -> f y2 x2
unFlip
            (Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) MaryEra)
 -> LedgerState (ShelleyBlock (TPraos c) MaryEra) EmptyMK)
-> (LedgerState (ShelleyBlock (TPraos c) AllegraEra) EmptyMK
    -> Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) MaryEra))
-> LedgerState (ShelleyBlock (TPraos c) AllegraEra) EmptyMK
-> LedgerState (ShelleyBlock (TPraos c) MaryEra) EmptyMK
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:.:) (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) MaryEra
-> Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) MaryEra)
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp
            ((:.:) (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) MaryEra
 -> Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) MaryEra))
-> (LedgerState (ShelleyBlock (TPraos c) AllegraEra) EmptyMK
    -> (:.:)
         (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) MaryEra)
-> LedgerState (ShelleyBlock (TPraos c) AllegraEra) EmptyMK
-> Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) MaryEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext MaryEra
-> (:.:)
     (Flip LedgerState EmptyMK)
     (ShelleyBlock (TPraos c))
     (PreviousEra MaryEra)
-> (:.:)
     (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) MaryEra
forall era (f :: * -> *).
(TranslateEra era f, TranslationError era f ~ Void) =>
TranslationContext era -> f (PreviousEra era) -> f era
SL.translateEra' TranslationContext MaryEra
NoGenesis MaryEra
forall era. NoGenesis era
SL.NoGenesis
            ((:.:)
   (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) AllegraEra
 -> (:.:)
      (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) MaryEra)
-> (LedgerState (ShelleyBlock (TPraos c) AllegraEra) EmptyMK
    -> (:.:)
         (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) AllegraEra)
-> LedgerState (ShelleyBlock (TPraos c) AllegraEra) EmptyMK
-> (:.:)
     (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) MaryEra
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) AllegraEra)
-> (:.:)
     (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) AllegraEra
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp
            (Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) AllegraEra)
 -> (:.:)
      (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) AllegraEra)
-> (LedgerState (ShelleyBlock (TPraos c) AllegraEra) EmptyMK
    -> Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) AllegraEra))
-> LedgerState (ShelleyBlock (TPraos c) AllegraEra) EmptyMK
-> (:.:)
     (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) AllegraEra
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (TPraos c) AllegraEra) EmptyMK
-> Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) AllegraEra)
forall x y (f :: x -> y -> *) (x1 :: y) (y1 :: x).
f y1 x1 -> Flip f x1 y1
Flip
      }

translateLedgerTablesAllegraToMaryWrapper ::
  TranslateLedgerTables
    (ShelleyBlock (TPraos c) AllegraEra)
    (ShelleyBlock (TPraos c) MaryEra)
translateLedgerTablesAllegraToMaryWrapper :: forall c.
TranslateLedgerTables
  (ShelleyBlock (TPraos c) AllegraEra)
  (ShelleyBlock (TPraos c) MaryEra)
translateLedgerTablesAllegraToMaryWrapper =
  TranslateLedgerTables
    { translateTxInWith :: TxIn (LedgerState (ShelleyBlock (TPraos c) AllegraEra))
-> TxIn (LedgerState (ShelleyBlock (TPraos c) MaryEra))
translateTxInWith = TxIn -> TxIn
TxIn (LedgerState (ShelleyBlock (TPraos c) AllegraEra))
-> TxIn (LedgerState (ShelleyBlock (TPraos c) MaryEra))
forall a b. Coercible a b => a -> b
coerce
    , translateTxOutWith :: TxOut (LedgerState (ShelleyBlock (TPraos c) AllegraEra))
-> TxOut (LedgerState (ShelleyBlock (TPraos c) MaryEra))
translateTxOutWith = TxOut (PreviousEra MaryEra) -> TxOut MaryEra
TxOut (LedgerState (ShelleyBlock (TPraos c) AllegraEra))
-> TxOut (LedgerState (ShelleyBlock (TPraos c) MaryEra))
forall era.
(EraTxOut era, EraTxOut (PreviousEra era)) =>
TxOut (PreviousEra era) -> TxOut era
SL.upgradeTxOut
    }

translateTxAllegraToMaryWrapper ::
  InjectTx
    (ShelleyBlock (TPraos c) AllegraEra)
    (ShelleyBlock (TPraos c) MaryEra)
translateTxAllegraToMaryWrapper :: forall c.
InjectTx
  (ShelleyBlock (TPraos c) AllegraEra)
  (ShelleyBlock (TPraos c) MaryEra)
translateTxAllegraToMaryWrapper =
  (GenTx (ShelleyBlock (TPraos c) AllegraEra)
 -> Maybe (GenTx (ShelleyBlock (TPraos c) MaryEra)))
-> InjectTx
     (ShelleyBlock (TPraos c) AllegraEra)
     (ShelleyBlock (TPraos c) MaryEra)
forall blk blk'.
(GenTx blk -> Maybe (GenTx blk')) -> InjectTx blk blk'
InjectTx ((GenTx (ShelleyBlock (TPraos c) AllegraEra)
  -> Maybe (GenTx (ShelleyBlock (TPraos c) MaryEra)))
 -> InjectTx
      (ShelleyBlock (TPraos c) AllegraEra)
      (ShelleyBlock (TPraos c) MaryEra))
-> (GenTx (ShelleyBlock (TPraos c) AllegraEra)
    -> Maybe (GenTx (ShelleyBlock (TPraos c) MaryEra)))
-> InjectTx
     (ShelleyBlock (TPraos c) AllegraEra)
     (ShelleyBlock (TPraos c) MaryEra)
forall a b. (a -> b) -> a -> b
$
    ((:.:) GenTx (ShelleyBlock (TPraos c)) MaryEra
 -> GenTx (ShelleyBlock (TPraos c) MaryEra))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) MaryEra)
-> Maybe (GenTx (ShelleyBlock (TPraos c) MaryEra))
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
-> GenTx (ShelleyBlock (TPraos c) MaryEra)
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp (Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) MaryEra)
 -> Maybe (GenTx (ShelleyBlock (TPraos c) MaryEra)))
-> (GenTx (ShelleyBlock (TPraos c) AllegraEra)
    -> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) MaryEra))
-> GenTx (ShelleyBlock (TPraos c) AllegraEra)
-> Maybe (GenTx (ShelleyBlock (TPraos c) MaryEra))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) MaryEra)
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) MaryEra)
forall a b. Either a b -> Maybe b
eitherToMaybe (Either
   DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) MaryEra)
 -> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) MaryEra))
-> (GenTx (ShelleyBlock (TPraos c) AllegraEra)
    -> Either
         DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) MaryEra))
-> GenTx (ShelleyBlock (TPraos c) AllegraEra)
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) MaryEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) MaryEra)
-> Either
     DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) MaryEra)
forall e a. Except e a -> Either e a
runExcept (Except
   DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) MaryEra)
 -> Either
      DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) MaryEra))
-> (GenTx (ShelleyBlock (TPraos c) AllegraEra)
    -> Except
         DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) MaryEra))
-> GenTx (ShelleyBlock (TPraos c) AllegraEra)
-> Either
     DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) MaryEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext MaryEra
-> (:.:) GenTx (ShelleyBlock (TPraos c)) (PreviousEra MaryEra)
-> Except
     (TranslationError MaryEra (GenTx :.: ShelleyBlock (TPraos c)))
     ((:.:) GenTx (ShelleyBlock (TPraos c)) MaryEra)
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra TranslationContext MaryEra
NoGenesis MaryEra
forall era. NoGenesis era
SL.NoGenesis ((:.:) GenTx (ShelleyBlock (TPraos c)) AllegraEra
 -> Except
      DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) MaryEra))
-> (GenTx (ShelleyBlock (TPraos c) AllegraEra)
    -> (:.:) GenTx (ShelleyBlock (TPraos c)) AllegraEra)
-> GenTx (ShelleyBlock (TPraos c) AllegraEra)
-> Except
     DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) MaryEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenTx (ShelleyBlock (TPraos c) AllegraEra)
-> (:.:) GenTx (ShelleyBlock (TPraos c)) AllegraEra
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp

translateValidatedTxAllegraToMaryWrapper ::
  InjectValidatedTx
    (ShelleyBlock (TPraos c) AllegraEra)
    (ShelleyBlock (TPraos c) MaryEra)
translateValidatedTxAllegraToMaryWrapper :: forall c.
InjectValidatedTx
  (ShelleyBlock (TPraos c) AllegraEra)
  (ShelleyBlock (TPraos c) MaryEra)
translateValidatedTxAllegraToMaryWrapper =
  (WrapValidatedGenTx (ShelleyBlock (TPraos c) AllegraEra)
 -> Maybe (WrapValidatedGenTx (ShelleyBlock (TPraos c) MaryEra)))
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) AllegraEra)
     (ShelleyBlock (TPraos c) MaryEra)
forall blk blk'.
(WrapValidatedGenTx blk -> Maybe (WrapValidatedGenTx blk'))
-> InjectValidatedTx blk blk'
InjectValidatedTx ((WrapValidatedGenTx (ShelleyBlock (TPraos c) AllegraEra)
  -> Maybe (WrapValidatedGenTx (ShelleyBlock (TPraos c) MaryEra)))
 -> InjectValidatedTx
      (ShelleyBlock (TPraos c) AllegraEra)
      (ShelleyBlock (TPraos c) MaryEra))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) AllegraEra)
    -> Maybe (WrapValidatedGenTx (ShelleyBlock (TPraos c) MaryEra)))
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) AllegraEra)
     (ShelleyBlock (TPraos c) MaryEra)
forall a b. (a -> b) -> a -> b
$
    ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) MaryEra
 -> WrapValidatedGenTx (ShelleyBlock (TPraos c) MaryEra))
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) MaryEra)
-> Maybe (WrapValidatedGenTx (ShelleyBlock (TPraos c) MaryEra))
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
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) MaryEra)
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp (Maybe ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) MaryEra)
 -> Maybe (WrapValidatedGenTx (ShelleyBlock (TPraos c) MaryEra)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) AllegraEra)
    -> Maybe
         ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) MaryEra))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) AllegraEra)
-> Maybe (WrapValidatedGenTx (ShelleyBlock (TPraos c) MaryEra))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
  DecoderError
  ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) MaryEra)
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) MaryEra)
forall a b. Either a b -> Maybe b
eitherToMaybe (Either
   DecoderError
   ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) MaryEra)
 -> Maybe
      ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) MaryEra))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) AllegraEra)
    -> Either
         DecoderError
         ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) MaryEra))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) AllegraEra)
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) MaryEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except
  DecoderError
  ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) MaryEra)
-> Either
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) MaryEra)
forall e a. Except e a -> Either e a
runExcept (Except
   DecoderError
   ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) MaryEra)
 -> Either
      DecoderError
      ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) MaryEra))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) AllegraEra)
    -> Except
         DecoderError
         ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) MaryEra))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) AllegraEra)
-> Either
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) MaryEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext MaryEra
-> (:.:)
     WrapValidatedGenTx (ShelleyBlock (TPraos c)) (PreviousEra MaryEra)
-> Except
     (TranslationError
        MaryEra (WrapValidatedGenTx :.: ShelleyBlock (TPraos c)))
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) MaryEra)
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra TranslationContext MaryEra
NoGenesis MaryEra
forall era. NoGenesis era
SL.NoGenesis ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AllegraEra
 -> Except
      DecoderError
      ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) MaryEra))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) AllegraEra)
    -> (:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AllegraEra)
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) AllegraEra)
-> Except
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) MaryEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapValidatedGenTx (ShelleyBlock (TPraos c) AllegraEra)
-> (:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AllegraEra
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp

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

translateLedgerStateMaryToAlonzoWrapper ::
  RequiringBoth
    WrapLedgerConfig
    TranslateLedgerState
    (ShelleyBlock (TPraos c) MaryEra)
    (ShelleyBlock (TPraos c) AlonzoEra)
translateLedgerStateMaryToAlonzoWrapper :: forall c.
RequiringBoth
  WrapLedgerConfig
  TranslateLedgerState
  (ShelleyBlock (TPraos c) MaryEra)
  (ShelleyBlock (TPraos c) AlonzoEra)
translateLedgerStateMaryToAlonzoWrapper =
  (WrapLedgerConfig (ShelleyBlock (TPraos c) MaryEra)
 -> WrapLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
 -> TranslateLedgerState
      (ShelleyBlock (TPraos c) MaryEra)
      (ShelleyBlock (TPraos c) AlonzoEra))
-> RequiringBoth
     WrapLedgerConfig
     TranslateLedgerState
     (ShelleyBlock (TPraos c) MaryEra)
     (ShelleyBlock (TPraos c) AlonzoEra)
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)
  -> WrapLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
  -> TranslateLedgerState
       (ShelleyBlock (TPraos c) MaryEra)
       (ShelleyBlock (TPraos c) AlonzoEra))
 -> RequiringBoth
      WrapLedgerConfig
      TranslateLedgerState
      (ShelleyBlock (TPraos c) MaryEra)
      (ShelleyBlock (TPraos c) AlonzoEra))
-> (WrapLedgerConfig (ShelleyBlock (TPraos c) MaryEra)
    -> WrapLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
    -> TranslateLedgerState
         (ShelleyBlock (TPraos c) MaryEra)
         (ShelleyBlock (TPraos c) AlonzoEra))
-> RequiringBoth
     WrapLedgerConfig
     TranslateLedgerState
     (ShelleyBlock (TPraos c) MaryEra)
     (ShelleyBlock (TPraos c) AlonzoEra)
forall a b. (a -> b) -> a -> b
$ \WrapLedgerConfig (ShelleyBlock (TPraos c) MaryEra)
_cfgMary WrapLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
cfgAlonzo ->
    TranslateLedgerState
      { translateLedgerStateWith :: EpochNo
-> LedgerState (ShelleyBlock (TPraos c) MaryEra) EmptyMK
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra) DiffMK
translateLedgerStateWith = \EpochNo
_epochNo ->
          LedgerState (ShelleyBlock (TPraos c) AlonzoEra) EmptyMK
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra) DiffMK
forall (l :: LedgerStateKind) (any :: * -> * -> *).
HasLedgerTables l =>
l any -> l DiffMK
noNewTickingDiffs
            (LedgerState (ShelleyBlock (TPraos c) AlonzoEra) EmptyMK
 -> LedgerState (ShelleyBlock (TPraos c) AlonzoEra) DiffMK)
-> (LedgerState (ShelleyBlock (TPraos c) MaryEra) EmptyMK
    -> LedgerState (ShelleyBlock (TPraos c) AlonzoEra) EmptyMK)
-> LedgerState (ShelleyBlock (TPraos c) MaryEra) EmptyMK
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra) DiffMK
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) AlonzoEra)
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra) EmptyMK
forall x1 y1 (f :: x1 -> y1 -> *) (x2 :: y1) (y2 :: x1).
Flip f x2 y2 -> f y2 x2
unFlip
            (Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) AlonzoEra)
 -> LedgerState (ShelleyBlock (TPraos c) AlonzoEra) EmptyMK)
-> (LedgerState (ShelleyBlock (TPraos c) MaryEra) EmptyMK
    -> Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) AlonzoEra))
-> LedgerState (ShelleyBlock (TPraos c) MaryEra) EmptyMK
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra) EmptyMK
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:.:)
  (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) AlonzoEra
-> Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) AlonzoEra)
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp
            ((:.:)
   (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) AlonzoEra
 -> Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) AlonzoEra))
-> (LedgerState (ShelleyBlock (TPraos c) MaryEra) EmptyMK
    -> (:.:)
         (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) AlonzoEra)
-> LedgerState (ShelleyBlock (TPraos c) MaryEra) EmptyMK
-> Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) AlonzoEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext AlonzoEra
-> (:.:)
     (Flip LedgerState EmptyMK)
     (ShelleyBlock (TPraos c))
     (PreviousEra AlonzoEra)
-> (:.:)
     (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) AlonzoEra
forall era (f :: * -> *).
(TranslateEra era f, TranslationError era f ~ Void) =>
TranslationContext era -> f (PreviousEra era) -> f era
SL.translateEra' (WrapLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
-> TranslationContext AlonzoEra
forall c.
WrapLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
-> TranslationContext AlonzoEra
getAlonzoTranslationContext WrapLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
cfgAlonzo)
            ((:.:) (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) MaryEra
 -> (:.:)
      (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) AlonzoEra)
-> (LedgerState (ShelleyBlock (TPraos c) MaryEra) EmptyMK
    -> (:.:)
         (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) MaryEra)
-> LedgerState (ShelleyBlock (TPraos c) MaryEra) EmptyMK
-> (:.:)
     (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) AlonzoEra
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) MaryEra)
-> (:.:)
     (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) MaryEra
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp
            (Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) MaryEra)
 -> (:.:)
      (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) MaryEra)
-> (LedgerState (ShelleyBlock (TPraos c) MaryEra) EmptyMK
    -> Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) MaryEra))
-> LedgerState (ShelleyBlock (TPraos c) MaryEra) EmptyMK
-> (:.:)
     (Flip LedgerState EmptyMK) (ShelleyBlock (TPraos c)) MaryEra
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (TPraos c) MaryEra) EmptyMK
-> Flip LedgerState EmptyMK (ShelleyBlock (TPraos c) MaryEra)
forall x y (f :: x -> y -> *) (x1 :: y) (y1 :: x).
f y1 x1 -> Flip f x1 y1
Flip
      }

translateLedgerTablesMaryToAlonzoWrapper ::
  TranslateLedgerTables
    (ShelleyBlock (TPraos c) MaryEra)
    (ShelleyBlock (TPraos c) AlonzoEra)
translateLedgerTablesMaryToAlonzoWrapper :: forall c.
TranslateLedgerTables
  (ShelleyBlock (TPraos c) MaryEra)
  (ShelleyBlock (TPraos c) AlonzoEra)
translateLedgerTablesMaryToAlonzoWrapper =
  TranslateLedgerTables
    { translateTxInWith :: TxIn (LedgerState (ShelleyBlock (TPraos c) MaryEra))
-> TxIn (LedgerState (ShelleyBlock (TPraos c) AlonzoEra))
translateTxInWith = TxIn -> TxIn
TxIn (LedgerState (ShelleyBlock (TPraos c) MaryEra))
-> TxIn (LedgerState (ShelleyBlock (TPraos c) AlonzoEra))
forall a b. Coercible a b => a -> b
coerce
    , translateTxOutWith :: TxOut (LedgerState (ShelleyBlock (TPraos c) MaryEra))
-> TxOut (LedgerState (ShelleyBlock (TPraos c) AlonzoEra))
translateTxOutWith = TxOut (PreviousEra AlonzoEra) -> TxOut AlonzoEra
TxOut (LedgerState (ShelleyBlock (TPraos c) MaryEra))
-> TxOut (LedgerState (ShelleyBlock (TPraos c) AlonzoEra))
forall era.
(EraTxOut era, EraTxOut (PreviousEra era)) =>
TxOut (PreviousEra era) -> TxOut era
SL.upgradeTxOut
    }

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

translateTxMaryToAlonzoWrapper ::
  SL.TranslationContext AlonzoEra ->
  InjectTx
    (ShelleyBlock (TPraos c) MaryEra)
    (ShelleyBlock (TPraos c) AlonzoEra)
translateTxMaryToAlonzoWrapper :: forall c.
TranslationContext AlonzoEra
-> InjectTx
     (ShelleyBlock (TPraos c) MaryEra)
     (ShelleyBlock (TPraos c) AlonzoEra)
translateTxMaryToAlonzoWrapper TranslationContext AlonzoEra
ctxt =
  (GenTx (ShelleyBlock (TPraos c) MaryEra)
 -> Maybe (GenTx (ShelleyBlock (TPraos c) AlonzoEra)))
-> InjectTx
     (ShelleyBlock (TPraos c) MaryEra)
     (ShelleyBlock (TPraos c) AlonzoEra)
forall blk blk'.
(GenTx blk -> Maybe (GenTx blk')) -> InjectTx blk blk'
InjectTx ((GenTx (ShelleyBlock (TPraos c) MaryEra)
  -> Maybe (GenTx (ShelleyBlock (TPraos c) AlonzoEra)))
 -> InjectTx
      (ShelleyBlock (TPraos c) MaryEra)
      (ShelleyBlock (TPraos c) AlonzoEra))
-> (GenTx (ShelleyBlock (TPraos c) MaryEra)
    -> Maybe (GenTx (ShelleyBlock (TPraos c) AlonzoEra)))
-> InjectTx
     (ShelleyBlock (TPraos c) MaryEra)
     (ShelleyBlock (TPraos c) AlonzoEra)
forall a b. (a -> b) -> a -> b
$
    ((:.:) GenTx (ShelleyBlock (TPraos c)) AlonzoEra
 -> GenTx (ShelleyBlock (TPraos c) AlonzoEra))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) AlonzoEra)
-> Maybe (GenTx (ShelleyBlock (TPraos c) AlonzoEra))
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
-> GenTx (ShelleyBlock (TPraos c) AlonzoEra)
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp (Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) AlonzoEra)
 -> Maybe (GenTx (ShelleyBlock (TPraos c) AlonzoEra)))
-> (GenTx (ShelleyBlock (TPraos c) MaryEra)
    -> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) AlonzoEra))
-> GenTx (ShelleyBlock (TPraos c) MaryEra)
-> Maybe (GenTx (ShelleyBlock (TPraos c) AlonzoEra))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
  DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) AlonzoEra)
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) AlonzoEra)
forall a b. Either a b -> Maybe b
eitherToMaybe (Either
   DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) AlonzoEra)
 -> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) AlonzoEra))
-> (GenTx (ShelleyBlock (TPraos c) MaryEra)
    -> Either
         DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) AlonzoEra))
-> GenTx (ShelleyBlock (TPraos c) MaryEra)
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) AlonzoEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except
  DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) AlonzoEra)
-> Either
     DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) AlonzoEra)
forall e a. Except e a -> Either e a
runExcept (Except
   DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) AlonzoEra)
 -> Either
      DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) AlonzoEra))
-> (GenTx (ShelleyBlock (TPraos c) MaryEra)
    -> Except
         DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) AlonzoEra))
-> GenTx (ShelleyBlock (TPraos c) MaryEra)
-> Either
     DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) AlonzoEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext AlonzoEra
-> (:.:) GenTx (ShelleyBlock (TPraos c)) (PreviousEra AlonzoEra)
-> Except
     (TranslationError AlonzoEra (GenTx :.: ShelleyBlock (TPraos c)))
     ((:.:) GenTx (ShelleyBlock (TPraos c)) AlonzoEra)
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra TranslationContext AlonzoEra
ctxt ((:.:) GenTx (ShelleyBlock (TPraos c)) MaryEra
 -> Except
      DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) AlonzoEra))
-> (GenTx (ShelleyBlock (TPraos c) MaryEra)
    -> (:.:) GenTx (ShelleyBlock (TPraos c)) MaryEra)
-> GenTx (ShelleyBlock (TPraos c) MaryEra)
-> Except
     DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) AlonzoEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenTx (ShelleyBlock (TPraos c) MaryEra)
-> (:.:) GenTx (ShelleyBlock (TPraos c)) MaryEra
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp

translateValidatedTxMaryToAlonzoWrapper ::
  forall c.
  SL.TranslationContext AlonzoEra ->
  InjectValidatedTx
    (ShelleyBlock (TPraos c) MaryEra)
    (ShelleyBlock (TPraos c) AlonzoEra)
translateValidatedTxMaryToAlonzoWrapper :: forall c.
TranslationContext AlonzoEra
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) MaryEra)
     (ShelleyBlock (TPraos c) AlonzoEra)
translateValidatedTxMaryToAlonzoWrapper TranslationContext AlonzoEra
ctxt =
  (WrapValidatedGenTx (ShelleyBlock (TPraos c) MaryEra)
 -> Maybe (WrapValidatedGenTx (ShelleyBlock (TPraos c) AlonzoEra)))
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) MaryEra)
     (ShelleyBlock (TPraos c) AlonzoEra)
forall blk blk'.
(WrapValidatedGenTx blk -> Maybe (WrapValidatedGenTx blk'))
-> InjectValidatedTx blk blk'
InjectValidatedTx ((WrapValidatedGenTx (ShelleyBlock (TPraos c) MaryEra)
  -> Maybe (WrapValidatedGenTx (ShelleyBlock (TPraos c) AlonzoEra)))
 -> InjectValidatedTx
      (ShelleyBlock (TPraos c) MaryEra)
      (ShelleyBlock (TPraos c) AlonzoEra))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) MaryEra)
    -> Maybe (WrapValidatedGenTx (ShelleyBlock (TPraos c) AlonzoEra)))
-> InjectValidatedTx
     (ShelleyBlock (TPraos c) MaryEra)
     (ShelleyBlock (TPraos c) AlonzoEra)
forall a b. (a -> b) -> a -> b
$
    ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AlonzoEra
 -> WrapValidatedGenTx (ShelleyBlock (TPraos c) AlonzoEra))
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AlonzoEra)
-> Maybe (WrapValidatedGenTx (ShelleyBlock (TPraos c) AlonzoEra))
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
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) AlonzoEra)
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp (Maybe
   ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AlonzoEra)
 -> Maybe (WrapValidatedGenTx (ShelleyBlock (TPraos c) AlonzoEra)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) MaryEra)
    -> Maybe
         ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AlonzoEra))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) MaryEra)
-> Maybe (WrapValidatedGenTx (ShelleyBlock (TPraos c) AlonzoEra))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
  DecoderError
  ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AlonzoEra)
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AlonzoEra)
forall a b. Either a b -> Maybe b
eitherToMaybe (Either
   DecoderError
   ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AlonzoEra)
 -> Maybe
      ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AlonzoEra))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) MaryEra)
    -> Either
         DecoderError
         ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AlonzoEra))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) MaryEra)
-> Maybe
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AlonzoEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except
  DecoderError
  ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AlonzoEra)
-> Either
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AlonzoEra)
forall e a. Except e a -> Either e a
runExcept (Except
   DecoderError
   ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AlonzoEra)
 -> Either
      DecoderError
      ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AlonzoEra))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) MaryEra)
    -> Except
         DecoderError
         ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AlonzoEra))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) MaryEra)
-> Either
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AlonzoEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext AlonzoEra
-> (:.:)
     WrapValidatedGenTx
     (ShelleyBlock (TPraos c))
     (PreviousEra AlonzoEra)
-> Except
     (TranslationError
        AlonzoEra (WrapValidatedGenTx :.: ShelleyBlock (TPraos c)))
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AlonzoEra)
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra TranslationContext AlonzoEra
ctxt ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) MaryEra
 -> Except
      DecoderError
      ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AlonzoEra))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) MaryEra)
    -> (:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) MaryEra)
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) MaryEra)
-> Except
     DecoderError
     ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) AlonzoEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapValidatedGenTx (ShelleyBlock (TPraos c) MaryEra)
-> (:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) MaryEra
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp

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

translateLedgerStateAlonzoToBabbageWrapper ::
  RequiringBoth
    WrapLedgerConfig
    TranslateLedgerState
    (ShelleyBlock (TPraos c) AlonzoEra)
    (ShelleyBlock (Praos c) BabbageEra)
translateLedgerStateAlonzoToBabbageWrapper :: forall c.
RequiringBoth
  WrapLedgerConfig
  TranslateLedgerState
  (ShelleyBlock (TPraos c) AlonzoEra)
  (ShelleyBlock (Praos c) BabbageEra)
translateLedgerStateAlonzoToBabbageWrapper =
  (WrapLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
 -> WrapLedgerConfig (ShelleyBlock (Praos c) BabbageEra)
 -> TranslateLedgerState
      (ShelleyBlock (TPraos c) AlonzoEra)
      (ShelleyBlock (Praos c) BabbageEra))
-> RequiringBoth
     WrapLedgerConfig
     TranslateLedgerState
     (ShelleyBlock (TPraos c) AlonzoEra)
     (ShelleyBlock (Praos c) BabbageEra)
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)
  -> WrapLedgerConfig (ShelleyBlock (Praos c) BabbageEra)
  -> TranslateLedgerState
       (ShelleyBlock (TPraos c) AlonzoEra)
       (ShelleyBlock (Praos c) BabbageEra))
 -> RequiringBoth
      WrapLedgerConfig
      TranslateLedgerState
      (ShelleyBlock (TPraos c) AlonzoEra)
      (ShelleyBlock (Praos c) BabbageEra))
-> (WrapLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
    -> WrapLedgerConfig (ShelleyBlock (Praos c) BabbageEra)
    -> TranslateLedgerState
         (ShelleyBlock (TPraos c) AlonzoEra)
         (ShelleyBlock (Praos c) BabbageEra))
-> RequiringBoth
     WrapLedgerConfig
     TranslateLedgerState
     (ShelleyBlock (TPraos c) AlonzoEra)
     (ShelleyBlock (Praos c) BabbageEra)
forall a b. (a -> b) -> a -> b
$ \WrapLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
_cfgAlonzo WrapLedgerConfig (ShelleyBlock (Praos c) BabbageEra)
_cfgBabbage ->
    TranslateLedgerState
      { translateLedgerStateWith :: EpochNo
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra) EmptyMK
-> LedgerState (ShelleyBlock (Praos c) BabbageEra) DiffMK
translateLedgerStateWith = \EpochNo
_epochNo ->
          LedgerState (ShelleyBlock (Praos c) BabbageEra) EmptyMK
-> LedgerState (ShelleyBlock (Praos c) BabbageEra) DiffMK
forall (l :: LedgerStateKind) (any :: * -> * -> *).
HasLedgerTables l =>
l any -> l DiffMK
noNewTickingDiffs
            (LedgerState (ShelleyBlock (Praos c) BabbageEra) EmptyMK
 -> LedgerState (ShelleyBlock (Praos c) BabbageEra) DiffMK)
-> (LedgerState (ShelleyBlock (TPraos c) AlonzoEra) EmptyMK
    -> LedgerState (ShelleyBlock (Praos c) BabbageEra) EmptyMK)
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra) EmptyMK
-> LedgerState (ShelleyBlock (Praos c) BabbageEra) DiffMK
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flip LedgerState EmptyMK (ShelleyBlock (Praos c) BabbageEra)
-> LedgerState (ShelleyBlock (Praos c) BabbageEra) EmptyMK
forall x1 y1 (f :: x1 -> y1 -> *) (x2 :: y1) (y2 :: x1).
Flip f x2 y2 -> f y2 x2
unFlip
            (Flip LedgerState EmptyMK (ShelleyBlock (Praos c) BabbageEra)
 -> LedgerState (ShelleyBlock (Praos c) BabbageEra) EmptyMK)
-> (LedgerState (ShelleyBlock (TPraos c) AlonzoEra) EmptyMK
    -> Flip LedgerState EmptyMK (ShelleyBlock (Praos c) BabbageEra))
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra) EmptyMK
-> LedgerState (ShelleyBlock (Praos c) BabbageEra) EmptyMK
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:.:)
  (Flip LedgerState EmptyMK) (ShelleyBlock (Praos c)) BabbageEra
-> Flip LedgerState EmptyMK (ShelleyBlock (Praos c) BabbageEra)
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp
            ((:.:)
   (Flip LedgerState EmptyMK) (ShelleyBlock (Praos c)) BabbageEra
 -> Flip LedgerState EmptyMK (ShelleyBlock (Praos c) BabbageEra))
-> (LedgerState (ShelleyBlock (TPraos c) AlonzoEra) EmptyMK
    -> (:.:)
         (Flip LedgerState EmptyMK) (ShelleyBlock (Praos c)) BabbageEra)
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra) EmptyMK
-> Flip LedgerState EmptyMK (ShelleyBlock (Praos c) BabbageEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext BabbageEra
-> (:.:)
     (Flip LedgerState EmptyMK)
     (ShelleyBlock (Praos c))
     (PreviousEra BabbageEra)
-> (:.:)
     (Flip LedgerState EmptyMK) (ShelleyBlock (Praos c)) BabbageEra
forall era (f :: * -> *).
(TranslateEra era f, TranslationError era f ~ Void) =>
TranslationContext era -> f (PreviousEra era) -> f era
SL.translateEra' TranslationContext BabbageEra
NoGenesis BabbageEra
forall era. NoGenesis era
SL.NoGenesis
            ((:.:)
   (Flip LedgerState EmptyMK) (ShelleyBlock (Praos c)) AlonzoEra
 -> (:.:)
      (Flip LedgerState EmptyMK) (ShelleyBlock (Praos c)) BabbageEra)
-> (LedgerState (ShelleyBlock (TPraos c) AlonzoEra) EmptyMK
    -> (:.:)
         (Flip LedgerState EmptyMK) (ShelleyBlock (Praos c)) AlonzoEra)
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra) EmptyMK
-> (:.:)
     (Flip LedgerState EmptyMK) (ShelleyBlock (Praos c)) BabbageEra
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flip LedgerState EmptyMK (ShelleyBlock (Praos c) AlonzoEra)
-> (:.:)
     (Flip LedgerState EmptyMK) (ShelleyBlock (Praos c)) AlonzoEra
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp
            (Flip LedgerState EmptyMK (ShelleyBlock (Praos c) AlonzoEra)
 -> (:.:)
      (Flip LedgerState EmptyMK) (ShelleyBlock (Praos c)) AlonzoEra)
-> (LedgerState (ShelleyBlock (TPraos c) AlonzoEra) EmptyMK
    -> Flip LedgerState EmptyMK (ShelleyBlock (Praos c) AlonzoEra))
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra) EmptyMK
-> (:.:)
     (Flip LedgerState EmptyMK) (ShelleyBlock (Praos c)) AlonzoEra
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (Praos c) AlonzoEra) EmptyMK
-> Flip LedgerState EmptyMK (ShelleyBlock (Praos c) AlonzoEra)
forall x y (f :: x -> y -> *) (x1 :: y) (y1 :: x).
f y1 x1 -> Flip f x1 y1
Flip
            (LedgerState (ShelleyBlock (Praos c) AlonzoEra) EmptyMK
 -> Flip LedgerState EmptyMK (ShelleyBlock (Praos c) AlonzoEra))
-> (LedgerState (ShelleyBlock (TPraos c) AlonzoEra) EmptyMK
    -> LedgerState (ShelleyBlock (Praos c) AlonzoEra) EmptyMK)
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra) EmptyMK
-> Flip LedgerState EmptyMK (ShelleyBlock (Praos c) AlonzoEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (TPraos c) AlonzoEra) EmptyMK
-> LedgerState (ShelleyBlock (Praos c) AlonzoEra) EmptyMK
forall c (mk :: * -> * -> *).
LedgerState (ShelleyBlock (TPraos c) AlonzoEra) mk
-> LedgerState (ShelleyBlock (Praos c) AlonzoEra) mk
transPraosLS
      }
 where
  transPraosLS ::
    LedgerState (ShelleyBlock (TPraos c) AlonzoEra) mk ->
    LedgerState (ShelleyBlock (Praos c) AlonzoEra) mk
  transPraosLS :: forall c (mk :: * -> * -> *).
LedgerState (ShelleyBlock (TPraos c) AlonzoEra) mk
-> LedgerState (ShelleyBlock (Praos c) AlonzoEra) mk
transPraosLS (ShelleyLedgerState WithOrigin (ShelleyTip (TPraos c) AlonzoEra)
wo NewEpochState AlonzoEra
nes ShelleyTransition
st LedgerTables (LedgerState (ShelleyBlock (TPraos c) AlonzoEra)) mk
tb) =
    ShelleyLedgerState
      { shelleyLedgerTip :: WithOrigin (ShelleyTip (Praos c) AlonzoEra)
shelleyLedgerTip = (ShelleyTip (TPraos c) AlonzoEra -> ShelleyTip (Praos c) AlonzoEra)
-> WithOrigin (ShelleyTip (TPraos c) AlonzoEra)
-> WithOrigin (ShelleyTip (Praos c) AlonzoEra)
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 -> ShelleyTip (Praos c) AlonzoEra
forall proto era proto' era'.
ShelleyTip proto era -> ShelleyTip proto' era'
castShelleyTip WithOrigin (ShelleyTip (TPraos c) AlonzoEra)
wo
      , shelleyLedgerState :: NewEpochState AlonzoEra
shelleyLedgerState = NewEpochState AlonzoEra
nes
      , shelleyLedgerTransition :: ShelleyTransition
shelleyLedgerTransition = ShelleyTransition
st
      , shelleyLedgerTables :: LedgerTables (LedgerState (ShelleyBlock (Praos c) AlonzoEra)) mk
shelleyLedgerTables = LedgerTables (LedgerState (ShelleyBlock (TPraos c) AlonzoEra)) mk
-> LedgerTables (LedgerState (ShelleyBlock (Praos c) AlonzoEra)) mk
forall a b. Coercible a b => a -> b
coerce LedgerTables (LedgerState (ShelleyBlock (TPraos c) AlonzoEra)) mk
tb
      }

translateLedgerTablesAlonzoToBabbageWrapper ::
  TranslateLedgerTables
    (ShelleyBlock (TPraos c) AlonzoEra)
    (ShelleyBlock (Praos c) BabbageEra)
translateLedgerTablesAlonzoToBabbageWrapper :: forall c.
TranslateLedgerTables
  (ShelleyBlock (TPraos c) AlonzoEra)
  (ShelleyBlock (Praos c) BabbageEra)
translateLedgerTablesAlonzoToBabbageWrapper =
  TranslateLedgerTables
    { translateTxInWith :: TxIn (LedgerState (ShelleyBlock (TPraos c) AlonzoEra))
-> TxIn (LedgerState (ShelleyBlock (Praos c) BabbageEra))
translateTxInWith = TxIn -> TxIn
TxIn (LedgerState (ShelleyBlock (TPraos c) AlonzoEra))
-> TxIn (LedgerState (ShelleyBlock (Praos c) BabbageEra))
forall a b. Coercible a b => a -> b
coerce
    , translateTxOutWith :: TxOut (LedgerState (ShelleyBlock (TPraos c) AlonzoEra))
-> TxOut (LedgerState (ShelleyBlock (Praos c) BabbageEra))
translateTxOutWith = TxOut (PreviousEra BabbageEra) -> TxOut BabbageEra
TxOut (LedgerState (ShelleyBlock (TPraos c) AlonzoEra))
-> TxOut (LedgerState (ShelleyBlock (Praos c) BabbageEra))
forall era.
(EraTxOut era, EraTxOut (PreviousEra era)) =>
TxOut (PreviousEra era) -> TxOut era
SL.upgradeTxOut
    }

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

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

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

translateLedgerStateBabbageToConwayWrapper ::
  RequiringBoth
    WrapLedgerConfig
    TranslateLedgerState
    (ShelleyBlock (Praos c) BabbageEra)
    (ShelleyBlock (Praos c) ConwayEra)
translateLedgerStateBabbageToConwayWrapper :: forall c.
RequiringBoth
  WrapLedgerConfig
  TranslateLedgerState
  (ShelleyBlock (Praos c) BabbageEra)
  (ShelleyBlock (Praos c) ConwayEra)
translateLedgerStateBabbageToConwayWrapper =
  (WrapLedgerConfig (ShelleyBlock (Praos c) BabbageEra)
 -> WrapLedgerConfig (ShelleyBlock (Praos c) ConwayEra)
 -> TranslateLedgerState
      (ShelleyBlock (Praos c) BabbageEra)
      (ShelleyBlock (Praos c) ConwayEra))
-> RequiringBoth
     WrapLedgerConfig
     TranslateLedgerState
     (ShelleyBlock (Praos c) BabbageEra)
     (ShelleyBlock (Praos c) ConwayEra)
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)
  -> WrapLedgerConfig (ShelleyBlock (Praos c) ConwayEra)
  -> TranslateLedgerState
       (ShelleyBlock (Praos c) BabbageEra)
       (ShelleyBlock (Praos c) ConwayEra))
 -> RequiringBoth
      WrapLedgerConfig
      TranslateLedgerState
      (ShelleyBlock (Praos c) BabbageEra)
      (ShelleyBlock (Praos c) ConwayEra))
-> (WrapLedgerConfig (ShelleyBlock (Praos c) BabbageEra)
    -> WrapLedgerConfig (ShelleyBlock (Praos c) ConwayEra)
    -> TranslateLedgerState
         (ShelleyBlock (Praos c) BabbageEra)
         (ShelleyBlock (Praos c) ConwayEra))
-> RequiringBoth
     WrapLedgerConfig
     TranslateLedgerState
     (ShelleyBlock (Praos c) BabbageEra)
     (ShelleyBlock (Praos c) ConwayEra)
forall a b. (a -> b) -> a -> b
$ \WrapLedgerConfig (ShelleyBlock (Praos c) BabbageEra)
_cfgBabbage WrapLedgerConfig (ShelleyBlock (Praos c) ConwayEra)
cfgConway ->
    TranslateLedgerState
      { translateLedgerStateWith :: EpochNo
-> LedgerState (ShelleyBlock (Praos c) BabbageEra) EmptyMK
-> LedgerState (ShelleyBlock (Praos c) ConwayEra) DiffMK
translateLedgerStateWith = \EpochNo
_epochNo ->
          LedgerState (ShelleyBlock (Praos c) ConwayEra) EmptyMK
-> LedgerState (ShelleyBlock (Praos c) ConwayEra) DiffMK
forall (l :: LedgerStateKind) (any :: * -> * -> *).
HasLedgerTables l =>
l any -> l DiffMK
noNewTickingDiffs
            (LedgerState (ShelleyBlock (Praos c) ConwayEra) EmptyMK
 -> LedgerState (ShelleyBlock (Praos c) ConwayEra) DiffMK)
-> (LedgerState (ShelleyBlock (Praos c) BabbageEra) EmptyMK
    -> LedgerState (ShelleyBlock (Praos c) ConwayEra) EmptyMK)
-> LedgerState (ShelleyBlock (Praos c) BabbageEra) EmptyMK
-> LedgerState (ShelleyBlock (Praos c) ConwayEra) DiffMK
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flip LedgerState EmptyMK (ShelleyBlock (Praos c) ConwayEra)
-> LedgerState (ShelleyBlock (Praos c) ConwayEra) EmptyMK
forall x1 y1 (f :: x1 -> y1 -> *) (x2 :: y1) (y2 :: x1).
Flip f x2 y2 -> f y2 x2
unFlip
            (Flip LedgerState EmptyMK (ShelleyBlock (Praos c) ConwayEra)
 -> LedgerState (ShelleyBlock (Praos c) ConwayEra) EmptyMK)
-> (LedgerState (ShelleyBlock (Praos c) BabbageEra) EmptyMK
    -> Flip LedgerState EmptyMK (ShelleyBlock (Praos c) ConwayEra))
-> LedgerState (ShelleyBlock (Praos c) BabbageEra) EmptyMK
-> LedgerState (ShelleyBlock (Praos c) ConwayEra) EmptyMK
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:.:) (Flip LedgerState EmptyMK) (ShelleyBlock (Praos c)) ConwayEra
-> Flip LedgerState EmptyMK (ShelleyBlock (Praos c) ConwayEra)
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp
            ((:.:)
   (Flip LedgerState EmptyMK) (ShelleyBlock (Praos c)) ConwayEra
 -> Flip LedgerState EmptyMK (ShelleyBlock (Praos c) ConwayEra))
-> (LedgerState (ShelleyBlock (Praos c) BabbageEra) EmptyMK
    -> (:.:)
         (Flip LedgerState EmptyMK) (ShelleyBlock (Praos c)) ConwayEra)
-> LedgerState (ShelleyBlock (Praos c) BabbageEra) EmptyMK
-> Flip LedgerState EmptyMK (ShelleyBlock (Praos c) ConwayEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext ConwayEra
-> (:.:)
     (Flip LedgerState EmptyMK)
     (ShelleyBlock (Praos c))
     (PreviousEra ConwayEra)
-> (:.:)
     (Flip LedgerState EmptyMK) (ShelleyBlock (Praos c)) ConwayEra
forall era (f :: * -> *).
(TranslateEra era f, TranslationError era f ~ Void) =>
TranslationContext era -> f (PreviousEra era) -> f era
SL.translateEra' (WrapLedgerConfig (ShelleyBlock (Praos c) ConwayEra)
-> TranslationContext ConwayEra
forall c.
WrapLedgerConfig (ShelleyBlock (Praos c) ConwayEra)
-> TranslationContext ConwayEra
getConwayTranslationContext WrapLedgerConfig (ShelleyBlock (Praos c) ConwayEra)
cfgConway)
            ((:.:)
   (Flip LedgerState EmptyMK) (ShelleyBlock (Praos c)) BabbageEra
 -> (:.:)
      (Flip LedgerState EmptyMK) (ShelleyBlock (Praos c)) ConwayEra)
-> (LedgerState (ShelleyBlock (Praos c) BabbageEra) EmptyMK
    -> (:.:)
         (Flip LedgerState EmptyMK) (ShelleyBlock (Praos c)) BabbageEra)
-> LedgerState (ShelleyBlock (Praos c) BabbageEra) EmptyMK
-> (:.:)
     (Flip LedgerState EmptyMK) (ShelleyBlock (Praos c)) ConwayEra
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flip LedgerState EmptyMK (ShelleyBlock (Praos c) BabbageEra)
-> (:.:)
     (Flip LedgerState EmptyMK) (ShelleyBlock (Praos c)) BabbageEra
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp
            (Flip LedgerState EmptyMK (ShelleyBlock (Praos c) BabbageEra)
 -> (:.:)
      (Flip LedgerState EmptyMK) (ShelleyBlock (Praos c)) BabbageEra)
-> (LedgerState (ShelleyBlock (Praos c) BabbageEra) EmptyMK
    -> Flip LedgerState EmptyMK (ShelleyBlock (Praos c) BabbageEra))
-> LedgerState (ShelleyBlock (Praos c) BabbageEra) EmptyMK
-> (:.:)
     (Flip LedgerState EmptyMK) (ShelleyBlock (Praos c)) BabbageEra
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (Praos c) BabbageEra) EmptyMK
-> Flip LedgerState EmptyMK (ShelleyBlock (Praos c) BabbageEra)
forall x y (f :: x -> y -> *) (x1 :: y) (y1 :: x).
f y1 x1 -> Flip f x1 y1
Flip
      }

translateLedgerTablesBabbageToConwayWrapper ::
  TranslateLedgerTables
    (ShelleyBlock (Praos c) BabbageEra)
    (ShelleyBlock (Praos c) ConwayEra)
translateLedgerTablesBabbageToConwayWrapper :: forall c.
TranslateLedgerTables
  (ShelleyBlock (Praos c) BabbageEra)
  (ShelleyBlock (Praos c) ConwayEra)
translateLedgerTablesBabbageToConwayWrapper =
  TranslateLedgerTables
    { translateTxInWith :: TxIn (LedgerState (ShelleyBlock (Praos c) BabbageEra))
-> TxIn (LedgerState (ShelleyBlock (Praos c) ConwayEra))
translateTxInWith = TxIn -> TxIn
TxIn (LedgerState (ShelleyBlock (Praos c) BabbageEra))
-> TxIn (LedgerState (ShelleyBlock (Praos c) ConwayEra))
forall a b. Coercible a b => a -> b
coerce
    , translateTxOutWith :: TxOut (LedgerState (ShelleyBlock (Praos c) BabbageEra))
-> TxOut (LedgerState (ShelleyBlock (Praos c) ConwayEra))
translateTxOutWith = TxOut (PreviousEra ConwayEra) -> TxOut ConwayEra
TxOut (LedgerState (ShelleyBlock (Praos c) BabbageEra))
-> TxOut (LedgerState (ShelleyBlock (Praos c) ConwayEra))
forall era.
(EraTxOut era, EraTxOut (PreviousEra era)) =>
TxOut (PreviousEra era) -> TxOut era
SL.upgradeTxOut
    }

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

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

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