Skip to content

Commit b93a33a

Browse files
committed
dmq: updated Sig according to the CIP#137
* signed fields of Sig include: `sigRawId`, `sigRawBody`, `sigRawKESPeriod`, `sigRawExpiresAt`. * added `SigRawWithSignedBytes`, which carries signed bytes by the KES key.
1 parent 844684b commit b93a33a

File tree

5 files changed

+138
-69
lines changed

5 files changed

+138
-69
lines changed

decentralized-message-queue/decentralized-message-queue.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -120,6 +120,7 @@ test-suite dmq-test
120120
QuickCheck,
121121
base >=4.14 && <4.22,
122122
cborg,
123+
cardano-binary,
123124
decentralized-message-queue,
124125
ouroboros-network-api,
125126
ouroboros-network-protocols:testlib,

decentralized-message-queue/src/DMQ/Protocol/SigSubmission/Codec.hs

Lines changed: 23 additions & 33 deletions
Original file line numberDiff line numberDiff line change
@@ -10,8 +10,8 @@ module DMQ.Protocol.SigSubmission.Codec
1010
, byteLimitsSigSubmission
1111
, timeLimitsSigSubmission
1212
, codecSigSubmissionId
13-
-- * Utils for testing
14-
, encodeSigRaw
13+
-- * Exported utility functions
14+
, encodeSigId
1515
) where
1616

1717
import Control.Monad (when)
@@ -29,6 +29,7 @@ import Network.TypedProtocol.Codec.CBOR
2929
import DMQ.Protocol.SigSubmission.Type
3030
import Ouroboros.Network.Protocol.Limits
3131
import Ouroboros.Network.Protocol.TxSubmission2.Codec qualified as TX
32+
import Ouroboros.Network.Protocol.TxSubmission2.Codec (cborBytesFromOffsets)
3233

3334

3435
-- | 'SigSubmission' time limits.
@@ -83,26 +84,6 @@ decodeSigId :: forall s. CBOR.Decoder s SigId
8384
decodeSigId = SigId . SigHash <$> CBOR.decodeBytes
8485

8586

86-
encodeSigRaw :: SigRaw
87-
-> CBOR.Encoding
88-
encodeSigRaw SigRaw {
89-
sigRawId,
90-
sigRawBody,
91-
sigRawKESPeriod,
92-
sigRawKESSignature,
93-
sigRawOpCertificate,
94-
sigRawExpiresAt,
95-
sigRawColdKey
96-
}
97-
= CBOR.encodeListLen 7
98-
<> encodeSigId sigRawId
99-
<> CBOR.encodeBytes (getSigBody sigRawBody)
100-
<> CBOR.encodeWord32 sigRawKESPeriod
101-
<> CBOR.encodeWord32 (floor sigRawExpiresAt)
102-
<> CBOR.encodeBytes (getSigOpCertificate sigRawOpCertificate)
103-
<> CBOR.encodeBytes (getSigColdKey sigRawColdKey)
104-
<> CBOR.encodeBytes (getSigKESSignature sigRawKESSignature)
105-
10687
-- | 'SigSubmission' protocol codec.
10788
--
10889
codecSigSubmission
@@ -118,25 +99,34 @@ codecSigSubmission =
11899
encodeSig :: Sig -> CBOR.Encoding
119100
encodeSig = TX.encodeBytes . sigRawBytes
120101

