{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE StandaloneDeriving #-}
module Ouroboros.Consensus.Protocol.Praos.Header (
Header (Header, headerBody, headerSig)
, HeaderBody (..)
, headerHash
, headerSize
) where
import qualified Cardano.Crypto.Hash as Hash
import qualified Cardano.Crypto.KES as KES
import Cardano.Crypto.Util
(SignableRepresentation (getSignableRepresentation))
import Cardano.Ledger.BaseTypes (ProtVer (pvMajor))
import Cardano.Ledger.Binary (Annotator (..), CBORGroup (unCBORGroup),
DecCBOR (decCBOR), EncCBOR (..), ToCBOR (..),
encodedSigKESSizeExpr, serialize', withSlice)
import Cardano.Ledger.Binary.Coders
import qualified Cardano.Ledger.Binary.Plain as Plain
import Cardano.Ledger.Crypto (Crypto (HASH))
import Cardano.Ledger.Hashes (EraIndependentBlockBody,
EraIndependentBlockHeader)
import Cardano.Ledger.Keys (CertifiedVRF, Hash, KeyRole (BlockIssuer),
SignedKES, VKey, VerKeyVRF, decodeSignedKES,
decodeVerKeyVRF, encodeSignedKES, encodeVerKeyVRF)
import Cardano.Protocol.TPraos.BHeader (PrevHash)
import Cardano.Protocol.TPraos.OCert (OCert)
import Cardano.Slotting.Block (BlockNo)
import Cardano.Slotting.Slot (SlotNo)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Lazy as BSL
import Data.Word (Word32)
import GHC.Generics (Generic)
import NoThunks.Class (AllowThunksIn (..), NoThunks (..))
import Ouroboros.Consensus.Protocol.Praos.VRF (InputVRF)
data HeaderBody crypto = HeaderBody
{
forall crypto. HeaderBody crypto -> BlockNo
hbBlockNo :: !BlockNo,
forall crypto. HeaderBody crypto -> SlotNo
hbSlotNo :: !SlotNo,
forall crypto. HeaderBody crypto -> PrevHash crypto
hbPrev :: !(PrevHash crypto),
forall crypto. HeaderBody crypto -> VKey 'BlockIssuer crypto
hbVk :: !(VKey 'BlockIssuer crypto),
forall crypto. HeaderBody crypto -> VerKeyVRF crypto
hbVrfVk :: !(VerKeyVRF crypto),
forall crypto. HeaderBody crypto -> CertifiedVRF crypto InputVRF
hbVrfRes :: !(CertifiedVRF crypto InputVRF),
forall crypto. HeaderBody crypto -> Word32
hbBodySize :: !Word32,
forall crypto.
HeaderBody crypto -> Hash crypto EraIndependentBlockBody
hbBodyHash :: !(Hash crypto EraIndependentBlockBody),
forall crypto. HeaderBody crypto -> OCert crypto
hbOCert :: !(OCert crypto),
forall crypto. HeaderBody crypto -> ProtVer
hbProtVer :: !ProtVer
}
deriving ((forall x. HeaderBody crypto -> Rep (HeaderBody crypto) x)
-> (forall x. Rep (HeaderBody crypto) x -> HeaderBody crypto)
-> Generic (HeaderBody crypto)
forall x. Rep (HeaderBody crypto) x -> HeaderBody crypto
forall x. HeaderBody crypto -> Rep (HeaderBody crypto) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall crypto x. Rep (HeaderBody crypto) x -> HeaderBody crypto
forall crypto x. HeaderBody crypto -> Rep (HeaderBody crypto) x
$cfrom :: forall crypto x. HeaderBody crypto -> Rep (HeaderBody crypto) x
from :: forall x. HeaderBody crypto -> Rep (HeaderBody crypto) x
$cto :: forall crypto x. Rep (HeaderBody crypto) x -> HeaderBody crypto
to :: forall x. Rep (HeaderBody crypto) x -> HeaderBody crypto
Generic)
deriving instance Crypto crypto => Show (HeaderBody crypto)
deriving instance Crypto crypto => Eq (HeaderBody crypto)
instance
Crypto crypto =>
SignableRepresentation (HeaderBody crypto)
where
getSignableRepresentation :: HeaderBody crypto -> ByteString
getSignableRepresentation HeaderBody crypto
hb = Version -> HeaderBody crypto -> ByteString
forall a. EncCBOR a => Version -> a -> ByteString
serialize' (ProtVer -> Version
pvMajor (HeaderBody crypto -> ProtVer
forall crypto. HeaderBody crypto -> ProtVer
hbProtVer HeaderBody crypto
hb)) HeaderBody crypto
hb
instance
Crypto crypto =>
NoThunks (HeaderBody crypto)
data crypto =
{ forall crypto. HeaderRaw crypto -> HeaderBody crypto
headerRawBody :: !(HeaderBody crypto),
:: !(SignedKES crypto (HeaderBody crypto))
}
deriving (Int -> HeaderRaw crypto -> ShowS
[HeaderRaw crypto] -> ShowS
HeaderRaw crypto -> String
(Int -> HeaderRaw crypto -> ShowS)
-> (HeaderRaw crypto -> String)
-> ([HeaderRaw crypto] -> ShowS)
-> Show (HeaderRaw crypto)
forall crypto. Crypto crypto => Int -> HeaderRaw crypto -> ShowS
forall crypto. Crypto crypto => [HeaderRaw crypto] -> ShowS
forall crypto. Crypto crypto => HeaderRaw crypto -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall crypto. Crypto crypto => Int -> HeaderRaw crypto -> ShowS
showsPrec :: Int -> HeaderRaw crypto -> ShowS
$cshow :: forall crypto. Crypto crypto => HeaderRaw crypto -> String
show :: HeaderRaw crypto -> String
$cshowList :: forall crypto. Crypto crypto => [HeaderRaw crypto] -> ShowS
showList :: [HeaderRaw crypto] -> ShowS
Show, (forall x. HeaderRaw crypto -> Rep (HeaderRaw crypto) x)
-> (forall x. Rep (HeaderRaw crypto) x -> HeaderRaw crypto)
-> Generic (HeaderRaw crypto)
forall x. Rep (HeaderRaw crypto) x -> HeaderRaw crypto
forall x. HeaderRaw crypto -> Rep (HeaderRaw crypto) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall crypto x. Rep (HeaderRaw crypto) x -> HeaderRaw crypto
forall crypto x. HeaderRaw crypto -> Rep (HeaderRaw crypto) x
$cfrom :: forall crypto x. HeaderRaw crypto -> Rep (HeaderRaw crypto) x
from :: forall x. HeaderRaw crypto -> Rep (HeaderRaw crypto) x
$cto :: forall crypto x. Rep (HeaderRaw crypto) x -> HeaderRaw crypto
to :: forall x. Rep (HeaderRaw crypto) x -> HeaderRaw crypto
Generic)
instance Crypto c => Eq (HeaderRaw c) where
HeaderRaw c
h1 == :: HeaderRaw c -> HeaderRaw c -> Bool
== HeaderRaw c
h2 = HeaderRaw c -> SignedKES (KES c) (HeaderBody c)
forall crypto.
HeaderRaw crypto -> SignedKES crypto (HeaderBody crypto)
headerRawSig HeaderRaw c
h1 SignedKES (KES c) (HeaderBody c)
-> SignedKES (KES c) (HeaderBody c) -> Bool
forall a. Eq a => a -> a -> Bool
== HeaderRaw c -> SignedKES (KES c) (HeaderBody c)
forall crypto.
HeaderRaw crypto -> SignedKES crypto (HeaderBody crypto)
headerRawSig HeaderRaw c
h2
Bool -> Bool -> Bool
&& HeaderRaw c -> HeaderBody c
forall crypto. HeaderRaw crypto -> HeaderBody crypto
headerRawBody HeaderRaw c
h1 HeaderBody c -> HeaderBody c -> Bool
forall a. Eq a => a -> a -> Bool
== HeaderRaw c -> HeaderBody c
forall crypto. HeaderRaw crypto -> HeaderBody crypto
headerRawBody HeaderRaw c
h2
instance Crypto c => Eq (Header c) where
Header c
h1 == :: Header c -> Header c -> Bool
== Header c
h2 = Header c -> ByteString
forall crypto. Header crypto -> ByteString
headerBytes Header c
h1 ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== Header c -> ByteString
forall crypto. Header crypto -> ByteString
headerBytes Header c
h2
Bool -> Bool -> Bool
&& Header c -> HeaderRaw c
forall crypto. Header crypto -> HeaderRaw crypto
headerRaw Header c
h1 HeaderRaw c -> HeaderRaw c -> Bool
forall a. Eq a => a -> a -> Bool
== Header c -> HeaderRaw c
forall crypto. Header crypto -> HeaderRaw crypto
headerRaw Header c
h2
instance
Crypto crypto =>
NoThunks (HeaderRaw crypto)
data crypto =
{ :: !(HeaderRaw crypto)
, :: BS.ByteString
}
deriving (Int -> Header crypto -> ShowS
[Header crypto] -> ShowS
Header crypto -> String
(Int -> Header crypto -> ShowS)
-> (Header crypto -> String)
-> ([Header crypto] -> ShowS)
-> Show (Header crypto)
forall crypto. Crypto crypto => Int -> Header crypto -> ShowS
forall crypto. Crypto crypto => [Header crypto] -> ShowS
forall crypto. Crypto crypto => Header crypto -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall crypto. Crypto crypto => Int -> Header crypto -> ShowS
showsPrec :: Int -> Header crypto -> ShowS
$cshow :: forall crypto. Crypto crypto => Header crypto -> String
show :: Header crypto -> String
$cshowList :: forall crypto. Crypto crypto => [Header crypto] -> ShowS
showList :: [Header crypto] -> ShowS
Show, (forall x. Header crypto -> Rep (Header crypto) x)
-> (forall x. Rep (Header crypto) x -> Header crypto)
-> Generic (Header crypto)
forall x. Rep (Header crypto) x -> Header crypto
forall x. Header crypto -> Rep (Header crypto) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall crypto x. Rep (Header crypto) x -> Header crypto
forall crypto x. Header crypto -> Rep (Header crypto) x
$cfrom :: forall crypto x. Header crypto -> Rep (Header crypto) x
from :: forall x. Header crypto -> Rep (Header crypto) x
$cto :: forall crypto x. Rep (Header crypto) x -> Header crypto
to :: forall x. Rep (Header crypto) x -> Header crypto
Generic)
deriving (Context -> Header crypto -> IO (Maybe ThunkInfo)
Proxy (Header crypto) -> String
(Context -> Header crypto -> IO (Maybe ThunkInfo))
-> (Context -> Header crypto -> IO (Maybe ThunkInfo))
-> (Proxy (Header crypto) -> String)
-> NoThunks (Header crypto)
forall crypto.
Crypto crypto =>
Context -> Header crypto -> IO (Maybe ThunkInfo)
forall crypto. Crypto crypto => Proxy (Header crypto) -> String
forall a.
(Context -> a -> IO (Maybe ThunkInfo))
-> (Context -> a -> IO (Maybe ThunkInfo))
-> (Proxy a -> String)
-> NoThunks a
$cnoThunks :: forall crypto.
Crypto crypto =>
Context -> Header crypto -> IO (Maybe ThunkInfo)
noThunks :: Context -> Header crypto -> IO (Maybe ThunkInfo)
$cwNoThunks :: forall crypto.
Crypto crypto =>
Context -> Header crypto -> IO (Maybe ThunkInfo)
wNoThunks :: Context -> Header crypto -> IO (Maybe ThunkInfo)
$cshowTypeOf :: forall crypto. Crypto crypto => Proxy (Header crypto) -> String
showTypeOf :: Proxy (Header crypto) -> String
NoThunks) via AllowThunksIn '["headerBytes"] (Header crypto)
pattern Header ::
Crypto crypto =>
HeaderBody crypto ->
SignedKES crypto (HeaderBody crypto) ->
Header crypto
pattern {forall crypto. Crypto crypto => Header crypto -> HeaderBody crypto
headerBody, } <-
HeaderConstr {
headerRaw =
HeaderRaw
{ headerRawBody = headerBody
, headerRawSig = headerSig
}
}
where
Header HeaderBody crypto
body SignedKES crypto (HeaderBody crypto)
sig =
let header :: HeaderRaw crypto
header = HeaderRaw
{ headerRawBody :: HeaderBody crypto
headerRawBody = HeaderBody crypto
body
, headerRawSig :: SignedKES crypto (HeaderBody crypto)
headerRawSig = SignedKES crypto (HeaderBody crypto)
sig
}
in HeaderConstr
{ headerRaw :: HeaderRaw crypto
headerRaw = HeaderRaw crypto
header
, headerBytes :: ByteString
headerBytes = Version -> HeaderRaw crypto -> ByteString
forall a. EncCBOR a => Version -> a -> ByteString
serialize' (ProtVer -> Version
pvMajor (HeaderBody crypto -> ProtVer
forall crypto. HeaderBody crypto -> ProtVer
hbProtVer HeaderBody crypto
body)) HeaderRaw crypto
header
}
{-# COMPLETE Header #-}
headerSize :: Header crypto -> Int
(HeaderConstr HeaderRaw crypto
_ ByteString
bytes) = ByteString -> Int
BS.length ByteString
bytes
headerHash ::
Crypto crypto =>
Header crypto ->
Hash.Hash (HASH crypto) EraIndependentBlockHeader
= Hash (HASH crypto) (Header crypto)
-> Hash (HASH crypto) EraIndependentBlockHeader
forall h a b. Hash h a -> Hash h b
Hash.castHash (Hash (HASH crypto) (Header crypto)
-> Hash (HASH crypto) EraIndependentBlockHeader)
-> (Header crypto -> Hash (HASH crypto) (Header crypto))
-> Header crypto
-> Hash (HASH crypto) EraIndependentBlockHeader
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Header crypto -> Encoding)
-> Header crypto -> Hash (HASH crypto) (Header crypto)
forall h a. HashAlgorithm h => (a -> Encoding) -> a -> Hash h a
Hash.hashWithSerialiser Header crypto -> Encoding
forall a. ToCBOR a => a -> Encoding
toCBOR
instance Crypto crypto => EncCBOR (HeaderBody crypto) where
encCBOR :: HeaderBody crypto -> Encoding
encCBOR
HeaderBody
{ BlockNo
hbBlockNo :: forall crypto. HeaderBody crypto -> BlockNo
hbBlockNo :: BlockNo
hbBlockNo,
SlotNo
hbSlotNo :: forall crypto. HeaderBody crypto -> SlotNo
hbSlotNo :: SlotNo
hbSlotNo,
PrevHash crypto
hbPrev :: forall crypto. HeaderBody crypto -> PrevHash crypto
hbPrev :: PrevHash crypto
hbPrev,
VKey 'BlockIssuer crypto
hbVk :: forall crypto. HeaderBody crypto -> VKey 'BlockIssuer crypto
hbVk :: VKey 'BlockIssuer crypto
hbVk,
VerKeyVRF crypto
hbVrfVk :: forall crypto. HeaderBody crypto -> VerKeyVRF crypto
hbVrfVk :: VerKeyVRF crypto
hbVrfVk,
CertifiedVRF (VRF crypto) InputVRF
hbVrfRes :: forall crypto. HeaderBody crypto -> CertifiedVRF crypto InputVRF
hbVrfRes :: CertifiedVRF (VRF crypto) InputVRF
hbVrfRes,
Word32
hbBodySize :: forall crypto. HeaderBody crypto -> Word32
hbBodySize :: Word32
hbBodySize,
Hash (HASH crypto) EraIndependentBlockBody
hbBodyHash :: forall crypto.
HeaderBody crypto -> Hash crypto EraIndependentBlockBody
hbBodyHash :: Hash (HASH crypto) EraIndependentBlockBody
hbBodyHash,
OCert crypto
hbOCert :: forall crypto. HeaderBody crypto -> OCert crypto
hbOCert :: OCert crypto
hbOCert,
ProtVer
hbProtVer :: forall crypto. HeaderBody crypto -> ProtVer
hbProtVer :: ProtVer
hbProtVer
} =
Encode ('Closed 'Dense) (HeaderBody crypto) -> Encoding
forall (w :: Wrapped) t. Encode w t -> Encoding
encode (Encode ('Closed 'Dense) (HeaderBody crypto) -> Encoding)
-> Encode ('Closed 'Dense) (HeaderBody crypto) -> Encoding
forall a b. (a -> b) -> a -> b
$
(BlockNo
-> SlotNo
-> PrevHash crypto
-> VKey 'BlockIssuer crypto
-> VerKeyVRF crypto
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
-> Encode
('Closed 'Dense)
(BlockNo
-> SlotNo
-> PrevHash crypto
-> VKey 'BlockIssuer crypto
-> VerKeyVRF crypto
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
forall t. t -> Encode ('Closed 'Dense) t
Rec BlockNo
-> SlotNo
-> PrevHash crypto
-> VKey 'BlockIssuer crypto
-> VerKeyVRF crypto
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto
forall crypto.
BlockNo
-> SlotNo
-> PrevHash crypto
-> VKey 'BlockIssuer crypto
-> VerKeyVRF crypto
-> CertifiedVRF crypto InputVRF
-> Word32
-> Hash crypto EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto
HeaderBody
Encode
('Closed 'Dense)
(BlockNo
-> SlotNo
-> PrevHash crypto
-> VKey 'BlockIssuer crypto
-> VerKeyVRF crypto
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
-> Encode ('Closed 'Dense) BlockNo
-> Encode
('Closed 'Dense)
(SlotNo
-> PrevHash crypto
-> VKey 'BlockIssuer crypto
-> VerKeyVRF crypto
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> BlockNo -> Encode ('Closed 'Dense) BlockNo
forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To BlockNo
hbBlockNo
Encode
('Closed 'Dense)
(SlotNo
-> PrevHash crypto
-> VKey 'BlockIssuer crypto
-> VerKeyVRF crypto
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
-> Encode ('Closed 'Dense) SlotNo
-> Encode
('Closed 'Dense)
(PrevHash crypto
-> VKey 'BlockIssuer crypto
-> VerKeyVRF crypto
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> SlotNo -> Encode ('Closed 'Dense) SlotNo
forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To SlotNo
hbSlotNo
Encode
('Closed 'Dense)
(PrevHash crypto
-> VKey 'BlockIssuer crypto
-> VerKeyVRF crypto
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
-> Encode ('Closed 'Dense) (PrevHash crypto)
-> Encode
('Closed 'Dense)
(VKey 'BlockIssuer crypto
-> VerKeyVRF crypto
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> PrevHash crypto -> Encode ('Closed 'Dense) (PrevHash crypto)
forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To PrevHash crypto
hbPrev
Encode
('Closed 'Dense)
(VKey 'BlockIssuer crypto
-> VerKeyVRF crypto
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
-> Encode ('Closed 'Dense) (VKey 'BlockIssuer crypto)
-> Encode
('Closed 'Dense)
(VerKeyVRF crypto
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> VKey 'BlockIssuer crypto
-> Encode ('Closed 'Dense) (VKey 'BlockIssuer crypto)
forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To VKey 'BlockIssuer crypto
hbVk
Encode
('Closed 'Dense)
(VerKeyVRF crypto
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
-> Encode ('Closed 'Dense) (VerKeyVRF crypto)
-> Encode
('Closed 'Dense)
(CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> (VerKeyVRF crypto -> Encoding)
-> VerKeyVRF crypto -> Encode ('Closed 'Dense) (VerKeyVRF crypto)
forall t. (t -> Encoding) -> t -> Encode ('Closed 'Dense) t
E VerKeyVRF crypto -> Encoding
forall v. VRFAlgorithm v => VerKeyVRF v -> Encoding
encodeVerKeyVRF VerKeyVRF crypto
hbVrfVk
Encode
('Closed 'Dense)
(CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
-> Encode ('Closed 'Dense) (CertifiedVRF (VRF crypto) InputVRF)
-> Encode
('Closed 'Dense)
(Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> CertifiedVRF (VRF crypto) InputVRF
-> Encode ('Closed 'Dense) (CertifiedVRF (VRF crypto) InputVRF)
forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To CertifiedVRF (VRF crypto) InputVRF
hbVrfRes
Encode
('Closed 'Dense)
(Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
-> Encode ('Closed 'Dense) Word32
-> Encode
('Closed 'Dense)
(Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto -> ProtVer -> HeaderBody crypto)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> Word32 -> Encode ('Closed 'Dense) Word32
forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Word32
hbBodySize
Encode
('Closed 'Dense)
(Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto -> ProtVer -> HeaderBody crypto)
-> Encode
('Closed 'Dense) (Hash (HASH crypto) EraIndependentBlockBody)
-> Encode
('Closed 'Dense) (OCert crypto -> ProtVer -> HeaderBody crypto)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> Hash (HASH crypto) EraIndependentBlockBody
-> Encode
('Closed 'Dense) (Hash (HASH crypto) EraIndependentBlockBody)
forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To Hash (HASH crypto) EraIndependentBlockBody
hbBodyHash
Encode
('Closed 'Dense) (OCert crypto -> ProtVer -> HeaderBody crypto)
-> Encode ('Closed 'Dense) (OCert crypto)
-> Encode ('Closed 'Dense) (ProtVer -> HeaderBody crypto)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> OCert crypto -> Encode ('Closed 'Dense) (OCert crypto)
forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To OCert crypto
hbOCert
Encode ('Closed 'Dense) (ProtVer -> HeaderBody crypto)
-> Encode ('Closed 'Dense) ProtVer
-> Encode ('Closed 'Dense) (HeaderBody crypto)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> ProtVer -> Encode ('Closed 'Dense) ProtVer
forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To ProtVer
hbProtVer
instance Crypto crypto => DecCBOR (HeaderBody crypto) where
decCBOR :: forall s. Decoder s (HeaderBody crypto)
decCBOR =
Decode ('Closed 'Dense) (HeaderBody crypto)
-> Decoder s (HeaderBody crypto)
forall (w :: Wrapped) t s. Decode w t -> Decoder s t
decode (Decode ('Closed 'Dense) (HeaderBody crypto)
-> Decoder s (HeaderBody crypto))
-> Decode ('Closed 'Dense) (HeaderBody crypto)
-> Decoder s (HeaderBody crypto)
forall a b. (a -> b) -> a -> b
$
(BlockNo
-> SlotNo
-> PrevHash crypto
-> VKey 'BlockIssuer crypto
-> VerKeyVRF (VRF crypto)
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
-> Decode
('Closed 'Dense)
(BlockNo
-> SlotNo
-> PrevHash crypto
-> VKey 'BlockIssuer crypto
-> VerKeyVRF (VRF crypto)
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
forall t. t -> Decode ('Closed 'Dense) t
RecD BlockNo
-> SlotNo
-> PrevHash crypto
-> VKey 'BlockIssuer crypto
-> VerKeyVRF (VRF crypto)
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto
forall crypto.
BlockNo
-> SlotNo
-> PrevHash crypto
-> VKey 'BlockIssuer crypto
-> VerKeyVRF crypto
-> CertifiedVRF crypto InputVRF
-> Word32
-> Hash crypto EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto
HeaderBody
Decode
('Closed 'Dense)
(BlockNo
-> SlotNo
-> PrevHash crypto
-> VKey 'BlockIssuer crypto
-> VerKeyVRF (VRF crypto)
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
-> Decode ('Closed Any) BlockNo
-> Decode
('Closed 'Dense)
(SlotNo
-> PrevHash crypto
-> VKey 'BlockIssuer crypto
-> VerKeyVRF (VRF crypto)
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) BlockNo
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Decode
('Closed 'Dense)
(SlotNo
-> PrevHash crypto
-> VKey 'BlockIssuer crypto
-> VerKeyVRF (VRF crypto)
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
-> Decode ('Closed Any) SlotNo
-> Decode
('Closed 'Dense)
(PrevHash crypto
-> VKey 'BlockIssuer crypto
-> VerKeyVRF (VRF crypto)
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) SlotNo
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Decode
('Closed 'Dense)
(PrevHash crypto
-> VKey 'BlockIssuer crypto
-> VerKeyVRF (VRF crypto)
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
-> Decode ('Closed Any) (PrevHash crypto)
-> Decode
('Closed 'Dense)
(VKey 'BlockIssuer crypto
-> VerKeyVRF (VRF crypto)
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) (PrevHash crypto)
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Decode
('Closed 'Dense)
(VKey 'BlockIssuer crypto
-> VerKeyVRF (VRF crypto)
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
-> Decode ('Closed Any) (VKey 'BlockIssuer crypto)
-> Decode
('Closed 'Dense)
(VerKeyVRF (VRF crypto)
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) (VKey 'BlockIssuer crypto)
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Decode
('Closed 'Dense)
(VerKeyVRF (VRF crypto)
-> CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
-> Decode ('Closed 'Dense) (VerKeyVRF (VRF crypto))
-> Decode
('Closed 'Dense)
(CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! (forall s. Decoder s (VerKeyVRF (VRF crypto)))
-> Decode ('Closed 'Dense) (VerKeyVRF (VRF crypto))
forall t. (forall s. Decoder s t) -> Decode ('Closed 'Dense) t
D Decoder s (VerKeyVRF (VRF crypto))
forall s. Decoder s (VerKeyVRF (VRF crypto))
forall v s. VRFAlgorithm v => Decoder s (VerKeyVRF v)
decodeVerKeyVRF
Decode
('Closed 'Dense)
(CertifiedVRF (VRF crypto) InputVRF
-> Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
-> Decode ('Closed Any) (CertifiedVRF (VRF crypto) InputVRF)
-> Decode
('Closed 'Dense)
(Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) (CertifiedVRF (VRF crypto) InputVRF)
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Decode
('Closed 'Dense)
(Word32
-> Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto
-> ProtVer
-> HeaderBody crypto)
-> Decode ('Closed Any) Word32
-> Decode
('Closed 'Dense)
(Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto -> ProtVer -> HeaderBody crypto)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) Word32
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Decode
('Closed 'Dense)
(Hash (HASH crypto) EraIndependentBlockBody
-> OCert crypto -> ProtVer -> HeaderBody crypto)
-> Decode
('Closed Any) (Hash (HASH crypto) EraIndependentBlockBody)
-> Decode
('Closed 'Dense) (OCert crypto -> ProtVer -> HeaderBody crypto)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) (Hash (HASH crypto) EraIndependentBlockBody)
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
Decode
('Closed 'Dense) (OCert crypto -> ProtVer -> HeaderBody crypto)
-> Decode ('Closed Any) (OCert crypto)
-> Decode ('Closed 'Dense) (ProtVer -> HeaderBody crypto)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! (CBORGroup (OCert crypto) -> OCert crypto
forall a. CBORGroup a -> a
unCBORGroup (CBORGroup (OCert crypto) -> OCert crypto)
-> Decode ('Closed Any) (CBORGroup (OCert crypto))
-> Decode ('Closed Any) (OCert crypto)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decode ('Closed Any) (CBORGroup (OCert crypto))
forall t (w :: Wrapped). DecCBOR t => Decode w t
From)
Decode ('Closed 'Dense) (ProtVer -> HeaderBody crypto)
-> Decode ('Closed Any) ProtVer
-> Decode ('Closed 'Dense) (HeaderBody crypto)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) ProtVer
forall t (w :: Wrapped). DecCBOR t => Decode w t
From
encodeHeaderRaw ::
Crypto crypto =>
HeaderRaw crypto ->
Encode ('Closed 'Dense) (HeaderRaw crypto)
(HeaderRaw HeaderBody crypto
body SignedKES crypto (HeaderBody crypto)
sig) =
(HeaderBody crypto
-> SignedKES crypto (HeaderBody crypto) -> HeaderRaw crypto)
-> Encode
('Closed 'Dense)
(HeaderBody crypto
-> SignedKES crypto (HeaderBody crypto) -> HeaderRaw crypto)
forall t. t -> Encode ('Closed 'Dense) t
Rec HeaderBody crypto
-> SignedKES crypto (HeaderBody crypto) -> HeaderRaw crypto
forall crypto.
HeaderBody crypto
-> SignedKES crypto (HeaderBody crypto) -> HeaderRaw crypto
HeaderRaw Encode
('Closed 'Dense)
(HeaderBody crypto
-> SignedKES crypto (HeaderBody crypto) -> HeaderRaw crypto)
-> Encode ('Closed 'Dense) (HeaderBody crypto)
-> Encode
('Closed 'Dense)
(SignedKES crypto (HeaderBody crypto) -> HeaderRaw crypto)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> HeaderBody crypto -> Encode ('Closed 'Dense) (HeaderBody crypto)
forall t. EncCBOR t => t -> Encode ('Closed 'Dense) t
To HeaderBody crypto
body Encode
('Closed 'Dense)
(SignedKES crypto (HeaderBody crypto) -> HeaderRaw crypto)
-> Encode ('Closed 'Dense) (SignedKES crypto (HeaderBody crypto))
-> Encode ('Closed 'Dense) (HeaderRaw crypto)
forall (w :: Wrapped) a t (r :: Density).
Encode w (a -> t) -> Encode ('Closed r) a -> Encode w t
!> (SignedKES crypto (HeaderBody crypto) -> Encoding)
-> SignedKES crypto (HeaderBody crypto)
-> Encode ('Closed 'Dense) (SignedKES crypto (HeaderBody crypto))
forall t. (t -> Encoding) -> t -> Encode ('Closed 'Dense) t
E SignedKES crypto (HeaderBody crypto) -> Encoding
forall v a. KESAlgorithm v => SignedKES v a -> Encoding
encodeSignedKES SignedKES crypto (HeaderBody crypto)
sig
instance Crypto crypto => EncCBOR (HeaderRaw crypto) where
encCBOR :: HeaderRaw crypto -> Encoding
encCBOR = Encode ('Closed 'Dense) (HeaderRaw crypto) -> Encoding
forall (w :: Wrapped) t. Encode w t -> Encoding
encode (Encode ('Closed 'Dense) (HeaderRaw crypto) -> Encoding)
-> (HeaderRaw crypto -> Encode ('Closed 'Dense) (HeaderRaw crypto))
-> HeaderRaw crypto
-> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HeaderRaw crypto -> Encode ('Closed 'Dense) (HeaderRaw crypto)
forall crypto.
Crypto crypto =>
HeaderRaw crypto -> Encode ('Closed 'Dense) (HeaderRaw crypto)
encodeHeaderRaw
instance Crypto crypto => DecCBOR (HeaderRaw crypto) where
decCBOR :: forall s. Decoder s (HeaderRaw crypto)
decCBOR = Decode ('Closed 'Dense) (HeaderRaw crypto)
-> Decoder s (HeaderRaw crypto)
forall (w :: Wrapped) t s. Decode w t -> Decoder s t
decode (Decode ('Closed 'Dense) (HeaderRaw crypto)
-> Decoder s (HeaderRaw crypto))
-> Decode ('Closed 'Dense) (HeaderRaw crypto)
-> Decoder s (HeaderRaw crypto)
forall a b. (a -> b) -> a -> b
$ (HeaderBody crypto
-> SignedKES (KES crypto) (HeaderBody crypto) -> HeaderRaw crypto)
-> Decode
('Closed 'Dense)
(HeaderBody crypto
-> SignedKES (KES crypto) (HeaderBody crypto) -> HeaderRaw crypto)
forall t. t -> Decode ('Closed 'Dense) t
RecD HeaderBody crypto
-> SignedKES (KES crypto) (HeaderBody crypto) -> HeaderRaw crypto
forall crypto.
HeaderBody crypto
-> SignedKES crypto (HeaderBody crypto) -> HeaderRaw crypto
HeaderRaw Decode
('Closed 'Dense)
(HeaderBody crypto
-> SignedKES (KES crypto) (HeaderBody crypto) -> HeaderRaw crypto)
-> Decode ('Closed Any) (HeaderBody crypto)
-> Decode
('Closed 'Dense)
(SignedKES (KES crypto) (HeaderBody crypto) -> HeaderRaw crypto)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! Decode ('Closed Any) (HeaderBody crypto)
forall t (w :: Wrapped). DecCBOR t => Decode w t
From Decode
('Closed 'Dense)
(SignedKES (KES crypto) (HeaderBody crypto) -> HeaderRaw crypto)
-> Decode
('Closed 'Dense) (SignedKES (KES crypto) (HeaderBody crypto))
-> Decode ('Closed 'Dense) (HeaderRaw crypto)
forall (w1 :: Wrapped) a t (w :: Density).
Decode w1 (a -> t) -> Decode ('Closed w) a -> Decode w1 t
<! (forall s. Decoder s (SignedKES (KES crypto) (HeaderBody crypto)))
-> Decode
('Closed 'Dense) (SignedKES (KES crypto) (HeaderBody crypto))
forall t. (forall s. Decoder s t) -> Decode ('Closed 'Dense) t
D Decoder s (SignedKES (KES crypto) (HeaderBody crypto))
forall s. Decoder s (SignedKES (KES crypto) (HeaderBody crypto))
forall v s a. KESAlgorithm v => Decoder s (SignedKES v a)
decodeSignedKES
instance Crypto crypto => DecCBOR (Annotator (HeaderRaw crypto)) where
decCBOR :: forall s. Decoder s (Annotator (HeaderRaw crypto))
decCBOR = HeaderRaw crypto -> Annotator (HeaderRaw crypto)
forall a. a -> Annotator a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (HeaderRaw crypto -> Annotator (HeaderRaw crypto))
-> Decoder s (HeaderRaw crypto)
-> Decoder s (Annotator (HeaderRaw crypto))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Decoder s (HeaderRaw crypto)
forall s. Decoder s (HeaderRaw crypto)
forall a s. DecCBOR a => Decoder s a
decCBOR
instance Crypto c => Plain.ToCBOR (Header c) where
toCBOR :: Header c -> Encoding
toCBOR (HeaderConstr HeaderRaw c
_ ByteString
bytes) = ByteString -> Encoding
Plain.encodePreEncoded ByteString
bytes
instance Crypto c => EncCBOR (Header c) where
encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (Header c) -> Size
encodedSizeExpr forall t. EncCBOR t => Proxy t -> Size
size Proxy (Header c)
proxy =
Size
1
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ (forall t. EncCBOR t => Proxy t -> Size)
-> Proxy (HeaderBody c) -> Size
forall a.
EncCBOR a =>
(forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size
encodedSizeExpr Proxy t -> Size
forall t. EncCBOR t => Proxy t -> Size
size (HeaderRaw c -> HeaderBody c
forall crypto. HeaderRaw crypto -> HeaderBody crypto
headerRawBody (HeaderRaw c -> HeaderBody c)
-> (Header c -> HeaderRaw c) -> Header c -> HeaderBody c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Header c -> HeaderRaw c
forall crypto. Header crypto -> HeaderRaw crypto
headerRaw (Header c -> HeaderBody c)
-> Proxy (Header c) -> Proxy (HeaderBody c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy (Header c)
proxy)
Size -> Size -> Size
forall a. Num a => a -> a -> a
+ Proxy (SigKES (KES c)) -> Size
forall v. KESAlgorithm v => Proxy (SigKES v) -> Size
encodedSigKESSizeExpr (SignedKES (KES c) (HeaderBody c) -> SigKES (KES c)
forall v a. SignedKES v a -> SigKES v
KES.getSig (SignedKES (KES c) (HeaderBody c) -> SigKES (KES c))
-> (Header c -> SignedKES (KES c) (HeaderBody c))
-> Header c
-> SigKES (KES c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. HeaderRaw c -> SignedKES (KES c) (HeaderBody c)
forall crypto.
HeaderRaw crypto -> SignedKES crypto (HeaderBody crypto)
headerRawSig (HeaderRaw c -> SignedKES (KES c) (HeaderBody c))
-> (Header c -> HeaderRaw c)
-> Header c
-> SignedKES (KES c) (HeaderBody c)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Header c -> HeaderRaw c
forall crypto. Header crypto -> HeaderRaw crypto
headerRaw (Header c -> SigKES (KES c))
-> Proxy (Header c) -> Proxy (SigKES (KES c))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Proxy (Header c)
proxy)
instance Crypto c => DecCBOR (Annotator (Header c)) where
decCBOR :: forall s. Decoder s (Annotator (Header c))
decCBOR = do
(Annotator FullByteString -> HeaderRaw c
getT, Annotator FullByteString -> ByteString
getBytes) <- Decoder s (Annotator (HeaderRaw c))
-> Decoder s (Annotator (HeaderRaw c), Annotator ByteString)
forall s a. Decoder s a -> Decoder s (a, Annotator ByteString)
withSlice Decoder s (Annotator (HeaderRaw c))
forall s. Decoder s (Annotator (HeaderRaw c))
forall a s. DecCBOR a => Decoder s a
decCBOR
Annotator (Header c) -> Decoder s (Annotator (Header c))
forall a. a -> Decoder s a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((FullByteString -> Header c) -> Annotator (Header c)
forall a. (FullByteString -> a) -> Annotator a
Annotator (\FullByteString
fullbytes -> HeaderRaw c -> ByteString -> Header c
forall crypto. HeaderRaw crypto -> ByteString -> Header crypto
HeaderConstr (FullByteString -> HeaderRaw c
getT FullByteString
fullbytes) (ByteString -> ByteString
BSL.toStrict (FullByteString -> ByteString
getBytes FullByteString
fullbytes))))