{-# LANGUAGE EmptyCase #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Ouroboros.Consensus.ByronDual.Node.Serialisation () where
import Cardano.Chain.Slotting (EpochSlots)
import qualified Data.ByteString.Lazy as Lazy
import Data.Proxy
import Ouroboros.Consensus.Block
import Ouroboros.Consensus.Byron.Ledger
import Ouroboros.Consensus.Byron.Node.Serialisation ()
import Ouroboros.Consensus.Byron.Protocol
import Ouroboros.Consensus.ByronDual.Ledger
import Ouroboros.Consensus.ByronSpec.Ledger
import Ouroboros.Consensus.HeaderValidation
import Ouroboros.Consensus.Ledger.Dual
import Ouroboros.Consensus.Ledger.SupportsMempool (GenTxId)
import Ouroboros.Consensus.Node.NetworkProtocolVersion
import Ouroboros.Consensus.Node.Run
import Ouroboros.Consensus.Node.Serialisation
import Ouroboros.Consensus.Protocol.PBFT.State (PBftState)
import Ouroboros.Consensus.Storage.Serialisation
import Ouroboros.Network.Block (Serialised, unwrapCBORinCBOR,
wrapCBORinCBOR)
pb :: Proxy ByronBlock
pb :: Proxy ByronBlock
pb = Proxy ByronBlock
forall {k} (t :: k). Proxy t
Proxy
instance HasNetworkProtocolVersion DualByronBlock where
type BlockNodeToNodeVersion DualByronBlock = BlockNodeToNodeVersion ByronBlock
type BlockNodeToClientVersion DualByronBlock = BlockNodeToClientVersion ByronBlock
instance SupportedNetworkProtocolVersion DualByronBlock where
supportedNodeToNodeVersions :: Proxy DualByronBlock
-> Map NodeToNodeVersion (BlockNodeToNodeVersion DualByronBlock)
supportedNodeToNodeVersions Proxy DualByronBlock
_ = Proxy ByronBlock
-> Map NodeToNodeVersion (BlockNodeToNodeVersion ByronBlock)
forall blk.
SupportedNetworkProtocolVersion blk =>
Proxy blk -> Map NodeToNodeVersion (BlockNodeToNodeVersion blk)
supportedNodeToNodeVersions Proxy ByronBlock
pb
supportedNodeToClientVersions :: Proxy DualByronBlock
-> Map
NodeToClientVersion (BlockNodeToClientVersion DualByronBlock)
supportedNodeToClientVersions Proxy DualByronBlock
_ = Proxy ByronBlock
-> Map NodeToClientVersion (BlockNodeToClientVersion ByronBlock)
forall blk.
SupportedNetworkProtocolVersion blk =>
Proxy blk -> Map NodeToClientVersion (BlockNodeToClientVersion blk)
supportedNodeToClientVersions Proxy ByronBlock
pb
latestReleasedNodeVersion :: Proxy DualByronBlock
-> (Maybe NodeToNodeVersion, Maybe NodeToClientVersion)
latestReleasedNodeVersion = Proxy DualByronBlock
-> (Maybe NodeToNodeVersion, Maybe NodeToClientVersion)
forall blk.
SupportedNetworkProtocolVersion blk =>
Proxy blk -> (Maybe NodeToNodeVersion, Maybe NodeToClientVersion)
latestReleasedNodeVersionDefault
instance SerialiseDiskConstraints DualByronBlock
instance EncodeDisk DualByronBlock DualByronBlock where
encodeDisk :: CodecConfig DualByronBlock -> DualByronBlock -> Encoding
encodeDisk CodecConfig DualByronBlock
_ = (ByronBlock -> Encoding) -> DualByronBlock -> Encoding
forall m a.
(Bridge m a, Serialise a) =>
(m -> Encoding) -> DualBlock m a -> Encoding
encodeDualBlock ByronBlock -> Encoding
encodeByronBlock
instance DecodeDisk DualByronBlock (Lazy.ByteString -> DualByronBlock) where
decodeDisk :: CodecConfig DualByronBlock
-> forall s. Decoder s (ByteString -> DualByronBlock)
decodeDisk CodecConfig DualByronBlock
ccfg = Decoder s (ByteString -> ByronBlock)
-> Decoder s (ByteString -> DualByronBlock)
forall m a s.
(Bridge m a, Serialise a) =>
Decoder s (ByteString -> m)
-> Decoder s (ByteString -> DualBlock m a)
decodeDualBlock (EpochSlots -> Decoder s (ByteString -> ByronBlock)
forall s. EpochSlots -> Decoder s (ByteString -> ByronBlock)
decodeByronBlock EpochSlots
epochSlots)
where
epochSlots :: EpochSlots
epochSlots = CodecConfig DualByronBlock -> EpochSlots
extractEpochSlots CodecConfig DualByronBlock
ccfg
instance DecodeDiskDep (NestedCtxt Header) DualByronBlock where
decodeDiskDep :: forall a.
CodecConfig DualByronBlock
-> NestedCtxt Header DualByronBlock a
-> forall s. Decoder s (ByteString -> a)
decodeDiskDep (DualCodecConfig CodecConfig ByronBlock
ccfg CodecConfig ByronSpecBlock
R:CodecConfigByronSpecBlock
ByronSpecCodecConfig)
(NestedCtxt (CtxtDual NestedCtxt_ ByronBlock Header a
ctxt)) =
CodecConfig ByronBlock
-> NestedCtxt Header ByronBlock a
-> forall s. Decoder s (ByteString -> a)
forall a.
CodecConfig ByronBlock
-> NestedCtxt Header ByronBlock a
-> forall s. Decoder s (ByteString -> a)
forall (f :: * -> * -> *) blk a.
DecodeDiskDep f blk =>
CodecConfig blk -> f blk a -> forall s. Decoder s (ByteString -> a)
decodeDiskDep CodecConfig ByronBlock
ccfg (NestedCtxt_ ByronBlock Header a -> NestedCtxt Header ByronBlock a
forall (f :: * -> *) blk a.
NestedCtxt_ blk f a -> NestedCtxt f blk a
NestedCtxt NestedCtxt_ ByronBlock Header a
ctxt)
instance EncodeDisk DualByronBlock (LedgerState DualByronBlock) where
encodeDisk :: CodecConfig DualByronBlock
-> LedgerState DualByronBlock -> Encoding
encodeDisk CodecConfig DualByronBlock
_ = (LedgerState ByronBlock -> Encoding)
-> LedgerState DualByronBlock -> Encoding
forall m a.
(Bridge m a, Serialise (LedgerState a)) =>
(LedgerState m -> Encoding)
-> LedgerState (DualBlock m a) -> Encoding
encodeDualLedgerState LedgerState ByronBlock -> Encoding
encodeByronLedgerState
instance DecodeDisk DualByronBlock (LedgerState DualByronBlock) where
decodeDisk :: CodecConfig DualByronBlock
-> forall s. Decoder s (LedgerState DualByronBlock)
decodeDisk CodecConfig DualByronBlock
_ = Decoder s (LedgerState ByronBlock)
-> Decoder s (LedgerState DualByronBlock)
forall m a s.
(Bridge m a, Serialise (LedgerState a)) =>
Decoder s (LedgerState m)
-> Decoder s (LedgerState (DualBlock m a))
decodeDualLedgerState Decoder s (LedgerState ByronBlock)
forall s. Decoder s (LedgerState ByronBlock)
decodeByronLedgerState
instance EncodeDisk DualByronBlock (PBftState PBftByronCrypto) where
encodeDisk :: CodecConfig DualByronBlock -> PBftState PBftByronCrypto -> Encoding
encodeDisk CodecConfig DualByronBlock
_ = ChainDepState (BlockProtocol ByronBlock) -> Encoding
PBftState PBftByronCrypto -> Encoding
encodeByronChainDepState
instance DecodeDisk DualByronBlock (PBftState PBftByronCrypto) where
decodeDisk :: CodecConfig DualByronBlock
-> forall s. Decoder s (PBftState PBftByronCrypto)
decodeDisk CodecConfig DualByronBlock
_ = Decoder s (ChainDepState (BlockProtocol ByronBlock))
Decoder s (PBftState PBftByronCrypto)
forall s. Decoder s (ChainDepState (BlockProtocol ByronBlock))
decodeByronChainDepState
instance EncodeDisk DualByronBlock (AnnTip DualByronBlock) where
encodeDisk :: CodecConfig DualByronBlock -> AnnTip DualByronBlock -> Encoding
encodeDisk CodecConfig DualByronBlock
ccfg = CodecConfig ByronBlock -> AnnTip ByronBlock -> Encoding
forall blk a. EncodeDisk blk a => CodecConfig blk -> a -> Encoding
encodeDisk (CodecConfig DualByronBlock -> CodecConfig ByronBlock
forall m a. CodecConfig (DualBlock m a) -> CodecConfig m
dualCodecConfigMain CodecConfig DualByronBlock
ccfg)
(AnnTip ByronBlock -> Encoding)
-> (AnnTip DualByronBlock -> AnnTip ByronBlock)
-> AnnTip DualByronBlock
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (AnnTip DualByronBlock -> AnnTip ByronBlock
forall blk blk'.
(TipInfo blk ~ TipInfo blk') =>
AnnTip blk -> AnnTip blk'
castAnnTip :: AnnTip DualByronBlock -> AnnTip ByronBlock)
instance DecodeDisk DualByronBlock (AnnTip DualByronBlock) where
decodeDisk :: CodecConfig DualByronBlock
-> forall s. Decoder s (AnnTip DualByronBlock)
decodeDisk CodecConfig DualByronBlock
ccfg = (AnnTip ByronBlock -> AnnTip DualByronBlock
forall blk blk'.
(TipInfo blk ~ TipInfo blk') =>
AnnTip blk -> AnnTip blk'
castAnnTip :: AnnTip ByronBlock -> AnnTip DualByronBlock)
(AnnTip ByronBlock -> AnnTip DualByronBlock)
-> Decoder s (AnnTip ByronBlock)
-> Decoder s (AnnTip DualByronBlock)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CodecConfig ByronBlock -> forall s. Decoder s (AnnTip ByronBlock)
forall blk a.
DecodeDisk blk a =>
CodecConfig blk -> forall s. Decoder s a
decodeDisk (CodecConfig DualByronBlock -> CodecConfig ByronBlock
forall m a. CodecConfig (DualBlock m a) -> CodecConfig m
dualCodecConfigMain CodecConfig DualByronBlock
ccfg)
instance SerialiseNodeToNodeConstraints DualByronBlock where
estimateBlockSize :: Header DualByronBlock -> SizeInBytes
estimateBlockSize = Header ByronBlock -> SizeInBytes
forall blk.
SerialiseNodeToNodeConstraints blk =>
Header blk -> SizeInBytes
estimateBlockSize (Header ByronBlock -> SizeInBytes)
-> (Header DualByronBlock -> Header ByronBlock)
-> Header DualByronBlock
-> SizeInBytes
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Header DualByronBlock -> Header ByronBlock
forall m a. Header (DualBlock m a) -> Header m
dualHeaderMain
instance SerialiseNodeToNode DualByronBlock DualByronBlock where
encodeNodeToNode :: CodecConfig DualByronBlock
-> BlockNodeToNodeVersion DualByronBlock
-> DualByronBlock
-> Encoding
encodeNodeToNode CodecConfig DualByronBlock
_ BlockNodeToNodeVersion DualByronBlock
_ = (DualByronBlock -> Encoding) -> DualByronBlock -> Encoding
forall a. (a -> Encoding) -> a -> Encoding
wrapCBORinCBOR ((ByronBlock -> Encoding) -> DualByronBlock -> Encoding
forall m a.
(Bridge m a, Serialise a) =>
(m -> Encoding) -> DualBlock m a -> Encoding
encodeDualBlock ByronBlock -> Encoding
encodeByronBlock)
decodeNodeToNode :: CodecConfig DualByronBlock
-> BlockNodeToNodeVersion DualByronBlock
-> forall s. Decoder s DualByronBlock
decodeNodeToNode CodecConfig DualByronBlock
ccfg BlockNodeToNodeVersion DualByronBlock
_ = (forall s. Decoder s (ByteString -> DualByronBlock))
-> forall s. Decoder s DualByronBlock
forall a.
(forall s. Decoder s (ByteString -> a)) -> forall s. Decoder s a
unwrapCBORinCBOR (Decoder s (ByteString -> ByronBlock)
-> Decoder s (ByteString -> DualByronBlock)
forall m a s.
(Bridge m a, Serialise a) =>
Decoder s (ByteString -> m)
-> Decoder s (ByteString -> DualBlock m a)
decodeDualBlock (EpochSlots -> Decoder s (ByteString -> ByronBlock)
forall s. EpochSlots -> Decoder s (ByteString -> ByronBlock)
decodeByronBlock EpochSlots
epochSlots))
where
epochSlots :: EpochSlots
epochSlots = CodecConfig DualByronBlock -> EpochSlots
extractEpochSlots CodecConfig DualByronBlock
ccfg
instance SerialiseNodeToNode DualByronBlock (Serialised DualByronBlock)
instance SerialiseNodeToNode DualByronBlock (Header DualByronBlock) where
encodeNodeToNode :: CodecConfig DualByronBlock
-> BlockNodeToNodeVersion DualByronBlock
-> Header DualByronBlock
-> Encoding
encodeNodeToNode CodecConfig DualByronBlock
ccfg BlockNodeToNodeVersion DualByronBlock
version =
CodecConfig ByronBlock
-> BlockNodeToNodeVersion ByronBlock
-> Header ByronBlock
-> Encoding
forall blk a.
SerialiseNodeToNode blk a =>
CodecConfig blk -> BlockNodeToNodeVersion blk -> a -> Encoding
encodeNodeToNode (CodecConfig DualByronBlock -> CodecConfig ByronBlock
forall m a. CodecConfig (DualBlock m a) -> CodecConfig m
dualCodecConfigMain CodecConfig DualByronBlock
ccfg) BlockNodeToNodeVersion DualByronBlock
BlockNodeToNodeVersion ByronBlock
version
(Header ByronBlock -> Encoding)
-> (Header DualByronBlock -> Header ByronBlock)
-> Header DualByronBlock
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Header DualByronBlock -> Header ByronBlock
forall m a. Header (DualBlock m a) -> Header m
dualHeaderMain
decodeNodeToNode :: CodecConfig DualByronBlock
-> BlockNodeToNodeVersion DualByronBlock
-> forall s. Decoder s (Header DualByronBlock)
decodeNodeToNode CodecConfig DualByronBlock
ccfg BlockNodeToNodeVersion DualByronBlock
version =
Header ByronBlock -> Header DualByronBlock
forall m a. Header m -> Header (DualBlock m a)
DualHeader
(Header ByronBlock -> Header DualByronBlock)
-> Decoder s (Header ByronBlock)
-> Decoder s (Header DualByronBlock)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CodecConfig ByronBlock
-> BlockNodeToNodeVersion ByronBlock
-> forall s. Decoder s (Header ByronBlock)
forall blk a.
SerialiseNodeToNode blk a =>
CodecConfig blk
-> BlockNodeToNodeVersion blk -> forall s. Decoder s a
decodeNodeToNode (CodecConfig DualByronBlock -> CodecConfig ByronBlock
forall m a. CodecConfig (DualBlock m a) -> CodecConfig m
dualCodecConfigMain CodecConfig DualByronBlock
ccfg) BlockNodeToNodeVersion DualByronBlock
BlockNodeToNodeVersion ByronBlock
version
instance SerialiseNodeToNode DualByronBlock (SerialisedHeader DualByronBlock) where
encodeNodeToNode :: CodecConfig DualByronBlock
-> BlockNodeToNodeVersion DualByronBlock
-> SerialisedHeader DualByronBlock
-> Encoding
encodeNodeToNode CodecConfig DualByronBlock
ccfg BlockNodeToNodeVersion DualByronBlock
version =
CodecConfig ByronBlock
-> BlockNodeToNodeVersion ByronBlock
-> SerialisedHeader ByronBlock
-> Encoding
forall blk a.
SerialiseNodeToNode blk a =>
CodecConfig blk -> BlockNodeToNodeVersion blk -> a -> Encoding
encodeNodeToNode (CodecConfig DualByronBlock -> CodecConfig ByronBlock
forall m a. CodecConfig (DualBlock m a) -> CodecConfig m
dualCodecConfigMain CodecConfig DualByronBlock
ccfg) BlockNodeToNodeVersion DualByronBlock
BlockNodeToNodeVersion ByronBlock
version
(SerialisedHeader ByronBlock -> Encoding)
-> (SerialisedHeader DualByronBlock -> SerialisedHeader ByronBlock)
-> SerialisedHeader DualByronBlock
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SerialisedHeader DualByronBlock -> SerialisedHeader ByronBlock
dualWrappedMain
decodeNodeToNode :: CodecConfig DualByronBlock
-> BlockNodeToNodeVersion DualByronBlock
-> forall s. Decoder s (SerialisedHeader DualByronBlock)
decodeNodeToNode CodecConfig DualByronBlock
ccfg BlockNodeToNodeVersion DualByronBlock
version =
SerialisedHeader ByronBlock -> SerialisedHeader DualByronBlock
rewrapMain
(SerialisedHeader ByronBlock -> SerialisedHeader DualByronBlock)
-> Decoder s (SerialisedHeader ByronBlock)
-> Decoder s (SerialisedHeader DualByronBlock)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CodecConfig ByronBlock
-> BlockNodeToNodeVersion ByronBlock
-> forall s. Decoder s (SerialisedHeader ByronBlock)
forall blk a.
SerialiseNodeToNode blk a =>
CodecConfig blk
-> BlockNodeToNodeVersion blk -> forall s. Decoder s a
decodeNodeToNode (CodecConfig DualByronBlock -> CodecConfig ByronBlock
forall m a. CodecConfig (DualBlock m a) -> CodecConfig m
dualCodecConfigMain CodecConfig DualByronBlock
ccfg) BlockNodeToNodeVersion DualByronBlock
BlockNodeToNodeVersion ByronBlock
version
instance SerialiseNodeToNode DualByronBlock (GenTx DualByronBlock) where
encodeNodeToNode :: CodecConfig DualByronBlock
-> BlockNodeToNodeVersion DualByronBlock
-> GenTx DualByronBlock
-> Encoding
encodeNodeToNode CodecConfig DualByronBlock
_ BlockNodeToNodeVersion DualByronBlock
_ = (GenTx ByronBlock -> Encoding) -> GenTx DualByronBlock -> Encoding
forall m a.
(Bridge m a, Serialise (GenTx a)) =>
(GenTx m -> Encoding) -> GenTx (DualBlock m a) -> Encoding
encodeDualGenTx GenTx ByronBlock -> Encoding
encodeByronGenTx
decodeNodeToNode :: CodecConfig DualByronBlock
-> BlockNodeToNodeVersion DualByronBlock
-> forall s. Decoder s (GenTx DualByronBlock)
decodeNodeToNode CodecConfig DualByronBlock
_ BlockNodeToNodeVersion DualByronBlock
_ = Decoder s (GenTx ByronBlock) -> Decoder s (GenTx DualByronBlock)
forall m a s.
(Bridge m a, Serialise (GenTx a)) =>
Decoder s (GenTx m) -> Decoder s (GenTx (DualBlock m a))
decodeDualGenTx Decoder s (GenTx ByronBlock)
forall s. Decoder s (GenTx ByronBlock)
decodeByronGenTx
instance SerialiseNodeToNode DualByronBlock (GenTxId DualByronBlock) where
encodeNodeToNode :: CodecConfig DualByronBlock
-> BlockNodeToNodeVersion DualByronBlock
-> GenTxId DualByronBlock
-> Encoding
encodeNodeToNode CodecConfig DualByronBlock
_ BlockNodeToNodeVersion DualByronBlock
_ = (GenTxId ByronBlock -> Encoding)
-> GenTxId DualByronBlock -> Encoding
forall m a.
(GenTxId m -> Encoding) -> GenTxId (DualBlock m a) -> Encoding
encodeDualGenTxId GenTxId ByronBlock -> Encoding
encodeByronGenTxId
decodeNodeToNode :: CodecConfig DualByronBlock
-> BlockNodeToNodeVersion DualByronBlock
-> forall s. Decoder s (GenTxId DualByronBlock)
decodeNodeToNode CodecConfig DualByronBlock
_ BlockNodeToNodeVersion DualByronBlock
_ = Decoder s (GenTxId ByronBlock)
-> Decoder s (GenTxId DualByronBlock)
forall s m a.
Decoder s (GenTxId m) -> Decoder s (GenTxId (DualBlock m a))
decodeDualGenTxId Decoder s (GenTxId ByronBlock)
forall s. Decoder s (GenTxId ByronBlock)
decodeByronGenTxId
instance SerialiseNodeToClientConstraints DualByronBlock
instance SerialiseNodeToClient DualByronBlock DualByronBlock where
encodeNodeToClient :: CodecConfig DualByronBlock
-> BlockNodeToClientVersion DualByronBlock
-> DualByronBlock
-> Encoding
encodeNodeToClient CodecConfig DualByronBlock
_ BlockNodeToClientVersion DualByronBlock
_ = (DualByronBlock -> Encoding) -> DualByronBlock -> Encoding
forall a. (a -> Encoding) -> a -> Encoding
wrapCBORinCBOR ((ByronBlock -> Encoding) -> DualByronBlock -> Encoding
forall m a.
(Bridge m a, Serialise a) =>
(m -> Encoding) -> DualBlock m a -> Encoding
encodeDualBlock ByronBlock -> Encoding
encodeByronBlock)
decodeNodeToClient :: CodecConfig DualByronBlock
-> BlockNodeToClientVersion DualByronBlock
-> forall s. Decoder s DualByronBlock
decodeNodeToClient CodecConfig DualByronBlock
ccfg BlockNodeToClientVersion DualByronBlock
_ = (forall s. Decoder s (ByteString -> DualByronBlock))
-> forall s. Decoder s DualByronBlock
forall a.
(forall s. Decoder s (ByteString -> a)) -> forall s. Decoder s a
unwrapCBORinCBOR (Decoder s (ByteString -> ByronBlock)
-> Decoder s (ByteString -> DualByronBlock)
forall m a s.
(Bridge m a, Serialise a) =>
Decoder s (ByteString -> m)
-> Decoder s (ByteString -> DualBlock m a)
decodeDualBlock (EpochSlots -> Decoder s (ByteString -> ByronBlock)
forall s. EpochSlots -> Decoder s (ByteString -> ByronBlock)
decodeByronBlock EpochSlots
epochSlots))
where
epochSlots :: EpochSlots
epochSlots = CodecConfig DualByronBlock -> EpochSlots
extractEpochSlots CodecConfig DualByronBlock
ccfg
instance SerialiseNodeToClient DualByronBlock (Serialised DualByronBlock)
instance SerialiseNodeToClient DualByronBlock (GenTx DualByronBlock) where
encodeNodeToClient :: CodecConfig DualByronBlock
-> BlockNodeToClientVersion DualByronBlock
-> GenTx DualByronBlock
-> Encoding
encodeNodeToClient CodecConfig DualByronBlock
_ BlockNodeToClientVersion DualByronBlock
_ = (GenTx ByronBlock -> Encoding) -> GenTx DualByronBlock -> Encoding
forall m a.
(Bridge m a, Serialise (GenTx a)) =>
(GenTx m -> Encoding) -> GenTx (DualBlock m a) -> Encoding
encodeDualGenTx GenTx ByronBlock -> Encoding
encodeByronGenTx
decodeNodeToClient :: CodecConfig DualByronBlock
-> BlockNodeToClientVersion DualByronBlock
-> forall s. Decoder s (GenTx DualByronBlock)
decodeNodeToClient CodecConfig DualByronBlock
_ BlockNodeToClientVersion DualByronBlock
_ = Decoder s (GenTx ByronBlock) -> Decoder s (GenTx DualByronBlock)
forall m a s.
(Bridge m a, Serialise (GenTx a)) =>
Decoder s (GenTx m) -> Decoder s (GenTx (DualBlock m a))
decodeDualGenTx Decoder s (GenTx ByronBlock)
forall s. Decoder s (GenTx ByronBlock)
decodeByronGenTx
instance SerialiseNodeToClient DualByronBlock (GenTxId DualByronBlock) where
encodeNodeToClient :: CodecConfig DualByronBlock
-> BlockNodeToClientVersion DualByronBlock
-> GenTxId DualByronBlock
-> Encoding
encodeNodeToClient CodecConfig DualByronBlock
_ BlockNodeToClientVersion DualByronBlock
_ = (GenTxId ByronBlock -> Encoding)
-> GenTxId DualByronBlock -> Encoding
forall m a.
(GenTxId m -> Encoding) -> GenTxId (DualBlock m a) -> Encoding
encodeDualGenTxId GenTxId ByronBlock -> Encoding
encodeByronGenTxId
decodeNodeToClient :: CodecConfig DualByronBlock
-> BlockNodeToClientVersion DualByronBlock
-> forall s. Decoder s (GenTxId DualByronBlock)
decodeNodeToClient CodecConfig DualByronBlock
_ BlockNodeToClientVersion DualByronBlock
_ = Decoder s (GenTxId ByronBlock)
-> Decoder s (GenTxId DualByronBlock)
forall s m a.
Decoder s (GenTxId m) -> Decoder s (GenTxId (DualBlock m a))
decodeDualGenTxId Decoder s (GenTxId ByronBlock)
forall s. Decoder s (GenTxId ByronBlock)
decodeByronGenTxId
instance SerialiseNodeToClient DualByronBlock (DualGenTxErr ByronBlock ByronSpecBlock) where
encodeNodeToClient :: CodecConfig DualByronBlock
-> BlockNodeToClientVersion DualByronBlock
-> DualGenTxErr ByronBlock ByronSpecBlock
-> Encoding
encodeNodeToClient CodecConfig DualByronBlock
_ BlockNodeToClientVersion DualByronBlock
_ = (ApplyTxErr ByronBlock -> Encoding)
-> ApplyTxErr DualByronBlock -> Encoding
forall a m.
Serialise (ApplyTxErr a) =>
(ApplyTxErr m -> Encoding)
-> ApplyTxErr (DualBlock m a) -> Encoding
encodeDualGenTxErr ApplyTxErr ByronBlock -> Encoding
encodeByronApplyTxError
decodeNodeToClient :: CodecConfig DualByronBlock
-> BlockNodeToClientVersion DualByronBlock
-> forall s. Decoder s (DualGenTxErr ByronBlock ByronSpecBlock)
decodeNodeToClient CodecConfig DualByronBlock
_ BlockNodeToClientVersion DualByronBlock
_ = Decoder s (ApplyTxErr ByronBlock)
-> Decoder s (ApplyTxErr DualByronBlock)
forall a s m.
Serialise (ApplyTxErr a) =>
Decoder s (ApplyTxErr m) -> Decoder s (ApplyTxErr (DualBlock m a))
decodeDualGenTxErr Decoder s (ApplyTxErr ByronBlock)
forall s. Decoder s (ApplyTxErr ByronBlock)
decodeByronApplyTxError
instance SerialiseNodeToClient DualByronBlock (SomeSecond BlockQuery DualByronBlock) where
encodeNodeToClient :: CodecConfig DualByronBlock
-> BlockNodeToClientVersion DualByronBlock
-> SomeSecond BlockQuery DualByronBlock
-> Encoding
encodeNodeToClient CodecConfig DualByronBlock
_ BlockNodeToClientVersion DualByronBlock
_ = \case {}
decodeNodeToClient :: CodecConfig DualByronBlock
-> BlockNodeToClientVersion DualByronBlock
-> forall s. Decoder s (SomeSecond BlockQuery DualByronBlock)
decodeNodeToClient CodecConfig DualByronBlock
_ BlockNodeToClientVersion DualByronBlock
_ = [Char] -> Decoder s (SomeSecond BlockQuery DualByronBlock)
forall a. HasCallStack => [Char] -> a
error [Char]
"DualByron: no query to decode"
instance SerialiseNodeToClient DualByronBlock SlotNo
instance SerialiseResult DualByronBlock (BlockQuery DualByronBlock) where
encodeResult :: forall result.
CodecConfig DualByronBlock
-> BlockNodeToClientVersion DualByronBlock
-> BlockQuery DualByronBlock result
-> result
-> Encoding
encodeResult CodecConfig DualByronBlock
_ BlockNodeToClientVersion DualByronBlock
_ = \case {}
decodeResult :: forall result.
CodecConfig DualByronBlock
-> BlockNodeToClientVersion DualByronBlock
-> BlockQuery DualByronBlock result
-> forall s. Decoder s result
decodeResult CodecConfig DualByronBlock
_ BlockNodeToClientVersion DualByronBlock
_ = \case {}
extractEpochSlots :: CodecConfig DualByronBlock -> EpochSlots
= CodecConfig ByronBlock -> EpochSlots
getByronEpochSlots (CodecConfig ByronBlock -> EpochSlots)
-> (CodecConfig DualByronBlock -> CodecConfig ByronBlock)
-> CodecConfig DualByronBlock
-> EpochSlots
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CodecConfig DualByronBlock -> CodecConfig ByronBlock
forall m a. CodecConfig (DualBlock m a) -> CodecConfig m
dualCodecConfigMain
dualWrappedMain :: SerialisedHeader DualByronBlock
-> SerialisedHeader ByronBlock
dualWrappedMain :: SerialisedHeader DualByronBlock -> SerialisedHeader ByronBlock
dualWrappedMain = (forall a.
NestedCtxt_ DualByronBlock Header a
-> NestedCtxt_ ByronBlock Header a)
-> SerialisedHeader DualByronBlock -> SerialisedHeader ByronBlock
forall blk blk'.
(forall a. NestedCtxt_ blk Header a -> NestedCtxt_ blk' Header a)
-> SerialisedHeader blk -> SerialisedHeader blk'
castSerialisedHeader NestedCtxt_ DualByronBlock Header a
-> NestedCtxt_ ByronBlock Header a
forall a.
NestedCtxt_ DualByronBlock Header a
-> NestedCtxt_ ByronBlock Header a
forall m a (f :: * -> *) x.
NestedCtxt_ (DualBlock m a) f x -> NestedCtxt_ m f x
ctxtDualMain
rewrapMain :: SerialisedHeader ByronBlock
-> SerialisedHeader DualByronBlock
rewrapMain :: SerialisedHeader ByronBlock -> SerialisedHeader DualByronBlock
rewrapMain = (forall a.
NestedCtxt_ ByronBlock Header a
-> NestedCtxt_ DualByronBlock Header a)
-> SerialisedHeader ByronBlock -> SerialisedHeader DualByronBlock
forall blk blk'.
(forall a. NestedCtxt_ blk Header a -> NestedCtxt_ blk' Header a)
-> SerialisedHeader blk -> SerialisedHeader blk'
castSerialisedHeader NestedCtxt_ ByronBlock Header a
-> NestedCtxt_ DualByronBlock Header a
forall a.
NestedCtxt_ ByronBlock Header a
-> NestedCtxt_ DualByronBlock Header a
forall m (f :: * -> *) x a.
NestedCtxt_ m f x -> NestedCtxt_ (DualBlock m a) f x
CtxtDual