{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DisambiguateRecordFields #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE TypeFamilies #-}
{-# 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.Functors
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.Query
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
, ShelleyBlock (TPraos c) AllegraEra
, ShelleyBlock (TPraos c) MaryEra
, ShelleyBlock (TPraos c) AlonzoEra
, ShelleyBlock (Praos c) BabbageEra
, ShelleyBlock (Praos c) ConwayEra
]
type ShelleyBasedLedgerEras :: Type -> [Type]
type ShelleyBasedLedgerEras c =
'[ ShelleyEra
, AllegraEra
, MaryEra
, AlonzoEra
, BabbageEra
, ConwayEra
]
pattern TagByron :: f ByronBlock -> NS f (CardanoEras c)
pattern TagShelley :: f (ShelleyBlock (TPraos c) ShelleyEra) -> NS f (CardanoEras c)
pattern TagAllegra :: f (ShelleyBlock (TPraos c) AllegraEra) -> NS f (CardanoEras c)
pattern TagMary :: f (ShelleyBlock (TPraos c) MaryEra) -> NS f (CardanoEras c)
pattern TagAlonzo :: f (ShelleyBlock (TPraos c) AlonzoEra) -> NS f (CardanoEras c)
pattern TagBabbage :: f (ShelleyBlock (Praos c) BabbageEra) -> NS f (CardanoEras c)
pattern TagConway :: f (ShelleyBlock (Praos c) ConwayEra) -> 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) -> r)
-> ((# #) -> r)
-> r
$bTagShelley :: forall (f :: * -> *) c.
f (ShelleyBlock (TPraos c) ShelleyEra) -> NS f (CardanoEras c)
TagShelley x = S (Z x)
pattern $mTagAllegra :: forall {r} {f :: * -> *} {c}.
NS f (CardanoEras c)
-> (f (ShelleyBlock (TPraos c) AllegraEra) -> r)
-> ((# #) -> r)
-> r
$bTagAllegra :: forall (f :: * -> *) c.
f (ShelleyBlock (TPraos c) AllegraEra) -> 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) -> r) -> ((# #) -> r) -> r
$bTagMary :: forall (f :: * -> *) c.
f (ShelleyBlock (TPraos c) MaryEra) -> 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) -> r)
-> ((# #) -> r)
-> r
$bTagAlonzo :: forall (f :: * -> *) c.
f (ShelleyBlock (TPraos c) AlonzoEra) -> 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) -> r)
-> ((# #) -> r)
-> r
$bTagBabbage :: forall (f :: * -> *) c.
f (ShelleyBlock (Praos c) BabbageEra) -> 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) -> r) -> ((# #) -> r) -> r
$bTagConway :: forall (f :: * -> *) c.
f (ShelleyBlock (Praos c) ConwayEra) -> 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) ->
Telescope g f (CardanoEras c)
pattern TeleAllegra ::
g ByronBlock ->
g (ShelleyBlock (TPraos c) ShelleyEra) ->
f (ShelleyBlock (TPraos c) AllegraEra) ->
Telescope g f (CardanoEras c)
pattern TeleMary ::
g ByronBlock ->
g (ShelleyBlock (TPraos c) ShelleyEra) ->
g (ShelleyBlock (TPraos c) AllegraEra) ->
f (ShelleyBlock (TPraos c) MaryEra) ->
Telescope g f (CardanoEras c)
pattern TeleAlonzo ::
g ByronBlock ->
g (ShelleyBlock (TPraos c) ShelleyEra) ->
g (ShelleyBlock (TPraos c) AllegraEra) ->
g (ShelleyBlock (TPraos c) MaryEra) ->
f (ShelleyBlock (TPraos c) AlonzoEra) ->
Telescope g f (CardanoEras c)
pattern TeleBabbage ::
g ByronBlock ->
g (ShelleyBlock (TPraos c) ShelleyEra) ->
g (ShelleyBlock (TPraos c) AllegraEra) ->
g (ShelleyBlock (TPraos c) MaryEra) ->
g (ShelleyBlock (TPraos c) AlonzoEra) ->
f (ShelleyBlock (Praos c) BabbageEra) ->
Telescope g f (CardanoEras c)
pattern TeleConway ::
g ByronBlock ->
g (ShelleyBlock (TPraos c) ShelleyEra) ->
g (ShelleyBlock (TPraos c) AllegraEra) ->
g (ShelleyBlock (TPraos c) MaryEra) ->
g (ShelleyBlock (TPraos c) AlonzoEra) ->
g (ShelleyBlock (Praos c) BabbageEra) ->
f (ShelleyBlock (Praos c) ConwayEra) ->
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) -> r)
-> ((# #) -> r)
-> r
$bTeleShelley :: forall (g :: * -> *) (f :: * -> *) c.
g ByronBlock
-> f (ShelleyBlock (TPraos c) ShelleyEra)
-> 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)
-> f (ShelleyBlock (TPraos c) AllegraEra)
-> r)
-> ((# #) -> r)
-> r
$bTeleAllegra :: forall (g :: * -> *) c (f :: * -> *).
g ByronBlock
-> g (ShelleyBlock (TPraos c) ShelleyEra)
-> f (ShelleyBlock (TPraos c) AllegraEra)
-> 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)
-> g (ShelleyBlock (TPraos c) AllegraEra)
-> f (ShelleyBlock (TPraos c) MaryEra)
-> r)
-> ((# #) -> r)
-> r
$bTeleMary :: forall (g :: * -> *) c (f :: * -> *).
g ByronBlock
-> g (ShelleyBlock (TPraos c) ShelleyEra)
-> g (ShelleyBlock (TPraos c) AllegraEra)
-> f (ShelleyBlock (TPraos c) MaryEra)
-> 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)
-> g (ShelleyBlock (TPraos c) AllegraEra)
-> g (ShelleyBlock (TPraos c) MaryEra)
-> f (ShelleyBlock (TPraos c) AlonzoEra)
-> r)
-> ((# #) -> r)
-> r
$bTeleAlonzo :: forall (g :: * -> *) c (f :: * -> *).
g ByronBlock
-> g (ShelleyBlock (TPraos c) ShelleyEra)
-> g (ShelleyBlock (TPraos c) AllegraEra)
-> g (ShelleyBlock (TPraos c) MaryEra)
-> f (ShelleyBlock (TPraos c) AlonzoEra)
-> 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)
-> g (ShelleyBlock (TPraos c) AllegraEra)
-> g (ShelleyBlock (TPraos c) MaryEra)
-> g (ShelleyBlock (TPraos c) AlonzoEra)
-> f (ShelleyBlock (Praos c) BabbageEra)
-> r)
-> ((# #) -> r)
-> r
$bTeleBabbage :: forall (g :: * -> *) c (f :: * -> *).
g ByronBlock
-> g (ShelleyBlock (TPraos c) ShelleyEra)
-> g (ShelleyBlock (TPraos c) AllegraEra)
-> g (ShelleyBlock (TPraos c) MaryEra)
-> g (ShelleyBlock (TPraos c) AlonzoEra)
-> f (ShelleyBlock (Praos c) BabbageEra)
-> 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)
-> g (ShelleyBlock (TPraos c) AllegraEra)
-> g (ShelleyBlock (TPraos c) MaryEra)
-> g (ShelleyBlock (TPraos c) AlonzoEra)
-> g (ShelleyBlock (Praos c) BabbageEra)
-> f (ShelleyBlock (Praos c) ConwayEra)
-> r)
-> ((# #) -> r)
-> r
$bTeleConway :: forall (g :: * -> *) c (f :: * -> *).
g ByronBlock
-> g (ShelleyBlock (TPraos c) ShelleyEra)
-> g (ShelleyBlock (TPraos c) AllegraEra)
-> g (ShelleyBlock (TPraos c) MaryEra)
-> g (ShelleyBlock (TPraos c) AlonzoEra)
-> g (ShelleyBlock (Praos c) BabbageEra)
-> f (ShelleyBlock (Praos c) ConwayEra)
-> 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 -> CardanoBlock c
pattern $mBlockShelley :: forall {r} {c}.
CardanoBlock c
-> (ShelleyBlock (TPraos c) ShelleyEra -> r) -> ((# #) -> r) -> r
$bBlockShelley :: forall c. ShelleyBlock (TPraos c) ShelleyEra -> CardanoBlock c
BlockShelley b = HardForkBlock (OneEraBlock (TagShelley (I b)))
pattern BlockAllegra :: ShelleyBlock (TPraos c) AllegraEra -> CardanoBlock c
pattern $mBlockAllegra :: forall {r} {c}.
CardanoBlock c
-> (ShelleyBlock (TPraos c) AllegraEra -> r) -> ((# #) -> r) -> r
$bBlockAllegra :: forall c. ShelleyBlock (TPraos c) AllegraEra -> CardanoBlock c
BlockAllegra b = HardForkBlock (OneEraBlock (TagAllegra (I b)))
pattern BlockMary :: ShelleyBlock (TPraos c) MaryEra -> CardanoBlock c
pattern $mBlockMary :: forall {r} {c}.
CardanoBlock c
-> (ShelleyBlock (TPraos c) MaryEra -> r) -> ((# #) -> r) -> r
$bBlockMary :: forall c. ShelleyBlock (TPraos c) MaryEra -> CardanoBlock c
BlockMary b = HardForkBlock (OneEraBlock (TagMary (I b)))
pattern BlockAlonzo :: ShelleyBlock (TPraos c) AlonzoEra -> CardanoBlock c
pattern $mBlockAlonzo :: forall {r} {c}.
CardanoBlock c
-> (ShelleyBlock (TPraos c) AlonzoEra -> r) -> ((# #) -> r) -> r
$bBlockAlonzo :: forall c. ShelleyBlock (TPraos c) AlonzoEra -> CardanoBlock c
BlockAlonzo b = HardForkBlock (OneEraBlock (TagAlonzo (I b)))
pattern BlockBabbage :: ShelleyBlock (Praos c) BabbageEra -> CardanoBlock c
pattern $mBlockBabbage :: forall {r} {c}.
CardanoBlock c
-> (ShelleyBlock (Praos c) BabbageEra -> r) -> ((# #) -> r) -> r
$bBlockBabbage :: forall c. ShelleyBlock (Praos c) BabbageEra -> CardanoBlock c
BlockBabbage b = HardForkBlock (OneEraBlock (TagBabbage (I b)))
pattern BlockConway :: ShelleyBlock (Praos c) ConwayEra -> CardanoBlock c
pattern $mBlockConway :: forall {r} {c}.
CardanoBlock c
-> (ShelleyBlock (Praos c) ConwayEra -> r) -> ((# #) -> r) -> r
$bBlockConway :: forall c. ShelleyBlock (Praos c) ConwayEra -> 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) ->
CardanoHeader c
pattern h = HardForkHeader (OneEraHeader (TagShelley h))
pattern HeaderAllegra ::
Header (ShelleyBlock (TPraos c) AllegraEra) ->
CardanoHeader c
pattern h = HardForkHeader (OneEraHeader (TagAllegra h))
pattern HeaderMary ::
Header (ShelleyBlock (TPraos c) MaryEra) ->
CardanoHeader c
pattern h = HardForkHeader (OneEraHeader (TagMary h))
pattern HeaderAlonzo ::
Header (ShelleyBlock (TPraos c) AlonzoEra) ->
CardanoHeader c
pattern h = HardForkHeader (OneEraHeader (TagAlonzo h))
pattern HeaderBabbage ::
Header (ShelleyBlock (Praos c) BabbageEra) ->
CardanoHeader c
pattern h = HardForkHeader (OneEraHeader (TagBabbage h))
pattern HeaderConway ::
Header (ShelleyBlock (Praos c) ConwayEra) ->
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) -> CardanoGenTx c
pattern $mGenTxShelley :: forall {r} {c}.
CardanoGenTx c
-> (GenTx (ShelleyBlock (TPraos c) ShelleyEra) -> r)
-> ((# #) -> r)
-> r
$bGenTxShelley :: forall c.
GenTx (ShelleyBlock (TPraos c) ShelleyEra) -> CardanoGenTx c
GenTxShelley tx = HardForkGenTx (OneEraGenTx (TagShelley tx))
pattern GenTxAllegra :: GenTx (ShelleyBlock (TPraos c) AllegraEra) -> CardanoGenTx c
pattern $mGenTxAllegra :: forall {r} {c}.
CardanoGenTx c
-> (GenTx (ShelleyBlock (TPraos c) AllegraEra) -> r)
-> ((# #) -> r)
-> r
$bGenTxAllegra :: forall c.
GenTx (ShelleyBlock (TPraos c) AllegraEra) -> CardanoGenTx c
GenTxAllegra tx = HardForkGenTx (OneEraGenTx (TagAllegra tx))
pattern GenTxMary :: GenTx (ShelleyBlock (TPraos c) MaryEra) -> CardanoGenTx c
pattern $mGenTxMary :: forall {r} {c}.
CardanoGenTx c
-> (GenTx (ShelleyBlock (TPraos c) MaryEra) -> r)
-> ((# #) -> r)
-> r
$bGenTxMary :: forall c. GenTx (ShelleyBlock (TPraos c) MaryEra) -> CardanoGenTx c
GenTxMary tx = HardForkGenTx (OneEraGenTx (TagMary tx))
pattern GenTxAlonzo :: GenTx (ShelleyBlock (TPraos c) AlonzoEra) -> CardanoGenTx c
pattern $mGenTxAlonzo :: forall {r} {c}.
CardanoGenTx c
-> (GenTx (ShelleyBlock (TPraos c) AlonzoEra) -> r)
-> ((# #) -> r)
-> r
$bGenTxAlonzo :: forall c.
GenTx (ShelleyBlock (TPraos c) AlonzoEra) -> CardanoGenTx c
GenTxAlonzo tx = HardForkGenTx (OneEraGenTx (TagAlonzo tx))
pattern GenTxBabbage :: GenTx (ShelleyBlock (Praos c) BabbageEra) -> CardanoGenTx c
pattern $mGenTxBabbage :: forall {r} {c}.
CardanoGenTx c
-> (GenTx (ShelleyBlock (Praos c) BabbageEra) -> r)
-> ((# #) -> r)
-> r
$bGenTxBabbage :: forall c.
GenTx (ShelleyBlock (Praos c) BabbageEra) -> CardanoGenTx c
GenTxBabbage tx = HardForkGenTx (OneEraGenTx (TagBabbage tx))
pattern GenTxConway :: GenTx (ShelleyBlock (Praos c) ConwayEra) -> CardanoGenTx c
pattern $mGenTxConway :: forall {r} {c}.
CardanoGenTx c
-> (GenTx (ShelleyBlock (Praos c) ConwayEra) -> r)
-> ((# #) -> r)
-> r
$bGenTxConway :: forall c.
GenTx (ShelleyBlock (Praos c) ConwayEra) -> 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) ->
CardanoGenTxId c
pattern $mGenTxIdShelley :: forall {r} {c}.
CardanoGenTxId c
-> (GenTxId (ShelleyBlock (TPraos c) ShelleyEra) -> r)
-> ((# #) -> r)
-> r
$bGenTxIdShelley :: forall c.
GenTxId (ShelleyBlock (TPraos c) ShelleyEra) -> CardanoGenTxId c
GenTxIdShelley txid =
HardForkGenTxId (OneEraGenTxId (TagShelley (WrapGenTxId txid)))
pattern GenTxIdAllegra ::
GenTxId (ShelleyBlock (TPraos c) AllegraEra) ->
CardanoGenTxId c
pattern $mGenTxIdAllegra :: forall {r} {c}.
CardanoGenTxId c
-> (GenTxId (ShelleyBlock (TPraos c) AllegraEra) -> r)
-> ((# #) -> r)
-> r
$bGenTxIdAllegra :: forall c.
GenTxId (ShelleyBlock (TPraos c) AllegraEra) -> CardanoGenTxId c
GenTxIdAllegra txid =
HardForkGenTxId (OneEraGenTxId (TagAllegra (WrapGenTxId txid)))
pattern GenTxIdMary ::
GenTxId (ShelleyBlock (TPraos c) MaryEra) ->
CardanoGenTxId c
pattern $mGenTxIdMary :: forall {r} {c}.
CardanoGenTxId c
-> (GenTxId (ShelleyBlock (TPraos c) MaryEra) -> r)
-> ((# #) -> r)
-> r
$bGenTxIdMary :: forall c.
GenTxId (ShelleyBlock (TPraos c) MaryEra) -> CardanoGenTxId c
GenTxIdMary txid =
HardForkGenTxId (OneEraGenTxId (TagMary (WrapGenTxId txid)))
pattern GenTxIdAlonzo ::
GenTxId (ShelleyBlock (TPraos c) AlonzoEra) ->
CardanoGenTxId c
pattern $mGenTxIdAlonzo :: forall {r} {c}.
CardanoGenTxId c
-> (GenTxId (ShelleyBlock (TPraos c) AlonzoEra) -> r)
-> ((# #) -> r)
-> r
$bGenTxIdAlonzo :: forall c.
GenTxId (ShelleyBlock (TPraos c) AlonzoEra) -> CardanoGenTxId c
GenTxIdAlonzo txid =
HardForkGenTxId (OneEraGenTxId (TagAlonzo (WrapGenTxId txid)))
pattern GenTxIdBabbage ::
GenTxId (ShelleyBlock (Praos c) BabbageEra) ->
CardanoGenTxId c
pattern $mGenTxIdBabbage :: forall {r} {c}.
CardanoGenTxId c
-> (GenTxId (ShelleyBlock (Praos c) BabbageEra) -> r)
-> ((# #) -> r)
-> r
$bGenTxIdBabbage :: forall c.
GenTxId (ShelleyBlock (Praos c) BabbageEra) -> CardanoGenTxId c
GenTxIdBabbage txid =
HardForkGenTxId (OneEraGenTxId (TagBabbage (WrapGenTxId txid)))
pattern GenTxIdConway ::
GenTxId (ShelleyBlock (Praos c) ConwayEra) ->
CardanoGenTxId c
pattern $mGenTxIdConway :: forall {r} {c}.
CardanoGenTxId c
-> (GenTxId (ShelleyBlock (Praos c) ConwayEra) -> r)
-> ((# #) -> r)
-> r
$bGenTxIdConway :: forall c.
GenTxId (ShelleyBlock (Praos c) ConwayEra) -> 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) ->
CardanoApplyTxErr c
pattern $mApplyTxErrShelley :: forall {r} {c}.
CardanoApplyTxErr c
-> (ApplyTxErr (ShelleyBlock (TPraos c) ShelleyEra) -> r)
-> ((# #) -> r)
-> r
$bApplyTxErrShelley :: forall c.
ApplyTxErr (ShelleyBlock (TPraos c) ShelleyEra)
-> CardanoApplyTxErr c
ApplyTxErrShelley err =
HardForkApplyTxErrFromEra (OneEraApplyTxErr (TagShelley (WrapApplyTxErr err)))
pattern ApplyTxErrAllegra ::
ApplyTxErr (ShelleyBlock (TPraos c) AllegraEra) ->
CardanoApplyTxErr c
pattern $mApplyTxErrAllegra :: forall {r} {c}.
CardanoApplyTxErr c
-> (ApplyTxErr (ShelleyBlock (TPraos c) AllegraEra) -> r)
-> ((# #) -> r)
-> r
$bApplyTxErrAllegra :: forall c.
ApplyTxErr (ShelleyBlock (TPraos c) AllegraEra)
-> CardanoApplyTxErr c
ApplyTxErrAllegra err =
HardForkApplyTxErrFromEra (OneEraApplyTxErr (TagAllegra (WrapApplyTxErr err)))
pattern ApplyTxErrMary ::
ApplyTxErr (ShelleyBlock (TPraos c) MaryEra) ->
CardanoApplyTxErr c
pattern $mApplyTxErrMary :: forall {r} {c}.
CardanoApplyTxErr c
-> (ApplyTxErr (ShelleyBlock (TPraos c) MaryEra) -> r)
-> ((# #) -> r)
-> r
$bApplyTxErrMary :: forall c.
ApplyTxErr (ShelleyBlock (TPraos c) MaryEra) -> CardanoApplyTxErr c
ApplyTxErrMary err =
HardForkApplyTxErrFromEra (OneEraApplyTxErr (TagMary (WrapApplyTxErr err)))
pattern ApplyTxErrAlonzo ::
ApplyTxErr (ShelleyBlock (TPraos c) AlonzoEra) ->
CardanoApplyTxErr c
pattern $mApplyTxErrAlonzo :: forall {r} {c}.
CardanoApplyTxErr c
-> (ApplyTxErr (ShelleyBlock (TPraos c) AlonzoEra) -> r)
-> ((# #) -> r)
-> r
$bApplyTxErrAlonzo :: forall c.
ApplyTxErr (ShelleyBlock (TPraos c) AlonzoEra)
-> CardanoApplyTxErr c
ApplyTxErrAlonzo err =
HardForkApplyTxErrFromEra (OneEraApplyTxErr (TagAlonzo (WrapApplyTxErr err)))
pattern ApplyTxErrBabbage ::
ApplyTxErr (ShelleyBlock (Praos c) BabbageEra) ->
CardanoApplyTxErr c
pattern $mApplyTxErrBabbage :: forall {r} {c}.
CardanoApplyTxErr c
-> (ApplyTxErr (ShelleyBlock (Praos c) BabbageEra) -> r)
-> ((# #) -> r)
-> r
$bApplyTxErrBabbage :: forall c.
ApplyTxErr (ShelleyBlock (Praos c) BabbageEra)
-> CardanoApplyTxErr c
ApplyTxErrBabbage err =
HardForkApplyTxErrFromEra (OneEraApplyTxErr (TagBabbage (WrapApplyTxErr err)))
pattern ApplyTxErrConway ::
ApplyTxErr (ShelleyBlock (Praos c) ConwayEra) ->
CardanoApplyTxErr c
pattern $mApplyTxErrConway :: forall {r} {c}.
CardanoApplyTxErr c
-> (ApplyTxErr (ShelleyBlock (Praos c) ConwayEra) -> r)
-> ((# #) -> r)
-> r
$bApplyTxErrConway :: forall c.
ApplyTxErr (ShelleyBlock (Praos c) ConwayEra)
-> 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) ->
CardanoLedgerError c
pattern $mLedgerErrorShelley :: forall {r} {c}.
CardanoLedgerError c
-> (LedgerError (ShelleyBlock (TPraos c) ShelleyEra) -> r)
-> ((# #) -> r)
-> r
$bLedgerErrorShelley :: forall c.
LedgerError (ShelleyBlock (TPraos c) ShelleyEra)
-> CardanoLedgerError c
LedgerErrorShelley err =
HardForkLedgerErrorFromEra
(OneEraLedgerError (TagShelley (WrapLedgerErr err)))
pattern LedgerErrorAllegra ::
LedgerError (ShelleyBlock (TPraos c) AllegraEra) ->
CardanoLedgerError c
pattern $mLedgerErrorAllegra :: forall {r} {c}.
CardanoLedgerError c
-> (LedgerError (ShelleyBlock (TPraos c) AllegraEra) -> r)
-> ((# #) -> r)
-> r
$bLedgerErrorAllegra :: forall c.
LedgerError (ShelleyBlock (TPraos c) AllegraEra)
-> CardanoLedgerError c
LedgerErrorAllegra err =
HardForkLedgerErrorFromEra
(OneEraLedgerError (TagAllegra (WrapLedgerErr err)))
pattern LedgerErrorMary ::
LedgerError (ShelleyBlock (TPraos c) MaryEra) ->
CardanoLedgerError c
pattern $mLedgerErrorMary :: forall {r} {c}.
CardanoLedgerError c
-> (LedgerError (ShelleyBlock (TPraos c) MaryEra) -> r)
-> ((# #) -> r)
-> r
$bLedgerErrorMary :: forall c.
LedgerError (ShelleyBlock (TPraos c) MaryEra)
-> CardanoLedgerError c
LedgerErrorMary err =
HardForkLedgerErrorFromEra
(OneEraLedgerError (TagMary (WrapLedgerErr err)))
pattern LedgerErrorAlonzo ::
LedgerError (ShelleyBlock (TPraos c) AlonzoEra) ->
CardanoLedgerError c
pattern $mLedgerErrorAlonzo :: forall {r} {c}.
CardanoLedgerError c
-> (LedgerError (ShelleyBlock (TPraos c) AlonzoEra) -> r)
-> ((# #) -> r)
-> r
$bLedgerErrorAlonzo :: forall c.
LedgerError (ShelleyBlock (TPraos c) AlonzoEra)
-> CardanoLedgerError c
LedgerErrorAlonzo err =
HardForkLedgerErrorFromEra
(OneEraLedgerError (TagAlonzo (WrapLedgerErr err)))
pattern LedgerErrorBabbage ::
LedgerError (ShelleyBlock (Praos c) BabbageEra) ->
CardanoLedgerError c
pattern $mLedgerErrorBabbage :: forall {r} {c}.
CardanoLedgerError c
-> (LedgerError (ShelleyBlock (Praos c) BabbageEra) -> r)
-> ((# #) -> r)
-> r
$bLedgerErrorBabbage :: forall c.
LedgerError (ShelleyBlock (Praos c) BabbageEra)
-> CardanoLedgerError c
LedgerErrorBabbage err =
HardForkLedgerErrorFromEra
(OneEraLedgerError (TagBabbage (WrapLedgerErr err)))
pattern LedgerErrorConway ::
LedgerError (ShelleyBlock (Praos c) ConwayEra) ->
CardanoLedgerError c
pattern $mLedgerErrorConway :: forall {r} {c}.
CardanoLedgerError c
-> (LedgerError (ShelleyBlock (Praos c) ConwayEra) -> r)
-> ((# #) -> r)
-> r
$bLedgerErrorConway :: forall c.
LedgerError (ShelleyBlock (Praos c) ConwayEra)
-> 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) ->
CardanoOtherHeaderEnvelopeError c
pattern err =
HardForkEnvelopeErrFromEra (OneEraEnvelopeErr (TagShelley (WrapEnvelopeErr err)))
pattern OtherHeaderEnvelopeErrorAllegra ::
OtherHeaderEnvelopeError (ShelleyBlock (TPraos c) AllegraEra) ->
CardanoOtherHeaderEnvelopeError c
pattern err =
HardForkEnvelopeErrFromEra (OneEraEnvelopeErr (TagAllegra (WrapEnvelopeErr err)))
pattern OtherHeaderEnvelopeErrorMary ::
OtherHeaderEnvelopeError (ShelleyBlock (TPraos c) MaryEra) ->
CardanoOtherHeaderEnvelopeError c
pattern err =
HardForkEnvelopeErrFromEra (OneEraEnvelopeErr (TagMary (WrapEnvelopeErr err)))
pattern OtherHeaderEnvelopeErrorAlonzo ::
OtherHeaderEnvelopeError (ShelleyBlock (TPraos c) AlonzoEra) ->
CardanoOtherHeaderEnvelopeError c
pattern err =
HardForkEnvelopeErrFromEra (OneEraEnvelopeErr (TagAlonzo (WrapEnvelopeErr err)))
pattern OtherHeaderEnvelopeErrorBabbage ::
OtherHeaderEnvelopeError (ShelleyBlock (Praos c) BabbageEra) ->
CardanoOtherHeaderEnvelopeError c
pattern err =
HardForkEnvelopeErrFromEra (OneEraEnvelopeErr (TagBabbage (WrapEnvelopeErr err)))
pattern OtherHeaderEnvelopeErrorConway ::
OtherHeaderEnvelopeError (ShelleyBlock (Praos c) ConwayEra) ->
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) ->
CardanoTipInfo c
pattern $mTipInfoShelley :: forall {r} {c}.
CardanoTipInfo c
-> (TipInfo (ShelleyBlock (TPraos c) ShelleyEra) -> r)
-> ((# #) -> r)
-> r
$bTipInfoShelley :: forall c.
TipInfo (ShelleyBlock (TPraos c) ShelleyEra) -> CardanoTipInfo c
TipInfoShelley ti = OneEraTipInfo (TagShelley (WrapTipInfo ti))
pattern TipInfoAllegra ::
TipInfo (ShelleyBlock (TPraos c) AllegraEra) ->
CardanoTipInfo c
pattern $mTipInfoAllegra :: forall {r} {c}.
CardanoTipInfo c
-> (TipInfo (ShelleyBlock (TPraos c) AllegraEra) -> r)
-> ((# #) -> r)
-> r
$bTipInfoAllegra :: forall c.
TipInfo (ShelleyBlock (TPraos c) AllegraEra) -> CardanoTipInfo c
TipInfoAllegra ti = OneEraTipInfo (TagAllegra (WrapTipInfo ti))
pattern TipInfoMary ::
TipInfo (ShelleyBlock (TPraos c) MaryEra) ->
CardanoTipInfo c
pattern $mTipInfoMary :: forall {r} {c}.
CardanoTipInfo c
-> (TipInfo (ShelleyBlock (TPraos c) MaryEra) -> r)
-> ((# #) -> r)
-> r
$bTipInfoMary :: forall c.
TipInfo (ShelleyBlock (TPraos c) MaryEra) -> CardanoTipInfo c
TipInfoMary ti = OneEraTipInfo (TagMary (WrapTipInfo ti))
pattern TipInfoAlonzo ::
TipInfo (ShelleyBlock (TPraos c) AlonzoEra) ->
CardanoTipInfo c
pattern $mTipInfoAlonzo :: forall {r} {c}.
CardanoTipInfo c
-> (TipInfo (ShelleyBlock (TPraos c) AlonzoEra) -> r)
-> ((# #) -> r)
-> r
$bTipInfoAlonzo :: forall c.
TipInfo (ShelleyBlock (TPraos c) AlonzoEra) -> CardanoTipInfo c
TipInfoAlonzo ti = OneEraTipInfo (TagAlonzo (WrapTipInfo ti))
pattern TipInfoBabbage ::
TipInfo (ShelleyBlock (Praos c) BabbageEra) ->
CardanoTipInfo c
pattern $mTipInfoBabbage :: forall {r} {c}.
CardanoTipInfo c
-> (TipInfo (ShelleyBlock (Praos c) BabbageEra) -> r)
-> ((# #) -> r)
-> r
$bTipInfoBabbage :: forall c.
TipInfo (ShelleyBlock (Praos c) BabbageEra) -> CardanoTipInfo c
TipInfoBabbage ti = OneEraTipInfo (TagBabbage (WrapTipInfo ti))
pattern TipInfoConway ::
TipInfo (ShelleyBlock (Praos c) ConwayEra) ->
CardanoTipInfo c
pattern $mTipInfoConway :: forall {r} {c}.
CardanoTipInfo c
-> (TipInfo (ShelleyBlock (Praos c) ConwayEra) -> r)
-> ((# #) -> r)
-> r
$bTipInfoConway :: forall c.
TipInfo (ShelleyBlock (Praos c) ConwayEra) -> 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 fp result ->
CardanoQuery c fp a
pattern QueryIfCurrentShelley ::
() =>
CardanoQueryResult c result ~ a =>
BlockQuery (ShelleyBlock (TPraos c) ShelleyEra) fp result ->
CardanoQuery c fp a
pattern QueryIfCurrentAllegra ::
() =>
CardanoQueryResult c result ~ a =>
BlockQuery (ShelleyBlock (TPraos c) AllegraEra) fp result ->
CardanoQuery c fp a
pattern QueryIfCurrentMary ::
() =>
CardanoQueryResult c result ~ a =>
BlockQuery (ShelleyBlock (TPraos c) MaryEra) fp result ->
CardanoQuery c fp a
pattern QueryIfCurrentAlonzo ::
() =>
CardanoQueryResult c result ~ a =>
BlockQuery (ShelleyBlock (TPraos c) AlonzoEra) fp result ->
CardanoQuery c fp a
pattern QueryIfCurrentBabbage ::
() =>
CardanoQueryResult c result ~ a =>
BlockQuery (ShelleyBlock (Praos c) BabbageEra) fp result ->
CardanoQuery c fp a
pattern QueryIfCurrentConway ::
() =>
CardanoQueryResult c result ~ a =>
BlockQuery (ShelleyBlock (Praos c) ConwayEra) fp result ->
CardanoQuery c fp a
pattern $mQueryIfCurrentByron :: forall {r} {c} {a} {fp :: QueryFootprint}.
CardanoQuery c fp a
-> (forall {result}.
(CardanoQueryResult c result ~ a) =>
BlockQuery ByronBlock fp result -> r)
-> ((# #) -> r)
-> r
$bQueryIfCurrentByron :: forall c a (fp :: QueryFootprint) result.
(CardanoQueryResult c result ~ a) =>
BlockQuery ByronBlock fp result -> CardanoQuery c fp a
QueryIfCurrentByron q = QueryIfCurrent (QZ q)
pattern $mQueryIfCurrentShelley :: forall {r} {c} {a} {fp :: QueryFootprint}.
CardanoQuery c fp a
-> (forall {result}.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (TPraos c) ShelleyEra) fp result -> r)
-> ((# #) -> r)
-> r
$bQueryIfCurrentShelley :: forall c a (fp :: QueryFootprint) result.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (TPraos c) ShelleyEra) fp result
-> CardanoQuery c fp a
QueryIfCurrentShelley q = QueryIfCurrent (QS (QZ q))
pattern $mQueryIfCurrentAllegra :: forall {r} {c} {a} {fp :: QueryFootprint}.
CardanoQuery c fp a
-> (forall {result}.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (TPraos c) AllegraEra) fp result -> r)
-> ((# #) -> r)
-> r
$bQueryIfCurrentAllegra :: forall c a (fp :: QueryFootprint) result.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (TPraos c) AllegraEra) fp result
-> CardanoQuery c fp a
QueryIfCurrentAllegra q = QueryIfCurrent (QS (QS (QZ q)))
pattern $mQueryIfCurrentMary :: forall {r} {c} {a} {fp :: QueryFootprint}.
CardanoQuery c fp a
-> (forall {result}.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (TPraos c) MaryEra) fp result -> r)
-> ((# #) -> r)
-> r
$bQueryIfCurrentMary :: forall c a (fp :: QueryFootprint) result.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (TPraos c) MaryEra) fp result
-> CardanoQuery c fp a
QueryIfCurrentMary q = QueryIfCurrent (QS (QS (QS (QZ q))))
pattern $mQueryIfCurrentAlonzo :: forall {r} {c} {a} {fp :: QueryFootprint}.
CardanoQuery c fp a
-> (forall {result}.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (TPraos c) AlonzoEra) fp result -> r)
-> ((# #) -> r)
-> r
$bQueryIfCurrentAlonzo :: forall c a (fp :: QueryFootprint) result.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (TPraos c) AlonzoEra) fp result
-> CardanoQuery c fp a
QueryIfCurrentAlonzo q = QueryIfCurrent (QS (QS (QS (QS (QZ q)))))
pattern $mQueryIfCurrentBabbage :: forall {r} {c} {a} {fp :: QueryFootprint}.
CardanoQuery c fp a
-> (forall {result}.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (Praos c) BabbageEra) fp result -> r)
-> ((# #) -> r)
-> r
$bQueryIfCurrentBabbage :: forall c a (fp :: QueryFootprint) result.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (Praos c) BabbageEra) fp result
-> CardanoQuery c fp a
QueryIfCurrentBabbage q = QueryIfCurrent (QS (QS (QS (QS (QS (QZ q))))))
pattern $mQueryIfCurrentConway :: forall {r} {c} {a} {fp :: QueryFootprint}.
CardanoQuery c fp a
-> (forall {result}.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (Praos c) ConwayEra) fp result -> r)
-> ((# #) -> r)
-> r
$bQueryIfCurrentConway :: forall c a (fp :: QueryFootprint) result.
(CardanoQueryResult c result ~ a) =>
BlockQuery (ShelleyBlock (Praos c) ConwayEra) fp result
-> CardanoQuery c fp a
QueryIfCurrentConway q = QueryIfCurrent (QS (QS (QS (QS (QS (QS (QZ q)))))))
pattern QueryAnytimeByron ::
QueryAnytime result ->
CardanoQuery c QFNoTables result
pattern $mQueryAnytimeByron :: forall {r} {result} {c}.
CardanoQuery c 'QFNoTables result
-> (QueryAnytime result -> r) -> ((# #) -> r) -> r
$bQueryAnytimeByron :: forall result c.
QueryAnytime result -> CardanoQuery c 'QFNoTables result
QueryAnytimeByron q = QueryAnytime q (EraIndex (TagByron (K ())))
pattern QueryAnytimeShelley ::
QueryAnytime result ->
CardanoQuery c QFNoTables result
pattern $mQueryAnytimeShelley :: forall {r} {result} {c}.
CardanoQuery c 'QFNoTables result
-> (QueryAnytime result -> r) -> ((# #) -> r) -> r
$bQueryAnytimeShelley :: forall result c.
QueryAnytime result -> CardanoQuery c 'QFNoTables result
QueryAnytimeShelley q = QueryAnytime q (EraIndex (TagShelley (K ())))
pattern QueryAnytimeAllegra ::
QueryAnytime result ->
CardanoQuery c QFNoTables result
pattern $mQueryAnytimeAllegra :: forall {r} {result} {c}.
CardanoQuery c 'QFNoTables result
-> (QueryAnytime result -> r) -> ((# #) -> r) -> r
$bQueryAnytimeAllegra :: forall result c.
QueryAnytime result -> CardanoQuery c 'QFNoTables result
QueryAnytimeAllegra q = QueryAnytime q (EraIndex (TagAllegra (K ())))
pattern QueryAnytimeMary ::
QueryAnytime result ->
CardanoQuery c QFNoTables result
pattern $mQueryAnytimeMary :: forall {r} {result} {c}.
CardanoQuery c 'QFNoTables result
-> (QueryAnytime result -> r) -> ((# #) -> r) -> r
$bQueryAnytimeMary :: forall result c.
QueryAnytime result -> CardanoQuery c 'QFNoTables result
QueryAnytimeMary q = QueryAnytime q (EraIndex (TagMary (K ())))
pattern QueryAnytimeAlonzo ::
QueryAnytime result ->
CardanoQuery c QFNoTables result
pattern $mQueryAnytimeAlonzo :: forall {r} {result} {c}.
CardanoQuery c 'QFNoTables result
-> (QueryAnytime result -> r) -> ((# #) -> r) -> r
$bQueryAnytimeAlonzo :: forall result c.
QueryAnytime result -> CardanoQuery c 'QFNoTables result
QueryAnytimeAlonzo q = QueryAnytime q (EraIndex (TagAlonzo (K ())))
pattern QueryAnytimeBabbage ::
QueryAnytime result ->
CardanoQuery c QFNoTables result
pattern $mQueryAnytimeBabbage :: forall {r} {result} {c}.
CardanoQuery c 'QFNoTables result
-> (QueryAnytime result -> r) -> ((# #) -> r) -> r
$bQueryAnytimeBabbage :: forall result c.
QueryAnytime result -> CardanoQuery c 'QFNoTables result
QueryAnytimeBabbage q = QueryAnytime q (EraIndex (TagBabbage (K ())))
pattern QueryAnytimeConway ::
QueryAnytime result ->
CardanoQuery c QFNoTables result
pattern $mQueryAnytimeConway :: forall {r} {result} {c}.
CardanoQuery c 'QFNoTables result
-> (QueryAnytime result -> r) -> ((# #) -> r) -> r
$bQueryAnytimeConway :: forall result c.
QueryAnytime result -> CardanoQuery c 'QFNoTables 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) ->
CodecConfig (ShelleyBlock (TPraos c) AllegraEra) ->
CodecConfig (ShelleyBlock (TPraos c) MaryEra) ->
CodecConfig (ShelleyBlock (TPraos c) AlonzoEra) ->
CodecConfig (ShelleyBlock (Praos c) BabbageEra) ->
CodecConfig (ShelleyBlock (Praos c) ConwayEra) ->
CardanoCodecConfig c
pattern $mCardanoCodecConfig :: forall {r} {c}.
CardanoCodecConfig c
-> (CodecConfig ByronBlock
-> CodecConfig (ShelleyBlock (TPraos c) ShelleyEra)
-> CodecConfig (ShelleyBlock (TPraos c) AllegraEra)
-> CodecConfig (ShelleyBlock (TPraos c) MaryEra)
-> CodecConfig (ShelleyBlock (TPraos c) AlonzoEra)
-> CodecConfig (ShelleyBlock (Praos c) BabbageEra)
-> CodecConfig (ShelleyBlock (Praos c) ConwayEra)
-> r)
-> ((# #) -> r)
-> r
$bCardanoCodecConfig :: forall c.
CodecConfig ByronBlock
-> CodecConfig (ShelleyBlock (TPraos c) ShelleyEra)
-> CodecConfig (ShelleyBlock (TPraos c) AllegraEra)
-> CodecConfig (ShelleyBlock (TPraos c) MaryEra)
-> CodecConfig (ShelleyBlock (TPraos c) AlonzoEra)
-> CodecConfig (ShelleyBlock (Praos c) BabbageEra)
-> CodecConfig (ShelleyBlock (Praos c) ConwayEra)
-> 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) ->
BlockConfig (ShelleyBlock (TPraos c) AllegraEra) ->
BlockConfig (ShelleyBlock (TPraos c) MaryEra) ->
BlockConfig (ShelleyBlock (TPraos c) AlonzoEra) ->
BlockConfig (ShelleyBlock (Praos c) BabbageEra) ->
BlockConfig (ShelleyBlock (Praos c) ConwayEra) ->
CardanoBlockConfig c
pattern $mCardanoBlockConfig :: forall {r} {c}.
CardanoBlockConfig c
-> (BlockConfig ByronBlock
-> BlockConfig (ShelleyBlock (TPraos c) ShelleyEra)
-> BlockConfig (ShelleyBlock (TPraos c) AllegraEra)
-> BlockConfig (ShelleyBlock (TPraos c) MaryEra)
-> BlockConfig (ShelleyBlock (TPraos c) AlonzoEra)
-> BlockConfig (ShelleyBlock (Praos c) BabbageEra)
-> BlockConfig (ShelleyBlock (Praos c) ConwayEra)
-> r)
-> ((# #) -> r)
-> r
$bCardanoBlockConfig :: forall c.
BlockConfig ByronBlock
-> BlockConfig (ShelleyBlock (TPraos c) ShelleyEra)
-> BlockConfig (ShelleyBlock (TPraos c) AllegraEra)
-> BlockConfig (ShelleyBlock (TPraos c) MaryEra)
-> BlockConfig (ShelleyBlock (TPraos c) AlonzoEra)
-> BlockConfig (ShelleyBlock (Praos c) BabbageEra)
-> BlockConfig (ShelleyBlock (Praos c) ConwayEra)
-> 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) ->
StorageConfig (ShelleyBlock (TPraos c) AllegraEra) ->
StorageConfig (ShelleyBlock (TPraos c) MaryEra) ->
StorageConfig (ShelleyBlock (TPraos c) AlonzoEra) ->
StorageConfig (ShelleyBlock (Praos c) BabbageEra) ->
StorageConfig (ShelleyBlock (Praos c) ConwayEra) ->
CardanoStorageConfig c
pattern $mCardanoStorageConfig :: forall {r} {c}.
CardanoStorageConfig c
-> (StorageConfig ByronBlock
-> StorageConfig (ShelleyBlock (TPraos c) ShelleyEra)
-> StorageConfig (ShelleyBlock (TPraos c) AllegraEra)
-> StorageConfig (ShelleyBlock (TPraos c) MaryEra)
-> StorageConfig (ShelleyBlock (TPraos c) AlonzoEra)
-> StorageConfig (ShelleyBlock (Praos c) BabbageEra)
-> StorageConfig (ShelleyBlock (Praos c) ConwayEra)
-> r)
-> ((# #) -> r)
-> r
$bCardanoStorageConfig :: forall c.
StorageConfig ByronBlock
-> StorageConfig (ShelleyBlock (TPraos c) ShelleyEra)
-> StorageConfig (ShelleyBlock (TPraos c) AllegraEra)
-> StorageConfig (ShelleyBlock (TPraos c) MaryEra)
-> StorageConfig (ShelleyBlock (TPraos c) AlonzoEra)
-> StorageConfig (ShelleyBlock (Praos c) BabbageEra)
-> StorageConfig (ShelleyBlock (Praos c) ConwayEra)
-> 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)) ->
PartialConsensusConfig (BlockProtocol (ShelleyBlock (TPraos c) AllegraEra)) ->
PartialConsensusConfig (BlockProtocol (ShelleyBlock (TPraos c) MaryEra)) ->
PartialConsensusConfig (BlockProtocol (ShelleyBlock (TPraos c) AlonzoEra)) ->
PartialConsensusConfig (BlockProtocol (ShelleyBlock (Praos c) BabbageEra)) ->
PartialConsensusConfig (BlockProtocol (ShelleyBlock (Praos c) ConwayEra)) ->
CardanoConsensusConfig c
pattern $mCardanoConsensusConfig :: forall {r} {c}.
CardanoConsensusConfig c
-> (PartialConsensusConfig (BlockProtocol ByronBlock)
-> PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) ShelleyEra))
-> PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) AllegraEra))
-> PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) MaryEra))
-> PartialConsensusConfig
(BlockProtocol (ShelleyBlock (TPraos c) AlonzoEra))
-> PartialConsensusConfig
(BlockProtocol (ShelleyBlock (Praos c) BabbageEra))
-> PartialConsensusConfig
(BlockProtocol (ShelleyBlock (Praos c) ConwayEra))
-> 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) ->
PartialLedgerConfig (ShelleyBlock (TPraos c) AllegraEra) ->
PartialLedgerConfig (ShelleyBlock (TPraos c) MaryEra) ->
PartialLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra) ->
PartialLedgerConfig (ShelleyBlock (Praos c) BabbageEra) ->
PartialLedgerConfig (ShelleyBlock (Praos c) ConwayEra) ->
CardanoLedgerConfig c
pattern $mCardanoLedgerConfig :: forall {r} {c}.
CardanoLedgerConfig c
-> (PartialLedgerConfig ByronBlock
-> PartialLedgerConfig (ShelleyBlock (TPraos c) ShelleyEra)
-> PartialLedgerConfig (ShelleyBlock (TPraos c) AllegraEra)
-> PartialLedgerConfig (ShelleyBlock (TPraos c) MaryEra)
-> PartialLedgerConfig (ShelleyBlock (TPraos c) AlonzoEra)
-> PartialLedgerConfig (ShelleyBlock (Praos c) BabbageEra)
-> PartialLedgerConfig (ShelleyBlock (Praos c) ConwayEra)
-> 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 mk = LedgerState (CardanoBlock c) mk
pattern LedgerStateByron ::
LedgerState ByronBlock mk ->
CardanoLedgerState c mk
pattern $mLedgerStateByron :: forall {r} {mk :: MapKind} {c}.
CardanoLedgerState c mk
-> (LedgerState ByronBlock mk -> r) -> ((# #) -> r) -> r
LedgerStateByron st <-
HardForkLedgerState
( State.HardForkState
(TeleByron (State.Current{currentState = Flip st}))
)
pattern LedgerStateShelley ::
LedgerState (ShelleyBlock (TPraos c) ShelleyEra) mk ->
CardanoLedgerState c mk
pattern $mLedgerStateShelley :: forall {r} {c} {mk :: MapKind}.
CardanoLedgerState c mk
-> (LedgerState (ShelleyBlock (TPraos c) ShelleyEra) mk -> r)
-> ((# #) -> r)
-> r
LedgerStateShelley st <-
HardForkLedgerState
( State.HardForkState
(TeleShelley _ (State.Current{currentState = Flip st}))
)
pattern LedgerStateAllegra ::
LedgerState (ShelleyBlock (TPraos c) AllegraEra) mk ->
CardanoLedgerState c mk
pattern $mLedgerStateAllegra :: forall {r} {c} {mk :: MapKind}.
CardanoLedgerState c mk
-> (LedgerState (ShelleyBlock (TPraos c) AllegraEra) mk -> r)
-> ((# #) -> r)
-> r
LedgerStateAllegra st <-
HardForkLedgerState
( State.HardForkState
(TeleAllegra _ _ (State.Current{currentState = Flip st}))
)
pattern LedgerStateMary ::
LedgerState (ShelleyBlock (TPraos c) MaryEra) mk ->
CardanoLedgerState c mk
pattern $mLedgerStateMary :: forall {r} {c} {mk :: MapKind}.
CardanoLedgerState c mk
-> (LedgerState (ShelleyBlock (TPraos c) MaryEra) mk -> r)
-> ((# #) -> r)
-> r
LedgerStateMary st <-
HardForkLedgerState
( State.HardForkState
(TeleMary _ _ _ (State.Current{currentState = Flip st}))
)
pattern LedgerStateAlonzo ::
LedgerState (ShelleyBlock (TPraos c) AlonzoEra) mk ->
CardanoLedgerState c mk
pattern $mLedgerStateAlonzo :: forall {r} {c} {mk :: MapKind}.
CardanoLedgerState c mk
-> (LedgerState (ShelleyBlock (TPraos c) AlonzoEra) mk -> r)
-> ((# #) -> r)
-> r
LedgerStateAlonzo st <-
HardForkLedgerState
( State.HardForkState
(TeleAlonzo _ _ _ _ (State.Current{currentState = Flip st}))
)
pattern LedgerStateBabbage ::
LedgerState (ShelleyBlock (Praos c) BabbageEra) mk ->
CardanoLedgerState c mk
pattern $mLedgerStateBabbage :: forall {r} {c} {mk :: MapKind}.
CardanoLedgerState c mk
-> (LedgerState (ShelleyBlock (Praos c) BabbageEra) mk -> r)
-> ((# #) -> r)
-> r
LedgerStateBabbage st <-
HardForkLedgerState
( State.HardForkState
(TeleBabbage _ _ _ _ _ (State.Current{currentState = Flip st}))
)
pattern LedgerStateConway ::
LedgerState (ShelleyBlock (Praos c) ConwayEra) mk ->
CardanoLedgerState c mk
pattern $mLedgerStateConway :: forall {r} {c} {mk :: MapKind}.
CardanoLedgerState c mk
-> (LedgerState (ShelleyBlock (Praos c) ConwayEra) mk -> r)
-> ((# #) -> r)
-> r
LedgerStateConway st <-
HardForkLedgerState
( State.HardForkState
(TeleConway _ _ _ _ _ _ (State.Current{currentState = Flip 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)) ->
CardanoChainDepState c
pattern $mChainDepStateShelley :: forall {r} {c}.
CardanoChainDepState c
-> (ChainDepState
(BlockProtocol (ShelleyBlock (TPraos c) ShelleyEra))
-> r)
-> ((# #) -> r)
-> r
ChainDepStateShelley st <-
State.HardForkState
(TeleShelley _ (State.Current{currentState = WrapChainDepState st}))
pattern ChainDepStateAllegra ::
ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) AllegraEra)) ->
CardanoChainDepState c
pattern $mChainDepStateAllegra :: forall {r} {c}.
CardanoChainDepState c
-> (ChainDepState
(BlockProtocol (ShelleyBlock (TPraos c) AllegraEra))
-> r)
-> ((# #) -> r)
-> r
ChainDepStateAllegra st <-
State.HardForkState
(TeleAllegra _ _ (State.Current{currentState = WrapChainDepState st}))
pattern ChainDepStateMary ::
ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) MaryEra)) ->
CardanoChainDepState c
pattern $mChainDepStateMary :: forall {r} {c}.
CardanoChainDepState c
-> (ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) MaryEra))
-> r)
-> ((# #) -> r)
-> r
ChainDepStateMary st <-
State.HardForkState
(TeleMary _ _ _ (State.Current{currentState = WrapChainDepState st}))
pattern ChainDepStateAlonzo ::
ChainDepState (BlockProtocol (ShelleyBlock (TPraos c) AlonzoEra)) ->
CardanoChainDepState c
pattern $mChainDepStateAlonzo :: forall {r} {c}.
CardanoChainDepState c
-> (ChainDepState
(BlockProtocol (ShelleyBlock (TPraos c) AlonzoEra))
-> r)
-> ((# #) -> r)
-> r
ChainDepStateAlonzo st <-
State.HardForkState
(TeleAlonzo _ _ _ _ (State.Current{currentState = WrapChainDepState st}))
pattern ChainDepStateBabbage ::
ChainDepState (BlockProtocol (ShelleyBlock (Praos c) BabbageEra)) ->
CardanoChainDepState c
pattern $mChainDepStateBabbage :: forall {r} {c}.
CardanoChainDepState c
-> (ChainDepState
(BlockProtocol (ShelleyBlock (Praos c) BabbageEra))
-> r)
-> ((# #) -> r)
-> r
ChainDepStateBabbage st <-
State.HardForkState
(TeleBabbage _ _ _ _ _ (State.Current{currentState = WrapChainDepState st}))
pattern ChainDepStateConway ::
ChainDepState (BlockProtocol (ShelleyBlock (Praos c) ConwayEra)) ->
CardanoChainDepState c
pattern $mChainDepStateConway :: forall {r} {c}.
CardanoChainDepState c
-> (ChainDepState
(BlockProtocol (ShelleyBlock (Praos c) ConwayEra))
-> r)
-> ((# #) -> r)
-> r
ChainDepStateConway st <-
State.HardForkState
(TeleConway _ _ _ _ _ _ (State.Current{currentState = WrapChainDepState st}))
{-# COMPLETE
ChainDepStateByron
, ChainDepStateShelley
, ChainDepStateAllegra
, ChainDepStateMary
, ChainDepStateAlonzo
, ChainDepStateBabbage
, ChainDepStateConway
#-}