{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Ouroboros.Consensus.Cardano.CanHardFork (
ByronPartialLedgerConfig (..)
, CardanoHardForkConstraints
, TriggerHardFork (..)
, ShelleyPartialLedgerConfig (..)
, forecastAcrossShelley
, translateChainDepStateAcrossShelley
) where
import Control.Monad
import Control.Monad.Except (runExcept, throwError)
import Data.Coerce (coerce)
import qualified Data.Map.Strict as Map
import Data.Maybe (listToMaybe, mapMaybe)
import Data.Proxy
import Data.SOP.Strict (NP (..), unComp, (:.:) (..))
import Data.Word
import GHC.Generics (Generic)
import NoThunks.Class (NoThunks)
import Cardano.Crypto.DSIGN (Ed25519DSIGN)
import Cardano.Crypto.Hash.Blake2b (Blake2b_224, Blake2b_256)
import qualified Cardano.Chain.Common as CC
import qualified Cardano.Chain.Genesis as CC.Genesis
import qualified Cardano.Chain.Update as CC.Update
import Ouroboros.Consensus.Block
import Ouroboros.Consensus.Forecast
import Ouroboros.Consensus.HardFork.History (Bound (boundSlot),
addSlots)
import Ouroboros.Consensus.HardFork.Simple
import Ouroboros.Consensus.Ledger.Abstract
import Ouroboros.Consensus.TypeFamilyWrappers
import Ouroboros.Consensus.Util (eitherToMaybe)
import Ouroboros.Consensus.Util.RedundantConstraints
import Ouroboros.Consensus.HardFork.Combinator
import Ouroboros.Consensus.HardFork.Combinator.State.Types
import Ouroboros.Consensus.HardFork.Combinator.Util.InPairs
(RequiringBoth (..), ignoringBoth)
import Ouroboros.Consensus.HardFork.Combinator.Util.Tails (Tails (..))
import Ouroboros.Consensus.Byron.Ledger
import qualified Ouroboros.Consensus.Byron.Ledger.Inspect as Byron.Inspect
import Ouroboros.Consensus.Byron.Node ()
import Ouroboros.Consensus.Protocol.PBFT (PBft, PBftCrypto)
import Ouroboros.Consensus.Protocol.PBFT.State (PBftState)
import qualified Ouroboros.Consensus.Protocol.PBFT.State as PBftState
import Ouroboros.Consensus.Protocol.TPraos
import Ouroboros.Consensus.Shelley.Ledger
import Ouroboros.Consensus.Shelley.Node ()
import Ouroboros.Consensus.Shelley.ShelleyHFC
import Cardano.Ledger.Allegra.Translation ()
import qualified Cardano.Ledger.Alonzo.Genesis as Alonzo
import Cardano.Ledger.Crypto (ADDRHASH, DSIGN, HASH)
import qualified Cardano.Ledger.Era as SL
import Cardano.Ledger.Hashes (EraIndependentTxBody)
import Cardano.Ledger.Keys (DSignable, Hash)
import Cardano.Ledger.Mary.Translation ()
import qualified Cardano.Ledger.Shelley.API as SL
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 Ouroboros.Consensus.Cardano.Block
import Ouroboros.Consensus.Ledger.SupportsProtocol
(LedgerSupportsProtocol)
import Ouroboros.Consensus.Protocol.Praos (Praos)
import qualified Ouroboros.Consensus.Protocol.Praos as Praos
import qualified Ouroboros.Consensus.Protocol.TPraos as TPraos
import Ouroboros.Consensus.Protocol.Translate (TranslateProto)
import Ouroboros.Consensus.Shelley.Protocol.Praos ()
byronTransition :: PartialLedgerConfig ByronBlock
-> Word16
-> LedgerState ByronBlock
-> Maybe EpochNo
byronTransition :: PartialLedgerConfig ByronBlock
-> Word16 -> LedgerState ByronBlock -> Maybe EpochNo
byronTransition ByronPartialLedgerConfig{..} Word16
shelleyMajorVersion LedgerState ByronBlock
state =
[EpochNo] -> Maybe EpochNo
forall a. [a] -> Maybe a
takeAny
([EpochNo] -> Maybe EpochNo)
-> (LedgerState ByronBlock -> [EpochNo])
-> LedgerState ByronBlock
-> Maybe EpochNo
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ProtocolUpdate -> Maybe EpochNo) -> [ProtocolUpdate] -> [EpochNo]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe ProtocolUpdate -> Maybe EpochNo
isTransitionToShelley
([ProtocolUpdate] -> [EpochNo])
-> (LedgerState ByronBlock -> [ProtocolUpdate])
-> LedgerState ByronBlock
-> [EpochNo]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerConfig ByronBlock
-> LedgerState ByronBlock -> [ProtocolUpdate]
Byron.Inspect.protocolUpdates LedgerConfig ByronBlock
byronLedgerConfig
(LedgerState ByronBlock -> Maybe EpochNo)
-> LedgerState ByronBlock -> Maybe EpochNo
forall a b. (a -> b) -> a -> b
$ LedgerState ByronBlock
state
where
ByronTransitionInfo Map ProtocolVersion BlockNo
transitionInfo = LedgerState ByronBlock -> ByronTransition
byronLedgerTransition LedgerState ByronBlock
state
genesis :: LedgerConfig ByronBlock
genesis = LedgerConfig ByronBlock
byronLedgerConfig
k :: BlockCount
k = GenesisData -> BlockCount
CC.Genesis.gdK (GenesisData -> BlockCount) -> GenesisData -> BlockCount
forall a b. (a -> b) -> a -> b
$ Config -> GenesisData
CC.Genesis.configGenesisData Config
LedgerConfig ByronBlock
genesis
isTransitionToShelley :: Byron.Inspect.ProtocolUpdate -> Maybe EpochNo
isTransitionToShelley :: ProtocolUpdate -> Maybe EpochNo
isTransitionToShelley ProtocolUpdate
update = do
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> Bool -> Maybe ()
forall a b. (a -> b) -> a -> b
$ ProtocolVersion -> Word16
CC.Update.pvMajor ProtocolVersion
version Word16 -> Word16 -> Bool
forall a. Eq a => a -> a -> Bool
== Word16
shelleyMajorVersion
case ProtocolUpdate -> UpdateState
Byron.Inspect.protocolUpdateState ProtocolUpdate
update of
Byron.Inspect.UpdateCandidate SlotNo
_becameCandidateSlotNo EpochNo
adoptedIn -> do
BlockNo
becameCandidateBlockNo <- ProtocolVersion -> Map ProtocolVersion BlockNo -> Maybe BlockNo
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup ProtocolVersion
version Map ProtocolVersion BlockNo
transitionInfo
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> Maybe ()) -> Bool -> Maybe ()
forall a b. (a -> b) -> a -> b
$ BlockNo -> Bool
isReallyStable BlockNo
becameCandidateBlockNo
EpochNo -> Maybe EpochNo
forall (m :: * -> *) a. Monad m => a -> m a
return EpochNo
adoptedIn
Byron.Inspect.UpdateStableCandidate EpochNo
adoptedIn ->
EpochNo -> Maybe EpochNo
forall (m :: * -> *) a. Monad m => a -> m a
return EpochNo
adoptedIn
UpdateState
_otherwise ->
Maybe EpochNo
forall (m :: * -> *) a. MonadPlus m => m a
mzero
where
version :: CC.Update.ProtocolVersion
version :: ProtocolVersion
version = ProtocolUpdate -> ProtocolVersion
Byron.Inspect.protocolUpdateVersion ProtocolUpdate
update
isReallyStable :: BlockNo -> Bool
isReallyStable :: BlockNo -> Bool
isReallyStable (BlockNo Word64
bno) = Word64
distance Word64 -> Word64 -> Bool
forall a. Ord a => a -> a -> Bool
>= BlockCount -> Word64
CC.unBlockCount BlockCount
k
where
distance :: Word64
distance :: Word64
distance = case LedgerState ByronBlock -> WithOrigin BlockNo
byronLedgerTipBlockNo LedgerState ByronBlock
state of
WithOrigin BlockNo
Origin -> Word64
bno Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
+ Word64
1
NotOrigin (BlockNo Word64
tip) -> Word64
tip Word64 -> Word64 -> Word64
forall a. Num a => a -> a -> a
- Word64
bno
takeAny :: [a] -> Maybe a
takeAny :: [a] -> Maybe a
takeAny = [a] -> Maybe a
forall a. [a] -> Maybe a
listToMaybe
instance SingleEraBlock ByronBlock where
singleEraTransition :: PartialLedgerConfig ByronBlock
-> EraParams -> Bound -> LedgerState ByronBlock -> Maybe EpochNo
singleEraTransition PartialLedgerConfig ByronBlock
pcfg EraParams
_eraParams Bound
_eraStart LedgerState ByronBlock
ledgerState =
case ByronPartialLedgerConfig -> TriggerHardFork
byronTriggerHardFork PartialLedgerConfig ByronBlock
ByronPartialLedgerConfig
pcfg of
TriggerHardFork
TriggerHardForkNever -> Maybe EpochNo
forall a. Maybe a
Nothing
TriggerHardForkAtEpoch EpochNo
epoch -> EpochNo -> Maybe EpochNo
forall a. a -> Maybe a
Just EpochNo
epoch
TriggerHardForkAtVersion Word16
shelleyMajorVersion ->
PartialLedgerConfig ByronBlock
-> Word16 -> LedgerState ByronBlock -> Maybe EpochNo
byronTransition
PartialLedgerConfig ByronBlock
pcfg
Word16
shelleyMajorVersion
LedgerState ByronBlock
ledgerState
singleEraInfo :: proxy ByronBlock -> SingleEraInfo ByronBlock
singleEraInfo proxy ByronBlock
_ = SingleEraInfo :: forall blk. Text -> SingleEraInfo blk
SingleEraInfo {
singleEraName :: Text
singleEraName = Text
"Byron"
}
instance PBftCrypto bc => HasPartialConsensusConfig (PBft bc)
data ByronPartialLedgerConfig = ByronPartialLedgerConfig {
ByronPartialLedgerConfig -> LedgerConfig ByronBlock
byronLedgerConfig :: !(LedgerConfig ByronBlock)
, ByronPartialLedgerConfig -> TriggerHardFork
byronTriggerHardFork :: !TriggerHardFork
}
deriving ((forall x.
ByronPartialLedgerConfig -> Rep ByronPartialLedgerConfig x)
-> (forall x.
Rep ByronPartialLedgerConfig x -> ByronPartialLedgerConfig)
-> Generic ByronPartialLedgerConfig
forall x.
Rep ByronPartialLedgerConfig x -> ByronPartialLedgerConfig
forall x.
ByronPartialLedgerConfig -> Rep ByronPartialLedgerConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ByronPartialLedgerConfig x -> ByronPartialLedgerConfig
$cfrom :: forall x.
ByronPartialLedgerConfig -> Rep ByronPartialLedgerConfig x
Generic, Context -> ByronPartialLedgerConfig -> IO (Maybe ThunkInfo)
Proxy ByronPartialLedgerConfig -> String
(Context -> ByronPartialLedgerConfig -> IO (Maybe ThunkInfo))
-> (Context -> ByronPartialLedgerConfig -> IO (Maybe ThunkInfo))
-> (Proxy ByronPartialLedgerConfig -> String)
-> NoThunks ByronPartialLedgerConfig
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
showTypeOf :: Proxy ByronPartialLedgerConfig -> String
$cshowTypeOf :: Proxy ByronPartialLedgerConfig -> String
wNoThunks :: Context -> ByronPartialLedgerConfig -> IO (Maybe ThunkInfo)
$cwNoThunks :: Context -> ByronPartialLedgerConfig -> IO (Maybe ThunkInfo)
noThunks :: Context -> ByronPartialLedgerConfig -> IO (Maybe ThunkInfo)
$cnoThunks :: Context -> ByronPartialLedgerConfig -> IO (Maybe ThunkInfo)
NoThunks)
instance HasPartialLedgerConfig ByronBlock where
type PartialLedgerConfig ByronBlock = ByronPartialLedgerConfig
completeLedgerConfig :: proxy ByronBlock
-> EpochInfo (Except PastHorizonException)
-> PartialLedgerConfig ByronBlock
-> LedgerConfig ByronBlock
completeLedgerConfig proxy ByronBlock
_ EpochInfo (Except PastHorizonException)
_ = PartialLedgerConfig ByronBlock -> LedgerConfig ByronBlock
ByronPartialLedgerConfig -> LedgerConfig ByronBlock
byronLedgerConfig
type CardanoHardForkConstraints c =
( TPraos.PraosCrypto c
, Praos.PraosCrypto c
, TranslateProto (TPraos c) (Praos c)
, ShelleyCompatible (TPraos c) (ShelleyEra c)
, LedgerSupportsProtocol (ShelleyBlock (TPraos c) (ShelleyEra c))
, ShelleyCompatible (TPraos c) (AllegraEra c)
, LedgerSupportsProtocol (ShelleyBlock (TPraos c) (AllegraEra c))
, ShelleyCompatible (TPraos c) (MaryEra c)
, LedgerSupportsProtocol (ShelleyBlock (TPraos c) (MaryEra c))
, ShelleyCompatible (TPraos c) (AlonzoEra c)
, LedgerSupportsProtocol (ShelleyBlock (TPraos c) (AlonzoEra c))
, ShelleyCompatible (Praos c) (BabbageEra c)
, LedgerSupportsProtocol (ShelleyBlock (Praos c) (BabbageEra c))
, HASH c ~ Blake2b_256
, ADDRHASH c ~ Blake2b_224
, DSIGN c ~ Ed25519DSIGN
)
instance CardanoHardForkConstraints c => CanHardFork (CardanoEras c) where
hardForkEraTranslation :: EraTranslation (CardanoEras c)
hardForkEraTranslation = EraTranslation :: forall (xs :: [*]).
InPairs (RequiringBoth WrapLedgerConfig (Translate LedgerState)) xs
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
xs
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
xs
-> EraTranslation xs
EraTranslation {
translateLedgerState :: InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
(CardanoEras c)
translateLedgerState =
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
(CardanoEras c)
forall k (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
forall c.
(ShelleyCompatible (TPraos c) (ShelleyEra c), HASH c ~ Blake2b_256,
ADDRHASH c ~ Blake2b_224) =>
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
translateLedgerStateByronToShelleyWrapper
(InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
(CardanoEras c))
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
(CardanoEras c)
forall a b. (a -> b) -> a -> b
$ RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
translateLedgerStateShelleyToAllegraWrapper
(InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)])
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
translateLedgerStateAllegraToMaryWrapper
(InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)])
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
translateLedgerStateMaryToAlonzoWrapper
(InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)])
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
forall c.
(PraosCrypto c, PraosCrypto c) =>
RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
translateLedgerStateAlonzoToBabbageWrapper
(InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)])
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall a b. (a -> b) -> a -> b
$ InPairs
(RequiringBoth WrapLedgerConfig (Translate LedgerState))
'[ShelleyBlock (Praos c) (BabbageEra c)]
forall k (f :: k -> k -> *) (x :: k). InPairs f '[x]
PNil
, translateChainDepState :: InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
(CardanoEras c)
translateChainDepState =
RequiringBoth
WrapConsensusConfig
(Translate WrapChainDepState)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
(CardanoEras c)
forall k (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
WrapConsensusConfig
(Translate WrapChainDepState)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
forall c.
RequiringBoth
WrapConsensusConfig
(Translate WrapChainDepState)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
translateChainDepStateByronToShelleyWrapper
(InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
(CardanoEras c))
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
(CardanoEras c)
forall a b. (a -> b) -> a -> b
$ RequiringBoth
WrapConsensusConfig
(Translate WrapChainDepState)
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
WrapConsensusConfig
(Translate WrapChainDepState)
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
forall eraFrom eraTo protoFrom protoTo.
TranslateProto protoFrom protoTo =>
RequiringBoth
WrapConsensusConfig
(Translate WrapChainDepState)
(ShelleyBlock protoFrom eraFrom)
(ShelleyBlock protoTo eraTo)
translateChainDepStateAcrossShelley
(InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)])
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
WrapConsensusConfig
(Translate WrapChainDepState)
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
WrapConsensusConfig
(Translate WrapChainDepState)
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
forall eraFrom eraTo protoFrom protoTo.
TranslateProto protoFrom protoTo =>
RequiringBoth
WrapConsensusConfig
(Translate WrapChainDepState)
(ShelleyBlock protoFrom eraFrom)
(ShelleyBlock protoTo eraTo)
translateChainDepStateAcrossShelley
(InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)])
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
WrapConsensusConfig
(Translate WrapChainDepState)
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
WrapConsensusConfig
(Translate WrapChainDepState)
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
forall eraFrom eraTo protoFrom protoTo.
TranslateProto protoFrom protoTo =>
RequiringBoth
WrapConsensusConfig
(Translate WrapChainDepState)
(ShelleyBlock protoFrom eraFrom)
(ShelleyBlock protoTo eraTo)
translateChainDepStateAcrossShelley
(InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)])
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
WrapConsensusConfig
(Translate WrapChainDepState)
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons RequiringBoth
WrapConsensusConfig
(Translate WrapChainDepState)
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
forall eraFrom eraTo protoFrom protoTo.
TranslateProto protoFrom protoTo =>
RequiringBoth
WrapConsensusConfig
(Translate WrapChainDepState)
(ShelleyBlock protoFrom eraFrom)
(ShelleyBlock protoTo eraTo)
translateChainDepStateAcrossShelley
(InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)])
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall a b. (a -> b) -> a -> b
$ InPairs
(RequiringBoth WrapConsensusConfig (Translate WrapChainDepState))
'[ShelleyBlock (Praos c) (BabbageEra c)]
forall k (f :: k -> k -> *) (x :: k). InPairs f '[x]
PNil
, translateLedgerView :: InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
(CardanoEras c)
translateLedgerView =
RequiringBoth
WrapLedgerConfig
(TranslateForecast LedgerState WrapLedgerView)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast 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
(TranslateForecast LedgerState WrapLedgerView)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
forall c.
RequiringBoth
WrapLedgerConfig
(TranslateForecast LedgerState WrapLedgerView)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
translateLedgerViewByronToShelleyWrapper
(InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
(CardanoEras c))
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
(CardanoEras c)
forall a b. (a -> b) -> a -> b
$ RequiringBoth
WrapLedgerConfig
(TranslateForecast LedgerState WrapLedgerView)
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
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
(TranslateForecast LedgerState WrapLedgerView)
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
forall eraFrom eraTo protoFrom protoTo.
(TranslateProto protoFrom protoTo,
LedgerSupportsProtocol (ShelleyBlock protoFrom eraFrom)) =>
RequiringBoth
WrapLedgerConfig
(TranslateForecast LedgerState WrapLedgerView)
(ShelleyBlock protoFrom eraFrom)
(ShelleyBlock protoTo eraTo)
translateLedgerViewAcrossShelley
(InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)])
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
WrapLedgerConfig
(TranslateForecast LedgerState WrapLedgerView)
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra 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
(TranslateForecast LedgerState WrapLedgerView)
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
forall eraFrom eraTo protoFrom protoTo.
(TranslateProto protoFrom protoTo,
LedgerSupportsProtocol (ShelleyBlock protoFrom eraFrom)) =>
RequiringBoth
WrapLedgerConfig
(TranslateForecast LedgerState WrapLedgerView)
(ShelleyBlock protoFrom eraFrom)
(ShelleyBlock protoTo eraTo)
translateLedgerViewAcrossShelley
(InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)])
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
WrapLedgerConfig
(TranslateForecast LedgerState WrapLedgerView)
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra 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
(TranslateForecast LedgerState WrapLedgerView)
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
forall eraFrom eraTo protoFrom protoTo.
(TranslateProto protoFrom protoTo,
LedgerSupportsProtocol (ShelleyBlock protoFrom eraFrom)) =>
RequiringBoth
WrapLedgerConfig
(TranslateForecast LedgerState WrapLedgerView)
(ShelleyBlock protoFrom eraFrom)
(ShelleyBlock protoTo eraTo)
translateLedgerViewAcrossShelley
(InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)])
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
WrapLedgerConfig
(TranslateForecast LedgerState WrapLedgerView)
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra 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
(TranslateForecast LedgerState WrapLedgerView)
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
forall eraFrom eraTo protoFrom protoTo.
(TranslateProto protoFrom protoTo,
LedgerSupportsProtocol (ShelleyBlock protoFrom eraFrom)) =>
RequiringBoth
WrapLedgerConfig
(TranslateForecast LedgerState WrapLedgerView)
(ShelleyBlock protoFrom eraFrom)
(ShelleyBlock protoTo eraTo)
translateLedgerViewAcrossShelley
(InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)])
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall a b. (a -> b) -> a -> b
$ InPairs
(RequiringBoth
WrapLedgerConfig (TranslateForecast LedgerState WrapLedgerView))
'[ShelleyBlock (Praos c) (BabbageEra c)]
forall k (f :: k -> k -> *) (x :: k). InPairs f '[x]
PNil
}
hardForkChainSel :: Tails AcrossEraSelection (CardanoEras c)
hardForkChainSel =
NP
(AcrossEraSelection ByronBlock)
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> 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 ( AcrossEraSelection
ByronBlock (ShelleyBlock (TPraos c) (ShelleyEra c))
forall a b. AcrossEraSelection a b
CompareBlockNo
AcrossEraSelection
ByronBlock (ShelleyBlock (TPraos c) (ShelleyEra c))
-> NP
(AcrossEraSelection ByronBlock)
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> NP
(AcrossEraSelection ByronBlock)
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* AcrossEraSelection
ByronBlock (ShelleyBlock (TPraos c) (AllegraEra c))
forall a b. AcrossEraSelection a b
CompareBlockNo
AcrossEraSelection
ByronBlock (ShelleyBlock (TPraos c) (AllegraEra c))
-> NP
(AcrossEraSelection ByronBlock)
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> NP
(AcrossEraSelection ByronBlock)
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* AcrossEraSelection ByronBlock (ShelleyBlock (TPraos c) (MaryEra c))
forall a b. AcrossEraSelection a b
CompareBlockNo
AcrossEraSelection ByronBlock (ShelleyBlock (TPraos c) (MaryEra c))
-> NP
(AcrossEraSelection ByronBlock)
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> NP
(AcrossEraSelection ByronBlock)
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* AcrossEraSelection
ByronBlock (ShelleyBlock (TPraos c) (AlonzoEra c))
forall a b. AcrossEraSelection a b
CompareBlockNo
AcrossEraSelection
ByronBlock (ShelleyBlock (TPraos c) (AlonzoEra c))
-> NP
(AcrossEraSelection ByronBlock)
'[ShelleyBlock (Praos c) (BabbageEra c)]
-> NP
(AcrossEraSelection ByronBlock)
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* AcrossEraSelection
ByronBlock (ShelleyBlock (Praos c) (BabbageEra c))
forall a b. AcrossEraSelection a b
CompareBlockNo
AcrossEraSelection
ByronBlock (ShelleyBlock (Praos c) (BabbageEra c))
-> NP (AcrossEraSelection ByronBlock) '[]
-> NP
(AcrossEraSelection ByronBlock)
'[ShelleyBlock (Praos c) (BabbageEra c)]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* NP (AcrossEraSelection ByronBlock) '[]
forall k (a :: k -> *). NP a '[]
Nil)
(Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> Tails AcrossEraSelection (CardanoEras c))
-> Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> Tails AcrossEraSelection (CardanoEras c)
forall a b. (a -> b) -> a -> b
$ NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (ShelleyEra c)))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (f :: k -> k -> *) (x :: k) (xs1 :: [k]).
NP (f x) xs1 -> Tails f xs1 -> Tails f (x : xs1)
TCons (AcrossEraSelection
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
forall a b.
(BlockProtocol a ~ BlockProtocol b) =>
AcrossEraSelection a b
SelectSameProtocol AcrossEraSelection
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
-> NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (ShelleyEra c)))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (ShelleyEra c)))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* AcrossEraSelection
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
forall a b.
(BlockProtocol a ~ BlockProtocol b) =>
AcrossEraSelection a b
SelectSameProtocol AcrossEraSelection
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
-> NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (ShelleyEra c)))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (ShelleyEra c)))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* AcrossEraSelection
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
forall a b.
(BlockProtocol a ~ BlockProtocol b) =>
AcrossEraSelection a b
SelectSameProtocol AcrossEraSelection
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
-> NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (ShelleyEra c)))
'[ShelleyBlock (Praos c) (BabbageEra c)]
-> NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (ShelleyEra c)))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* AcrossEraSelection
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
forall e1 e2.
AcrossEraSelection
(ShelleyBlock (TPraos c) e1) (ShelleyBlock (Praos c) e2)
alonzoBabbageEraSelection AcrossEraSelection
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
-> NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (ShelleyEra c))) '[]
-> NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (ShelleyEra c)))
'[ShelleyBlock (Praos c) (BabbageEra c)]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (ShelleyEra c))) '[]
forall k (a :: k -> *). NP a '[]
Nil)
(Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)])
-> Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall a b. (a -> b) -> a -> b
$ NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (AllegraEra c)))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (f :: k -> k -> *) (x :: k) (xs1 :: [k]).
NP (f x) xs1 -> Tails f xs1 -> Tails f (x : xs1)
TCons (AcrossEraSelection
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
forall a b.
(BlockProtocol a ~ BlockProtocol b) =>
AcrossEraSelection a b
SelectSameProtocol AcrossEraSelection
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
-> NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (AllegraEra c)))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (AllegraEra c)))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* AcrossEraSelection
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
forall a b.
(BlockProtocol a ~ BlockProtocol b) =>
AcrossEraSelection a b
SelectSameProtocol AcrossEraSelection
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
-> NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (AllegraEra c)))
'[ShelleyBlock (Praos c) (BabbageEra c)]
-> NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (AllegraEra c)))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* AcrossEraSelection
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
forall e1 e2.
AcrossEraSelection
(ShelleyBlock (TPraos c) e1) (ShelleyBlock (Praos c) e2)
alonzoBabbageEraSelection AcrossEraSelection
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
-> NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (AllegraEra c))) '[]
-> NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (AllegraEra c)))
'[ShelleyBlock (Praos c) (BabbageEra c)]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (AllegraEra c))) '[]
forall k (a :: k -> *). NP a '[]
Nil)
(Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)])
-> Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall a b. (a -> b) -> a -> b
$ NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (MaryEra c)))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (f :: k -> k -> *) (x :: k) (xs1 :: [k]).
NP (f x) xs1 -> Tails f xs1 -> Tails f (x : xs1)
TCons (AcrossEraSelection
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
forall a b.
(BlockProtocol a ~ BlockProtocol b) =>
AcrossEraSelection a b
SelectSameProtocol AcrossEraSelection
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
-> NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (MaryEra c)))
'[ShelleyBlock (Praos c) (BabbageEra c)]
-> NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (MaryEra c)))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* AcrossEraSelection
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
forall e1 e2.
AcrossEraSelection
(ShelleyBlock (TPraos c) e1) (ShelleyBlock (Praos c) e2)
alonzoBabbageEraSelection AcrossEraSelection
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
-> NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (MaryEra c))) '[]
-> NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (MaryEra c)))
'[ShelleyBlock (Praos c) (BabbageEra c)]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* NP (AcrossEraSelection (ShelleyBlock (TPraos c) (MaryEra c))) '[]
forall k (a :: k -> *). NP a '[]
Nil)
(Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)])
-> Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall a b. (a -> b) -> a -> b
$ NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (AlonzoEra c)))
'[ShelleyBlock (Praos c) (BabbageEra c)]
-> Tails
AcrossEraSelection '[ShelleyBlock (Praos c) (BabbageEra c)]
-> Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (f :: k -> k -> *) (x :: k) (xs1 :: [k]).
NP (f x) xs1 -> Tails f xs1 -> Tails f (x : xs1)
TCons (AcrossEraSelection
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
forall e1 e2.
AcrossEraSelection
(ShelleyBlock (TPraos c) e1) (ShelleyBlock (Praos c) e2)
alonzoBabbageEraSelection AcrossEraSelection
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
-> NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (AlonzoEra c))) '[]
-> NP
(AcrossEraSelection (ShelleyBlock (TPraos c) (AlonzoEra c)))
'[ShelleyBlock (Praos c) (BabbageEra c)]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* NP (AcrossEraSelection (ShelleyBlock (TPraos c) (AlonzoEra c))) '[]
forall k (a :: k -> *). NP a '[]
Nil)
(Tails AcrossEraSelection '[ShelleyBlock (Praos c) (BabbageEra c)]
-> Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)])
-> Tails
AcrossEraSelection '[ShelleyBlock (Praos c) (BabbageEra c)]
-> Tails
AcrossEraSelection
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall a b. (a -> b) -> a -> b
$ NP (AcrossEraSelection (ShelleyBlock (Praos c) (BabbageEra c))) '[]
-> Tails AcrossEraSelection '[]
-> Tails
AcrossEraSelection '[ShelleyBlock (Praos c) (BabbageEra c)]
forall k (f :: k -> k -> *) (x :: k) (xs1 :: [k]).
NP (f x) xs1 -> Tails f xs1 -> Tails f (x : xs1)
TCons NP (AcrossEraSelection (ShelleyBlock (Praos c) (BabbageEra c))) '[]
forall k (a :: k -> *). NP a '[]
Nil
(Tails AcrossEraSelection '[]
-> Tails
AcrossEraSelection '[ShelleyBlock (Praos c) (BabbageEra c)])
-> Tails AcrossEraSelection '[]
-> Tails
AcrossEraSelection '[ShelleyBlock (Praos c) (BabbageEra c)]
forall a b. (a -> b) -> a -> b
$ Tails AcrossEraSelection '[]
forall k (f :: k -> k -> *). Tails f '[]
TNil
where
alonzoBabbageEraSelection :: AcrossEraSelection
(ShelleyBlock (TPraos c) e1)
(ShelleyBlock (Praos c) e2)
alonzoBabbageEraSelection :: AcrossEraSelection
(ShelleyBlock (TPraos c) e1) (ShelleyBlock (Praos c) e2)
alonzoBabbageEraSelection = (SelectView (BlockProtocol (ShelleyBlock (TPraos c) e1))
-> SelectView (BlockProtocol (ShelleyBlock (Praos c) e2))
-> Ordering)
-> AcrossEraSelection
(ShelleyBlock (TPraos c) e1) (ShelleyBlock (Praos c) e2)
forall a b.
(SelectView (BlockProtocol a)
-> SelectView (BlockProtocol b) -> Ordering)
-> AcrossEraSelection a b
CustomChainSel (
\SelectView (BlockProtocol (ShelleyBlock (TPraos c) e1))
l SelectView (BlockProtocol (ShelleyBlock (Praos c) e2))
r -> PraosChainSelectView c -> PraosChainSelectView c -> Ordering
forall a. Ord a => a -> a -> Ordering
compare SelectView (BlockProtocol (ShelleyBlock (TPraos c) e1))
PraosChainSelectView c
l (PraosChainSelectView c -> PraosChainSelectView c
coerce SelectView (BlockProtocol (ShelleyBlock (Praos c) e2))
PraosChainSelectView c
r)
)
hardForkInjectTxs :: InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
(CardanoEras c)
hardForkInjectTxs =
RequiringBoth
WrapLedgerConfig
(Product2 InjectTx InjectValidatedTx)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
(CardanoEras c)
forall k (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons (Product2
InjectTx
InjectValidatedTx
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
-> RequiringBoth
WrapLedgerConfig
(Product2 InjectTx InjectValidatedTx)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
forall k (f :: k -> k -> *) (x :: k) (y :: k) (h :: k -> *).
f x y -> RequiringBoth h f x y
ignoringBoth (Product2
InjectTx
InjectValidatedTx
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
-> RequiringBoth
WrapLedgerConfig
(Product2 InjectTx InjectValidatedTx)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c)))
-> Product2
InjectTx
InjectValidatedTx
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
-> RequiringBoth
WrapLedgerConfig
(Product2 InjectTx InjectValidatedTx)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
forall a b. (a -> b) -> a -> b
$ InjectPolyTx
GenTx ByronBlock (ShelleyBlock (TPraos c) (ShelleyEra c))
-> InjectPolyTx
WrapValidatedGenTx
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
-> Product2
InjectTx
InjectValidatedTx
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
forall (f :: * -> * -> *) (g :: * -> * -> *) x y.
f x y -> g x y -> Product2 f g x y
Pair2 InjectPolyTx
GenTx ByronBlock (ShelleyBlock (TPraos c) (ShelleyEra c))
forall blk blk'. InjectTx blk blk'
cannotInjectTx InjectPolyTx
WrapValidatedGenTx
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
forall blk blk'. InjectValidatedTx blk blk'
cannotInjectValidatedTx)
(InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
(CardanoEras c))
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
(CardanoEras c)
forall a b. (a -> b) -> a -> b
$ RequiringBoth
WrapLedgerConfig
(Product2 InjectTx InjectValidatedTx)
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons ( Product2
InjectTx
InjectValidatedTx
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
-> RequiringBoth
WrapLedgerConfig
(Product2 InjectTx InjectValidatedTx)
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
forall k (f :: k -> k -> *) (x :: k) (y :: k) (h :: k -> *).
f x y -> RequiringBoth h f x y
ignoringBoth
(Product2
InjectTx
InjectValidatedTx
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
-> RequiringBoth
WrapLedgerConfig
(Product2 InjectTx InjectValidatedTx)
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c)))
-> Product2
InjectTx
InjectValidatedTx
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
-> RequiringBoth
WrapLedgerConfig
(Product2 InjectTx InjectValidatedTx)
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
forall a b. (a -> b) -> a -> b
$ InjectPolyTx
GenTx
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
-> InjectPolyTx
WrapValidatedGenTx
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
-> Product2
InjectTx
InjectValidatedTx
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
forall (f :: * -> * -> *) (g :: * -> * -> *) x y.
f x y -> g x y -> Product2 f g x y
Pair2
InjectPolyTx
GenTx
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
InjectTx
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
translateTxShelleyToAllegraWrapper
InjectPolyTx
WrapValidatedGenTx
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
InjectValidatedTx
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
translateValidatedTxShelleyToAllegraWrapper
)
(InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)])
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (ShelleyEra c),
ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
WrapLedgerConfig
(Product2 InjectTx InjectValidatedTx)
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons ( Product2
InjectTx
InjectValidatedTx
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
-> RequiringBoth
WrapLedgerConfig
(Product2 InjectTx InjectValidatedTx)
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
forall k (f :: k -> k -> *) (x :: k) (y :: k) (h :: k -> *).
f x y -> RequiringBoth h f x y
ignoringBoth
(Product2
InjectTx
InjectValidatedTx
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
-> RequiringBoth
WrapLedgerConfig
(Product2 InjectTx InjectValidatedTx)
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c)))
-> Product2
InjectTx
InjectValidatedTx
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
-> RequiringBoth
WrapLedgerConfig
(Product2 InjectTx InjectValidatedTx)
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
forall a b. (a -> b) -> a -> b
$ InjectPolyTx
GenTx
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
-> InjectPolyTx
WrapValidatedGenTx
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
-> Product2
InjectTx
InjectValidatedTx
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
forall (f :: * -> * -> *) (g :: * -> * -> *) x y.
f x y -> g x y -> Product2 f g x y
Pair2
InjectPolyTx
GenTx
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
InjectTx
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
translateTxAllegraToMaryWrapper
InjectPolyTx
WrapValidatedGenTx
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
InjectValidatedTx
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
translateValidatedTxAllegraToMaryWrapper
)
(InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)])
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (AllegraEra c),
ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
WrapLedgerConfig
(Product2 InjectTx InjectValidatedTx)
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons ((WrapLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Product2
InjectTx
InjectValidatedTx
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c)))
-> RequiringBoth
WrapLedgerConfig
(Product2 InjectTx InjectValidatedTx)
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
forall k (h :: k -> *) (f :: k -> k -> *) (x :: k) (y :: k).
(h x -> h y -> f x y) -> RequiringBoth h f x y
RequireBoth ((WrapLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Product2
InjectTx
InjectValidatedTx
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c)))
-> RequiringBoth
WrapLedgerConfig
(Product2 InjectTx InjectValidatedTx)
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c)))
-> (WrapLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Product2
InjectTx
InjectValidatedTx
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c)))
-> RequiringBoth
WrapLedgerConfig
(Product2 InjectTx InjectValidatedTx)
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
forall a b. (a -> b) -> a -> b
$ \WrapLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
_cfgMary WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
cfgAlonzo ->
let ctxt :: AlonzoGenesis
ctxt = WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> AlonzoGenesis
forall c.
WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> AlonzoGenesis
getAlonzoTranslationContext WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
cfgAlonzo
in
InjectPolyTx
GenTx
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
-> InjectPolyTx
WrapValidatedGenTx
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
-> Product2
InjectTx
InjectValidatedTx
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
forall (f :: * -> * -> *) (g :: * -> * -> *) x y.
f x y -> g x y -> Product2 f g x y
Pair2
(AlonzoGenesis
-> InjectPolyTx
GenTx
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
AlonzoGenesis
-> InjectTx
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
translateTxMaryToAlonzoWrapper AlonzoGenesis
ctxt)
(AlonzoGenesis
-> InjectPolyTx
WrapValidatedGenTx
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) =>
AlonzoGenesis
-> InjectValidatedTx
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
translateValidatedTxMaryToAlonzoWrapper AlonzoGenesis
ctxt)
)
(InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)])
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (MaryEra c),
ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall a b. (a -> b) -> a -> b
$ RequiringBoth
WrapLedgerConfig
(Product2 InjectTx InjectValidatedTx)
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall k (f :: k -> k -> *) (x :: k) (y :: k) (zs :: [k]).
f x y -> InPairs f (y : zs) -> InPairs f (x : y : zs)
PCons ((WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> Product2
InjectTx
InjectValidatedTx
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c)))
-> RequiringBoth
WrapLedgerConfig
(Product2 InjectTx InjectValidatedTx)
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
forall k (h :: k -> *) (f :: k -> k -> *) (x :: k) (y :: k).
(h x -> h y -> f x y) -> RequiringBoth h f x y
RequireBoth ((WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> Product2
InjectTx
InjectValidatedTx
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c)))
-> RequiringBoth
WrapLedgerConfig
(Product2 InjectTx InjectValidatedTx)
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c)))
-> (WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> Product2
InjectTx
InjectValidatedTx
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c)))
-> RequiringBoth
WrapLedgerConfig
(Product2 InjectTx InjectValidatedTx)
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
forall a b. (a -> b) -> a -> b
$ \WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
_cfgAlonzo WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
cfgBabbage ->
let ctxt :: AlonzoGenesis
ctxt = WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> AlonzoGenesis
forall c.
WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> AlonzoGenesis
getBabbageTranslationContext WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
cfgBabbage
in
InjectPolyTx
GenTx
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
-> InjectPolyTx
WrapValidatedGenTx
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
-> Product2
InjectTx
InjectValidatedTx
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
forall (f :: * -> * -> *) (g :: * -> * -> *) x y.
f x y -> g x y -> Product2 f g x y
Pair2
(AlonzoGenesis
-> InjectPolyTx
GenTx
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
forall c.
PraosCrypto c =>
AlonzoGenesis
-> InjectTx
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
translateTxAlonzoToBabbageWrapper AlonzoGenesis
ctxt)
(AlonzoGenesis
-> InjectPolyTx
WrapValidatedGenTx
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
forall c.
PraosCrypto c =>
AlonzoGenesis
-> InjectValidatedTx
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
translateValidatedTxAlonzoToBabbageWrapper AlonzoGenesis
ctxt)
)
(InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)])
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (Praos c) (BabbageEra c)]
-> InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (TPraos c) (AlonzoEra c),
ShelleyBlock (Praos c) (BabbageEra c)]
forall a b. (a -> b) -> a -> b
$ InPairs
(RequiringBoth
WrapLedgerConfig (Product2 InjectTx InjectValidatedTx))
'[ShelleyBlock (Praos c) (BabbageEra c)]
forall k (f :: k -> k -> *) (x :: k). InPairs f '[x]
PNil
translateHeaderHashByronToShelley ::
forall c.
( ShelleyCompatible (TPraos c) (ShelleyEra c)
, HASH c ~ Blake2b_256
)
=> HeaderHash ByronBlock
-> HeaderHash (ShelleyBlock (TPraos c) (ShelleyEra c))
=
Proxy (ShelleyBlock (TPraos c) (ShelleyEra c))
-> ShortByteString
-> HeaderHash (ShelleyBlock (TPraos c) (ShelleyEra c))
forall blk (proxy :: * -> *).
ConvertRawHash blk =>
proxy blk -> ShortByteString -> HeaderHash blk
fromShortRawHash (Proxy (ShelleyBlock (TPraos c) (ShelleyEra c))
forall k (t :: k). Proxy t
Proxy @(ShelleyBlock (TPraos c) (ShelleyEra c)))
(ShortByteString -> ShelleyHash c)
-> (ByronHash -> ShortByteString) -> ByronHash -> ShelleyHash c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Proxy ByronBlock -> HeaderHash ByronBlock -> ShortByteString
forall blk (proxy :: * -> *).
ConvertRawHash blk =>
proxy blk -> HeaderHash blk -> ShortByteString
toShortRawHash (Proxy ByronBlock
forall k (t :: k). Proxy t
Proxy @ByronBlock)
where
()
_ = Proxy (HASH c ~ Blake2b_256) -> ()
forall (c :: Constraint) (proxy :: Constraint -> *).
c =>
proxy c -> ()
keepRedundantConstraint (Proxy (HASH c ~ Blake2b_256)
forall k (t :: k). Proxy t
Proxy @(HASH c ~ Blake2b_256))
translatePointByronToShelley ::
( ShelleyCompatible (TPraos c) (ShelleyEra c)
, HASH c ~ Blake2b_256
)
=> Point ByronBlock
-> WithOrigin BlockNo
-> WithOrigin (ShelleyTip (TPraos c) (ShelleyEra c))
translatePointByronToShelley :: Point ByronBlock
-> WithOrigin BlockNo
-> WithOrigin (ShelleyTip (TPraos c) (ShelleyEra c))
translatePointByronToShelley Point ByronBlock
point WithOrigin BlockNo
bNo =
case (Point ByronBlock
point, WithOrigin BlockNo
bNo) of
(Point ByronBlock
GenesisPoint, WithOrigin BlockNo
Origin) ->
WithOrigin (ShelleyTip (TPraos c) (ShelleyEra c))
forall t. WithOrigin t
Origin
(BlockPoint SlotNo
s HeaderHash ByronBlock
h, NotOrigin BlockNo
n) -> ShelleyTip (TPraos c) (ShelleyEra c)
-> WithOrigin (ShelleyTip (TPraos c) (ShelleyEra c))
forall t. t -> WithOrigin t
NotOrigin ShelleyTip :: forall proto era.
SlotNo
-> BlockNo
-> HeaderHash (ShelleyBlock proto era)
-> ShelleyTip proto era
ShelleyTip {
shelleyTipSlotNo :: SlotNo
shelleyTipSlotNo = SlotNo
s
, shelleyTipBlockNo :: BlockNo
shelleyTipBlockNo = BlockNo
n
, shelleyTipHash :: HeaderHash (ShelleyBlock (TPraos c) (ShelleyEra c))
shelleyTipHash = HeaderHash ByronBlock
-> HeaderHash (ShelleyBlock (TPraos c) (ShelleyEra c))
forall c.
(ShelleyCompatible (TPraos c) (ShelleyEra c),
HASH c ~ Blake2b_256) =>
HeaderHash ByronBlock
-> HeaderHash (ShelleyBlock (TPraos c) (ShelleyEra c))
translateHeaderHashByronToShelley HeaderHash ByronBlock
h
}
(Point ByronBlock, WithOrigin BlockNo)
_otherwise ->
String -> WithOrigin (ShelleyTip (TPraos c) (ShelleyEra c))
forall a. HasCallStack => String -> a
error String
"translatePointByronToShelley: invalid Byron state"
translateLedgerStateByronToShelleyWrapper ::
( ShelleyCompatible (TPraos c) (ShelleyEra c)
, HASH c ~ Blake2b_256
, ADDRHASH c ~ Blake2b_224
)
=> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
translateLedgerStateByronToShelleyWrapper :: RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
translateLedgerStateByronToShelleyWrapper =
(WrapLedgerConfig ByronBlock
-> WrapLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Translate
LedgerState ByronBlock (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
forall k (h :: k -> *) (f :: k -> k -> *) (x :: k) (y :: k).
(h x -> h y -> f x y) -> RequiringBoth h f x y
RequireBoth ((WrapLedgerConfig ByronBlock
-> WrapLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Translate
LedgerState ByronBlock (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c)))
-> (WrapLedgerConfig ByronBlock
-> WrapLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Translate
LedgerState ByronBlock (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
forall a b. (a -> b) -> a -> b
$ \WrapLedgerConfig ByronBlock
_ (WrapLedgerConfig LedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
cfgShelley) ->
(EpochNo
-> LedgerState ByronBlock
-> LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> Translate
LedgerState ByronBlock (ShelleyBlock (TPraos c) (ShelleyEra c))
forall (f :: * -> *) x y.
(EpochNo -> f x -> f y) -> Translate f x y
Translate ((EpochNo
-> LedgerState ByronBlock
-> LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> Translate
LedgerState ByronBlock (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> (EpochNo
-> LedgerState ByronBlock
-> LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> Translate
LedgerState ByronBlock (ShelleyBlock (TPraos c) (ShelleyEra c))
forall a b. (a -> b) -> a -> b
$ \EpochNo
epochNo LedgerState ByronBlock
ledgerByron ->
ShelleyLedgerState :: forall proto era.
WithOrigin (ShelleyTip proto era)
-> NewEpochState era
-> ShelleyTransition
-> LedgerState (ShelleyBlock proto era)
ShelleyLedgerState {
shelleyLedgerTip :: WithOrigin (ShelleyTip (TPraos c) (ShelleyEra c))
shelleyLedgerTip =
Point ByronBlock
-> WithOrigin BlockNo
-> WithOrigin (ShelleyTip (TPraos c) (ShelleyEra c))
forall c.
(ShelleyCompatible (TPraos c) (ShelleyEra c),
HASH c ~ Blake2b_256) =>
Point ByronBlock
-> WithOrigin BlockNo
-> WithOrigin (ShelleyTip (TPraos c) (ShelleyEra c))
translatePointByronToShelley
(Proxy ByronBlock -> LedgerState ByronBlock -> Point ByronBlock
forall blk.
UpdateLedger blk =>
Proxy blk -> LedgerState blk -> Point blk
ledgerTipPoint (Proxy ByronBlock
forall k (t :: k). Proxy t
Proxy @ByronBlock) LedgerState ByronBlock
ledgerByron)
(LedgerState ByronBlock -> WithOrigin BlockNo
byronLedgerTipBlockNo LedgerState ByronBlock
ledgerByron)
, shelleyLedgerState :: NewEpochState (ShelleyEra c)
shelleyLedgerState =
ShelleyGenesis (ShelleyEra c)
-> EpochNo -> ChainValidationState -> NewEpochState (ShelleyEra c)
forall c.
(Crypto c, ADDRHASH c ~ Blake2b_224) =>
ShelleyGenesis (ShelleyEra c)
-> EpochNo -> ChainValidationState -> NewEpochState (ShelleyEra c)
SL.translateToShelleyLedgerState
(ShelleyLedgerConfig (ShelleyEra c) -> ShelleyGenesis (ShelleyEra c)
forall era. ShelleyLedgerConfig era -> ShelleyGenesis era
shelleyLedgerGenesis LedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
ShelleyLedgerConfig (ShelleyEra c)
cfgShelley)
EpochNo
epochNo
(LedgerState ByronBlock -> ChainValidationState
byronLedgerState LedgerState ByronBlock
ledgerByron)
, shelleyLedgerTransition :: ShelleyTransition
shelleyLedgerTransition =
ShelleyTransitionInfo :: Word32 -> ShelleyTransition
ShelleyTransitionInfo{shelleyAfterVoting :: Word32
shelleyAfterVoting = Word32
0}
}
translateChainDepStateByronToShelleyWrapper ::
RequiringBoth
WrapConsensusConfig
(Translate WrapChainDepState)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
translateChainDepStateByronToShelleyWrapper :: RequiringBoth
WrapConsensusConfig
(Translate WrapChainDepState)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
translateChainDepStateByronToShelleyWrapper =
(WrapConsensusConfig ByronBlock
-> WrapConsensusConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Translate
WrapChainDepState
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c)))
-> RequiringBoth
WrapConsensusConfig
(Translate WrapChainDepState)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
forall k (h :: k -> *) (f :: k -> k -> *) (x :: k) (y :: k).
(h x -> h y -> f x y) -> RequiringBoth h f x y
RequireBoth ((WrapConsensusConfig ByronBlock
-> WrapConsensusConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Translate
WrapChainDepState
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c)))
-> RequiringBoth
WrapConsensusConfig
(Translate WrapChainDepState)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c)))
-> (WrapConsensusConfig ByronBlock
-> WrapConsensusConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Translate
WrapChainDepState
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c)))
-> RequiringBoth
WrapConsensusConfig
(Translate WrapChainDepState)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
forall a b. (a -> b) -> a -> b
$ \WrapConsensusConfig ByronBlock
_ (WrapConsensusConfig ConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c)))
cfgShelley) ->
(EpochNo
-> WrapChainDepState ByronBlock
-> WrapChainDepState (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> Translate
WrapChainDepState
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
forall (f :: * -> *) x y.
(EpochNo -> f x -> f y) -> Translate f x y
Translate ((EpochNo
-> WrapChainDepState ByronBlock
-> WrapChainDepState (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> Translate
WrapChainDepState
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c)))
-> (EpochNo
-> WrapChainDepState ByronBlock
-> WrapChainDepState (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> Translate
WrapChainDepState
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
forall a b. (a -> b) -> a -> b
$ \EpochNo
_ (WrapChainDepState ChainDepState (BlockProtocol ByronBlock)
pbftState) ->
ChainDepState
(BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> WrapChainDepState (ShelleyBlock (TPraos c) (ShelleyEra c))
forall blk.
ChainDepState (BlockProtocol blk) -> WrapChainDepState blk
WrapChainDepState (ChainDepState
(BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> WrapChainDepState (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> ChainDepState
(BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> WrapChainDepState (ShelleyBlock (TPraos c) (ShelleyEra c))
forall a b. (a -> b) -> a -> b
$
ConsensusConfig (TPraos c)
-> PBftState PBftByronCrypto -> TPraosState c
forall bc c.
ConsensusConfig (TPraos c) -> PBftState bc -> TPraosState c
translateChainDepStateByronToShelley ConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c)))
ConsensusConfig (TPraos c)
cfgShelley PBftState PBftByronCrypto
ChainDepState (BlockProtocol ByronBlock)
pbftState
translateChainDepStateByronToShelley ::
forall bc c.
ConsensusConfig (TPraos c)
-> PBftState bc
-> TPraosState c
translateChainDepStateByronToShelley :: ConsensusConfig (TPraos c) -> PBftState bc -> TPraosState c
translateChainDepStateByronToShelley TPraosConfig { tpraosParams } PBftState bc
pbftState =
WithOrigin SlotNo -> ChainDepState c -> TPraosState c
forall c. WithOrigin SlotNo -> ChainDepState c -> TPraosState c
TPraosState (PBftState bc -> WithOrigin SlotNo
forall c. PBftState c -> WithOrigin SlotNo
PBftState.lastSignedSlot PBftState bc
pbftState) (ChainDepState c -> TPraosState c)
-> ChainDepState c -> TPraosState c
forall a b. (a -> b) -> a -> b
$
ChainDepState :: forall crypto.
PrtclState crypto -> TicknState -> Nonce -> ChainDepState crypto
SL.ChainDepState
{ csProtocol :: PrtclState c
SL.csProtocol = Map (KeyHash 'BlockIssuer c) Word64
-> Nonce -> Nonce -> PrtclState c
forall crypto.
Map (KeyHash 'BlockIssuer crypto) Word64
-> Nonce -> Nonce -> PrtclState crypto
SL.PrtclState Map (KeyHash 'BlockIssuer c) Word64
forall k a. Map k a
Map.empty Nonce
nonce Nonce
nonce
, csTickn :: TicknState
SL.csTickn = TicknState :: Nonce -> Nonce -> TicknState
SL.TicknState {
ticknStateEpochNonce :: Nonce
ticknStateEpochNonce = Nonce
nonce
, ticknStatePrevHashNonce :: Nonce
ticknStatePrevHashNonce = Nonce
SL.NeutralNonce
}
, csLabNonce :: Nonce
SL.csLabNonce = Nonce
SL.NeutralNonce
}
where
nonce :: Nonce
nonce = TPraosParams -> Nonce
tpraosInitialNonce TPraosParams
tpraosParams
translateLedgerViewByronToShelleyWrapper ::
forall c.
RequiringBoth
WrapLedgerConfig
(TranslateForecast LedgerState WrapLedgerView)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
translateLedgerViewByronToShelleyWrapper :: RequiringBoth
WrapLedgerConfig
(TranslateForecast LedgerState WrapLedgerView)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
translateLedgerViewByronToShelleyWrapper =
(WrapLedgerConfig ByronBlock
-> WrapLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> TranslateForecast
LedgerState
WrapLedgerView
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c)))
-> RequiringBoth
WrapLedgerConfig
(TranslateForecast LedgerState WrapLedgerView)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
forall k (h :: k -> *) (f :: k -> k -> *) (x :: k) (y :: k).
(h x -> h y -> f x y) -> RequiringBoth h f x y
RequireBoth ((WrapLedgerConfig ByronBlock
-> WrapLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> TranslateForecast
LedgerState
WrapLedgerView
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c)))
-> RequiringBoth
WrapLedgerConfig
(TranslateForecast LedgerState WrapLedgerView)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c)))
-> (WrapLedgerConfig ByronBlock
-> WrapLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> TranslateForecast
LedgerState
WrapLedgerView
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c)))
-> RequiringBoth
WrapLedgerConfig
(TranslateForecast LedgerState WrapLedgerView)
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
forall a b. (a -> b) -> a -> b
$ \WrapLedgerConfig ByronBlock
_ (WrapLedgerConfig LedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
cfgShelley) ->
(Bound
-> SlotNo
-> LedgerState ByronBlock
-> Except
OutsideForecastRange
(Ticked (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c)))))
-> TranslateForecast
LedgerState
WrapLedgerView
ByronBlock
(ShelleyBlock (TPraos c) (ShelleyEra c))
forall (f :: * -> *) (g :: * -> *) x y.
(Bound
-> SlotNo -> f x -> Except OutsideForecastRange (Ticked (g y)))
-> TranslateForecast f g x y
TranslateForecast (ShelleyLedgerConfig (ShelleyEra c)
-> Bound
-> SlotNo
-> LedgerState ByronBlock
-> Except
OutsideForecastRange
(Ticked (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c))))
forecast LedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
ShelleyLedgerConfig (ShelleyEra c)
cfgShelley)
where
forecast ::
ShelleyLedgerConfig (ShelleyEra c)
-> Bound
-> SlotNo
-> LedgerState ByronBlock
-> Except
OutsideForecastRange
(Ticked (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c))))
forecast :: ShelleyLedgerConfig (ShelleyEra c)
-> Bound
-> SlotNo
-> LedgerState ByronBlock
-> Except
OutsideForecastRange
(Ticked (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c))))
forecast ShelleyLedgerConfig (ShelleyEra c)
cfgShelley Bound
bound SlotNo
forecastFor LedgerState ByronBlock
currentByronState
| SlotNo
forecastFor SlotNo -> SlotNo -> Bool
forall a. Ord a => a -> a -> Bool
< SlotNo
maxFor
= Ticked (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> Except
OutsideForecastRange
(Ticked (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c))))
forall (m :: * -> *) a. Monad m => a -> m a
return (Ticked (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> Except
OutsideForecastRange
(Ticked (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c)))))
-> Ticked (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> Except
OutsideForecastRange
(Ticked (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c))))
forall a b. (a -> b) -> a -> b
$
Ticked
(LedgerView
(BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c))))
-> Ticked (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c)))
forall blk.
Ticked (LedgerView (BlockProtocol blk))
-> Ticked (WrapLedgerView blk)
WrapTickedLedgerView (Ticked
(LedgerView
(BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c))))
-> Ticked
(WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c))))
-> Ticked
(LedgerView
(BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c))))
-> Ticked (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c)))
forall a b. (a -> b) -> a -> b
$ LedgerView c -> Ticked (LedgerView c)
forall c. LedgerView c -> Ticked (LedgerView c)
TickedPraosLedgerView (LedgerView c -> Ticked (LedgerView c))
-> LedgerView c -> Ticked (LedgerView c)
forall a b. (a -> b) -> a -> b
$
ShelleyGenesis (ShelleyEra c) -> LedgerView c
forall c. ShelleyGenesis (ShelleyEra c) -> LedgerView c
SL.mkInitialShelleyLedgerView
(ShelleyLedgerConfig (ShelleyEra c) -> ShelleyGenesis (ShelleyEra c)
forall era. ShelleyLedgerConfig era -> ShelleyGenesis era
shelleyLedgerGenesis ShelleyLedgerConfig (ShelleyEra c)
cfgShelley)
| Bool
otherwise
= OutsideForecastRange
-> Except
OutsideForecastRange
(Ticked (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c))))
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (OutsideForecastRange
-> Except
OutsideForecastRange
(Ticked (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c)))))
-> OutsideForecastRange
-> Except
OutsideForecastRange
(Ticked (WrapLedgerView (ShelleyBlock (TPraos c) (ShelleyEra c))))
forall a b. (a -> b) -> a -> b
$ OutsideForecastRange :: WithOrigin SlotNo -> SlotNo -> SlotNo -> OutsideForecastRange
OutsideForecastRange {
outsideForecastAt :: WithOrigin SlotNo
outsideForecastAt = LedgerState ByronBlock -> WithOrigin SlotNo
forall blk.
UpdateLedger blk =>
LedgerState blk -> WithOrigin SlotNo
ledgerTipSlot LedgerState ByronBlock
currentByronState
, outsideForecastMaxFor :: SlotNo
outsideForecastMaxFor = SlotNo
maxFor
, outsideForecastFor :: SlotNo
outsideForecastFor = SlotNo
forecastFor
}
where
globals :: Globals
globals = ShelleyLedgerConfig (ShelleyEra c) -> Globals
forall era. ShelleyLedgerConfig era -> Globals
shelleyLedgerGlobals ShelleyLedgerConfig (ShelleyEra c)
cfgShelley
swindow :: Word64
swindow = Globals -> Word64
SL.stabilityWindow Globals
globals
maxFor :: SlotNo
maxFor :: SlotNo
maxFor = Word64 -> SlotNo -> SlotNo
addSlots Word64
swindow (Bound -> SlotNo
boundSlot Bound
bound)
translateLedgerStateShelleyToAllegraWrapper ::
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
=> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
translateLedgerStateShelleyToAllegraWrapper :: RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
translateLedgerStateShelleyToAllegraWrapper =
Translate
LedgerState
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
forall k (f :: k -> k -> *) (x :: k) (y :: k) (h :: k -> *).
f x y -> RequiringBoth h f x y
ignoringBoth (Translate
LedgerState
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c)))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
forall a b. (a -> b) -> a -> b
$
(EpochNo
-> LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c))
-> LedgerState (ShelleyBlock (TPraos c) (AllegraEra c)))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
forall (f :: * -> *) x y.
(EpochNo -> f x -> f y) -> Translate f x y
Translate ((EpochNo
-> LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c))
-> LedgerState (ShelleyBlock (TPraos c) (AllegraEra c)))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c)))
-> (EpochNo
-> LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c))
-> LedgerState (ShelleyBlock (TPraos c) (AllegraEra c)))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
forall a b. (a -> b) -> a -> b
$ \EpochNo
_epochNo ->
(:.:) LedgerState (ShelleyBlock (TPraos c)) (AllegraEra c)
-> LedgerState (ShelleyBlock (TPraos c) (AllegraEra c))
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp ((:.:) LedgerState (ShelleyBlock (TPraos c)) (AllegraEra c)
-> LedgerState (ShelleyBlock (TPraos c) (AllegraEra c)))
-> (LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (AllegraEra c))
-> LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c))
-> LedgerState (ShelleyBlock (TPraos c) (AllegraEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (AllegraEra c)
-> (:.:)
LedgerState (ShelleyBlock (TPraos c)) (PreviousEra (AllegraEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (AllegraEra c)
forall era (f :: * -> *).
(TranslateEra era f, TranslationError era f ~ Void) =>
TranslationContext era -> f (PreviousEra era) -> f era
SL.translateEra' () ((:.:) LedgerState (ShelleyBlock (TPraos c)) (ShelleyEra c)
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (AllegraEra c))
-> (LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (ShelleyEra c))
-> LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (AllegraEra c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (ShelleyEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp
translateTxShelleyToAllegraWrapper ::
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
=> InjectTx
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
translateTxShelleyToAllegraWrapper :: InjectTx
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
translateTxShelleyToAllegraWrapper = (GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (AllegraEra c))))
-> InjectTx
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
forall blk blk'.
(GenTx blk -> Maybe (GenTx blk')) -> InjectTx blk blk'
InjectTx ((GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (AllegraEra c))))
-> InjectTx
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (AllegraEra c))))
-> InjectTx
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
forall a b. (a -> b) -> a -> b
$
((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c)
-> GenTx (ShelleyBlock (TPraos c) (AllegraEra c)))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (AllegraEra c)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c)
-> GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp (Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (AllegraEra c))))
-> (GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (AllegraEra c)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall a b. Either a b -> Maybe b
eitherToMaybe (Either
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Either
DecoderError
((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
-> Either
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall e a. Except e a -> Either e a
runExcept (Except
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
-> Either
DecoderError
((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Except
DecoderError
((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Either
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (AllegraEra c)
-> (:.:)
GenTx (ShelleyBlock (TPraos c)) (PreviousEra (AllegraEra c))
-> Except
(TranslationError
(AllegraEra c) (GenTx :.: ShelleyBlock (TPraos c)))
((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra () ((:.:) GenTx (ShelleyBlock (TPraos c)) (ShelleyEra c)
-> Except
DecoderError
((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> (:.:) GenTx (ShelleyBlock (TPraos c)) (ShelleyEra c))
-> GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Except
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> (:.:) GenTx (ShelleyBlock (TPraos c)) (ShelleyEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp
translateValidatedTxShelleyToAllegraWrapper ::
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
=> InjectValidatedTx
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
translateValidatedTxShelleyToAllegraWrapper :: InjectValidatedTx
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
translateValidatedTxShelleyToAllegraWrapper = (WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Maybe
(WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))))
-> InjectValidatedTx
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
forall blk blk'.
(WrapValidatedGenTx blk -> Maybe (WrapValidatedGenTx blk'))
-> InjectValidatedTx blk blk'
InjectValidatedTx ((WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Maybe
(WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))))
-> InjectValidatedTx
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Maybe
(WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))))
-> InjectValidatedTx
(ShelleyBlock (TPraos c) (ShelleyEra c))
(ShelleyBlock (TPraos c) (AllegraEra c))
forall a b. (a -> b) -> a -> b
$
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c)
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c)))
-> Maybe
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
-> Maybe
(WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c)
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp (Maybe
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
-> Maybe
(WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Maybe
((:.:)
WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Maybe
(WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
-> Maybe
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall a b. Either a b -> Maybe b
eitherToMaybe (Either
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
-> Maybe
((:.:)
WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Either
DecoderError
((:.:)
WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Maybe
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
-> Either
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall e a. Except e a -> Either e a
runExcept (Except
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
-> Either
DecoderError
((:.:)
WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Except
DecoderError
((:.:)
WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Either
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (AllegraEra c)
-> (:.:)
WrapValidatedGenTx
(ShelleyBlock (TPraos c))
(PreviousEra (AllegraEra c))
-> Except
(TranslationError
(AllegraEra c) (WrapValidatedGenTx :.: ShelleyBlock (TPraos c)))
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra () ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (ShelleyEra c)
-> Except
DecoderError
((:.:)
WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> (:.:)
WrapValidatedGenTx (ShelleyBlock (TPraos c)) (ShelleyEra c))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Except
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapValidatedGenTx (ShelleyBlock (TPraos c) (ShelleyEra c))
-> (:.:)
WrapValidatedGenTx (ShelleyBlock (TPraos c)) (ShelleyEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp
translateLedgerStateAllegraToMaryWrapper ::
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
=> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
translateLedgerStateAllegraToMaryWrapper :: RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
translateLedgerStateAllegraToMaryWrapper =
Translate
LedgerState
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
forall k (f :: k -> k -> *) (x :: k) (y :: k) (h :: k -> *).
f x y -> RequiringBoth h f x y
ignoringBoth (Translate
LedgerState
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c)))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
forall a b. (a -> b) -> a -> b
$
(EpochNo
-> LedgerState (ShelleyBlock (TPraos c) (AllegraEra c))
-> LedgerState (ShelleyBlock (TPraos c) (MaryEra c)))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
forall (f :: * -> *) x y.
(EpochNo -> f x -> f y) -> Translate f x y
Translate ((EpochNo
-> LedgerState (ShelleyBlock (TPraos c) (AllegraEra c))
-> LedgerState (ShelleyBlock (TPraos c) (MaryEra c)))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c)))
-> (EpochNo
-> LedgerState (ShelleyBlock (TPraos c) (AllegraEra c))
-> LedgerState (ShelleyBlock (TPraos c) (MaryEra c)))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
forall a b. (a -> b) -> a -> b
$ \EpochNo
_epochNo ->
(:.:) LedgerState (ShelleyBlock (TPraos c)) (MaryEra c)
-> LedgerState (ShelleyBlock (TPraos c) (MaryEra c))
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp ((:.:) LedgerState (ShelleyBlock (TPraos c)) (MaryEra c)
-> LedgerState (ShelleyBlock (TPraos c) (MaryEra c)))
-> (LedgerState (ShelleyBlock (TPraos c) (AllegraEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (MaryEra c))
-> LedgerState (ShelleyBlock (TPraos c) (AllegraEra c))
-> LedgerState (ShelleyBlock (TPraos c) (MaryEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (MaryEra c)
-> (:.:)
LedgerState (ShelleyBlock (TPraos c)) (PreviousEra (MaryEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (MaryEra c)
forall era (f :: * -> *).
(TranslateEra era f, TranslationError era f ~ Void) =>
TranslationContext era -> f (PreviousEra era) -> f era
SL.translateEra' () ((:.:) LedgerState (ShelleyBlock (TPraos c)) (AllegraEra c)
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (MaryEra c))
-> (LedgerState (ShelleyBlock (TPraos c) (AllegraEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (AllegraEra c))
-> LedgerState (ShelleyBlock (TPraos c) (AllegraEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (MaryEra c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (TPraos c) (AllegraEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (AllegraEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp
translateTxAllegraToMaryWrapper ::
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
=> InjectTx
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
translateTxAllegraToMaryWrapper :: InjectTx
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
translateTxAllegraToMaryWrapper = (GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (MaryEra c))))
-> InjectTx
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
forall blk blk'.
(GenTx blk -> Maybe (GenTx blk')) -> InjectTx blk blk'
InjectTx ((GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (MaryEra c))))
-> InjectTx
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (MaryEra c))))
-> InjectTx
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
forall a b. (a -> b) -> a -> b
$
((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c)
-> GenTx (ShelleyBlock (TPraos c) (MaryEra c)))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (MaryEra c)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c)
-> GenTx (ShelleyBlock (TPraos c) (MaryEra c))
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp (Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (MaryEra c))))
-> (GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (MaryEra c)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall a b. Either a b -> Maybe b
eitherToMaybe (Either
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Either
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
-> Either
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall e a. Except e a -> Either e a
runExcept (Except
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
-> Either
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Except
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Either
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (MaryEra c)
-> (:.:) GenTx (ShelleyBlock (TPraos c)) (PreviousEra (MaryEra c))
-> Except
(TranslationError (MaryEra c) (GenTx :.: ShelleyBlock (TPraos c)))
((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra () ((:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c)
-> Except
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> (:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
-> GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Except
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> (:.:) GenTx (ShelleyBlock (TPraos c)) (AllegraEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp
translateValidatedTxAllegraToMaryWrapper ::
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
=> InjectValidatedTx
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
translateValidatedTxAllegraToMaryWrapper :: InjectValidatedTx
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
translateValidatedTxAllegraToMaryWrapper = (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Maybe
(WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))))
-> InjectValidatedTx
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
forall blk blk'.
(WrapValidatedGenTx blk -> Maybe (WrapValidatedGenTx blk'))
-> InjectValidatedTx blk blk'
InjectValidatedTx ((WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Maybe
(WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))))
-> InjectValidatedTx
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Maybe
(WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))))
-> InjectValidatedTx
(ShelleyBlock (TPraos c) (AllegraEra c))
(ShelleyBlock (TPraos c) (MaryEra c))
forall a b. (a -> b) -> a -> b
$
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c)
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c)))
-> Maybe
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
-> Maybe (WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c)
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp (Maybe
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
-> Maybe
(WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Maybe
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Maybe (WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
-> Maybe
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall a b. Either a b -> Maybe b
eitherToMaybe (Either
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
-> Maybe
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Either
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Maybe
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
-> Either
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall e a. Except e a -> Either e a
runExcept (Except
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
-> Either
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Except
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Either
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (MaryEra c)
-> (:.:)
WrapValidatedGenTx
(ShelleyBlock (TPraos c))
(PreviousEra (MaryEra c))
-> Except
(TranslationError
(MaryEra c) (WrapValidatedGenTx :.: ShelleyBlock (TPraos c)))
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra () ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c)
-> Except
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> (:.:)
WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> Except
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapValidatedGenTx (ShelleyBlock (TPraos c) (AllegraEra c))
-> (:.:)
WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AllegraEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp
translateLedgerStateMaryToAlonzoWrapper ::
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
=> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
translateLedgerStateMaryToAlonzoWrapper :: RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
translateLedgerStateMaryToAlonzoWrapper =
(WrapLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c)))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
forall k (h :: k -> *) (f :: k -> k -> *) (x :: k) (y :: k).
(h x -> h y -> f x y) -> RequiringBoth h f x y
RequireBoth ((WrapLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c)))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c)))
-> (WrapLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c)))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
forall a b. (a -> b) -> a -> b
$ \WrapLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
_cfgMary WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
cfgAlonzo ->
(EpochNo
-> LedgerState (ShelleyBlock (TPraos c) (MaryEra c))
-> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
forall (f :: * -> *) x y.
(EpochNo -> f x -> f y) -> Translate f x y
Translate ((EpochNo
-> LedgerState (ShelleyBlock (TPraos c) (MaryEra c))
-> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c)))
-> (EpochNo
-> LedgerState (ShelleyBlock (TPraos c) (MaryEra c))
-> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
forall a b. (a -> b) -> a -> b
$ \EpochNo
_epochNo ->
(:.:) LedgerState (ShelleyBlock (TPraos c)) (AlonzoEra c)
-> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp ((:.:) LedgerState (ShelleyBlock (TPraos c)) (AlonzoEra c)
-> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> (LedgerState (ShelleyBlock (TPraos c) (MaryEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (AlonzoEra c))
-> LedgerState (ShelleyBlock (TPraos c) (MaryEra c))
-> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (AlonzoEra c)
-> (:.:)
LedgerState (ShelleyBlock (TPraos c)) (PreviousEra (AlonzoEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (AlonzoEra c)
forall era (f :: * -> *).
(TranslateEra era f, TranslationError era f ~ Void) =>
TranslationContext era -> f (PreviousEra era) -> f era
SL.translateEra' (WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> AlonzoGenesis
forall c.
WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> AlonzoGenesis
getAlonzoTranslationContext WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
cfgAlonzo) ((:.:) LedgerState (ShelleyBlock (TPraos c)) (MaryEra c)
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (AlonzoEra c))
-> (LedgerState (ShelleyBlock (TPraos c) (MaryEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (MaryEra c))
-> LedgerState (ShelleyBlock (TPraos c) (MaryEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (AlonzoEra c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (TPraos c) (MaryEra c))
-> (:.:) LedgerState (ShelleyBlock (TPraos c)) (MaryEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp
getAlonzoTranslationContext ::
WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Alonzo.AlonzoGenesis
getAlonzoTranslationContext :: WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> AlonzoGenesis
getAlonzoTranslationContext =
ShelleyLedgerConfig (AlonzoEra c) -> AlonzoGenesis
forall era. ShelleyLedgerConfig era -> TranslationContext era
shelleyLedgerTranslationContext (ShelleyLedgerConfig (AlonzoEra c) -> AlonzoGenesis)
-> (WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> ShelleyLedgerConfig (AlonzoEra c))
-> WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> AlonzoGenesis
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> ShelleyLedgerConfig (AlonzoEra c)
forall blk. WrapLedgerConfig blk -> LedgerConfig blk
unwrapLedgerConfig
translateTxMaryToAlonzoWrapper ::
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
=> Alonzo.AlonzoGenesis
-> InjectTx
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
translateTxMaryToAlonzoWrapper :: AlonzoGenesis
-> InjectTx
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
translateTxMaryToAlonzoWrapper AlonzoGenesis
ctxt = (GenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))))
-> InjectTx
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
forall blk blk'.
(GenTx blk -> Maybe (GenTx blk')) -> InjectTx blk blk'
InjectTx ((GenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))))
-> InjectTx
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))))
-> InjectTx
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
forall a b. (a -> b) -> a -> b
$
((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)
-> GenTx (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)
-> GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp (Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))))
-> (GenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> GenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Maybe (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall a b. Either a b -> Maybe b
eitherToMaybe (Either
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Either
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> GenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
-> Either
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall e a. Except e a -> Either e a
runExcept (Except
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
-> Either
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Except
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> GenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Either
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (AlonzoEra c)
-> (:.:)
GenTx (ShelleyBlock (TPraos c)) (PreviousEra (AlonzoEra c))
-> Except
(TranslationError
(AlonzoEra c) (GenTx :.: ShelleyBlock (TPraos c)))
((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra AlonzoGenesis
TranslationContext (AlonzoEra c)
ctxt ((:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c)
-> Except
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> (:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c))
-> GenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Except
DecoderError ((:.:) GenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> (:.:) GenTx (ShelleyBlock (TPraos c)) (MaryEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp
translateValidatedTxMaryToAlonzoWrapper ::
forall c.
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
=> Alonzo.AlonzoGenesis
-> InjectValidatedTx
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
translateValidatedTxMaryToAlonzoWrapper :: AlonzoGenesis
-> InjectValidatedTx
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
translateValidatedTxMaryToAlonzoWrapper AlonzoGenesis
ctxt = (WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Maybe
(WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))))
-> InjectValidatedTx
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
forall blk blk'.
(WrapValidatedGenTx blk -> Maybe (WrapValidatedGenTx blk'))
-> InjectValidatedTx blk blk'
InjectValidatedTx ((WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Maybe
(WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))))
-> InjectValidatedTx
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Maybe
(WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))))
-> InjectValidatedTx
(ShelleyBlock (TPraos c) (MaryEra c))
(ShelleyBlock (TPraos c) (AlonzoEra c))
forall a b. (a -> b) -> a -> b
$
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> Maybe
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
-> Maybe
(WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp (Maybe
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
-> Maybe
(WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Maybe
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Maybe
(WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
-> Maybe
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall a b. Either a b -> Maybe b
eitherToMaybe (Either
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
-> Maybe
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Either
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Maybe
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
-> Either
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall e a. Except e a -> Either e a
runExcept (Except
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
-> Either
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Except
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Either
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (AlonzoEra c)
-> (:.:)
WrapValidatedGenTx
(ShelleyBlock (TPraos c))
(PreviousEra (AlonzoEra c))
-> Except
(TranslationError
(AlonzoEra c) (WrapValidatedGenTx :.: ShelleyBlock (TPraos c)))
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra AlonzoGenesis
TranslationContext (AlonzoEra c)
ctxt ((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c)
-> Except
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> (:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> Except
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (AlonzoEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapValidatedGenTx (ShelleyBlock (TPraos c) (MaryEra c))
-> (:.:) WrapValidatedGenTx (ShelleyBlock (TPraos c)) (MaryEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp
translateLedgerStateAlonzoToBabbageWrapper ::
(Praos.PraosCrypto c, TPraos.PraosCrypto c)
=> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
translateLedgerStateAlonzoToBabbageWrapper :: RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
translateLedgerStateAlonzoToBabbageWrapper =
(WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c)))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
forall k (h :: k -> *) (f :: k -> k -> *) (x :: k) (y :: k).
(h x -> h y -> f x y) -> RequiringBoth h f x y
RequireBoth ((WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c)))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c)))
-> (WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c)))
-> RequiringBoth
WrapLedgerConfig
(Translate LedgerState)
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
forall a b. (a -> b) -> a -> b
$ \WrapLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
_cfgAlonzo WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
cfgBabbage ->
(EpochNo
-> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
-> LedgerState (ShelleyBlock (Praos c) (BabbageEra c)))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
forall (f :: * -> *) x y.
(EpochNo -> f x -> f y) -> Translate f x y
Translate ((EpochNo
-> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
-> LedgerState (ShelleyBlock (Praos c) (BabbageEra c)))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c)))
-> (EpochNo
-> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
-> LedgerState (ShelleyBlock (Praos c) (BabbageEra c)))
-> Translate
LedgerState
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
forall a b. (a -> b) -> a -> b
$ \EpochNo
_epochNo ->
(:.:) LedgerState (ShelleyBlock (Praos c)) (BabbageEra c)
-> LedgerState (ShelleyBlock (Praos c) (BabbageEra c))
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp ((:.:) LedgerState (ShelleyBlock (Praos c)) (BabbageEra c)
-> LedgerState (ShelleyBlock (Praos c) (BabbageEra c)))
-> (LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
-> (:.:) LedgerState (ShelleyBlock (Praos c)) (BabbageEra c))
-> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
-> LedgerState (ShelleyBlock (Praos c) (BabbageEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (BabbageEra c)
-> (:.:)
LedgerState (ShelleyBlock (Praos c)) (PreviousEra (BabbageEra c))
-> (:.:) LedgerState (ShelleyBlock (Praos c)) (BabbageEra c)
forall era (f :: * -> *).
(TranslateEra era f, TranslationError era f ~ Void) =>
TranslationContext era -> f (PreviousEra era) -> f era
SL.translateEra' (WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> AlonzoGenesis
forall c.
WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> AlonzoGenesis
getBabbageTranslationContext WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
cfgBabbage) ((:.:) LedgerState (ShelleyBlock (Praos c)) (AlonzoEra c)
-> (:.:) LedgerState (ShelleyBlock (Praos c)) (BabbageEra c))
-> (LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
-> (:.:) LedgerState (ShelleyBlock (Praos c)) (AlonzoEra c))
-> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
-> (:.:) LedgerState (ShelleyBlock (Praos c)) (BabbageEra c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (Praos c) (AlonzoEra c))
-> (:.:) LedgerState (ShelleyBlock (Praos c)) (AlonzoEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp (LedgerState (ShelleyBlock (Praos c) (AlonzoEra c))
-> (:.:) LedgerState (ShelleyBlock (Praos c)) (AlonzoEra c))
-> (LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
-> LedgerState (ShelleyBlock (Praos c) (AlonzoEra c)))
-> LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
-> (:.:) LedgerState (ShelleyBlock (Praos c)) (AlonzoEra c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
-> LedgerState (ShelleyBlock (Praos c) (AlonzoEra c))
forall c.
LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
-> LedgerState (ShelleyBlock (Praos c) (AlonzoEra c))
transPraosLS
where
transPraosLS ::
LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c)) ->
LedgerState (ShelleyBlock (Praos c) (AlonzoEra c))
transPraosLS :: LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
-> LedgerState (ShelleyBlock (Praos c) (AlonzoEra c))
transPraosLS (ShelleyLedgerState wo nes st) =
ShelleyLedgerState :: forall proto era.
WithOrigin (ShelleyTip proto era)
-> NewEpochState era
-> ShelleyTransition
-> LedgerState (ShelleyBlock proto era)
ShelleyLedgerState
{ shelleyLedgerTip :: WithOrigin (ShelleyTip (Praos c) (AlonzoEra c))
shelleyLedgerTip = (ShelleyTip (TPraos c) (AlonzoEra c)
-> ShelleyTip (Praos c) (AlonzoEra c))
-> WithOrigin (ShelleyTip (TPraos c) (AlonzoEra c))
-> WithOrigin (ShelleyTip (Praos c) (AlonzoEra c))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ShelleyTip (TPraos c) (AlonzoEra c)
-> ShelleyTip (Praos c) (AlonzoEra c)
forall proto era proto' era'.
(HeaderHash (ShelleyBlock proto era)
~ HeaderHash (ShelleyBlock proto' era')) =>
ShelleyTip proto era -> ShelleyTip proto' era'
castShelleyTip WithOrigin (ShelleyTip (TPraos c) (AlonzoEra c))
wo
, shelleyLedgerState :: NewEpochState (AlonzoEra c)
shelleyLedgerState = NewEpochState (AlonzoEra c)
nes
, shelleyLedgerTransition :: ShelleyTransition
shelleyLedgerTransition = ShelleyTransition
st
}
getBabbageTranslationContext ::
WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> Alonzo.AlonzoGenesis
getBabbageTranslationContext :: WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> AlonzoGenesis
getBabbageTranslationContext =
ShelleyLedgerConfig (BabbageEra c) -> AlonzoGenesis
forall era. ShelleyLedgerConfig era -> TranslationContext era
shelleyLedgerTranslationContext (ShelleyLedgerConfig (BabbageEra c) -> AlonzoGenesis)
-> (WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> ShelleyLedgerConfig (BabbageEra c))
-> WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> AlonzoGenesis
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> ShelleyLedgerConfig (BabbageEra c)
forall blk. WrapLedgerConfig blk -> LedgerConfig blk
unwrapLedgerConfig
translateTxAlonzoToBabbageWrapper ::
(Praos.PraosCrypto c)
=> Alonzo.AlonzoGenesis
-> InjectTx
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
translateTxAlonzoToBabbageWrapper :: AlonzoGenesis
-> InjectTx
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
translateTxAlonzoToBabbageWrapper AlonzoGenesis
ctxt = (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Maybe (GenTx (ShelleyBlock (Praos c) (BabbageEra c))))
-> InjectTx
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
forall blk blk'.
(GenTx blk -> Maybe (GenTx blk')) -> InjectTx blk blk'
InjectTx ((GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Maybe (GenTx (ShelleyBlock (Praos c) (BabbageEra c))))
-> InjectTx
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Maybe (GenTx (ShelleyBlock (Praos c) (BabbageEra c))))
-> InjectTx
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
forall a b. (a -> b) -> a -> b
$
((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c)
-> GenTx (ShelleyBlock (Praos c) (BabbageEra c)))
-> Maybe ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
-> Maybe (GenTx (ShelleyBlock (Praos c) (BabbageEra c)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c)
-> GenTx (ShelleyBlock (Praos c) (BabbageEra c))
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp (Maybe ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
-> Maybe (GenTx (ShelleyBlock (Praos c) (BabbageEra c))))
-> (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Maybe (GenTx (ShelleyBlock (Praos c) (BabbageEra c)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall a b. Either a b -> Maybe b
eitherToMaybe (Either
DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Either
DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Maybe ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except
DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
-> Either
DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall e a. Except e a -> Either e a
runExcept (Except
DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
-> Either
DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Except
DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Either
DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (BabbageEra c)
-> (:.:)
GenTx (ShelleyBlock (Praos c)) (PreviousEra (BabbageEra c))
-> Except
(TranslationError
(BabbageEra c) (GenTx :.: ShelleyBlock (Praos c)))
((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra AlonzoGenesis
TranslationContext (BabbageEra c)
ctxt ((:.:) GenTx (ShelleyBlock (Praos c)) (AlonzoEra c)
-> Except
DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> (:.:) GenTx (ShelleyBlock (Praos c)) (AlonzoEra c))
-> GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Except
DecoderError ((:.:) GenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenTx (ShelleyBlock (Praos c) (AlonzoEra c))
-> (:.:) GenTx (ShelleyBlock (Praos c)) (AlonzoEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp (GenTx (ShelleyBlock (Praos c) (AlonzoEra c))
-> (:.:) GenTx (ShelleyBlock (Praos c)) (AlonzoEra c))
-> (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> GenTx (ShelleyBlock (Praos c) (AlonzoEra c)))
-> GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> (:.:) GenTx (ShelleyBlock (Praos c)) (AlonzoEra c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> GenTx (ShelleyBlock (Praos c) (AlonzoEra c))
forall c.
GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> GenTx (ShelleyBlock (Praos c) (AlonzoEra c))
transPraosTx
where
transPraosTx
:: GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> GenTx (ShelleyBlock (Praos c) (AlonzoEra c))
transPraosTx :: GenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> GenTx (ShelleyBlock (Praos c) (AlonzoEra c))
transPraosTx (ShelleyTx ti tx) = TxId (EraCrypto (AlonzoEra c))
-> Tx (AlonzoEra c) -> GenTx (ShelleyBlock (Praos c) (AlonzoEra c))
forall proto era.
TxId (EraCrypto era) -> Tx era -> GenTx (ShelleyBlock proto era)
ShelleyTx TxId (EraCrypto (AlonzoEra c))
ti (ValidatedTx (AlonzoEra c) -> ValidatedTx (AlonzoEra c)
coerce Tx (AlonzoEra c)
ValidatedTx (AlonzoEra c)
tx)
translateValidatedTxAlonzoToBabbageWrapper ::
forall c.
(Praos.PraosCrypto c)
=> Alonzo.AlonzoGenesis
-> InjectValidatedTx
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
translateValidatedTxAlonzoToBabbageWrapper :: AlonzoGenesis
-> InjectValidatedTx
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
translateValidatedTxAlonzoToBabbageWrapper AlonzoGenesis
ctxt = (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Maybe
(WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c))))
-> InjectValidatedTx
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
forall blk blk'.
(WrapValidatedGenTx blk -> Maybe (WrapValidatedGenTx blk'))
-> InjectValidatedTx blk blk'
InjectValidatedTx ((WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Maybe
(WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c))))
-> InjectValidatedTx
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Maybe
(WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c))))
-> InjectValidatedTx
(ShelleyBlock (TPraos c) (AlonzoEra c))
(ShelleyBlock (Praos c) (BabbageEra c))
forall a b. (a -> b) -> a -> b
$
((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c)
-> WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c)))
-> Maybe
((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
-> Maybe
(WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c)
-> WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c))
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
(:.:) f g p -> f (g p)
unComp
(Maybe
((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
-> Maybe
(WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c))))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Maybe
((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Maybe
(WrapValidatedGenTx (ShelleyBlock (Praos c) (BabbageEra c)))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
-> Maybe
((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall a b. Either a b -> Maybe b
eitherToMaybe
(Either
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
-> Maybe
((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Either
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Maybe
((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Except
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
-> Either
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall e a. Except e a -> Either e a
runExcept
(Except
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
-> Either
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Except
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Either
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TranslationContext (BabbageEra c)
-> (:.:)
WrapValidatedGenTx
(ShelleyBlock (Praos c))
(PreviousEra (BabbageEra c))
-> Except
(TranslationError
(BabbageEra c) (WrapValidatedGenTx :.: ShelleyBlock (Praos c)))
((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall era (f :: * -> *).
TranslateEra era f =>
TranslationContext era
-> f (PreviousEra era) -> Except (TranslationError era f) (f era)
SL.translateEra AlonzoGenesis
TranslationContext (BabbageEra c)
ctxt
((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (AlonzoEra c)
-> Except
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c)))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> (:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (AlonzoEra c))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Except
DecoderError
((:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (BabbageEra c))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapValidatedGenTx (ShelleyBlock (Praos c) (AlonzoEra c))
-> (:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (AlonzoEra c)
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp
(WrapValidatedGenTx (ShelleyBlock (Praos c) (AlonzoEra c))
-> (:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (AlonzoEra c))
-> (WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> WrapValidatedGenTx (ShelleyBlock (Praos c) (AlonzoEra c)))
-> WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> (:.:) WrapValidatedGenTx (ShelleyBlock (Praos c)) (AlonzoEra c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> WrapValidatedGenTx (ShelleyBlock (Praos c) (AlonzoEra c))
transPraosValidatedTx
where
transPraosValidatedTx
:: WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> WrapValidatedGenTx (ShelleyBlock (Praos c) (AlonzoEra c))
transPraosValidatedTx :: WrapValidatedGenTx (ShelleyBlock (TPraos c) (AlonzoEra c))
-> WrapValidatedGenTx (ShelleyBlock (Praos c) (AlonzoEra c))
transPraosValidatedTx (WrapValidatedGenTx Validated (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c)))
x) = case Validated (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c)))
x of
ShelleyValidatedTx txid vtx -> Validated (GenTx (ShelleyBlock (Praos c) (AlonzoEra c)))
-> WrapValidatedGenTx (ShelleyBlock (Praos c) (AlonzoEra c))
forall blk. Validated (GenTx blk) -> WrapValidatedGenTx blk
WrapValidatedGenTx (Validated (GenTx (ShelleyBlock (Praos c) (AlonzoEra c)))
-> WrapValidatedGenTx (ShelleyBlock (Praos c) (AlonzoEra c)))
-> Validated (GenTx (ShelleyBlock (Praos c) (AlonzoEra c)))
-> WrapValidatedGenTx (ShelleyBlock (Praos c) (AlonzoEra c))
forall a b. (a -> b) -> a -> b
$
TxId (EraCrypto (AlonzoEra c))
-> Validated (Tx (AlonzoEra c))
-> Validated (GenTx (ShelleyBlock (Praos c) (AlonzoEra c)))
forall proto era.
TxId (EraCrypto era)
-> Validated (Tx era) -> Validated (GenTx (ShelleyBlock proto era))
ShelleyValidatedTx TxId (EraCrypto (AlonzoEra c))
txid (Validated (ValidatedTx (AlonzoEra c))
-> Validated (ValidatedTx (AlonzoEra c))
forall a b. Coercible a b => Validated a -> Validated b
SL.coerceValidated Validated (Tx (AlonzoEra c))
Validated (ValidatedTx (AlonzoEra c))
vtx)