{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Ouroboros.Consensus.Shelley.HFEras
( StandardAllegraBlock
, StandardAlonzoBlock
, StandardBabbageBlock
, StandardConwayBlock
, StandardMaryBlock
, StandardShelleyBlock
) where
import Ouroboros.Consensus.Protocol.Praos (Praos)
import qualified Ouroboros.Consensus.Protocol.Praos as Praos
import Ouroboros.Consensus.Protocol.TPraos (StandardCrypto, TPraos)
import qualified Ouroboros.Consensus.Protocol.TPraos as TPraos
import Ouroboros.Consensus.Shelley.Eras
( AllegraEra
, AlonzoEra
, BabbageEra
, ConwayEra
, MaryEra
, ShelleyEra
)
import Ouroboros.Consensus.Shelley.Ledger.Block
( ShelleyBlock
, ShelleyCompatible
)
import Ouroboros.Consensus.Shelley.Ledger.Protocol ()
import Ouroboros.Consensus.Shelley.Protocol.Praos ()
import Ouroboros.Consensus.Shelley.Protocol.TPraos ()
import Ouroboros.Consensus.Shelley.ShelleyHFC ()
type StandardShelleyBlock = ShelleyBlock (TPraos StandardCrypto) ShelleyEra
type StandardAllegraBlock = ShelleyBlock (TPraos StandardCrypto) AllegraEra
type StandardMaryBlock = ShelleyBlock (TPraos StandardCrypto) MaryEra
type StandardAlonzoBlock = ShelleyBlock (TPraos StandardCrypto) AlonzoEra
type StandardBabbageBlock = ShelleyBlock (Praos StandardCrypto) BabbageEra
type StandardConwayBlock = ShelleyBlock (Praos StandardCrypto) ConwayEra
instance
TPraos.PraosCrypto c =>
ShelleyCompatible (TPraos c) ShelleyEra
instance
TPraos.PraosCrypto c =>
ShelleyCompatible (TPraos c) AllegraEra
instance
TPraos.PraosCrypto c =>
ShelleyCompatible (TPraos c) MaryEra
instance
TPraos.PraosCrypto c =>
ShelleyCompatible (TPraos c) AlonzoEra
instance
(Praos.PraosCrypto c, TPraos.PraosCrypto c) =>
ShelleyCompatible (TPraos c) BabbageEra
instance Praos.PraosCrypto c => ShelleyCompatible (Praos c) BabbageEra
instance
(Praos.PraosCrypto c, TPraos.PraosCrypto c) =>
ShelleyCompatible (TPraos c) ConwayEra
instance Praos.PraosCrypto c => ShelleyCompatible (Praos c) ConwayEra