{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DisambiguateRecordFields #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ViewPatterns #-}
module Ouroboros.Consensus.Cardano.Block (
CardanoEras
, CardanoShelleyEras
, module Ouroboros.Consensus.Shelley.Eras
, ShelleyBasedLedgerEras
, CardanoBlock
, HardForkBlock (BlockAllegra, BlockAlonzo, BlockByron, BlockMary, BlockShelley, BlockBabbage, BlockConway)
, CardanoHeader
, Header (HeaderAllegra, HeaderAlonzo, HeaderByron, HeaderMary, HeaderShelley, HeaderBabbage, HeaderConway)
, CardanoApplyTxErr
, CardanoGenTx
, CardanoGenTxId
, GenTx (GenTxAllegra, GenTxAlonzo, GenTxByron, GenTxMary, GenTxShelley, GenTxBabbage, GenTxConway)
, HardForkApplyTxErr (ApplyTxErrAllegra, ApplyTxErrAlonzo, ApplyTxErrByron, ApplyTxErrMary, ApplyTxErrShelley, ApplyTxErrWrongEra, ApplyTxErrBabbage, ApplyTxErrConway)
, TxId (GenTxIdAllegra, GenTxIdAlonzo, GenTxIdByron, GenTxIdMary, GenTxIdShelley, GenTxIdBabbage, GenTxIdConway)
, CardanoLedgerError
, HardForkLedgerError (LedgerErrorAllegra, LedgerErrorAlonzo, LedgerErrorByron, LedgerErrorMary, LedgerErrorShelley, LedgerErrorWrongEra, LedgerErrorBabbage, LedgerErrorConway)
, CardanoOtherHeaderEnvelopeError
, HardForkEnvelopeErr (OtherHeaderEnvelopeErrorAllegra, OtherHeaderEnvelopeErrorBabbage, OtherHeaderEnvelopeErrorConway, OtherHeaderEnvelopeErrorAlonzo, OtherHeaderEnvelopeErrorByron, OtherHeaderEnvelopeErrorMary, OtherHeaderEnvelopeErrorShelley, OtherHeaderEnvelopeErrorWrongEra)
, CardanoTipInfo
, OneEraTipInfo (TipInfoAllegra, TipInfoAlonzo, TipInfoByron, TipInfoBabbage, TipInfoConway, TipInfoMary, TipInfoShelley)
, BlockQuery (QueryAnytimeAllegra, QueryAnytimeAlonzo, QueryAnytimeBabbage, QueryAnytimeConway, QueryAnytimeByron, QueryAnytimeMary, QueryAnytimeShelley, QueryHardFork, QueryIfCurrentAllegra, QueryIfCurrentAlonzo, QueryIfCurrentBabbage, QueryIfCurrentConway, QueryIfCurrentByron, QueryIfCurrentMary, QueryIfCurrentShelley)
, CardanoQuery
, CardanoQueryResult
, Either (QueryResultSuccess, QueryResultEraMismatch)
, CardanoCodecConfig
, CodecConfig (CardanoCodecConfig)
, BlockConfig (CardanoBlockConfig)
, CardanoBlockConfig
, CardanoStorageConfig
, StorageConfig (CardanoStorageConfig)
, CardanoConsensusConfig
, ConsensusConfig (CardanoConsensusConfig)
, CardanoLedgerConfig
, HardForkLedgerConfig (CardanoLedgerConfig)
, CardanoLedgerState
, LedgerState (LedgerStateAllegra, LedgerStateAlonzo, LedgerStateBabbage, LedgerStateConway, LedgerStateByron, LedgerStateMary, LedgerStateShelley)
, CardanoChainDepState
, HardForkState (ChainDepStateAllegra, ChainDepStateAlonzo, ChainDepStateBabbage, ChainDepStateConway, ChainDepStateByron, ChainDepStateMary, ChainDepStateShelley)
, EraMismatch (..)
) where
import Data.Kind
import Data.SOP.BasicFunctors
import Data.SOP.Strict
import Ouroboros.Consensus.Block (BlockProtocol)
import Ouroboros.Consensus.Byron.Ledger.Block (ByronBlock)
import Ouroboros.Consensus.HardFork.Combinator
import Ouroboros.Consensus.HardFork.Combinator.AcrossEras
import qualified Ouroboros.Consensus.HardFork.Combinator.State as State
import Ouroboros.Consensus.HeaderValidation (OtherHeaderEnvelopeError,
TipInfo)
import Ouroboros.Consensus.Ledger.Abstract (LedgerError)
import Ouroboros.Consensus.Ledger.SupportsMempool (ApplyTxErr,
GenTxId)
import Ouroboros.Consensus.Protocol.Abstract (ChainDepState)
import Ouroboros.Consensus.Protocol.Praos (Praos)
import Ouroboros.Consensus.Protocol.TPraos (TPraos)
import Ouroboros.Consensus.Shelley.Eras
import Ouroboros.Consensus.Shelley.Ledger (ShelleyBlock)
import Ouroboros.Consensus.TypeFamilyWrappers
type CardanoEras :: Type -> [Type]
type CardanoEras c = ByronBlock ': CardanoShelleyEras c
type CardanoShelleyEras :: Type -> [Type]
type CardanoShelleyEras c =
'[ ShelleyBlock (TPraos c) (ShelleyEra c)
, ShelleyBlock (TPraos c) (AllegraEra c)
, ShelleyBlock (TPraos c) (MaryEra c)
, ShelleyBlock (TPraos c) (AlonzoEra c)
, ShelleyBlock (Praos c) (BabbageEra c)
, ShelleyBlock (Praos c) (ConwayEra c)
]
type ShelleyBasedLedgerEras :: Type -> [Type]
type ShelleyBasedLedgerEras c =
'[ ShelleyEra c
, AllegraEra c
, MaryEra c
, AlonzoEra c
, BabbageEra c
, ConwayEra c
]
pattern TagByron :: f ByronBlock -> NS f (CardanoEras c)
pattern TagShelley :: f (ShelleyBlock (TPraos c) (ShelleyEra c)) -> NS f (CardanoEras c)
pattern TagAllegra :: f (ShelleyBlock (TPraos c) (AllegraEra c)) -> NS f (CardanoEras c)
pattern TagMary :: f (ShelleyBlock (TPraos c) (MaryEra c)) -> NS f (CardanoEras c)
pattern TagAlonzo :: f (ShelleyBlock (TPraos c) (AlonzoEra c)) -> NS f (CardanoEras c)
pattern TagBabbage :: f (ShelleyBlock (Praos c) (BabbageEra c)) -> NS f (CardanoEras c)
pattern TagConway :: f (ShelleyBlock (Praos c) (ConwayEra c)) -> NS f (CardanoEras c)
pattern $mTagByron :: forall {r} {f :: * -> *} {c}.
NS f (CardanoEras c) -> (f ByronBlock -> r) -> ((# #) -> r) -> r
$bTagByron :: forall (f :: * -> *) c. f ByronBlock -> NS f (CardanoEras c)
TagByron x = Z x
pattern $mTagShelley :: forall {r} {f :: * -> *} {c}.
NS f (CardanoEras c)
-> (f (ShelleyBlock (TPraos c) (ShelleyEra c)) -> r)
-> ((# #) -> r)
-> r
$bTagShelley :: forall (f :: * -> *) c.
f (ShelleyBlock (TPraos c) (ShelleyEra c)) -> NS f (CardanoEras c)
TagShelley x = S (Z x)
pattern $mTagAllegra :: forall {r} {f :: * -> *} {c}.
NS f (CardanoEras c)
-> (f (ShelleyBlock (TPraos c) (AllegraEra c)) -> r)
-> ((# #) -> r)
-> r
$bTagAllegra :: forall (f :: * -> *) c.
f (ShelleyBlock (TPraos c) (AllegraEra c)) -> NS f (CardanoEras c)
TagAllegra x = S (S (Z x))
pattern $mTagMary :: forall {r} {f :: * -> *} {c}.
NS f (CardanoEras c)
-> (f (ShelleyBlock (TPraos c) (MaryEra c)) -> r)
-> ((# #) -> r)
-> r
$bTagMary :: forall (f :: * -> *) c.
f (ShelleyBlock (TPraos c) (MaryEra c)) -> NS f (CardanoEras c)
TagMary x = S (S (S (Z x)))
pattern $mTagAlonzo :: forall {r} {f :: * -> *} {c}.
NS f (CardanoEras c)
-> (f (ShelleyBlock (TPraos c) (AlonzoEra c)) -> r)
-> ((# #) -> r)
-> r
$bTagAlonzo :: forall (f :: * -> *) c.
f (ShelleyBlock (TPraos c) (AlonzoEra c)) -> NS f (CardanoEras c)
TagAlonzo x = S (S (S (S (Z x))))
pattern $mTagBabbage :: forall {r} {f :: * -> *} {c}.
NS f (CardanoEras c)
-> (f (ShelleyBlock (Praos c) (BabbageEra c)) -> r)
-> ((# #) -> r)
-> r
$bTagBabbage :: forall (f :: * -> *) c.
f (ShelleyBlock (Praos c) (BabbageEra c)) -> NS f (CardanoEras c)
TagBabbage x = S (S (S (S (S (Z x)))))
pattern $mTagConway :: forall {r} {f :: * -> *} {c}.
NS f (CardanoEras c)
-> (f (ShelleyBlock (Praos c) (ConwayEra c)) -> r)
-> ((# #) -> r)
-> r
$bTagConway :: forall (f :: * -> *) c.
f (ShelleyBlock (Praos c) (ConwayEra c)) -> NS f (CardanoEras c)
TagConway x = S (S (S (S (S (S (Z x))))))
pattern TeleByron ::
f ByronBlock
-> Telescope g f (CardanoEras c)
pattern TeleShelley ::
g ByronBlock
-> f (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Telescope g f (CardanoEras c)
pattern TeleAllegra ::
g ByronBlock
-> g (ShelleyBlock (TPraos c) (ShelleyEra c))
-> f (ShelleyBlock (TPraos c) (AllegraEra c))
-> Telescope g f (CardanoEras c)
pattern TeleMary ::
g ByronBlock
-> g (ShelleyBlock (TPraos c) (ShelleyEra c))
-> g (ShelleyBlock (TPraos c) (AllegraEra c))
-> f (ShelleyBlock (TPraos c) (MaryEra c))
-> Telescope g f (CardanoEras c)
pattern TeleAlonzo ::
g ByronBlock
-> g (ShelleyBlock (TPraos c) (ShelleyEra c))
-> g (ShelleyBlock (TPraos c) (AllegraEra c))
-> g (ShelleyBlock (TPraos c) (MaryEra c))
-> f (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Telescope g f (CardanoEras c)
pattern TeleBabbage ::
g ByronBlock
-> g (ShelleyBlock (TPraos c) (ShelleyEra c))
-> g (ShelleyBlock (TPraos c) (AllegraEra c))
-> g (ShelleyBlock (TPraos c) (MaryEra c))
-> g (ShelleyBlock (TPraos c) (AlonzoEra c))
-> f (ShelleyBlock (Praos c) (BabbageEra c))
-> Telescope g f (CardanoEras c)
pattern TeleConway ::
g ByronBlock
-> g (ShelleyBlock (TPraos c) (ShelleyEra c))
-> g (ShelleyBlock (TPraos c) (AllegraEra c))
-> g (ShelleyBlock (TPraos c) (MaryEra c))
-> g (ShelleyBlock (TPraos c) (AlonzoEra c))
-> g (ShelleyBlock (Praos c) (BabbageEra c))
-> f (ShelleyBlock (Praos c) (ConwayEra c))
-> Telescope g f (CardanoEras c)
pattern $mTeleByron :: forall {r} {f :: * -> *} {g :: * -> *} {c}.
Telescope g f (CardanoEras c)
-> (f ByronBlock -> r) -> ((# #) -> r) -> r
$bTeleByron :: forall (f :: * -> *) (g :: * -> *) c.
f ByronBlock -> Telescope g f (CardanoEras c)
TeleByron x = TZ x
pattern $mTeleShelley :: forall {r} {g :: * -> *} {f :: * -> *} {c}.
Telescope g f (CardanoEras c)
-> (g ByronBlock
-> f (ShelleyBlock (TPraos c) (ShelleyEra c)) -> r)
-> ((# #) -> r)
-> r
$bTeleShelley :: forall (g :: * -> *) (f :: * -> *) c.
g ByronBlock
-> f (ShelleyBlock (TPraos c) (ShelleyEra c))
-> Telescope g f (CardanoEras c)
TeleShelley byron x = TS byron (TZ x)
pattern $mTeleAllegra :: forall {r} {g :: * -> *} {c} {f :: * -> *}.
Telescope g f (CardanoEras c)
-> (g ByronBlock
-> g (ShelleyBlock (TPraos c) (ShelleyEra c))
-> f (ShelleyBlock (TPraos c) (AllegraEra c))
-> r)
-> ((# #) -> r)
-> r
$bTeleAllegra :: forall (g :: * -> *) c (f :: * -> *).
g ByronBlock
-> g (ShelleyBlock (TPraos c) (ShelleyEra c))
-> f (ShelleyBlock (TPraos c) (AllegraEra c))
-> Telescope g f (CardanoEras c)
TeleAllegra byron shelley x = TS byron (TS shelley (TZ x))
pattern $mTeleMary :: forall {r} {g :: * -> *} {c} {f :: * -> *}.
Telescope g f (CardanoEras c)
-> (g ByronBlock
-> g (ShelleyBlock (TPraos c) (ShelleyEra c))
-> g (ShelleyBlock (TPraos c) (AllegraEra c))
-> f (ShelleyBlock (TPraos c) (MaryEra c))
-> r)
-> ((# #) -> r)
-> r
$bTeleMary :: forall (g :: * -> *) c (f :: * -> *).
g ByronBlock
-> g (ShelleyBlock (TPraos c) (ShelleyEra c))
-> g (ShelleyBlock (TPraos c) (AllegraEra c))
-> f (ShelleyBlock (TPraos c) (MaryEra c))
-> Telescope g f (CardanoEras c)
TeleMary byron shelley allegra x = TS byron (TS shelley (TS allegra (TZ x)))
pattern $mTeleAlonzo :: forall {r} {g :: * -> *} {c} {f :: * -> *}.
Telescope g f (CardanoEras c)
-> (g ByronBlock
-> g (ShelleyBlock (TPraos c) (ShelleyEra c))
-> g (ShelleyBlock (TPraos c) (AllegraEra c))
-> g (ShelleyBlock (TPraos c) (MaryEra c))
-> f (ShelleyBlock (TPraos c) (AlonzoEra c))
-> r)
-> ((# #) -> r)
-> r
$bTeleAlonzo :: forall (g :: * -> *) c (f :: * -> *).
g ByronBlock
-> g (ShelleyBlock (TPraos c) (ShelleyEra c))
-> g (ShelleyBlock (TPraos c) (AllegraEra c))
-> g (ShelleyBlock (TPraos c) (MaryEra c))
-> f (ShelleyBlock (TPraos c) (AlonzoEra c))
-> Telescope g f (CardanoEras c)
TeleAlonzo byron shelley allegra mary x = TS byron (TS shelley (TS allegra (TS mary (TZ x))))
pattern $mTeleBabbage :: forall {r} {g :: * -> *} {c} {f :: * -> *}.
Telescope g f (CardanoEras c)
-> (g ByronBlock
-> g (ShelleyBlock (TPraos c) (ShelleyEra c))
-> g (ShelleyBlock (TPraos c) (AllegraEra c))
-> g (ShelleyBlock (TPraos c) (MaryEra c))
-> g (ShelleyBlock (TPraos c) (AlonzoEra c))
-> f (ShelleyBlock (Praos c) (BabbageEra c))
-> r)
-> ((# #) -> r)
-> r
$bTeleBabbage :: forall (g :: * -> *) c (f :: * -> *).
g ByronBlock
-> g (ShelleyBlock (TPraos c) (ShelleyEra c))
-> g (ShelleyBlock (TPraos c) (AllegraEra c))
-> g (ShelleyBlock (TPraos c) (MaryEra c))
-> g (ShelleyBlock (TPraos c) (AlonzoEra c))
-> f (ShelleyBlock (Praos c) (BabbageEra c))
-> Telescope g f (CardanoEras c)
TeleBabbage byron shelley allegra mary alonzo x = TS byron (TS shelley (TS allegra (TS mary (TS alonzo (TZ x)))))
pattern $mTeleConway :: forall {r} {g :: * -> *} {c} {f :: * -> *}.
Telescope g f (CardanoEras c)
-> (g ByronBlock
-> g (ShelleyBlock (TPraos c) (ShelleyEra c))
-> g (ShelleyBlock (TPraos c) (AllegraEra c))
-> g (ShelleyBlock (TPraos c) (MaryEra c))
-> g (ShelleyBlock (TPraos c) (AlonzoEra c))
-> g (ShelleyBlock (Praos c) (BabbageEra c))
-> f (ShelleyBlock (Praos c) (ConwayEra c))
-> r)
-> ((# #) -> r)
-> r
$bTeleConway :: forall (g :: * -> *) c (f :: * -> *).
g ByronBlock
-> g (ShelleyBlock (TPraos c) (ShelleyEra c))
-> g (ShelleyBlock (TPraos c) (AllegraEra c))
-> g (ShelleyBlock (TPraos c) (MaryEra c))
-> g (ShelleyBlock (TPraos c) (AlonzoEra c))
-> g (ShelleyBlock (Praos c) (BabbageEra c))
-> f (ShelleyBlock (Praos c) (ConwayEra c))
-> Telescope g f (CardanoEras c)
TeleConway byron shelley allegra mary alonzo babbage x = TS byron (TS shelley (TS allegra (TS mary (TS alonzo (TS babbage (TZ x))))))
type CardanoBlock c = HardForkBlock (CardanoEras c)
pattern BlockByron :: ByronBlock -> CardanoBlock c
pattern $mBlockByron :: forall {r} {c}.
CardanoBlock c -> (ByronBlock -> r) -> ((# #) -> r) -> r
$bBlockByron :: forall c. ByronBlock -> CardanoBlock c
BlockByron b = HardForkBlock (OneEraBlock (TagByron (I b)))
pattern BlockShelley :: ShelleyBlock (TPraos c) (ShelleyEra c) -> CardanoBlock c
pattern $mBlockShelley :: forall {r} {c}.
CardanoBlock c
-> (ShelleyBlock (TPraos c) (ShelleyEra c) -> r)
-> ((# #) -> r)
-> r
$bBlockShelley :: forall c. ShelleyBlock (TPraos c) (ShelleyEra c) -> CardanoBlock c
BlockShelley b = HardForkBlock (OneEraBlock (TagShelley (I b)))
pattern BlockAllegra :: ShelleyBlock (TPraos c) (AllegraEra c) -> CardanoBlock c
pattern $mBlockAllegra :: forall {r} {c}.
CardanoBlock c
-> (ShelleyBlock (TPraos c) (AllegraEra c) -> r)
-> ((# #) -> r)
-> r
$bBlockAllegra :: forall c. ShelleyBlock (TPraos c) (AllegraEra c) -> CardanoBlock c
BlockAllegra b = HardForkBlock (OneEraBlock (TagAllegra (I b)))
pattern BlockMary :: ShelleyBlock (TPraos c) (MaryEra c) -> CardanoBlock c
pattern $mBlockMary :: forall {r} {c}.
CardanoBlock c
-> (ShelleyBlock (TPraos c) (MaryEra c) -> r) -> ((# #) -> r) -> r
$bBlockMary :: forall c. ShelleyBlock (TPraos c) (MaryEra c) -> CardanoBlock c
BlockMary b = HardForkBlock (OneEraBlock (TagMary (I b)))
pattern BlockAlonzo :: ShelleyBlock (TPraos c) (AlonzoEra c) -> CardanoBlock c
pattern $mBlockAlonzo :: forall {r} {c}.
CardanoBlock c
-> (ShelleyBlock (TPraos c) (AlonzoEra c) -> r)
-> ((# #) -> r)
-> r
$bBlockAlonzo :: forall c. ShelleyBlock (TPraos c) (AlonzoEra c) -> CardanoBlock c
BlockAlonzo b = HardForkBlock (OneEraBlock (TagAlonzo (I b)))
pattern BlockBabbage :: ShelleyBlock (Praos c) (BabbageEra c) -> CardanoBlock c
pattern $mBlockBabbage :: forall {r} {c}.
CardanoBlock c
-> (ShelleyBlock (Praos c) (BabbageEra c) -> r)
-> ((# #) -> r)
-> r
$bBlockBabbage :: forall c. ShelleyBlock (Praos c) (BabbageEra c) -> CardanoBlock c
BlockBabbage b = HardForkBlock (OneEraBlock (TagBabbage (I b)))
pattern BlockConway :: ShelleyBlock (Praos c) (ConwayEra c) -> CardanoBlock c
pattern $mBlockConway :: forall {r} {c}.
CardanoBlock c
-> (ShelleyBlock (Praos c) (ConwayEra c) -> r) -> ((# #) -> r) -> r
$bBlockConway :: forall c. ShelleyBlock (Praos c) (ConwayEra c) -> CardanoBlock c
BlockConway b = HardForkBlock (OneEraBlock (TagConway (I b)))
{-# COMPLETE
BlockByron
, BlockShelley
, BlockAllegra
, BlockMary
, BlockAlonzo
, BlockBabbage
, BlockConway
#-}
type c = Header (CardanoBlock c)
pattern HeaderByron :: Header ByronBlock -> CardanoHeader c
pattern h = HardForkHeader (OneEraHeader (TagByron h))
pattern HeaderShelley ::
Header (ShelleyBlock (TPraos c) (ShelleyEra c))
-> CardanoHeader c
pattern h = HardForkHeader (OneEraHeader (TagShelley h))
pattern HeaderAllegra ::
Header (ShelleyBlock (TPraos c) (AllegraEra c))
-> CardanoHeader c
pattern h = HardForkHeader (OneEraHeader (TagAllegra h))
pattern HeaderMary ::
Header (ShelleyBlock (TPraos c) (MaryEra c))
-> CardanoHeader c
pattern h = HardForkHeader (OneEraHeader (TagMary h))
pattern HeaderAlonzo ::
Header (ShelleyBlock (TPraos c) (AlonzoEra c))
-> CardanoHeader c
pattern h = HardForkHeader (OneEraHeader (TagAlonzo h))
pattern HeaderBabbage ::
Header (ShelleyBlock (Praos c) (BabbageEra c))
-> CardanoHeader c
pattern h = HardForkHeader (OneEraHeader (TagBabbage h))
pattern HeaderConway ::
Header (ShelleyBlock (Praos c) (ConwayEra c))
-> CardanoHeader c
pattern h = HardForkHeader (OneEraHeader (TagConway h))
{-# COMPLETE HeaderByron
, HeaderShelley
, HeaderAllegra
, HeaderMary
, HeaderAlonzo
, HeaderBabbage
, HeaderConway
#-}
type CardanoGenTx c = GenTx (CardanoBlock c)
pattern GenTxByron :: GenTx ByronBlock -> CardanoGenTx c
pattern $mGenTxByron :: forall {r} {c}.
CardanoGenTx c -> (GenTx ByronBlock -> r) -> ((# #) -> r) -> r
$bGenTxByron :: forall c. GenTx ByronBlock -> CardanoGenTx c
GenTxByron tx = HardForkGenTx (OneEraGenTx (TagByron tx))
pattern GenTxShelley :: GenTx (ShelleyBlock (TPraos c) (ShelleyEra c)) -> CardanoGenTx c
pattern $mGenTxShelley :: forall {r} {c}.
CardanoGenTx c
-> (GenTx (ShelleyBlock (TPraos c) (ShelleyEra c)) -> r)
-> ((# #) -> r)
-> r
$bGenTxShelley :: forall c.
GenTx (ShelleyBlock (TPraos c) (ShelleyEra c)) -> CardanoGenTx c
GenTxShelley tx = HardForkGenTx (OneEraGenTx (TagShelley tx))
pattern GenTxAllegra :: GenTx (ShelleyBlock (TPraos c) (AllegraEra c)) -> CardanoGenTx c
pattern $mGenTxAllegra :: forall {r} {c}.
CardanoGenTx c
-> (GenTx (ShelleyBlock (TPraos c) (AllegraEra c)) -> r)
-> ((# #) -> r)
-> r
$bGenTxAllegra :: forall c.
GenTx (ShelleyBlock (TPraos c) (AllegraEra c)) -> CardanoGenTx c
GenTxAllegra tx = HardForkGenTx (OneEraGenTx (TagAllegra tx))
pattern GenTxMary :: GenTx (ShelleyBlock (TPraos c) (MaryEra c)) -> CardanoGenTx c
pattern $mGenTxMary :: forall {r} {c}.
CardanoGenTx c
-> (GenTx (ShelleyBlock (TPraos c) (MaryEra c)) -> r)
-> ((# #) -> r)
-> r
$bGenTxMary :: forall c.
GenTx (ShelleyBlock (TPraos c) (MaryEra c)) -> CardanoGenTx c
GenTxMary tx = HardForkGenTx (OneEraGenTx (TagMary tx))
pattern GenTxAlonzo :: GenTx (ShelleyBlock (TPraos c) (AlonzoEra c)) -> CardanoGenTx c
pattern $mGenTxAlonzo :: forall {r} {c}.
CardanoGenTx c
-> (GenTx (ShelleyBlock (TPraos c) (AlonzoEra c)) -> r)
-> ((# #) -> r)
-> r
$bGenTxAlonzo :: forall c.
GenTx (ShelleyBlock (TPraos c) (AlonzoEra c)) -> CardanoGenTx c
GenTxAlonzo tx = HardForkGenTx (OneEraGenTx (TagAlonzo tx))
pattern GenTxBabbage :: GenTx (ShelleyBlock (Praos c) (BabbageEra c)) -> CardanoGenTx c
pattern $mGenTxBabbage :: forall {r} {c}.
CardanoGenTx c
-> (GenTx (ShelleyBlock (Praos c) (BabbageEra c)) -> r)
-> ((# #) -> r)
-> r
$bGenTxBabbage :: forall c.
GenTx (ShelleyBlock (Praos c) (BabbageEra c)) -> CardanoGenTx c
GenTxBabbage tx = HardForkGenTx (OneEraGenTx (TagBabbage tx))
pattern GenTxConway :: GenTx (ShelleyBlock (Praos c) (ConwayEra c)) -> CardanoGenTx c
pattern $mGenTxConway :: forall {r} {c}.
CardanoGenTx c
-> (GenTx (ShelleyBlock (Praos c) (ConwayEra c)) -> r)
-> ((# #) -> r)
-> r
$bGenTxConway :: forall c.
GenTx (ShelleyBlock (Praos c) (ConwayEra c)) -> CardanoGenTx c
GenTxConway tx = HardForkGenTx (OneEraGenTx (TagConway tx))
{-# COMPLETE
GenTxByron
, GenTxShelley
, GenTxAllegra
, GenTxMary
, GenTxAlonzo
, GenTxBabbage
, GenTxConway
#-}
type CardanoGenTxId c = GenTxId (CardanoBlock c)
pattern GenTxIdByron :: GenTxId ByronBlock -> CardanoGenTxId c
pattern $mGenTxIdByron :: forall {r} {c}.
CardanoGenTxId c -> (GenTxId ByronBlock -> r) -> ((# #) -> r) -> r
$bGenTxIdByron :: forall c. GenTxId ByronBlock -> CardanoGenTxId c
GenTxIdByron txid =
HardForkGenTxId (OneEraGenTxId (TagByron (WrapGenTxId txid)))
pattern GenTxIdShelley ::
GenTxId (ShelleyBlock (TPraos c) (ShelleyEra c))
-> CardanoGenTxId c
pattern $mGenTxIdShelley :: forall {r} {c}.
CardanoGenTxId c
-> (GenTxId (ShelleyBlock (TPraos c) (ShelleyEra c)) -> r)
-> ((# #) -> r)
-> r
$bGenTxIdShelley :: forall c.
GenTxId (ShelleyBlock (TPraos c) (ShelleyEra c))
-> CardanoGenTxId c
GenTxIdShelley txid =
HardForkGenTxId (OneEraGenTxId (TagShelley (WrapGenTxId txid)))
pattern GenTxIdAllegra ::
GenTxId (ShelleyBlock (TPraos c) (AllegraEra c))
-> CardanoGenTxId c
pattern $mGenTxIdAllegra :: forall {r} {c}.
CardanoGenTxId c
-> (GenTxId (ShelleyBlock (TPraos c) (AllegraEra c)) -> r)
-> ((# #) -> r)
-> r
$bGenTxIdAllegra :: forall c.
GenTxId (ShelleyBlock (TPraos c) (AllegraEra c))
-> CardanoGenTxId c
GenTxIdAllegra txid =
HardForkGenTxId (OneEraGenTxId (TagAllegra (WrapGenTxId txid)))
pattern GenTxIdMary ::
GenTxId (ShelleyBlock (TPraos c) (MaryEra c))
-> CardanoGenTxId c
pattern $mGenTxIdMary :: forall {r} {c}.
CardanoGenTxId c
-> (GenTxId (ShelleyBlock (TPraos c) (MaryEra c)) -> r)
-> ((# #) -> r)
-> r
$bGenTxIdMary :: forall c.
GenTxId (ShelleyBlock (TPraos c) (MaryEra c)) -> CardanoGenTxId c
GenTxIdMary txid =
HardForkGenTxId (OneEraGenTxId (TagMary (WrapGenTxId txid)))
pattern GenTxIdAlonzo ::
GenTxId (ShelleyBlock (TPraos c) (AlonzoEra c))
-> CardanoGenTxId c
pattern $mGenTxIdAlonzo :: forall {r} {c}.
CardanoGenTxId c
-> (GenTxId (ShelleyBlock (TPraos c) (AlonzoEra c)) -> r)
-> ((# #) -> r)
-> r
$bGenTxIdAlonzo :: forall c.
GenTxId (ShelleyBlock (TPraos c) (AlonzoEra c)) -> CardanoGenTxId c
GenTxIdAlonzo txid =
HardForkGenTxId (OneEraGenTxId (TagAlonzo (WrapGenTxId txid)))
pattern GenTxIdBabbage ::
GenTxId (ShelleyBlock (Praos c) (BabbageEra c))
-> CardanoGenTxId c
pattern $mGenTxIdBabbage :: forall {r} {c}.
CardanoGenTxId c
-> (GenTxId (ShelleyBlock (Praos c) (BabbageEra c)) -> r)
-> ((# #) -> r)
-> r
$bGenTxIdBabbage :: forall c.
GenTxId (ShelleyBlock (Praos c) (BabbageEra c)) -> CardanoGenTxId c
GenTxIdBabbage txid =
HardForkGenTxId (OneEraGenTxId (TagBabbage (WrapGenTxId txid)))
pattern GenTxIdConway ::
GenTxId (ShelleyBlock (Praos c) (ConwayEra c))
-> CardanoGenTxId c
pattern $mGenTxIdConway :: forall {r} {c}.
CardanoGenTxId c
-> (GenTxId (ShelleyBlock (Praos c) (ConwayEra c)) -> r)
-> ((# #) -> r)
-> r
$bGenTxIdConway :: forall c.
GenTxId (ShelleyBlock (Praos c) (ConwayEra c)) -> CardanoGenTxId c
GenTxIdConway txid =
HardForkGenTxId (OneEraGenTxId (TagConway (WrapGenTxId txid)))
{-# COMPLETE GenTxIdByron
, GenTxIdShelley
, GenTxIdAllegra
, GenTxIdMary
, GenTxIdAlonzo
, GenTxIdBabbage
, GenTxIdConway
#-}
type CardanoApplyTxErr c = HardForkApplyTxErr (CardanoEras c)
pattern ApplyTxErrByron :: ApplyTxErr ByronBlock -> CardanoApplyTxErr c
pattern $mApplyTxErrByron :: forall {r} {c}.
CardanoApplyTxErr c
-> (ApplyTxErr ByronBlock -> r) -> ((# #) -> r) -> r
$bApplyTxErrByron :: forall c. ApplyTxErr ByronBlock -> CardanoApplyTxErr c
ApplyTxErrByron err =
HardForkApplyTxErrFromEra (OneEraApplyTxErr (TagByron (WrapApplyTxErr err)))
pattern ApplyTxErrShelley ::
ApplyTxErr (ShelleyBlock (TPraos c) (ShelleyEra c))
-> CardanoApplyTxErr c
pattern $mApplyTxErrShelley :: forall {r} {c}.
CardanoApplyTxErr c
-> (ApplyTxErr (ShelleyBlock (TPraos c) (ShelleyEra c)) -> r)
-> ((# #) -> r)
-> r
$bApplyTxErrShelley :: forall c.
ApplyTxErr (ShelleyBlock (TPraos c) (ShelleyEra c))
-> CardanoApplyTxErr c
ApplyTxErrShelley err =
HardForkApplyTxErrFromEra (OneEraApplyTxErr (TagShelley (WrapApplyTxErr err)))
pattern ApplyTxErrAllegra ::
ApplyTxErr (ShelleyBlock (TPraos c) (AllegraEra c))
-> CardanoApplyTxErr c
pattern $mApplyTxErrAllegra :: forall {r} {c}.
CardanoApplyTxErr c
-> (ApplyTxErr (ShelleyBlock (TPraos c) (AllegraEra c)) -> r)
-> ((# #) -> r)
-> r
$bApplyTxErrAllegra :: forall c.
ApplyTxErr (ShelleyBlock (TPraos c) (AllegraEra c))
-> CardanoApplyTxErr c
ApplyTxErrAllegra err =
HardForkApplyTxErrFromEra (OneEraApplyTxErr (TagAllegra (WrapApplyTxErr err)))
pattern ApplyTxErrMary ::
ApplyTxErr (ShelleyBlock (TPraos c) (MaryEra c))
-> CardanoApplyTxErr c
pattern $mApplyTxErrMary :: forall {r} {c}.
CardanoApplyTxErr c
-> (ApplyTxErr (ShelleyBlock (TPraos c) (MaryEra c)) -> r)
-> ((# #) -> r)
-> r
$bApplyTxErrMary :: forall c.
ApplyTxErr (ShelleyBlock (TPraos c) (MaryEra c))
-> CardanoApplyTxErr c
ApplyTxErrMary err =
HardForkApplyTxErrFromEra (OneEraApplyTxErr (TagMary (WrapApplyTxErr err)))
pattern ApplyTxErrAlonzo ::
ApplyTxErr (ShelleyBlock (TPraos c) (AlonzoEra c))
-> CardanoApplyTxErr c
pattern $mApplyTxErrAlonzo :: forall {r} {c}.
CardanoApplyTxErr c
-> (ApplyTxErr (ShelleyBlock (TPraos c) (AlonzoEra c)) -> r)
-> ((# #) -> r)
-> r
$bApplyTxErrAlonzo :: forall c.
ApplyTxErr (ShelleyBlock (TPraos c) (AlonzoEra c))
-> CardanoApplyTxErr c
ApplyTxErrAlonzo err =
HardForkApplyTxErrFromEra (OneEraApplyTxErr (TagAlonzo (WrapApplyTxErr err)))
pattern ApplyTxErrBabbage ::
ApplyTxErr (ShelleyBlock (Praos c) (BabbageEra c))
-> CardanoApplyTxErr c
pattern $mApplyTxErrBabbage :: forall {r} {c}.
CardanoApplyTxErr c
-> (ApplyTxErr (ShelleyBlock (Praos c) (BabbageEra c)) -> r)
-> ((# #) -> r)
-> r
$bApplyTxErrBabbage :: forall c.
ApplyTxErr (ShelleyBlock (Praos c) (BabbageEra c))
-> CardanoApplyTxErr c
ApplyTxErrBabbage err =
HardForkApplyTxErrFromEra (OneEraApplyTxErr (TagBabbage (WrapApplyTxErr err)))
pattern ApplyTxErrConway ::
ApplyTxErr (ShelleyBlock (Praos c) (ConwayEra c))
-> CardanoApplyTxErr c
pattern $mApplyTxErrConway :: forall {r} {c}.
CardanoApplyTxErr c
-> (ApplyTxErr (ShelleyBlock (Praos c) (ConwayEra c)) -> r)
-> ((# #) -> r)
-> r
$bApplyTxErrConway :: forall c.
ApplyTxErr (ShelleyBlock (Praos c) (ConwayEra c))
-> CardanoApplyTxErr c
ApplyTxErrConway err =
HardForkApplyTxErrFromEra (OneEraApplyTxErr (TagConway (WrapApplyTxErr err)))
pattern ApplyTxErrWrongEra :: EraMismatch -> CardanoApplyTxErr c
pattern $mApplyTxErrWrongEra :: forall {r} {c}.
CardanoApplyTxErr c -> (EraMismatch -> r) -> ((# #) -> r) -> r
ApplyTxErrWrongEra eraMismatch <-
HardForkApplyTxErrWrongEra (mkEraMismatch -> eraMismatch)
{-# COMPLETE ApplyTxErrByron
, ApplyTxErrShelley
, ApplyTxErrAllegra
, ApplyTxErrMary
, ApplyTxErrAlonzo
, ApplyTxErrBabbage
, ApplyTxErrConway
, ApplyTxErrWrongEra
#-}
type CardanoLedgerError c = HardForkLedgerError (CardanoEras c)
pattern LedgerErrorByron :: LedgerError ByronBlock -> CardanoLedgerError c
pattern $mLedgerErrorByron :: forall {r} {c}.
CardanoLedgerError c
-> (LedgerError ByronBlock -> r) -> ((# #) -> r) -> r
$bLedgerErrorByron :: forall c. LedgerError ByronBlock -> CardanoLedgerError c
LedgerErrorByron err =
HardForkLedgerErrorFromEra (OneEraLedgerError (TagByron (WrapLedgerErr err)))
pattern LedgerErrorShelley ::
LedgerError (ShelleyBlock (TPraos c) (ShelleyEra c))
-> CardanoLedgerError c
pattern $mLedgerErrorShelley :: forall {r} {c}.
CardanoLedgerError c
-> (LedgerError (ShelleyBlock (TPraos c) (ShelleyEra c)) -> r)
-> ((# #) -> r)
-> r
$bLedgerErrorShelley :: forall c.
LedgerError (ShelleyBlock (TPraos c) (ShelleyEra c))
-> CardanoLedgerError c
LedgerErrorShelley err =
HardForkLedgerErrorFromEra
(OneEraLedgerError (TagShelley (WrapLedgerErr err)))
pattern LedgerErrorAllegra ::
LedgerError (ShelleyBlock (TPraos c) (AllegraEra c))
-> CardanoLedgerError c
pattern $mLedgerErrorAllegra :: forall {r} {c}.
CardanoLedgerError c
-> (LedgerError (ShelleyBlock (TPraos c) (AllegraEra c)) -> r)
-> ((# #) -> r)
-> r
$bLedgerErrorAllegra :: forall c.
LedgerError (ShelleyBlock (TPraos c) (AllegraEra c))
-> CardanoLedgerError c
LedgerErrorAllegra err =
HardForkLedgerErrorFromEra
(OneEraLedgerError (TagAllegra (WrapLedgerErr err)))
pattern LedgerErrorMary ::
LedgerError (ShelleyBlock (TPraos c) (MaryEra c))
-> CardanoLedgerError c
pattern $mLedgerErrorMary :: forall {r} {c}.
CardanoLedgerError c
-> (LedgerError (ShelleyBlock (TPraos c) (MaryEra c)) -> r)
-> ((# #) -> r)
-> r
$bLedgerErrorMary :: forall c.
LedgerError (ShelleyBlock (TPraos c) (MaryEra c))
-> CardanoLedgerError c
LedgerErrorMary err =
HardForkLedgerErrorFromEra
(OneEraLedgerError (TagMary (WrapLedgerErr err)))
pattern LedgerErrorAlonzo ::
LedgerError (ShelleyBlock (TPraos c) (AlonzoEra c))
-> CardanoLedgerError c
pattern $mLedgerErrorAlonzo :: forall {r} {c}.
CardanoLedgerError c
-> (LedgerError (ShelleyBlock (TPraos c) (AlonzoEra c)) -> r)
-> ((# #) -> r)
-> r
$bLedgerErrorAlonzo :: forall c.
LedgerError (ShelleyBlock (TPraos c) (AlonzoEra c))
-> CardanoLedgerError c
LedgerErrorAlonzo err =
HardForkLedgerErrorFromEra
(OneEraLedgerError (TagAlonzo (WrapLedgerErr err)))
pattern LedgerErrorBabbage ::
LedgerError (ShelleyBlock (Praos c) (BabbageEra c))
-> CardanoLedgerError c
pattern $mLedgerErrorBabbage :: forall {r} {c}.
CardanoLedgerError c
-> (LedgerError (ShelleyBlock (Praos c) (BabbageEra c)) -> r)
-> ((# #) -> r)
-> r
$bLedgerErrorBabbage :: forall c.
LedgerError (ShelleyBlock (Praos c) (BabbageEra c))
-> CardanoLedgerError c
LedgerErrorBabbage err =
HardForkLedgerErrorFromEra
(OneEraLedgerError (TagBabbage (WrapLedgerErr err)))
pattern LedgerErrorConway ::
LedgerError (ShelleyBlock (Praos c) (ConwayEra c))
-> CardanoLedgerError c
pattern $mLedgerErrorConway :: forall {r} {c}.
CardanoLedgerError c
-> (LedgerError (ShelleyBlock (Praos c) (ConwayEra c)) -> r)
-> ((# #) -> r)
-> r
$bLedgerErrorConway :: forall c.
LedgerError (ShelleyBlock (Praos c) (ConwayEra c))
-> CardanoLedgerError c
LedgerErrorConway err =
HardForkLedgerErrorFromEra
(OneEraLedgerError (TagConway (WrapLedgerErr err)))
pattern LedgerErrorWrongEra :: EraMismatch -> CardanoLedgerError c
pattern $mLedgerErrorWrongEra :: forall {r} {c}.
CardanoLedgerError c -> (EraMismatch -> r) -> ((# #) -> r) -> r
LedgerErrorWrongEra eraMismatch <-
HardForkLedgerErrorWrongEra (mkEraMismatch -> eraMismatch)
{-# COMPLETE LedgerErrorByron
, LedgerErrorShelley
, LedgerErrorAllegra
, LedgerErrorMary
, LedgerErrorAlonzo
, LedgerErrorBabbage
, LedgerErrorConway
, LedgerErrorWrongEra
#-}
type c = HardForkEnvelopeErr (CardanoEras c)
pattern OtherHeaderEnvelopeErrorByron
:: OtherHeaderEnvelopeError ByronBlock
-> CardanoOtherHeaderEnvelopeError c
pattern err =
HardForkEnvelopeErrFromEra
(OneEraEnvelopeErr (TagByron (WrapEnvelopeErr err)))
pattern OtherHeaderEnvelopeErrorShelley
:: OtherHeaderEnvelopeError (ShelleyBlock (TPraos c) (ShelleyEra c))
-> CardanoOtherHeaderEnvelopeError c
pattern err =
HardForkEnvelopeErrFromEra (OneEraEnvelopeErr (TagShelley (WrapEnvelopeErr err)))
pattern OtherHeaderEnvelopeErrorAllegra
:: OtherHeaderEnvelopeError (ShelleyBlock (TPraos c) (AllegraEra c))
-> CardanoOtherHeaderEnvelopeError c
pattern err =
HardForkEnvelopeErrFromEra (OneEraEnvelopeErr (TagAllegra (WrapEnvelopeErr err)))
pattern OtherHeaderEnvelopeErrorMary
:: OtherHeaderEnvelopeError (ShelleyBlock (TPraos c) (MaryEra c))
-> CardanoOtherHeaderEnvelopeError c
pattern err =
HardForkEnvelopeErrFromEra (OneEraEnvelopeErr (TagMary (WrapEnvelopeErr err)))
pattern OtherHeaderEnvelopeErrorAlonzo
:: OtherHeaderEnvelopeError (ShelleyBlock (TPraos c) (AlonzoEra c))
-> CardanoOtherHeaderEnvelopeError c
pattern err =
HardForkEnvelopeErrFromEra (OneEraEnvelopeErr (TagAlonzo (WrapEnvelopeErr err)))
pattern OtherHeaderEnvelopeErrorBabbage
:: OtherHeaderEnvelopeError (ShelleyBlock (Praos c) (BabbageEra c))
-> CardanoOtherHeaderEnvelopeError c
pattern err =
HardForkEnvelopeErrFromEra (OneEraEnvelopeErr (TagBabbage (WrapEnvelopeErr err)))
pattern OtherHeaderEnvelopeErrorConway
:: OtherHeaderEnvelopeError (ShelleyBlock (Praos c) (ConwayEra c))
-> CardanoOtherHeaderEnvelopeError c
pattern err =
HardForkEnvelopeErrFromEra (OneEraEnvelopeErr (TagConway (WrapEnvelopeErr err)))
pattern OtherHeaderEnvelopeErrorWrongEra
:: EraMismatch
-> CardanoOtherHeaderEnvelopeError c
pattern eraMismatch <-
HardForkEnvelopeErrWrongEra (mkEraMismatch -> eraMismatch)
{-# COMPLETE OtherHeaderEnvelopeErrorByron
, OtherHeaderEnvelopeErrorShelley
, OtherHeaderEnvelopeErrorAllegra
, OtherHeaderEnvelopeErrorMary
, OtherHeaderEnvelopeErrorAlonzo
, OtherHeaderEnvelopeErrorBabbage
, OtherHeaderEnvelopeErrorConway
, OtherHeaderEnvelopeErrorWrongEra
#-}
type CardanoTipInfo c = OneEraTipInfo (CardanoEras c)
pattern TipInfoByron :: TipInfo ByronBlock -> CardanoTipInfo c
pattern $mTipInfoByron :: forall {r} {c}.
CardanoTipInfo c -> (TipInfo ByronBlock -> r) -> ((# #) -> r) -> r
$bTipInfoByron :: forall c. TipInfo ByronBlock -> CardanoTipInfo c
TipInfoByron ti = OneEraTipInfo (TagByron (WrapTipInfo ti))
pattern TipInfoShelley ::
TipInfo (ShelleyBlock (TPraos c) (ShelleyEra c))
-> CardanoTipInfo c
pattern $mTipInfoShelley :: forall {r} {c}.
CardanoTipInfo c
-> (TipInfo (ShelleyBlock (TPraos c) (ShelleyEra c)) -> r)
-> ((# #) -> r)
-> r
$bTipInfoShelley :: forall c.
TipInfo (ShelleyBlock (TPraos c) (ShelleyEra c))
-> CardanoTipInfo c
TipInfoShelley ti = OneEraTipInfo (TagShelley (WrapTipInfo ti))
pattern TipInfoAllegra ::
TipInfo (ShelleyBlock (TPraos c) (AllegraEra c))
-> CardanoTipInfo c
pattern $mTipInfoAllegra :: forall {r} {c}.
CardanoTipInfo c
-> (TipInfo (ShelleyBlock (TPraos c) (AllegraEra c)) -> r)
-> ((# #) -> r)
-> r
$bTipInfoAllegra :: forall c.
TipInfo (ShelleyBlock (TPraos c) (AllegraEra c))
-> CardanoTipInfo c
TipInfoAllegra ti = OneEraTipInfo (TagAllegra (WrapTipInfo ti))
pattern TipInfoMary ::
TipInfo (ShelleyBlock (TPraos c) (MaryEra c))
-> CardanoTipInfo c
pattern $mTipInfoMary :: forall {r} {c}.
CardanoTipInfo c
-> (TipInfo (ShelleyBlock (TPraos c) (MaryEra c)) -> r)
-> ((# #) -> r)
-> r
$bTipInfoMary :: forall c.
TipInfo (ShelleyBlock (TPraos c) (MaryEra c)) -> CardanoTipInfo c
TipInfoMary ti = OneEraTipInfo (TagMary (WrapTipInfo ti))
pattern TipInfoAlonzo ::
TipInfo (ShelleyBlock (TPraos c) (AlonzoEra c))
-> CardanoTipInfo c
pattern $mTipInfoAlonzo :: forall {r} {c}.
CardanoTipInfo c
-> (TipInfo (ShelleyBlock (TPraos c) (AlonzoEra c)) -> r)
-> ((# #) -> r)
-> r
$bTipInfoAlonzo :: forall c.
TipInfo (ShelleyBlock (TPraos c) (AlonzoEra c)) -> CardanoTipInfo c
TipInfoAlonzo ti = OneEraTipInfo (TagAlonzo (WrapTipInfo ti))
pattern TipInfoBabbage ::
TipInfo (ShelleyBlock (Praos c) (BabbageEra c))
-> CardanoTipInfo c
pattern $mTipInfoBabbage :: forall {r} {c}.
CardanoTipInfo c
-> (TipInfo (ShelleyBlock (Praos c) (BabbageEra c)) -> r)
-> ((# #) -> r)
-> r
$bTipInfoBabbage :: forall c.
TipInfo (ShelleyBlock (Praos c) (BabbageEra c)) -> CardanoTipInfo c
TipInfoBabbage ti = OneEraTipInfo (TagBabbage (WrapTipInfo ti))
pattern TipInfoConway ::
TipInfo (ShelleyBlock (Praos c) (ConwayEra c))
-> CardanoTipInfo c
pattern $mTipInfoConway :: forall {r} {c}.
CardanoTipInfo c
-> (TipInfo (ShelleyBlock (Praos c) (ConwayEra c)) -> r)
-> ((# #) -> r)
-> r
$bTipInfoConway :: forall c.
TipInfo (ShelleyBlock (Praos c) (ConwayEra c)) -> CardanoTipInfo c
TipInfoConway ti = OneEraTipInfo (TagConway (WrapTipInfo ti))
{-# COMPLETE TipInfoByron
, TipInfoShelley
, TipInfoAllegra
, TipInfoMary
, TipInfoAlonzo
, TipInfoBabbage
, TipInfoConway
#-}
type CardanoQuery c = BlockQuery (CardanoBlock c)
pattern QueryIfCurrentByron
:: ()
=> CardanoQueryResult c result ~ a
=> BlockQuery ByronBlock result
-> CardanoQuery c a
pattern QueryIfCurrentShelley
:: ()
=> CardanoQueryResult c result ~ a
=> BlockQuery (ShelleyBlock (TPraos c) (ShelleyEra c)) result
-> CardanoQuery c a
pattern QueryIfCurrentAllegra
:: ()
=> CardanoQueryResult c result ~ a
=> BlockQuery (ShelleyBlock (TPraos c) (AllegraEra c)) result
-> CardanoQuery c a
pattern QueryIfCurrentMary
:: ()
=> CardanoQueryResult c result ~ a
=> BlockQuery (ShelleyBlock (TPraos c) (MaryEra c)) result
-> CardanoQuery c a
pattern QueryIfCurrentAlonzo
:: ()
=> CardanoQueryResult c result ~ a
=> BlockQuery (ShelleyBlock (TPraos c) (AlonzoEra c)) result
-> CardanoQuery c a
pattern QueryIfCurrentBabbage
:: ()
=> CardanoQueryResult c result ~ a
=> BlockQuery (ShelleyBlock (Praos c) (BabbageEra c)) result
-> CardanoQuery c a
pattern QueryIfCurrentConway
:: ()
=> CardanoQueryResult c result ~ a
=> BlockQuery (ShelleyBlock (Praos c) (ConwayEra c)) result
-> CardanoQuery c a
pattern $mQueryIfCurrentByron :: forall {r} {c} {a}.
CardanoQuery c a
-> (forall {result}.
(CardanoQueryResult c result ~ a) =>
BlockQuery ByronBlock result -> r)
-> ((# #) -> r)
-> r
$bQueryIfCurrentByron :: forall c a result.
(CardanoQueryResult c result ~ a) =>
BlockQuery ByronBlock result -> CardanoQuery c a
QueryIfCurrentByron q = QueryIfCurrent (QZ q)
pattern $mQueryIfCurrentShelley :: forall {r} {c} {a}.
CardanoQuery c a
-> (forall {result}.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (TPraos c) (ShelleyEra c)) result -> r)
-> ((# #) -> r)
-> r
$bQueryIfCurrentShelley :: forall c a result.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (TPraos c) (ShelleyEra c)) result
-> CardanoQuery c a
QueryIfCurrentShelley q = QueryIfCurrent (QS (QZ q))
pattern $mQueryIfCurrentAllegra :: forall {r} {c} {a}.
CardanoQuery c a
-> (forall {result}.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (TPraos c) (AllegraEra c)) result -> r)
-> ((# #) -> r)
-> r
$bQueryIfCurrentAllegra :: forall c a result.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (TPraos c) (AllegraEra c)) result
-> CardanoQuery c a
QueryIfCurrentAllegra q = QueryIfCurrent (QS (QS (QZ q)))
pattern $mQueryIfCurrentMary :: forall {r} {c} {a}.
CardanoQuery c a
-> (forall {result}.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (TPraos c) (MaryEra c)) result -> r)
-> ((# #) -> r)
-> r
$bQueryIfCurrentMary :: forall c a result.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (TPraos c) (MaryEra c)) result
-> CardanoQuery c a
QueryIfCurrentMary q = QueryIfCurrent (QS (QS (QS (QZ q))))
pattern $mQueryIfCurrentAlonzo :: forall {r} {c} {a}.
CardanoQuery c a
-> (forall {result}.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (TPraos c) (AlonzoEra c)) result -> r)
-> ((# #) -> r)
-> r
$bQueryIfCurrentAlonzo :: forall c a result.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (TPraos c) (AlonzoEra c)) result
-> CardanoQuery c a
QueryIfCurrentAlonzo q = QueryIfCurrent (QS (QS (QS (QS (QZ q)))))
pattern $mQueryIfCurrentBabbage :: forall {r} {c} {a}.
CardanoQuery c a
-> (forall {result}.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (Praos c) (BabbageEra c)) result -> r)
-> ((# #) -> r)
-> r
$bQueryIfCurrentBabbage :: forall c a result.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (Praos c) (BabbageEra c)) result
-> CardanoQuery c a
QueryIfCurrentBabbage q = QueryIfCurrent (QS (QS (QS (QS (QS (QZ q))))))
pattern $mQueryIfCurrentConway :: forall {r} {c} {a}.
CardanoQuery c a
-> (forall {result}.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (Praos c) (ConwayEra c)) result -> r)
-> ((# #) -> r)
-> r
$bQueryIfCurrentConway :: forall c a result.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (Praos c) (ConwayEra c)) result
-> CardanoQuery c a
QueryIfCurrentConway q = QueryIfCurrent (QS (QS (QS (QS (QS (QS (QZ q)))))))
pattern QueryAnytimeByron
:: QueryAnytime result
-> CardanoQuery c result
pattern $mQueryAnytimeByron :: forall {r} {result} {c}.
CardanoQuery c result
-> (QueryAnytime result -> r) -> ((# #) -> r) -> r
$bQueryAnytimeByron :: forall result c. QueryAnytime result -> CardanoQuery c result
QueryAnytimeByron q = QueryAnytime q (EraIndex (TagByron (K ())))
pattern QueryAnytimeShelley
:: QueryAnytime result
-> CardanoQuery c result
pattern $mQueryAnytimeShelley :: forall {r} {result} {c}.
CardanoQuery c result
-> (QueryAnytime result -> r) -> ((# #) -> r) -> r
$bQueryAnytimeShelley :: forall result c. QueryAnytime result -> CardanoQuery c result
QueryAnytimeShelley q = QueryAnytime q (EraIndex (TagShelley (K ())))
pattern QueryAnytimeAllegra
:: QueryAnytime result
-> CardanoQuery c result
pattern $mQueryAnytimeAllegra :: forall {r} {result} {c}.
CardanoQuery c result
-> (QueryAnytime result -> r) -> ((# #) -> r) -> r
$bQueryAnytimeAllegra :: forall result c. QueryAnytime result -> CardanoQuery c result
QueryAnytimeAllegra q = QueryAnytime q (EraIndex (TagAllegra (K ())))
pattern QueryAnytimeMary
:: QueryAnytime result
-> CardanoQuery c result
pattern $mQueryAnytimeMary :: forall {r} {result} {c}.
CardanoQuery c result
-> (QueryAnytime result -> r) -> ((# #) -> r) -> r
$bQueryAnytimeMary :: forall result c. QueryAnytime result -> CardanoQuery c result
QueryAnytimeMary q = QueryAnytime q (EraIndex (TagMary (K ())))
pattern QueryAnytimeAlonzo
:: QueryAnytime result
-> CardanoQuery c result
pattern $mQueryAnytimeAlonzo :: forall {r} {result} {c}.
CardanoQuery c result
-> (QueryAnytime result -> r) -> ((# #) -> r) -> r
$bQueryAnytimeAlonzo :: forall result c. QueryAnytime result -> CardanoQuery c result
QueryAnytimeAlonzo q = QueryAnytime q (EraIndex (TagAlonzo (K ())))
pattern QueryAnytimeBabbage
:: QueryAnytime result
-> CardanoQuery c result
pattern $mQueryAnytimeBabbage :: forall {r} {result} {c}.
CardanoQuery c result
-> (QueryAnytime result -> r) -> ((# #) -> r) -> r
$bQueryAnytimeBabbage :: forall result c. QueryAnytime result -> CardanoQuery c result
QueryAnytimeBabbage q = QueryAnytime q (EraIndex (TagBabbage (K ())))
pattern QueryAnytimeConway
:: QueryAnytime result
-> CardanoQuery c result
pattern $mQueryAnytimeConway :: forall {r} {result} {c}.
CardanoQuery c result
-> (QueryAnytime result -> r) -> ((# #) -> r) -> r
$bQueryAnytimeConway :: forall result c. QueryAnytime result -> CardanoQuery c result
QueryAnytimeConway q = QueryAnytime q (EraIndex (TagConway (K ())))
{-# COMPLETE QueryIfCurrentByron
, QueryIfCurrentShelley
, QueryIfCurrentAllegra
, QueryIfCurrentMary
, QueryIfCurrentAlonzo
, QueryIfCurrentBabbage
, QueryAnytimeByron
, QueryAnytimeShelley
, QueryAnytimeAllegra
, QueryAnytimeMary
, QueryAnytimeAlonzo
, QueryAnytimeBabbage
, QueryAnytimeConway
, QueryHardFork
#-}
type CardanoQueryResult c = HardForkQueryResult (CardanoEras c)
pattern QueryResultSuccess :: result -> CardanoQueryResult c result
pattern $mQueryResultSuccess :: forall {r} {result} {c}.
CardanoQueryResult c result -> (result -> r) -> ((# #) -> r) -> r
$bQueryResultSuccess :: forall result c. result -> CardanoQueryResult c result
QueryResultSuccess result = Right result
pattern QueryResultEraMismatch :: EraMismatch -> CardanoQueryResult c result
pattern $mQueryResultEraMismatch :: forall {r} {c} {result}.
CardanoQueryResult c result
-> (EraMismatch -> r) -> ((# #) -> r) -> r
QueryResultEraMismatch eraMismatch <- Left (mkEraMismatch -> eraMismatch)
{-# COMPLETE QueryResultSuccess, QueryResultEraMismatch #-}
type CardanoCodecConfig c = CodecConfig (CardanoBlock c)
pattern CardanoCodecConfig
:: CodecConfig ByronBlock
-> CodecConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> CodecConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> CodecConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> CardanoCodecConfig c
pattern $mCardanoCodecConfig :: forall {r} {c}.
CardanoCodecConfig c
-> (CodecConfig ByronBlock
-> CodecConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> CodecConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> CodecConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> r)
-> ((# #) -> r)
-> r
$bCardanoCodecConfig :: forall c.
CodecConfig ByronBlock
-> CodecConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> CodecConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> CodecConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> CodecConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> CardanoCodecConfig c
CardanoCodecConfig cfgByron cfgShelley cfgAllegra cfgMary cfgAlonzo cfgBabbage cfgConway =
HardForkCodecConfig {
hardForkCodecConfigPerEra = PerEraCodecConfig
( cfgByron
:* cfgShelley
:* cfgAllegra
:* cfgMary
:* cfgAlonzo
:* cfgBabbage
:* cfgConway
:* Nil
)
}
{-# COMPLETE CardanoCodecConfig #-}
type CardanoBlockConfig c = BlockConfig (CardanoBlock c)
pattern CardanoBlockConfig
:: BlockConfig ByronBlock
-> BlockConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> BlockConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> BlockConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> BlockConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> BlockConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> BlockConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> CardanoBlockConfig c
pattern $mCardanoBlockConfig :: forall {r} {c}.
CardanoBlockConfig c
-> (BlockConfig ByronBlock
-> BlockConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> BlockConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> BlockConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> BlockConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> BlockConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> BlockConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> r)
-> ((# #) -> r)
-> r
$bCardanoBlockConfig :: forall c.
BlockConfig ByronBlock
-> BlockConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> BlockConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> BlockConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> BlockConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> BlockConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> BlockConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> CardanoBlockConfig c
CardanoBlockConfig cfgByron cfgShelley cfgAllegra cfgMary cfgAlonzo cfgBabbage cfgConway =
HardForkBlockConfig {
hardForkBlockConfigPerEra = PerEraBlockConfig
( cfgByron
:* cfgShelley
:* cfgAllegra
:* cfgMary
:* cfgAlonzo
:* cfgBabbage
:* cfgConway
:* Nil
)
}
{-# COMPLETE CardanoBlockConfig #-}
type CardanoStorageConfig c = StorageConfig (CardanoBlock c)
pattern CardanoStorageConfig
:: StorageConfig ByronBlock
-> StorageConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> StorageConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> StorageConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> StorageConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> StorageConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> StorageConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> CardanoStorageConfig c
pattern $mCardanoStorageConfig :: forall {r} {c}.
CardanoStorageConfig c
-> (StorageConfig ByronBlock
-> StorageConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> StorageConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> StorageConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> StorageConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> StorageConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> StorageConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> r)
-> ((# #) -> r)
-> r
$bCardanoStorageConfig :: forall c.
StorageConfig ByronBlock
-> StorageConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> StorageConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> StorageConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> StorageConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> StorageConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> StorageConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> CardanoStorageConfig c
CardanoStorageConfig cfgByron cfgShelley cfgAllegra cfgMary cfgAlonzo cfgBabbage cfgConway =
HardForkStorageConfig {
hardForkStorageConfigPerEra = PerEraStorageConfig
( cfgByron
:* cfgShelley
:* cfgAllegra
:* cfgMary
:* cfgAlonzo
:* cfgBabbage
:* cfgConway
:* Nil
)
}
{-# COMPLETE CardanoStorageConfig #-}
type CardanoConsensusConfig c =
ConsensusConfig (HardForkProtocol (CardanoEras c))
pattern CardanoConsensusConfig
:: PartialConsensusConfig (BlockProtocol ByronBlock)
-> PartialConsensusConfig (BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> PartialConsensusConfig (BlockProtocol (ShelleyBlock (TPraos c) (AllegraEra c)))
-> PartialConsensusConfig (BlockProtocol (ShelleyBlock (TPraos c) (MaryEra c)))
-> PartialConsensusConfig (BlockProtocol (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> PartialConsensusConfig (BlockProtocol (ShelleyBlock (Praos c) (BabbageEra c)))
-> PartialConsensusConfig (BlockProtocol (ShelleyBlock (Praos c) (ConwayEra c)))
-> CardanoConsensusConfig c
pattern $mCardanoConsensusConfig :: forall {r} {c}.
CardanoConsensusConfig c
-> (PartialConsensusConfig (BlockProtocol ByronBlock)
-> PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) (AllegraEra c)))
-> PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) (MaryEra c)))
-> PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> PartialConsensusConfig
(BlockProtocol (ShelleyBlock (Praos c) (BabbageEra c)))
-> PartialConsensusConfig
(BlockProtocol (ShelleyBlock (Praos c) (ConwayEra c)))
-> r)
-> ((# #) -> r)
-> r
CardanoConsensusConfig cfgByron cfgShelley cfgAllegra cfgMary cfgAlonzo cfgBabbage cfgConway <-
HardForkConsensusConfig {
hardForkConsensusConfigPerEra = PerEraConsensusConfig
( WrapPartialConsensusConfig cfgByron
:* WrapPartialConsensusConfig cfgShelley
:* WrapPartialConsensusConfig cfgAllegra
:* WrapPartialConsensusConfig cfgMary
:* WrapPartialConsensusConfig cfgAlonzo
:* WrapPartialConsensusConfig cfgBabbage
:* WrapPartialConsensusConfig cfgConway
:* Nil
)
}
{-# COMPLETE CardanoConsensusConfig #-}
type CardanoLedgerConfig c = HardForkLedgerConfig (CardanoEras c)
pattern CardanoLedgerConfig
:: PartialLedgerConfig ByronBlock
-> PartialLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> PartialLedgerConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> PartialLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> PartialLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> PartialLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> PartialLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> CardanoLedgerConfig c
pattern $mCardanoLedgerConfig :: forall {r} {c}.
CardanoLedgerConfig c
-> (PartialLedgerConfig ByronBlock
-> PartialLedgerConfig (ShelleyBlock (TPraos c) (ShelleyEra c))
-> PartialLedgerConfig (ShelleyBlock (TPraos c) (AllegraEra c))
-> PartialLedgerConfig (ShelleyBlock (TPraos c) (MaryEra c))
-> PartialLedgerConfig (ShelleyBlock (TPraos c) (AlonzoEra c))
-> PartialLedgerConfig (ShelleyBlock (Praos c) (BabbageEra c))
-> PartialLedgerConfig (ShelleyBlock (Praos c) (ConwayEra c))
-> r)
-> ((# #) -> r)
-> r
CardanoLedgerConfig cfgByron cfgShelley cfgAllegra cfgMary cfgAlonzo cfgBabbage cfgConway <-
HardForkLedgerConfig {
hardForkLedgerConfigPerEra = PerEraLedgerConfig
( WrapPartialLedgerConfig cfgByron
:* WrapPartialLedgerConfig cfgShelley
:* WrapPartialLedgerConfig cfgAllegra
:* WrapPartialLedgerConfig cfgMary
:* WrapPartialLedgerConfig cfgAlonzo
:* WrapPartialLedgerConfig cfgBabbage
:* WrapPartialLedgerConfig cfgConway
:* Nil
)
}
{-# COMPLETE CardanoLedgerConfig #-}
type CardanoLedgerState c = LedgerState (CardanoBlock c)
pattern LedgerStateByron
:: LedgerState ByronBlock
-> CardanoLedgerState c
pattern $mLedgerStateByron :: forall {r} {c}.
CardanoLedgerState c
-> (LedgerState ByronBlock -> r) -> ((# #) -> r) -> r
LedgerStateByron st <-
HardForkLedgerState
(State.HardForkState
(TeleByron (State.Current { currentState = st })))
pattern LedgerStateShelley
:: LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c))
-> CardanoLedgerState c
pattern $mLedgerStateShelley :: forall {r} {c}.
CardanoLedgerState c
-> (LedgerState (ShelleyBlock (TPraos c) (ShelleyEra c)) -> r)
-> ((# #) -> r)
-> r
LedgerStateShelley st <-
HardForkLedgerState
(State.HardForkState
(TeleShelley _ (State.Current { currentState = st })))
pattern LedgerStateAllegra
:: LedgerState (ShelleyBlock (TPraos c) (AllegraEra c))
-> CardanoLedgerState c
pattern $mLedgerStateAllegra :: forall {r} {c}.
CardanoLedgerState c
-> (LedgerState (ShelleyBlock (TPraos c) (AllegraEra c)) -> r)
-> ((# #) -> r)
-> r
LedgerStateAllegra st <-
HardForkLedgerState
(State.HardForkState
(TeleAllegra _ _ (State.Current { currentState = st })))
pattern LedgerStateMary
:: LedgerState (ShelleyBlock (TPraos c) (MaryEra c))
-> CardanoLedgerState c
pattern $mLedgerStateMary :: forall {r} {c}.
CardanoLedgerState c
-> (LedgerState (ShelleyBlock (TPraos c) (MaryEra c)) -> r)
-> ((# #) -> r)
-> r
LedgerStateMary st <-
HardForkLedgerState
(State.HardForkState
(TeleMary _ _ _ (State.Current { currentState = st })))
pattern LedgerStateAlonzo
:: LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c))
-> CardanoLedgerState c
pattern $mLedgerStateAlonzo :: forall {r} {c}.
CardanoLedgerState c
-> (LedgerState (ShelleyBlock (TPraos c) (AlonzoEra c)) -> r)
-> ((# #) -> r)
-> r
LedgerStateAlonzo st <-
HardForkLedgerState
(State.HardForkState
(TeleAlonzo _ _ _ _ (State.Current { currentState = st })))
pattern LedgerStateBabbage
:: LedgerState (ShelleyBlock (Praos c) (BabbageEra c))
-> CardanoLedgerState c
pattern $mLedgerStateBabbage :: forall {r} {c}.
CardanoLedgerState c
-> (LedgerState (ShelleyBlock (Praos c) (BabbageEra c)) -> r)
-> ((# #) -> r)
-> r
LedgerStateBabbage st <-
HardForkLedgerState
(State.HardForkState
(TeleBabbage _ _ _ _ _ (State.Current { currentState = st })))
pattern LedgerStateConway
:: LedgerState (ShelleyBlock (Praos c) (ConwayEra c))
-> CardanoLedgerState c
pattern $mLedgerStateConway :: forall {r} {c}.
CardanoLedgerState c
-> (LedgerState (ShelleyBlock (Praos c) (ConwayEra c)) -> r)
-> ((# #) -> r)
-> r
LedgerStateConway st <-
HardForkLedgerState
(State.HardForkState
(TeleConway _ _ _ _ _ _ (State.Current { currentState = st })))
{-# COMPLETE LedgerStateByron
, LedgerStateShelley
, LedgerStateAllegra
, LedgerStateMary
, LedgerStateAlonzo
, LedgerStateBabbage
, LedgerStateConway
#-}
type CardanoChainDepState c = HardForkChainDepState (CardanoEras c)
pattern ChainDepStateByron
:: ChainDepState (BlockProtocol ByronBlock)
-> CardanoChainDepState c
pattern $mChainDepStateByron :: forall {r} {c}.
CardanoChainDepState c
-> (ChainDepState (BlockProtocol ByronBlock) -> r)
-> ((# #) -> r)
-> r
ChainDepStateByron st <-
State.HardForkState
(TeleByron (State.Current { currentState = WrapChainDepState st }))
pattern ChainDepStateShelley
:: ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> CardanoChainDepState c
pattern $mChainDepStateShelley :: forall {r} {c}.
CardanoChainDepState c
-> (ChainDepState
(BlockProtocol (ShelleyBlock (TPraos c) (ShelleyEra c)))
-> r)
-> ((# #) -> r)
-> r
ChainDepStateShelley st <-
State.HardForkState
(TeleShelley _ (State.Current { currentState = WrapChainDepState st }))
pattern ChainDepStateAllegra
:: ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (AllegraEra c)))
-> CardanoChainDepState c
pattern $mChainDepStateAllegra :: forall {r} {c}.
CardanoChainDepState c
-> (ChainDepState
(BlockProtocol (ShelleyBlock (TPraos c) (AllegraEra c)))
-> r)
-> ((# #) -> r)
-> r
ChainDepStateAllegra st <-
State.HardForkState
(TeleAllegra _ _ (State.Current { currentState = WrapChainDepState st }))
pattern ChainDepStateMary
:: ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (MaryEra c)))
-> CardanoChainDepState c
pattern $mChainDepStateMary :: forall {r} {c}.
CardanoChainDepState c
-> (ChainDepState
(BlockProtocol (ShelleyBlock (TPraos c) (MaryEra c)))
-> r)
-> ((# #) -> r)
-> r
ChainDepStateMary st <-
State.HardForkState
(TeleMary _ _ _ (State.Current { currentState = WrapChainDepState st }))
pattern ChainDepStateAlonzo
:: ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> CardanoChainDepState c
pattern $mChainDepStateAlonzo :: forall {r} {c}.
CardanoChainDepState c
-> (ChainDepState
(BlockProtocol (ShelleyBlock (TPraos c) (AlonzoEra c)))
-> r)
-> ((# #) -> r)
-> r
ChainDepStateAlonzo st <-
State.HardForkState
(TeleAlonzo _ _ _ _ (State.Current { currentState = WrapChainDepState st }))
pattern ChainDepStateBabbage
:: ChainDepState (BlockProtocol (ShelleyBlock (Praos c) (BabbageEra c)))
-> CardanoChainDepState c
pattern $mChainDepStateBabbage :: forall {r} {c}.
CardanoChainDepState c
-> (ChainDepState
(BlockProtocol (ShelleyBlock (Praos c) (BabbageEra c)))
-> r)
-> ((# #) -> r)
-> r
ChainDepStateBabbage st <-
State.HardForkState
(TeleBabbage _ _ _ _ _ (State.Current { currentState = WrapChainDepState st }))
pattern ChainDepStateConway
:: ChainDepState (BlockProtocol (ShelleyBlock (Praos c) (ConwayEra c)))
-> CardanoChainDepState c
pattern $mChainDepStateConway :: forall {r} {c}.
CardanoChainDepState c
-> (ChainDepState
(BlockProtocol (ShelleyBlock (Praos c) (ConwayEra c)))
-> r)
-> ((# #) -> r)
-> r
ChainDepStateConway st <-
State.HardForkState
(TeleConway _ _ _ _ _ _ (State.Current { currentState = WrapChainDepState st }))
{-# COMPLETE ChainDepStateByron
, ChainDepStateShelley
, ChainDepStateAllegra
, ChainDepStateMary
, ChainDepStateAlonzo
, ChainDepStateBabbage
, ChainDepStateConway
#-}