{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE QuantifiedConstraints #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToNode () where
import Codec.CBOR.Decoding (Decoder)
import Codec.CBOR.Encoding (Encoding)
import qualified Codec.Serialise as Serialise
import Control.Exception (throw)
import Data.Proxy
import Data.SOP.NonEmpty (ProofNonEmpty (..), isNonEmpty)
import Data.SOP.Strict
import Ouroboros.Consensus.Block
import Ouroboros.Consensus.HardFork.Combinator.Abstract.SingleEraBlock
import Ouroboros.Consensus.HardFork.Combinator.AcrossEras
import Ouroboros.Consensus.HardFork.Combinator.Basics
import Ouroboros.Consensus.HardFork.Combinator.Block
import Ouroboros.Consensus.HardFork.Combinator.Mempool
import Ouroboros.Consensus.HardFork.Combinator.Serialisation.Common
import Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk ()
import Ouroboros.Consensus.Ledger.SupportsMempool
import Ouroboros.Consensus.Node.NetworkProtocolVersion
import Ouroboros.Consensus.Node.Run
import Ouroboros.Consensus.Node.Serialisation
import Ouroboros.Consensus.Storage.Serialisation
import Ouroboros.Consensus.Util ((.:))
import Ouroboros.Network.Block (Serialised, unwrapCBORinCBOR,
wrapCBORinCBOR)
instance SerialiseHFC xs => SerialiseNodeToNodeConstraints (HardForkBlock xs) where
estimateBlockSize :: Header (HardForkBlock xs) -> SizeInBytes
estimateBlockSize = Header (HardForkBlock xs) -> SizeInBytes
forall (xs :: [*]).
SerialiseHFC xs =>
Header (HardForkBlock xs) -> SizeInBytes
estimateHfcBlockSize
dispatchEncoder :: forall f xs. (
SerialiseHFC xs
, forall blk. SerialiseNodeToNodeConstraints blk
=> SerialiseNodeToNode blk (f blk)
)
=> CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs)
-> NS f xs -> Encoding
dispatchEncoder :: CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs) -> NS f xs -> Encoding
dispatchEncoder CodecConfig (HardForkBlock xs)
ccfg BlockNodeToNodeVersion (HardForkBlock xs)
version NS f xs
ns =
case Proxy xs -> ProofNonEmpty xs
forall a (xs :: [a]) (proxy :: [a] -> *).
IsNonEmpty xs =>
proxy xs -> ProofNonEmpty xs
isNonEmpty (Proxy xs
forall k (t :: k). Proxy t
Proxy @xs) of
ProofNonEmpty {} ->
case (NP CodecConfig xs
ccfgs, BlockNodeToNodeVersion (HardForkBlock xs)
HardForkNodeToNodeVersion xs
version, NS f xs
ns) of
(CodecConfig x
c0 :* NP CodecConfig xs
_, HardForkNodeToNodeDisabled v0, Z f x
x0) ->
CodecConfig x -> BlockNodeToNodeVersion x -> f x -> Encoding
forall blk a.
SerialiseNodeToNode blk a =>
CodecConfig blk -> BlockNodeToNodeVersion blk -> a -> Encoding
encodeNodeToNode CodecConfig x
c0 BlockNodeToNodeVersion x
BlockNodeToNodeVersion x
v0 f x
x0
(NP CodecConfig xs
_, HardForkNodeToNodeDisabled BlockNodeToNodeVersion x
_, S NS f xs
later) ->
HardForkEncoderException -> Encoding
forall a e. Exception e => e -> a
throw (HardForkEncoderException -> Encoding)
-> HardForkEncoderException -> Encoding
forall a b. (a -> b) -> a -> b
$ NS SingleEraInfo xs -> HardForkEncoderException
forall (xs :: [*]).
SListI xs =>
NS SingleEraInfo xs -> HardForkEncoderException
futureEraException (NS f xs -> NS SingleEraInfo xs
forall (xs :: [*]) (f :: * -> *).
All SingleEraBlock xs =>
NS f xs -> NS SingleEraInfo xs
notFirstEra NS f xs
later)
(NP CodecConfig xs
_, HardForkNodeToNodeEnabled HardForkSpecificNodeToNodeVersion
_ NP EraNodeToNodeVersion xs
versions, NS f xs
_) ->
NP (f -.-> K Encoding) xs -> NS f xs -> Encoding
forall (xs :: [*]) (f :: * -> *).
SListI xs =>
NP (f -.-> K Encoding) xs -> NS f xs -> Encoding
encodeNS (Proxy SerialiseConstraintsHFC
-> (forall a.
SerialiseConstraintsHFC a =>
CodecConfig a -> EraNodeToNodeVersion a -> (-.->) f (K Encoding) a)
-> Prod NP CodecConfig xs
-> NP EraNodeToNodeVersion xs
-> NP (f -.-> K Encoding) xs
forall k l (h :: (k -> *) -> l -> *) (c :: k -> Constraint)
(xs :: l) (proxy :: (k -> Constraint) -> *) (f :: k -> *)
(f' :: k -> *) (f'' :: k -> *).
(AllN (Prod h) c xs, HAp h, HAp (Prod h)) =>
proxy c
-> (forall (a :: k). c a => f a -> f' a -> f'' a)
-> Prod h f xs
-> h f' xs
-> h f'' xs
hczipWith Proxy SerialiseConstraintsHFC
pSHFC forall blk.
(SingleEraBlock blk, SerialiseNodeToNodeConstraints blk) =>
CodecConfig blk
-> EraNodeToNodeVersion blk -> (-.->) f (K Encoding) blk
forall a.
SerialiseConstraintsHFC a =>
CodecConfig a -> EraNodeToNodeVersion a -> (-.->) f (K Encoding) a
aux Prod NP CodecConfig xs
NP CodecConfig xs
ccfgs NP EraNodeToNodeVersion xs
versions) NS f xs
ns
where
ccfgs :: NP CodecConfig xs
ccfgs = PerEraCodecConfig xs -> NP CodecConfig xs
forall (xs :: [*]). PerEraCodecConfig xs -> NP CodecConfig xs
getPerEraCodecConfig (PerEraCodecConfig xs -> NP CodecConfig xs)
-> PerEraCodecConfig xs -> NP CodecConfig xs
forall a b. (a -> b) -> a -> b
$ CodecConfig (HardForkBlock xs) -> PerEraCodecConfig xs
forall (xs :: [*]).
CodecConfig (HardForkBlock xs) -> PerEraCodecConfig xs
hardForkCodecConfigPerEra CodecConfig (HardForkBlock xs)
ccfg
aux :: forall blk. (SingleEraBlock blk, SerialiseNodeToNodeConstraints blk)
=> CodecConfig blk
-> EraNodeToNodeVersion blk
-> (f -.-> K Encoding) blk
aux :: CodecConfig blk
-> EraNodeToNodeVersion blk -> (-.->) f (K Encoding) blk
aux CodecConfig blk
ccfg' (EraNodeToNodeEnabled BlockNodeToNodeVersion blk
v) = (f blk -> K Encoding blk) -> (-.->) f (K Encoding) blk
forall k (f :: k -> *) (g :: k -> *) (a :: k).
(f a -> g a) -> (-.->) f g a
Fn ((f blk -> K Encoding blk) -> (-.->) f (K Encoding) blk)
-> (f blk -> K Encoding blk) -> (-.->) f (K Encoding) blk
forall a b. (a -> b) -> a -> b
$ Encoding -> K Encoding blk
forall k a (b :: k). a -> K a b
K (Encoding -> K Encoding blk)
-> (f blk -> Encoding) -> f blk -> K Encoding blk
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CodecConfig blk -> BlockNodeToNodeVersion blk -> f blk -> Encoding
forall blk a.
SerialiseNodeToNode blk a =>
CodecConfig blk -> BlockNodeToNodeVersion blk -> a -> Encoding
encodeNodeToNode CodecConfig blk
ccfg' BlockNodeToNodeVersion blk
v
aux CodecConfig blk
_ EraNodeToNodeVersion blk
EraNodeToNodeDisabled = (f blk -> K Encoding blk) -> (-.->) f (K Encoding) blk
forall k (f :: k -> *) (g :: k -> *) (a :: k).
(f a -> g a) -> (-.->) f g a
Fn ((f blk -> K Encoding blk) -> (-.->) f (K Encoding) blk)
-> (f blk -> K Encoding blk) -> (-.->) f (K Encoding) blk
forall a b. (a -> b) -> a -> b
$ \f blk
_ ->
HardForkEncoderException -> K Encoding blk
forall a e. Exception e => e -> a
throw (HardForkEncoderException -> K Encoding blk)
-> HardForkEncoderException -> K Encoding blk
forall a b. (a -> b) -> a -> b
$ Proxy blk -> HardForkEncoderException
forall blk.
SingleEraBlock blk =>
Proxy blk -> HardForkEncoderException
disabledEraException (Proxy blk
forall k (t :: k). Proxy t
Proxy @blk)
dispatchDecoder :: forall f xs. (
SerialiseHFC xs
, forall blk. SerialiseNodeToNodeConstraints blk
=> SerialiseNodeToNode blk (f blk)
)
=> CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs)
-> forall s. Decoder s (NS f xs)
dispatchDecoder :: CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs)
-> forall s. Decoder s (NS f xs)
dispatchDecoder CodecConfig (HardForkBlock xs)
ccfg BlockNodeToNodeVersion (HardForkBlock xs)
version =
case Proxy xs -> ProofNonEmpty xs
forall a (xs :: [a]) (proxy :: [a] -> *).
IsNonEmpty xs =>
proxy xs -> ProofNonEmpty xs
isNonEmpty (Proxy xs
forall k (t :: k). Proxy t
Proxy @xs) of
ProofNonEmpty {} ->
case (NP CodecConfig xs
ccfgs, BlockNodeToNodeVersion (HardForkBlock xs)
HardForkNodeToNodeVersion xs
version) of
(CodecConfig x
c0 :* NP CodecConfig xs
_, HardForkNodeToNodeDisabled v0) ->
f x -> NS f (x : xs)
forall a (f :: a -> *) (x :: a) (xs :: [a]). f x -> NS f (x : xs)
Z (f x -> NS f (x : xs))
-> Decoder s (f x) -> Decoder s (NS f (x : xs))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CodecConfig x
-> BlockNodeToNodeVersion x -> forall s. Decoder s (f x)
forall blk a.
SerialiseNodeToNode blk a =>
CodecConfig blk
-> BlockNodeToNodeVersion blk -> forall s. Decoder s a
decodeNodeToNode CodecConfig x
c0 BlockNodeToNodeVersion x
BlockNodeToNodeVersion x
v0
(NP CodecConfig xs
_, HardForkNodeToNodeEnabled HardForkSpecificNodeToNodeVersion
_ NP EraNodeToNodeVersion xs
versions) ->
NP (Decoder s :.: f) xs -> Decoder s (NS f xs)
forall (xs :: [*]) s (f :: * -> *).
SListI xs =>
NP (Decoder s :.: f) xs -> Decoder s (NS f xs)
decodeNS (Proxy SerialiseConstraintsHFC
-> (forall a.
SerialiseConstraintsHFC a =>
CodecConfig a -> EraNodeToNodeVersion a -> (:.:) (Decoder s) f a)
-> Prod NP CodecConfig xs
-> NP EraNodeToNodeVersion xs
-> NP (Decoder s :.: f) xs
forall k l (h :: (k -> *) -> l -> *) (c :: k -> Constraint)
(xs :: l) (proxy :: (k -> Constraint) -> *) (f :: k -> *)
(f' :: k -> *) (f'' :: k -> *).
(AllN (Prod h) c xs, HAp h, HAp (Prod h)) =>
proxy c
-> (forall (a :: k). c a => f a -> f' a -> f'' a)
-> Prod h f xs
-> h f' xs
-> h f'' xs
hczipWith Proxy SerialiseConstraintsHFC
pSHFC forall blk.
(SingleEraBlock blk, SerialiseNodeToNodeConstraints blk) =>
CodecConfig blk
-> EraNodeToNodeVersion blk -> forall s. (:.:) (Decoder s) f blk
forall a.
SerialiseConstraintsHFC a =>
CodecConfig a -> EraNodeToNodeVersion a -> (:.:) (Decoder s) f a
aux Prod NP CodecConfig xs
NP CodecConfig xs
ccfgs NP EraNodeToNodeVersion xs
versions)
where
ccfgs :: NP CodecConfig xs
ccfgs = PerEraCodecConfig xs -> NP CodecConfig xs
forall (xs :: [*]). PerEraCodecConfig xs -> NP CodecConfig xs
getPerEraCodecConfig (PerEraCodecConfig xs -> NP CodecConfig xs)
-> PerEraCodecConfig xs -> NP CodecConfig xs
forall a b. (a -> b) -> a -> b
$ CodecConfig (HardForkBlock xs) -> PerEraCodecConfig xs
forall (xs :: [*]).
CodecConfig (HardForkBlock xs) -> PerEraCodecConfig xs
hardForkCodecConfigPerEra CodecConfig (HardForkBlock xs)
ccfg
aux :: forall blk. (SingleEraBlock blk, SerialiseNodeToNodeConstraints blk)
=> CodecConfig blk
-> EraNodeToNodeVersion blk
-> forall s. (Decoder s :.: f) blk
aux :: CodecConfig blk
-> EraNodeToNodeVersion blk -> forall s. (:.:) (Decoder s) f blk
aux CodecConfig blk
ccfg' (EraNodeToNodeEnabled BlockNodeToNodeVersion blk
v) = Decoder s (f blk) -> (:.:) (Decoder s) f blk
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp (Decoder s (f blk) -> (:.:) (Decoder s) f blk)
-> Decoder s (f blk) -> (:.:) (Decoder s) f blk
forall a b. (a -> b) -> a -> b
$ CodecConfig blk
-> BlockNodeToNodeVersion blk -> forall s. Decoder s (f blk)
forall blk a.
SerialiseNodeToNode blk a =>
CodecConfig blk
-> BlockNodeToNodeVersion blk -> forall s. Decoder s a
decodeNodeToNode CodecConfig blk
ccfg' BlockNodeToNodeVersion blk
v
aux CodecConfig blk
_ EraNodeToNodeVersion blk
EraNodeToNodeDisabled = Decoder s (f blk) -> (:.:) (Decoder s) f blk
forall l k (f :: l -> *) (g :: k -> l) (p :: k).
f (g p) -> (:.:) f g p
Comp (Decoder s (f blk) -> (:.:) (Decoder s) f blk)
-> Decoder s (f blk) -> (:.:) (Decoder s) f blk
forall a b. (a -> b) -> a -> b
$
String -> Decoder s (f blk)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Decoder s (f blk))
-> (HardForkEncoderException -> String)
-> HardForkEncoderException
-> Decoder s (f blk)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HardForkEncoderException -> String
forall a. Show a => a -> String
show (HardForkEncoderException -> Decoder s (f blk))
-> HardForkEncoderException -> Decoder s (f blk)
forall a b. (a -> b) -> a -> b
$ Proxy blk -> HardForkEncoderException
forall blk.
SingleEraBlock blk =>
Proxy blk -> HardForkEncoderException
disabledEraException (Proxy blk
forall k (t :: k). Proxy t
Proxy @blk)
after :: (a -> b -> d -> e) -> (c -> d) -> a -> b -> c -> e
after :: (a -> b -> d -> e) -> (c -> d) -> a -> b -> c -> e
after a -> b -> d -> e
f c -> d
g a
x b
y c
z = a -> b -> d -> e
f a
x b
y (c -> d
g c
z)
instance SerialiseHFC xs
=> SerialiseNodeToNode (HardForkBlock xs) (HardForkBlock xs) where
encodeNodeToNode :: CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs)
-> HardForkBlock xs
-> Encoding
encodeNodeToNode CodecConfig (HardForkBlock xs)
ccfg BlockNodeToNodeVersion (HardForkBlock xs)
_ = (HardForkBlock xs -> Encoding) -> HardForkBlock xs -> Encoding
forall a. (a -> Encoding) -> a -> Encoding
wrapCBORinCBOR (CodecConfig (HardForkBlock xs) -> HardForkBlock xs -> Encoding
forall (xs :: [*]).
SerialiseHFC xs =>
CodecConfig (HardForkBlock xs) -> HardForkBlock xs -> Encoding
encodeDiskHfcBlock CodecConfig (HardForkBlock xs)
ccfg)
decodeNodeToNode :: CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs)
-> forall s. Decoder s (HardForkBlock xs)
decodeNodeToNode CodecConfig (HardForkBlock xs)
ccfg BlockNodeToNodeVersion (HardForkBlock xs)
_ = (forall s. Decoder s (ByteString -> HardForkBlock xs))
-> forall s. Decoder s (HardForkBlock xs)
forall a.
(forall s. Decoder s (ByteString -> a)) -> forall s. Decoder s a
unwrapCBORinCBOR (CodecConfig (HardForkBlock xs)
-> forall s. Decoder s (ByteString -> HardForkBlock xs)
forall (xs :: [*]).
SerialiseHFC xs =>
CodecConfig (HardForkBlock xs)
-> forall s. Decoder s (ByteString -> HardForkBlock xs)
decodeDiskHfcBlock CodecConfig (HardForkBlock xs)
ccfg)
instance SerialiseHFC xs
=> SerialiseNodeToNode (HardForkBlock xs) (Header (HardForkBlock xs)) where
encodeNodeToNode :: CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs)
-> Header (HardForkBlock xs)
-> Encoding
encodeNodeToNode = CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs -> NS Header xs -> Encoding
forall (f :: * -> *) (xs :: [*]).
(SerialiseHFC xs,
forall blk.
SerialiseNodeToNodeConstraints blk =>
SerialiseNodeToNode blk (f blk)) =>
CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs) -> NS f xs -> Encoding
dispatchEncoder (CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs -> NS Header xs -> Encoding)
-> (Header (HardForkBlock xs) -> NS Header xs)
-> CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs
-> Header (HardForkBlock xs)
-> Encoding
forall a b d e c.
(a -> b -> d -> e) -> (c -> d) -> a -> b -> c -> e
`after` (OneEraHeader xs -> NS Header xs
forall (xs :: [*]). OneEraHeader xs -> NS Header xs
getOneEraHeader (OneEraHeader xs -> NS Header xs)
-> (Header (HardForkBlock xs) -> OneEraHeader xs)
-> Header (HardForkBlock xs)
-> NS Header xs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Header (HardForkBlock xs) -> OneEraHeader xs
forall (xs :: [*]). Header (HardForkBlock xs) -> OneEraHeader xs
getHardForkHeader)
decodeNodeToNode :: CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs)
-> forall s. Decoder s (Header (HardForkBlock xs))
decodeNodeToNode = (NS Header xs -> Header (HardForkBlock xs))
-> Decoder s (NS Header xs)
-> Decoder s (Header (HardForkBlock xs))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (OneEraHeader xs -> Header (HardForkBlock xs)
forall (xs :: [*]). OneEraHeader xs -> Header (HardForkBlock xs)
HardForkHeader (OneEraHeader xs -> Header (HardForkBlock xs))
-> (NS Header xs -> OneEraHeader xs)
-> NS Header xs
-> Header (HardForkBlock xs)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NS Header xs -> OneEraHeader xs
forall (xs :: [*]). NS Header xs -> OneEraHeader xs
OneEraHeader) (Decoder s (NS Header xs) -> Decoder s (Header (HardForkBlock xs)))
-> (CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs -> Decoder s (NS Header xs))
-> CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs
-> Decoder s (Header (HardForkBlock xs))
forall y z x0 x1. (y -> z) -> (x0 -> x1 -> y) -> x0 -> x1 -> z
.: CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs -> Decoder s (NS Header xs)
forall (f :: * -> *) (xs :: [*]).
(SerialiseHFC xs,
forall blk.
SerialiseNodeToNodeConstraints blk =>
SerialiseNodeToNode blk (f blk)) =>
CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs)
-> forall s. Decoder s (NS f xs)
dispatchDecoder
instance SerialiseHFC xs
=> SerialiseNodeToNode (HardForkBlock xs) (Serialised (HardForkBlock xs)) where
encodeNodeToNode :: CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs)
-> Serialised (HardForkBlock xs)
-> Encoding
encodeNodeToNode CodecConfig (HardForkBlock xs)
_ BlockNodeToNodeVersion (HardForkBlock xs)
_ = Serialised (HardForkBlock xs) -> Encoding
forall a. Serialise a => a -> Encoding
Serialise.encode
decodeNodeToNode :: CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs)
-> forall s. Decoder s (Serialised (HardForkBlock xs))
decodeNodeToNode CodecConfig (HardForkBlock xs)
_ BlockNodeToNodeVersion (HardForkBlock xs)
_ = Decoder s (Serialised (HardForkBlock xs))
forall a s. Serialise a => Decoder s a
Serialise.decode
instance SerialiseHFC xs
=> SerialiseNodeToNode (HardForkBlock xs) (SerialisedHeader (HardForkBlock xs)) where
encodeNodeToNode :: CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs)
-> SerialisedHeader (HardForkBlock xs)
-> Encoding
encodeNodeToNode = CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs
-> NS SerialisedHeader xs
-> Encoding
forall (f :: * -> *) (xs :: [*]).
(SerialiseHFC xs,
forall blk.
SerialiseNodeToNodeConstraints blk =>
SerialiseNodeToNode blk (f blk)) =>
CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs) -> NS f xs -> Encoding
dispatchEncoder (CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs
-> NS SerialisedHeader xs
-> Encoding)
-> (SerialisedHeader (HardForkBlock xs) -> NS SerialisedHeader xs)
-> CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs
-> SerialisedHeader (HardForkBlock xs)
-> Encoding
forall a b d e c.
(a -> b -> d -> e) -> (c -> d) -> a -> b -> c -> e
`after` SerialisedHeader (HardForkBlock xs) -> NS SerialisedHeader xs
forall (xs :: [*]).
SerialisedHeader (HardForkBlock xs) -> NS SerialisedHeader xs
distribSerialisedHeader
decodeNodeToNode :: CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs)
-> forall s. Decoder s (SerialisedHeader (HardForkBlock xs))
decodeNodeToNode = (NS SerialisedHeader xs -> SerialisedHeader (HardForkBlock xs))
-> Decoder s (NS SerialisedHeader xs)
-> Decoder s (SerialisedHeader (HardForkBlock xs))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap NS SerialisedHeader xs -> SerialisedHeader (HardForkBlock xs)
forall (xs :: [*]).
NS SerialisedHeader xs -> SerialisedHeader (HardForkBlock xs)
undistribSerialisedHeader (Decoder s (NS SerialisedHeader xs)
-> Decoder s (SerialisedHeader (HardForkBlock xs)))
-> (CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs
-> Decoder s (NS SerialisedHeader xs))
-> CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs
-> Decoder s (SerialisedHeader (HardForkBlock xs))
forall y z x0 x1. (y -> z) -> (x0 -> x1 -> y) -> x0 -> x1 -> z
.: CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs
-> Decoder s (NS SerialisedHeader xs)
forall (f :: * -> *) (xs :: [*]).
(SerialiseHFC xs,
forall blk.
SerialiseNodeToNodeConstraints blk =>
SerialiseNodeToNode blk (f blk)) =>
CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs)
-> forall s. Decoder s (NS f xs)
dispatchDecoder
instance SerialiseHFC xs
=> SerialiseNodeToNode (HardForkBlock xs) (GenTx (HardForkBlock xs)) where
encodeNodeToNode :: CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs)
-> GenTx (HardForkBlock xs)
-> Encoding
encodeNodeToNode = CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs -> NS GenTx xs -> Encoding
forall (f :: * -> *) (xs :: [*]).
(SerialiseHFC xs,
forall blk.
SerialiseNodeToNodeConstraints blk =>
SerialiseNodeToNode blk (f blk)) =>
CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs) -> NS f xs -> Encoding
dispatchEncoder (CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs -> NS GenTx xs -> Encoding)
-> (GenTx (HardForkBlock xs) -> NS GenTx xs)
-> CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs
-> GenTx (HardForkBlock xs)
-> Encoding
forall a b d e c.
(a -> b -> d -> e) -> (c -> d) -> a -> b -> c -> e
`after` (OneEraGenTx xs -> NS GenTx xs
forall (xs :: [*]). OneEraGenTx xs -> NS GenTx xs
getOneEraGenTx (OneEraGenTx xs -> NS GenTx xs)
-> (GenTx (HardForkBlock xs) -> OneEraGenTx xs)
-> GenTx (HardForkBlock xs)
-> NS GenTx xs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenTx (HardForkBlock xs) -> OneEraGenTx xs
forall (xs :: [*]). GenTx (HardForkBlock xs) -> OneEraGenTx xs
getHardForkGenTx)
decodeNodeToNode :: CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs)
-> forall s. Decoder s (GenTx (HardForkBlock xs))
decodeNodeToNode = (NS GenTx xs -> GenTx (HardForkBlock xs))
-> Decoder s (NS GenTx xs) -> Decoder s (GenTx (HardForkBlock xs))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (OneEraGenTx xs -> GenTx (HardForkBlock xs)
forall (xs :: [*]). OneEraGenTx xs -> GenTx (HardForkBlock xs)
HardForkGenTx (OneEraGenTx xs -> GenTx (HardForkBlock xs))
-> (NS GenTx xs -> OneEraGenTx xs)
-> NS GenTx xs
-> GenTx (HardForkBlock xs)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NS GenTx xs -> OneEraGenTx xs
forall (xs :: [*]). NS GenTx xs -> OneEraGenTx xs
OneEraGenTx) (Decoder s (NS GenTx xs) -> Decoder s (GenTx (HardForkBlock xs)))
-> (CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs -> Decoder s (NS GenTx xs))
-> CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs
-> Decoder s (GenTx (HardForkBlock xs))
forall y z x0 x1. (y -> z) -> (x0 -> x1 -> y) -> x0 -> x1 -> z
.: CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs -> Decoder s (NS GenTx xs)
forall (f :: * -> *) (xs :: [*]).
(SerialiseHFC xs,
forall blk.
SerialiseNodeToNodeConstraints blk =>
SerialiseNodeToNode blk (f blk)) =>
CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs)
-> forall s. Decoder s (NS f xs)
dispatchDecoder
instance SerialiseHFC xs
=> SerialiseNodeToNode (HardForkBlock xs) (GenTxId (HardForkBlock xs)) where
encodeNodeToNode :: CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs)
-> GenTxId (HardForkBlock xs)
-> Encoding
encodeNodeToNode = CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs -> NS WrapGenTxId xs -> Encoding
forall (f :: * -> *) (xs :: [*]).
(SerialiseHFC xs,
forall blk.
SerialiseNodeToNodeConstraints blk =>
SerialiseNodeToNode blk (f blk)) =>
CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs) -> NS f xs -> Encoding
dispatchEncoder (CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs -> NS WrapGenTxId xs -> Encoding)
-> (GenTxId (HardForkBlock xs) -> NS WrapGenTxId xs)
-> CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs
-> GenTxId (HardForkBlock xs)
-> Encoding
forall a b d e c.
(a -> b -> d -> e) -> (c -> d) -> a -> b -> c -> e
`after` (OneEraGenTxId xs -> NS WrapGenTxId xs
forall (xs :: [*]). OneEraGenTxId xs -> NS WrapGenTxId xs
getOneEraGenTxId (OneEraGenTxId xs -> NS WrapGenTxId xs)
-> (GenTxId (HardForkBlock xs) -> OneEraGenTxId xs)
-> GenTxId (HardForkBlock xs)
-> NS WrapGenTxId xs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GenTxId (HardForkBlock xs) -> OneEraGenTxId xs
forall (xs :: [*]).
TxId (GenTx (HardForkBlock xs)) -> OneEraGenTxId xs
getHardForkGenTxId)
decodeNodeToNode :: CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs)
-> forall s. Decoder s (GenTxId (HardForkBlock xs))
decodeNodeToNode = (NS WrapGenTxId xs -> GenTxId (HardForkBlock xs))
-> Decoder s (NS WrapGenTxId xs)
-> Decoder s (GenTxId (HardForkBlock xs))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (OneEraGenTxId xs -> GenTxId (HardForkBlock xs)
forall (xs :: [*]).
OneEraGenTxId xs -> TxId (GenTx (HardForkBlock xs))
HardForkGenTxId (OneEraGenTxId xs -> GenTxId (HardForkBlock xs))
-> (NS WrapGenTxId xs -> OneEraGenTxId xs)
-> NS WrapGenTxId xs
-> GenTxId (HardForkBlock xs)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NS WrapGenTxId xs -> OneEraGenTxId xs
forall (xs :: [*]). NS WrapGenTxId xs -> OneEraGenTxId xs
OneEraGenTxId) (Decoder s (NS WrapGenTxId xs)
-> Decoder s (GenTxId (HardForkBlock xs)))
-> (CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs -> Decoder s (NS WrapGenTxId xs))
-> CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs
-> Decoder s (GenTxId (HardForkBlock xs))
forall y z x0 x1. (y -> z) -> (x0 -> x1 -> y) -> x0 -> x1 -> z
.: CodecConfig (HardForkBlock xs)
-> HardForkNodeToNodeVersion xs -> Decoder s (NS WrapGenTxId xs)
forall (f :: * -> *) (xs :: [*]).
(SerialiseHFC xs,
forall blk.
SerialiseNodeToNodeConstraints blk =>
SerialiseNodeToNode blk (f blk)) =>
CodecConfig (HardForkBlock xs)
-> BlockNodeToNodeVersion (HardForkBlock xs)
-> forall s. Decoder s (NS f xs)
dispatchDecoder