121-
decodeSig :: forall s. CBOR.Decoder s (ByteString -> SigRaw)
102+
decodeSig :: forall s. CBOR.Decoder s (ByteString -> SigRawWithSignedBytes)
122103
decodeSig = do
104+
-- start of signed data
105+
startOffset <- CBOR.peekByteOffset
123106
a <- CBOR.decodeListLen
124107
when (a /= 7) $ fail (printf "codecSigSubmission: unexpected number of parameters %d" a)
125108
sigRawId <- decodeSigId
126109
sigRawBody <- SigBody <$> CBOR.decodeBytes
127-
sigRawKESPeriod <- CBOR.decodeWord32
110+
sigRawKESPeriod <- CBOR.decodeWord
128111
sigRawExpiresAt <- realToFrac <$> CBOR.decodeWord32
112+
-- end of signed data
113+
endOffset <- CBOR.peekByteOffset
114+
115+
sigRawKESSignature <- SigKESSignature <$> CBOR.decodeBytes
129116
sigRawOpCertificate <- SigOpCertificate <$> CBOR.decodeBytes
130117
sigRawColdKey <- SigColdKey <$> CBOR.decodeBytes
131-
sigRawKESSignature <- SigKESSignature <$> CBOR.decodeBytes
132-
return $ \_ -> SigRaw {
133-
sigRawId,
134-
sigRawBody,
135-
sigRawKESSignature,
136-
sigRawKESPeriod,
137-
sigRawOpCertificate,
138-
sigRawColdKey,
139-
sigRawExpiresAt
118+
return $ \bytes -- ^ full bytes of the message, not just the sig part
119+
-> SigRawWithSignedBytes {
120+
sigRawSignedBytes = cborBytesFromOffsets startOffset endOffset bytes,
121+
sigRaw = SigRaw {
122+
sigRawId,
123+
sigRawBody,
124+
sigRawKESSignature,
125+
sigRawKESPeriod,
126+
sigRawOpCertificate,
127+
sigRawColdKey,
128+
sigRawExpiresAt
129+
}
140130
}
141131

142132

decentralized-message-queue/src/DMQ/Protocol/SigSubmission/Type.hs

Lines changed: 44 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,8 @@ module DMQ.Protocol.SigSubmission.Type
1414
, SigOpCertificate (..)
1515
, SigColdKey (..)
1616
, SigRaw (..)
17-
, Sig (Sig, SigWithBytes, sigRaw, sigRawBytes, sigId, sigBody, sigExpiresAt, sigOpCertificate, sigKESPeriod, sigKESSignature, sigColdKey, sigBytes)
17+
, SigRawWithSignedBytes (..)
18+
, Sig (Sig, SigWithBytes, sigRawWithSignedBytes, sigRawBytes, sigId, sigBody, sigExpiresAt, sigOpCertificate, sigKESPeriod, sigKESSignature, sigColdKey, sigSignedBytes, sigBytes)
1819
-- * `TxSubmission` mini-protocol
1920
, SigSubmission
2021
, module SigSubmission
@@ -23,7 +24,6 @@ module DMQ.Protocol.SigSubmission.Type
2324
import Data.ByteString (ByteString)
2425
import Data.ByteString.Lazy qualified as LBS
2526
import Data.Time.Clock.POSIX (POSIXTime)
26-
import Data.Word (Word32)
2727

2828
import Ouroboros.Network.Protocol.TxSubmission2.Type as SigSubmission hiding
2929
(TxSubmission2)
@@ -54,7 +54,7 @@ newtype SigKESSignature = SigKESSignature { getSigKESSignature :: ByteString }
5454
newtype SigOpCertificate = SigOpCertificate { getSigOpCertificate :: ByteString }
5555
deriving stock (Show, Eq)
5656

57-
type SigKESPeriod = Word32
57+
type SigKESPeriod = Word
5858

5959
newtype SigColdKey = SigColdKey { getSigColdKey :: ByteString }
6060
deriving stock (Show, Eq)
@@ -65,20 +65,37 @@ newtype SigColdKey = SigColdKey { getSigColdKey :: ByteString }
6565
data SigRaw = SigRaw {
6666
sigRawId :: SigId,
6767
sigRawBody :: SigBody,
68-
sigRawKESSignature :: SigKESSignature,
6968
sigRawKESPeriod :: SigKESPeriod,
69+
-- ^ KES period when this signature was created.
70+
--
71+
-- NOTE: `kes-agent` library is using `Word` for KES period, CIP-137
72+
-- requires `Word64`, thus we're only supporting 64-bit architectures.
73+
sigRawExpiresAt :: POSIXTime,
74+
sigRawKESSignature :: SigKESSignature,
7075
sigRawOpCertificate :: SigOpCertificate,
71-
sigRawColdKey :: SigColdKey,
72-
sigRawExpiresAt :: POSIXTime
76+
sigRawColdKey :: SigColdKey
77+
}
78+
deriving stock (Show, Eq)
79+
80+
81+
data SigRawWithSignedBytes = SigRawWithSignedBytes {
82+
sigRawSignedBytes :: LBS.ByteString,
83+
-- ^ bytes signed by the KES key
84+
sigRaw :: SigRaw
85+
-- ^ the `SigRaw` data type
7386
}
7487
deriving stock (Show, Eq)
7588

89+
7690
data Sig = SigWithBytes {
77-
sigRawBytes :: LBS.ByteString,
78-
sigRaw :: SigRaw
91+
sigRawBytes :: LBS.ByteString,
92+
-- ^ encoded `SigRaw` data type
93+
sigRawWithSignedBytes :: SigRawWithSignedBytes
94+
-- ^ the `SigRaw` data type along with signed bytes
7995
}
8096
deriving stock (Show, Eq)
8197

98+
8299
-- | A convenient bidirectional pattern synonym for the `Sig` type.
83100
--
84101
pattern Sig
@@ -90,6 +107,7 @@ pattern Sig
90107
-> SigColdKey
91108
-> POSIXTime
92109
-> LBS.ByteString
110+
-> LBS.ByteString
93111
-> Sig
94112
pattern
95113
Sig { sigId,
@@ -99,20 +117,24 @@ pattern
99117
sigOpCertificate,
100118
sigColdKey,
101119
sigExpiresAt,
120+
sigSignedBytes,
102121
sigBytes
103122
}
104123
<-
105124
SigWithBytes {
106125
sigRawBytes = sigBytes,
107-
sigRaw =
108-
SigRaw {
109-
sigRawId = sigId,
110-
sigRawBody = sigBody,
111-
sigRawKESSignature = sigKESSignature,
112-
sigRawKESPeriod = sigKESPeriod,
113-
sigRawOpCertificate = sigOpCertificate,
114-
sigRawColdKey = sigColdKey,
115-
sigRawExpiresAt = sigExpiresAt
126+
sigRawWithSignedBytes =
127+
SigRawWithSignedBytes {
128+
sigRawSignedBytes = sigSignedBytes,
129+
sigRaw = SigRaw {
130+
sigRawId = sigId,
131+
sigRawBody = sigBody,
132+
sigRawKESSignature = sigKESSignature,
133+
sigRawKESPeriod = sigKESPeriod,
134+
sigRawOpCertificate = sigOpCertificate,
135+
sigRawColdKey = sigColdKey,
136+
sigRawExpiresAt = sigExpiresAt
137+
}
116138
}
117139
}
118140
where
@@ -123,12 +145,14 @@ pattern
123145
sigRawOpCertificate
124146
sigRawColdKey
125147
sigRawExpiresAt
148+
sigRawSignedBytes
126149
sigRawBytes
127150
=
128151
SigWithBytes {
129152
sigRawBytes = sigRawBytes,
130-
sigRaw =
131-
SigRaw {
153+
sigRawWithSignedBytes = SigRawWithSignedBytes {
154+
sigRawSignedBytes,
155+
sigRaw = SigRaw {
132156
sigRawId,
133157
sigRawBody,
134158
sigRawKESPeriod,
@@ -137,6 +161,7 @@ pattern
137161
sigRawColdKey,
138162
sigRawExpiresAt
139163
}
164+
}
140165
}
141166
{-# COMPLETE Sig #-}
142167

decentralized-message-queue/test/Test/DMQ/Protocol/SigSubmission.hs

Lines changed: 52 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@
66

77
module Test.DMQ.Protocol.SigSubmission where
88

9+
import Codec.CBOR.Encoding qualified as CBOR
910
import Codec.CBOR.Write qualified as CBOR
1011
import Control.Monad.ST (runST)
1112
import Data.Time.Clock.POSIX (POSIXTime)
@@ -14,6 +15,8 @@ import Data.Word (Word32)
1415
import Network.TypedProtocol.Codec
1516
import Network.TypedProtocol.Codec.Properties hiding (prop_codec)
1617

18+
import Cardano.Binary (ToCBOR (..))
19+
1720
import DMQ.Protocol.SigSubmission.Codec
1821
import DMQ.Protocol.SigSubmission.Type
1922

@@ -115,17 +118,63 @@ instance Arbitrary SigRaw where
115118
| sigRawExpiresAt' <- shrink sigRawExpiresAt
116119
]
117120

121+
mkSigRawWithSignedBytes :: SigRaw -> SigRawWithSignedBytes
122+
mkSigRawWithSignedBytes sigRaw =
123+
SigRawWithSignedBytes {
124+
sigRaw,
125+
sigRawSignedBytes
126+
}
127+
where
128+
sigRawSignedBytes = CBOR.toLazyByteString (encodeSigRaw' sigRaw)
129+
130+
instance Arbitrary SigRawWithSignedBytes where
131+
arbitrary = mkSigRawWithSignedBytes <$> arbitrary
132+
shrink SigRawWithSignedBytes {sigRaw} = mkSigRawWithSignedBytes <$> shrink sigRaw
133+
118134
-- NOTE: this function is not exposed in the main library on purpose. We
119135
-- should never construct `Sig` by serialising `SigRaw`.
120136
--
121-
mkSig :: SigRaw -> Sig
122-
mkSig sigRaw = SigWithBytes {sigRawBytes, sigRaw}
137+
mkSig :: SigRawWithSignedBytes -> Sig
138+
mkSig sigRawWithSignedBytes@SigRawWithSignedBytes { sigRaw } =
139+
SigWithBytes {
140+
sigRawBytes,
141+
sigRawWithSignedBytes
142+
}
123143
where
124144
sigRawBytes = CBOR.toLazyByteString (encodeSigRaw sigRaw)
125145

126146
instance Arbitrary Sig where
127147
arbitrary = mkSig <$> arbitrary
128-
shrink SigWithBytes {sigRaw} = mkSig <$> shrink sigRaw
148+
shrink SigWithBytes {sigRawWithSignedBytes} = mkSig <$> shrink sigRawWithSignedBytes
149+
150+
-- encode only signed part
151+
encodeSigRaw' :: SigRaw
152+
-> CBOR.Encoding
153+
encodeSigRaw' SigRaw {
154+
sigRawId,
155+
sigRawBody,
156+
sigRawKESPeriod,
157+
sigRawExpiresAt
158+
}
159+
= CBOR.encodeListLen 7
160+
<> encodeSigId sigRawId
161+
<> CBOR.encodeBytes (getSigBody sigRawBody)
162+
<> CBOR.encodeWord sigRawKESPeriod
163+
<> CBOR.encodeWord32 (floor sigRawExpiresAt)
164+
165+
-- encode together with KES signature, OCert and cold key.
166+
encodeSigRaw :: SigRaw
167+
-> CBOR.Encoding
168+
encodeSigRaw sigRaw@SigRaw { sigRawKESSignature, sigRawOpCertificate, sigRawColdKey } =
169+
encodeSigRaw' sigRaw
170+
<> CBOR.encodeBytes (getSigKESSignature sigRawKESSignature)
171+
<> toCBOR (getSigOpCertificate sigRawOpCertificate)
172+
<> CBOR.encodeBytes (getSigColdKey sigRawColdKey)
173+
174+
175+
shrinkSigFn :: Sig -> [Sig]
176+
shrinkSigFn SigWithBytes {sigRawWithSignedBytes = SigRawWithSignedBytes { sigRaw, sigRawSignedBytes } } =
177+
mkSig . (\sigRaw' -> SigRawWithSignedBytes { sigRaw = sigRaw', sigRawSignedBytes }) <$> shrink sigRaw
129178

130179
prop_codec :: AnyMessage SigSubmission -> Property
131180
prop_codec msg =

0 commit comments

Comments
 (0)