{-# 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 (..)
, ShelleyPartialLedgerConfig (..)
, crossEraForecastAcrossShelley
, translateChainDepStateAcrossShelley
) where
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.InPairs (RequiringBoth (..), ignoringBoth)
import qualified Data.SOP.Strict as SOP
import Data.SOP.Tails (Tails (..))
import qualified Data.SOP.Tails as Tails
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 Ouroboros.Consensus.Protocol.Abstract (SelectView,
TranslateProto)
import Ouroboros.Consensus.Protocol.PBFT.State (PBftState)
import qualified Ouroboros.Consensus.Protocol.PBFT.State as PBftState
import Ouroboros.Consensus.Protocol.Praos (Praos)
import qualified Ouroboros.Consensus.Protocol.Praos as Praos
import Ouroboros.Consensus.Protocol.TPraos
import qualified Ouroboros.Consensus.Protocol.TPraos as TPraos
import Ouroboros.Consensus.Shelley.Ledger
import Ouroboros.Consensus.Shelley.Node ()
import Ouroboros.Consensus.Shelley.Protocol.Praos ()
import Ouroboros.Consensus.Shelley.ShelleyHFC
import Ouroboros.Consensus.TypeFamilyWrappers
import Ouroboros.Consensus.Util (eitherToMaybe)
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)
)
instance CardanoHardForkConstraints c => CanHardFork (CardanoEras c) where
type HardForkTxMeasure (CardanoEras c) = ConwayMeasure
hardForkEraTranslation :: EraTranslation (CardanoEras c)
hardForkEraTranslation = EraTranslation {
translateLedgerState :: InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
(CardanoEras c)
translateLedgerState =
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
ByronBlock
(ShelleyBlock (TPraos c) ShelleyEra)
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[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 (Translate LedgerState))
(CardanoEras c)
forall {k} (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
ByronBlock
(ShelleyBlock (TPraos c) ShelleyEra)
forall c.
ShelleyCompatible (TPraos c) ShelleyEra =>
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
ByronBlock
(ShelleyBlock (TPraos c) ShelleyEra)
translateLedgerStateByronToShelleyWrapper
(InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[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 (Translate LedgerState))
(CardanoEras c))
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[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 (Translate LedgerState))
(CardanoEras c)
forall a b. (a -> b) -> a -> b
$ RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) ShelleyEra)
(ShelleyBlock (TPraos c) AllegraEra)
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) AllegraEra,
ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
ShelleyBlock (Praos c) BabbageEra,
ShelleyBlock (Praos c) ConwayEra]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[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
(Translate LedgerState)
(ShelleyBlock (TPraos c) ShelleyEra)
(ShelleyBlock (TPraos c) AllegraEra)
forall c.
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) ShelleyEra)
(ShelleyBlock (TPraos c) AllegraEra)
translateLedgerStateShelleyToAllegraWrapper
(InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) AllegraEra,
ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
ShelleyBlock (Praos c) BabbageEra,
ShelleyBlock (Praos c) ConwayEra]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[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 (Translate LedgerState))
'[ShelleyBlock (TPraos c) AllegraEra,
ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
ShelleyBlock (Praos c) BabbageEra,
ShelleyBlock (Praos c) ConwayEra]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[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
(Translate LedgerState)
(ShelleyBlock (TPraos c) AllegraEra)
(ShelleyBlock (TPraos c) MaryEra)
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) MaryEra,
ShelleyBlock (TPraos c) AlonzoEra,
ShelleyBlock (Praos c) BabbageEra,
ShelleyBlock (Praos c) ConwayEra]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[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
(Translate LedgerState)
(ShelleyBlock (TPraos c) AllegraEra)
(ShelleyBlock (TPraos c) MaryEra)
forall c.
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) AllegraEra)
(ShelleyBlock (TPraos c) MaryEra)
translateLedgerStateAllegraToMaryWrapper
(InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) MaryEra,
ShelleyBlock (TPraos c) AlonzoEra,
ShelleyBlock (Praos c) BabbageEra,
ShelleyBlock (Praos c) ConwayEra]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) AllegraEra,
ShelleyBlock (TPraos c) MaryEra, ShelleyBlock (TPraos c) AlonzoEra,
ShelleyBlock (Praos c) BabbageEra,
ShelleyBlock (Praos c) ConwayEra])
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) MaryEra,
ShelleyBlock (TPraos c) AlonzoEra,
ShelleyBlock (Praos c) BabbageEra,
ShelleyBlock (Praos c) ConwayEra]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[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
(Translate LedgerState)
(ShelleyBlock (TPraos c) MaryEra)
(ShelleyBlock (TPraos c) AlonzoEra)
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) AlonzoEra,
ShelleyBlock (Praos c) BabbageEra,
ShelleyBlock (Praos c) ConwayEra]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[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
(Translate LedgerState)
(ShelleyBlock (TPraos c) MaryEra)
(ShelleyBlock (TPraos c) AlonzoEra)
forall c.
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) MaryEra)
(ShelleyBlock (TPraos c) AlonzoEra)
translateLedgerStateMaryToAlonzoWrapper
(InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) AlonzoEra,
ShelleyBlock (Praos c) BabbageEra,
ShelleyBlock (Praos c) ConwayEra]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) MaryEra,
ShelleyBlock (TPraos c) AlonzoEra,
ShelleyBlock (Praos c) BabbageEra,
ShelleyBlock (Praos c) ConwayEra])
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) AlonzoEra,
ShelleyBlock (Praos c) BabbageEra,
ShelleyBlock (Praos c) ConwayEra]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[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
(Translate LedgerState)
(ShelleyBlock (TPraos c) AlonzoEra)
(ShelleyBlock (Praos c) BabbageEra)
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (Praos c) BabbageEra,
ShelleyBlock (Praos c) ConwayEra]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[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
(Translate LedgerState)
(ShelleyBlock (TPraos c) AlonzoEra)
(ShelleyBlock (Praos c) BabbageEra)
forall c.
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) AlonzoEra)
(ShelleyBlock (Praos c) BabbageEra)
translateLedgerStateAlonzoToBabbageWrapper
(InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (Praos c) BabbageEra,
ShelleyBlock (Praos c) ConwayEra]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) AlonzoEra,
ShelleyBlock (Praos c) BabbageEra,
ShelleyBlock (Praos c) ConwayEra])
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (Praos c) BabbageEra,
ShelleyBlock (Praos c) ConwayEra]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) AlonzoEra,
ShelleyBlock (Praos c) BabbageEra,
ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (Praos c) BabbageEra)
(ShelleyBlock (Praos c) ConwayEra)
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (Praos c) ConwayEra]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[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
(Translate LedgerState)
(ShelleyBlock (Praos c) BabbageEra)
(ShelleyBlock (Praos c) ConwayEra)
forall c.
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (Praos c) BabbageEra)
(ShelleyBlock (Praos c) ConwayEra)
translateLedgerStateBabbageToConwayWrapper
(InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (Praos c) ConwayEra]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (Praos c) BabbageEra,
ShelleyBlock (Praos c) ConwayEra])
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (Praos c) ConwayEra]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (Praos c) BabbageEra,
ShelleyBlock (Praos c) ConwayEra]
forall a b. (a -> b) -> a -> b
$ InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[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 =
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)
(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 `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
translateHeaderHashByronToShelley ::
forall c.
ShelleyCompatible (TPraos c) ShelleyEra
=> Proxy c
-> HeaderHash ByronBlock
-> HeaderHash (ShelleyBlock (TPraos c) ShelleyEra)
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
(Translate LedgerState)
ByronBlock
(ShelleyBlock (TPraos c) ShelleyEra)
translateLedgerStateByronToShelleyWrapper :: forall c.
ShelleyCompatible (TPraos c) ShelleyEra =>
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
ByronBlock
(ShelleyBlock (TPraos c) ShelleyEra)
translateLedgerStateByronToShelleyWrapper =
(WrapLedgerConfig ByronBlock
-> WrapLedgerConfig (ShelleyBlock (TPraos c) ShelleyEra)
-> Translate
LedgerState ByronBlock (ShelleyBlock (TPraos c) ShelleyEra))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
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)
-> Translate
LedgerState ByronBlock (ShelleyBlock (TPraos c) ShelleyEra))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
ByronBlock
(ShelleyBlock (TPraos c) ShelleyEra))
-> (WrapLedgerConfig ByronBlock
-> WrapLedgerConfig (ShelleyBlock (TPraos c) ShelleyEra)
-> Translate
LedgerState ByronBlock (ShelleyBlock (TPraos c) ShelleyEra))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
ByronBlock
(ShelleyBlock (TPraos c) ShelleyEra)
forall a b. (a -> b) -> a -> b
$ \WrapLedgerConfig ByronBlock
_ (WrapLedgerConfig LedgerConfig (ShelleyBlock (TPraos c) ShelleyEra)
cfgShelley) ->
(EpochNo
-> LedgerState ByronBlock
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra))
-> Translate
LedgerState ByronBlock (ShelleyBlock (TPraos c) ShelleyEra)
forall (f :: * -> *) x y.
(EpochNo -> f x -> f y) -> Translate f x y
Translate ((EpochNo
-> LedgerState ByronBlock
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra))
-> Translate
LedgerState ByronBlock (ShelleyBlock (TPraos c) ShelleyEra))
-> (EpochNo
-> LedgerState ByronBlock
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra))
-> Translate
LedgerState ByronBlock (ShelleyBlock (TPraos c) ShelleyEra)
forall a b. (a -> b) -> a -> b
$ \EpochNo
epochNo LedgerState ByronBlock
ledgerByron ->
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 -> Point ByronBlock
forall blk. UpdateLedger blk => LedgerState blk -> Point blk
ledgerTipPoint LedgerState ByronBlock
ledgerByron)
(LedgerState ByronBlock -> WithOrigin BlockNo
byronLedgerTipBlockNo LedgerState ByronBlock
ledgerByron)
, shelleyLedgerState :: NewEpochState ShelleyEra
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 -> ChainValidationState
byronLedgerState LedgerState ByronBlock
ledgerByron)
, shelleyLedgerTransition :: ShelleyTransition
shelleyLedgerTransition =
ShelleyTransitionInfo{shelleyAfterVoting :: Word32
shelleyAfterVoting = Word32
0}
}
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 =
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
}
, 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
-> Except
OutsideForecastRange
(WrapLedgerView (ShelleyBlock (TPraos c) ShelleyEra)))
-> CrossEraForecaster
LedgerState
WrapLedgerView
ByronBlock
(ShelleyBlock (TPraos c) ShelleyEra)
forall (state :: * -> *) (view :: * -> *) x y.
(Bound
-> SlotNo -> state x -> Except OutsideForecastRange (view y))
-> CrossEraForecaster state view x y
CrossEraForecaster (ShelleyLedgerConfig ShelleyEra
-> Bound
-> SlotNo
-> LedgerState ByronBlock
-> Except
OutsideForecastRange
(WrapLedgerView (ShelleyBlock (TPraos c) ShelleyEra))
forecast LedgerConfig (ShelleyBlock (TPraos c) ShelleyEra)
ShelleyLedgerConfig ShelleyEra
cfgShelley)
where
forecast ::
ShelleyLedgerConfig ShelleyEra
-> Bound
-> SlotNo
-> LedgerState ByronBlock
-> Except
OutsideForecastRange
(WrapLedgerView (ShelleyBlock (TPraos c) ShelleyEra))
forecast :: ShelleyLedgerConfig ShelleyEra
-> Bound
-> SlotNo
-> LedgerState ByronBlock
-> Except
OutsideForecastRange
(WrapLedgerView (ShelleyBlock (TPraos c) ShelleyEra))
forecast ShelleyLedgerConfig ShelleyEra
cfgShelley Bound
bound SlotNo
forecastFor LedgerState ByronBlock
currentByronState
| SlotNo
forecastFor SlotNo -> SlotNo -> Bool
forall a. Ord a => a -> a -> Bool
< SlotNo
maxFor
= WrapLedgerView (ShelleyBlock (TPraos c) ShelleyEra)
-> 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 -> WithOrigin SlotNo
forall blk.
UpdateLedger blk =>
LedgerState blk -> WithOrigin SlotNo
ledgerTipSlot LedgerState ByronBlock
currentByronState
, outsideForecastMaxFor :: SlotNo
outsideForecastMaxFor = SlotNo
maxFor
, outsideForecastFor :: SlotNo
outsideForecastFor = SlotNo
forecastFor
}
where
globals :: Globals
globals = ShelleyLedgerConfig ShelleyEra -> Globals
forall era. ShelleyLedgerConfig era -> Globals
shelleyLedgerGlobals ShelleyLedgerConfig ShelleyEra
cfgShelley
swindow :: Word64
swindow = Globals -> Word64
SL.stabilityWindow Globals
globals
maxFor :: SlotNo
maxFor :: SlotNo
maxFor = Word64 -> SlotNo -> SlotNo
addSlots Word64
swindow (Bound -> SlotNo
boundSlot Bound
bound)
translateLedgerStateShelleyToAllegraWrapper ::
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) ShelleyEra)
(ShelleyBlock (TPraos c) AllegraEra)
translateLedgerStateShelleyToAllegraWrapper :: forall c.
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) ShelleyEra)
(ShelleyBlock (TPraos c) AllegraEra)
translateLedgerStateShelleyToAllegraWrapper =
Translate
LedgerState
(ShelleyBlock (TPraos c) ShelleyEra)
(ShelleyBlock (TPraos c) AllegraEra)
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(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 (Translate
LedgerState
(ShelleyBlock (TPraos c) ShelleyEra)
(ShelleyBlock (TPraos c) AllegraEra)
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) ShelleyEra)
(ShelleyBlock (TPraos c) AllegraEra))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) ShelleyEra)
(ShelleyBlock (TPraos c) AllegraEra)
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) ShelleyEra)
(ShelleyBlock (TPraos c) AllegraEra)
forall a b. (a -> b) -> a -> b
$
(EpochNo
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra)
-> LedgerState (ShelleyBlock (TPraos c) AllegraEra))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) ShelleyEra)
(ShelleyBlock (TPraos c) AllegraEra)
forall (f :: * -> *) x y.
(EpochNo -> f x -> f y) -> Translate f x y
Translate ((EpochNo
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra)
-> LedgerState (ShelleyBlock (TPraos c) AllegraEra))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) ShelleyEra)
(ShelleyBlock (TPraos c) AllegraEra))
-> (EpochNo
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra)
-> LedgerState (ShelleyBlock (TPraos c) AllegraEra))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) ShelleyEra)
(ShelleyBlock (TPraos c) AllegraEra)
forall a b. (a -> b) -> a -> b
$ \EpochNo
_epochNo ->
(:.:) LedgerState (ShelleyBlock (TPraos c)) AllegraEra
-> LedgerState (ShelleyBlock (TPraos c) AllegraEra)
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp ((:.:) LedgerState (ShelleyBlock (TPraos c)) AllegraEra
-> LedgerState (ShelleyBlock (TPraos c) AllegraEra))
-> (LedgerState (ShelleyBlock (TPraos c) ShelleyEra)
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) AllegraEra)
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra)
-> LedgerState (ShelleyBlock (TPraos c) AllegraEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext AllegraEra
-> (:.:)
LedgerState (ShelleyBlock (TPraos c)) (PreviousEra AllegraEra)
-> (:.:) LedgerState (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 ((:.:) LedgerState (ShelleyBlock (TPraos c)) ShelleyEra
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) AllegraEra)
-> (LedgerState (ShelleyBlock (TPraos c) ShelleyEra)
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) ShelleyEra)
-> LedgerState (ShelleyBlock (TPraos c) ShelleyEra)
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) AllegraEra
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (TPraos c) ShelleyEra)
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) ShelleyEra
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp
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
translateLedgerStateAllegraToMaryWrapper ::
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) AllegraEra)
(ShelleyBlock (TPraos c) MaryEra)
translateLedgerStateAllegraToMaryWrapper :: forall c.
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) AllegraEra)
(ShelleyBlock (TPraos c) MaryEra)
translateLedgerStateAllegraToMaryWrapper =
Translate
LedgerState
(ShelleyBlock (TPraos c) AllegraEra)
(ShelleyBlock (TPraos c) MaryEra)
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(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 (Translate
LedgerState
(ShelleyBlock (TPraos c) AllegraEra)
(ShelleyBlock (TPraos c) MaryEra)
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) AllegraEra)
(ShelleyBlock (TPraos c) MaryEra))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) AllegraEra)
(ShelleyBlock (TPraos c) MaryEra)
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) AllegraEra)
(ShelleyBlock (TPraos c) MaryEra)
forall a b. (a -> b) -> a -> b
$
(EpochNo
-> LedgerState (ShelleyBlock (TPraos c) AllegraEra)
-> LedgerState (ShelleyBlock (TPraos c) MaryEra))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) AllegraEra)
(ShelleyBlock (TPraos c) MaryEra)
forall (f :: * -> *) x y.
(EpochNo -> f x -> f y) -> Translate f x y
Translate ((EpochNo
-> LedgerState (ShelleyBlock (TPraos c) AllegraEra)
-> LedgerState (ShelleyBlock (TPraos c) MaryEra))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) AllegraEra)
(ShelleyBlock (TPraos c) MaryEra))
-> (EpochNo
-> LedgerState (ShelleyBlock (TPraos c) AllegraEra)
-> LedgerState (ShelleyBlock (TPraos c) MaryEra))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) AllegraEra)
(ShelleyBlock (TPraos c) MaryEra)
forall a b. (a -> b) -> a -> b
$ \EpochNo
_epochNo ->
(:.:) LedgerState (ShelleyBlock (TPraos c)) MaryEra
-> LedgerState (ShelleyBlock (TPraos c) MaryEra)
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp ((:.:) LedgerState (ShelleyBlock (TPraos c)) MaryEra
-> LedgerState (ShelleyBlock (TPraos c) MaryEra))
-> (LedgerState (ShelleyBlock (TPraos c) AllegraEra)
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) MaryEra)
-> LedgerState (ShelleyBlock (TPraos c) AllegraEra)
-> LedgerState (ShelleyBlock (TPraos c) MaryEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext MaryEra
-> (:.:)
LedgerState (ShelleyBlock (TPraos c)) (PreviousEra MaryEra)
-> (:.:) LedgerState (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 ((:.:) LedgerState (ShelleyBlock (TPraos c)) AllegraEra
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) MaryEra)
-> (LedgerState (ShelleyBlock (TPraos c) AllegraEra)
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) AllegraEra)
-> LedgerState (ShelleyBlock (TPraos c) AllegraEra)
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) MaryEra
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (TPraos c) AllegraEra)
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) AllegraEra
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp
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
translateLedgerStateMaryToAlonzoWrapper ::
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) MaryEra)
(ShelleyBlock (TPraos c) AlonzoEra)
translateLedgerStateMaryToAlonzoWrapper :: forall c.
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) MaryEra)
(ShelleyBlock (TPraos c) AlonzoEra)
translateLedgerStateMaryToAlonzoWrapper =
(WrapLedgerConfig (ShelleyBlock (TPraos c) MaryEra)
-> WrapLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
-> Translate
LedgerState
(ShelleyBlock (TPraos c) MaryEra)
(ShelleyBlock (TPraos c) AlonzoEra))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(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)
-> Translate
LedgerState
(ShelleyBlock (TPraos c) MaryEra)
(ShelleyBlock (TPraos c) AlonzoEra))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) MaryEra)
(ShelleyBlock (TPraos c) AlonzoEra))
-> (WrapLedgerConfig (ShelleyBlock (TPraos c) MaryEra)
-> WrapLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
-> Translate
LedgerState
(ShelleyBlock (TPraos c) MaryEra)
(ShelleyBlock (TPraos c) AlonzoEra))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(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 ->
(EpochNo
-> LedgerState (ShelleyBlock (TPraos c) MaryEra)
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) MaryEra)
(ShelleyBlock (TPraos c) AlonzoEra)
forall (f :: * -> *) x y.
(EpochNo -> f x -> f y) -> Translate f x y
Translate ((EpochNo
-> LedgerState (ShelleyBlock (TPraos c) MaryEra)
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) MaryEra)
(ShelleyBlock (TPraos c) AlonzoEra))
-> (EpochNo
-> LedgerState (ShelleyBlock (TPraos c) MaryEra)
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) MaryEra)
(ShelleyBlock (TPraos c) AlonzoEra)
forall a b. (a -> b) -> a -> b
$ \EpochNo
_epochNo ->
(:.:) LedgerState (ShelleyBlock (TPraos c)) AlonzoEra
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra)
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp ((:.:) LedgerState (ShelleyBlock (TPraos c)) AlonzoEra
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra))
-> (LedgerState (ShelleyBlock (TPraos c) MaryEra)
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) AlonzoEra)
-> LedgerState (ShelleyBlock (TPraos c) MaryEra)
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext AlonzoEra
-> (:.:)
LedgerState (ShelleyBlock (TPraos c)) (PreviousEra AlonzoEra)
-> (:.:) LedgerState (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) ((:.:) LedgerState (ShelleyBlock (TPraos c)) MaryEra
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) AlonzoEra)
-> (LedgerState (ShelleyBlock (TPraos c) MaryEra)
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) MaryEra)
-> LedgerState (ShelleyBlock (TPraos c) MaryEra)
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) AlonzoEra
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (TPraos c) MaryEra)
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) MaryEra
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp
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
translateLedgerStateAlonzoToBabbageWrapper ::
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) AlonzoEra)
(ShelleyBlock (Praos c) BabbageEra)
translateLedgerStateAlonzoToBabbageWrapper :: forall c.
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) AlonzoEra)
(ShelleyBlock (Praos c) BabbageEra)
translateLedgerStateAlonzoToBabbageWrapper =
(WrapLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
-> WrapLedgerConfig (ShelleyBlock (Praos c) BabbageEra)
-> Translate
LedgerState
(ShelleyBlock (TPraos c) AlonzoEra)
(ShelleyBlock (Praos c) BabbageEra))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(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)
-> Translate
LedgerState
(ShelleyBlock (TPraos c) AlonzoEra)
(ShelleyBlock (Praos c) BabbageEra))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) AlonzoEra)
(ShelleyBlock (Praos c) BabbageEra))
-> (WrapLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
-> WrapLedgerConfig (ShelleyBlock (Praos c) BabbageEra)
-> Translate
LedgerState
(ShelleyBlock (TPraos c) AlonzoEra)
(ShelleyBlock (Praos c) BabbageEra))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(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 ->
(EpochNo
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra)
-> LedgerState (ShelleyBlock (Praos c) BabbageEra))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) AlonzoEra)
(ShelleyBlock (Praos c) BabbageEra)
forall (f :: * -> *) x y.
(EpochNo -> f x -> f y) -> Translate f x y
Translate ((EpochNo
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra)
-> LedgerState (ShelleyBlock (Praos c) BabbageEra))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) AlonzoEra)
(ShelleyBlock (Praos c) BabbageEra))
-> (EpochNo
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra)
-> LedgerState (ShelleyBlock (Praos c) BabbageEra))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) AlonzoEra)
(ShelleyBlock (Praos c) BabbageEra)
forall a b. (a -> b) -> a -> b
$ \EpochNo
_epochNo ->
(:.:) LedgerState (ShelleyBlock (Praos c)) BabbageEra
-> LedgerState (ShelleyBlock (Praos c) BabbageEra)
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp ((:.:) LedgerState (ShelleyBlock (Praos c)) BabbageEra
-> LedgerState (ShelleyBlock (Praos c) BabbageEra))
-> (LedgerState (ShelleyBlock (TPraos c) AlonzoEra)
-> (:.:) LedgerState (ShelleyBlock (Praos c)) BabbageEra)
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra)
-> LedgerState (ShelleyBlock (Praos c) BabbageEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext BabbageEra
-> (:.:)
LedgerState (ShelleyBlock (Praos c)) (PreviousEra BabbageEra)
-> (:.:) LedgerState (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 ((:.:) LedgerState (ShelleyBlock (Praos c)) AlonzoEra
-> (:.:) LedgerState (ShelleyBlock (Praos c)) BabbageEra)
-> (LedgerState (ShelleyBlock (TPraos c) AlonzoEra)
-> (:.:) LedgerState (ShelleyBlock (Praos c)) AlonzoEra)
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra)
-> (:.:) LedgerState (ShelleyBlock (Praos c)) BabbageEra
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (Praos c) AlonzoEra)
-> (:.:) LedgerState (ShelleyBlock (Praos c)) AlonzoEra
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp (LedgerState (ShelleyBlock (Praos c) AlonzoEra)
-> (:.:) LedgerState (ShelleyBlock (Praos c)) AlonzoEra)
-> (LedgerState (ShelleyBlock (TPraos c) AlonzoEra)
-> LedgerState (ShelleyBlock (Praos c) AlonzoEra))
-> LedgerState (ShelleyBlock (TPraos c) AlonzoEra)
-> (:.:) LedgerState (ShelleyBlock (Praos c)) AlonzoEra
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (TPraos c) AlonzoEra)
-> LedgerState (ShelleyBlock (Praos c) AlonzoEra)
forall c.
LedgerState (ShelleyBlock (TPraos c) AlonzoEra)
-> LedgerState (ShelleyBlock (Praos c) AlonzoEra)
transPraosLS
where
transPraosLS ::
LedgerState (ShelleyBlock (TPraos c) AlonzoEra) ->
LedgerState (ShelleyBlock (Praos c) AlonzoEra)
transPraosLS :: forall c.
LedgerState (ShelleyBlock (TPraos c) AlonzoEra)
-> LedgerState (ShelleyBlock (Praos c) AlonzoEra)
transPraosLS (ShelleyLedgerState WithOrigin (ShelleyTip (TPraos c) AlonzoEra)
wo NewEpochState AlonzoEra
nes ShelleyTransition
st) =
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
}
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)
translateLedgerStateBabbageToConwayWrapper ::
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (Praos c) BabbageEra)
(ShelleyBlock (Praos c) ConwayEra)
translateLedgerStateBabbageToConwayWrapper :: forall c.
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (Praos c) BabbageEra)
(ShelleyBlock (Praos c) ConwayEra)
translateLedgerStateBabbageToConwayWrapper =
(WrapLedgerConfig (ShelleyBlock (Praos c) BabbageEra)
-> WrapLedgerConfig (ShelleyBlock (Praos c) ConwayEra)
-> Translate
LedgerState
(ShelleyBlock (Praos c) BabbageEra)
(ShelleyBlock (Praos c) ConwayEra))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(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)
-> Translate
LedgerState
(ShelleyBlock (Praos c) BabbageEra)
(ShelleyBlock (Praos c) ConwayEra))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (Praos c) BabbageEra)
(ShelleyBlock (Praos c) ConwayEra))
-> (WrapLedgerConfig (ShelleyBlock (Praos c) BabbageEra)
-> WrapLedgerConfig (ShelleyBlock (Praos c) ConwayEra)
-> Translate
LedgerState
(ShelleyBlock (Praos c) BabbageEra)
(ShelleyBlock (Praos c) ConwayEra))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(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 ->
(EpochNo
-> LedgerState (ShelleyBlock (Praos c) BabbageEra)
-> LedgerState (ShelleyBlock (Praos c) ConwayEra))
-> Translate
LedgerState
(ShelleyBlock (Praos c) BabbageEra)
(ShelleyBlock (Praos c) ConwayEra)
forall (f :: * -> *) x y.
(EpochNo -> f x -> f y) -> Translate f x y
Translate ((EpochNo
-> LedgerState (ShelleyBlock (Praos c) BabbageEra)
-> LedgerState (ShelleyBlock (Praos c) ConwayEra))
-> Translate
LedgerState
(ShelleyBlock (Praos c) BabbageEra)
(ShelleyBlock (Praos c) ConwayEra))
-> (EpochNo
-> LedgerState (ShelleyBlock (Praos c) BabbageEra)
-> LedgerState (ShelleyBlock (Praos c) ConwayEra))
-> Translate
LedgerState
(ShelleyBlock (Praos c) BabbageEra)
(ShelleyBlock (Praos c) ConwayEra)
forall a b. (a -> b) -> a -> b
$ \EpochNo
_epochNo ->
(:.:) LedgerState (ShelleyBlock (Praos c)) ConwayEra
-> LedgerState (ShelleyBlock (Praos c) ConwayEra)
forall {l} {k} (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp ((:.:) LedgerState (ShelleyBlock (Praos c)) ConwayEra
-> LedgerState (ShelleyBlock (Praos c) ConwayEra))
-> (LedgerState (ShelleyBlock (Praos c) BabbageEra)
-> (:.:) LedgerState (ShelleyBlock (Praos c)) ConwayEra)
-> LedgerState (ShelleyBlock (Praos c) BabbageEra)
-> LedgerState (ShelleyBlock (Praos c) ConwayEra)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext ConwayEra
-> (:.:)
LedgerState (ShelleyBlock (Praos c)) (PreviousEra ConwayEra)
-> (:.:) LedgerState (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) ((:.:) LedgerState (ShelleyBlock (Praos c)) BabbageEra
-> (:.:) LedgerState (ShelleyBlock (Praos c)) ConwayEra)
-> (LedgerState (ShelleyBlock (Praos c) BabbageEra)
-> (:.:) LedgerState (ShelleyBlock (Praos c)) BabbageEra)
-> LedgerState (ShelleyBlock (Praos c) BabbageEra)
-> (:.:) LedgerState (ShelleyBlock (Praos c)) ConwayEra
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (Praos c) BabbageEra)
-> (:.:) LedgerState (ShelleyBlock (Praos c)) BabbageEra
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp
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