44{-# LANGUAGE NamedFieldPuns #-}
55{-# LANGUAGE OverloadedStrings #-}
66{-# LANGUAGE PatternSynonyms #-}
7+ {-# LANGUAGE ScopedTypeVariables #-}
78{-# LANGUAGE StandaloneDeriving #-}
8- {-# LANGUAGE TypeSynonymInstances #-}
9+ {-# LANGUAGE TypeOperators #-}
910{-# LANGUAGE UndecidableInstances #-}
1011
1112module DMQ.Protocol.SigSubmission.Type
@@ -14,21 +15,24 @@ module DMQ.Protocol.SigSubmission.Type
1415 , SigId (.. )
1516 , SigBody (.. )
1617 , SigKESSignature (.. )
17- , SigKESPeriod
1818 , SigOpCertificate (.. )
1919 , SigColdKey (.. )
2020 , SigRaw (.. )
2121 , SigRawWithSignedBytes (.. )
2222 , Sig (Sig , SigWithBytes , sigRawWithSignedBytes , sigRawBytes , sigId , sigBody , sigExpiresAt , sigOpCertificate , sigKESPeriod , sigKESSignature , sigColdKey , sigSignedBytes , sigBytes )
23+ , validateSig
2324 -- * `TxSubmission` mini-protocol
2425 , SigSubmission
2526 , module SigSubmission
2627 , POSIXTime
2728 -- * Utilities
2829 , CBORBytes (.. )
30+ -- * Re-exports from `kes-agent`
31+ , KESPeriod (.. )
2932 ) where
3033
3134import Data.Aeson
35+ import Data.Bifunctor (first )
3236import Data.ByteString (ByteString )
3337import Data.ByteString.Base16 as BS.Base16
3438import Data.ByteString.Base16.Lazy as LBS.Base16
@@ -37,12 +41,14 @@ import Data.ByteString.Lazy.Char8 qualified as LBS.Char8
3741import Data.Text.Encoding qualified as Text
3842import Data.Time.Clock.POSIX (POSIXTime )
3943import Data.Typeable
44+ import Data.Word (Word64 )
4045
41- import Cardano.Crypto.DSIGN.Class (DSIGNAlgorithm )
42- import Cardano.Crypto.KES .Class ( VerKeyKES )
43- -- import Cardano.Crypto.Util (SignableRepresentation (..))
46+ import Cardano.Crypto.DSIGN.Class (ContextDSIGN , DSIGNAlgorithm , VerKeyDSIGN )
47+ import Cardano.Crypto.DSIGN .Class qualified as DSIGN
48+ import Cardano.Crypto.KES.Class ( KESAlgorithm (.. ), Signable )
4449import Cardano.KESAgent.KES.Crypto as KES
45- import Cardano.KESAgent.KES.OCert (OCert (.. ))
50+ import Cardano.KESAgent.KES.OCert (KESPeriod (.. ), OCert (.. ), OCertSignable ,
51+ validateOCert )
4652
4753import Ouroboros.Network.Protocol.TxSubmission2.Type as SigSubmission hiding
4854 (TxSubmission2 )
@@ -66,13 +72,13 @@ newtype SigBody = SigBody { getSigBody :: ByteString }
6672 deriving stock (Show , Eq )
6773
6874
69- -- TODO:
70- -- This type should be something like: `SignedKES (KES crypto) SigPayload`
71- newtype SigKESSignature = SigKESSignature { getSigKESSignature :: ByteString }
72- deriving stock (Show , Eq )
75+ newtype SigKESSignature crypto = SigKESSignature { getSigKESSignature :: SigKES (KES crypto ) }
76+
77+ deriving instance Show (SigKES (KES crypto ))
78+ => Show (SigKESSignature crypto )
79+ deriving instance Eq (SigKES (KES crypto ))
80+ => Eq (SigKESSignature crypto )
7381
74- -- TODO:
75- -- This type should be more than just a `ByteString`.
7682newtype SigOpCertificate crypto = SigOpCertificate { getSigOpCertificate :: OCert crypto }
7783
7884deriving instance ( DSIGNAlgorithm (KES. DSIGN crypto )
@@ -81,37 +87,45 @@ deriving instance ( DSIGNAlgorithm (KES.DSIGN crypto)
8187 => Show (SigOpCertificate crypto )
8288deriving instance ( DSIGNAlgorithm (KES. DSIGN crypto )
8389 , Eq (VerKeyKES (KES crypto ))
84- ) => Eq (SigOpCertificate crypto )
90+ ) => Eq (SigOpCertificate crypto )
8591
8692
87- type SigKESPeriod = Word
93+ newtype SigColdKey crypto = SigColdKey { getSigColdKey :: VerKeyDSIGN ( KES. DSIGN crypto ) }
8894
89- newtype SigColdKey = SigColdKey { getSigColdKey :: ByteString }
90- deriving stock (Show , Eq )
95+ deriving instance Show (VerKeyDSIGN (KES. DSIGN crypto ))
96+ => Show (SigColdKey crypto )
97+
98+ deriving instance Eq (VerKeyDSIGN (KES. DSIGN crypto ))
99+ => Eq (SigColdKey crypto )
91100
92101-- | Sig type consists of payload and its KES signature.
93102--
94103-- TODO: add signed bytes.
95104data SigRaw crypto = SigRaw {
96105 sigRawId :: SigId ,
97106 sigRawBody :: SigBody ,
98- sigRawKESPeriod :: SigKESPeriod ,
107+ sigRawKESPeriod :: KESPeriod ,
99108 -- ^ KES period when this signature was created.
100109 --
101110 -- NOTE: `kes-agent` library is using `Word` for KES period, CIP-137
102111 -- requires `Word64`, thus we're only supporting 64-bit architectures.
103- sigRawExpiresAt :: POSIXTime ,
104- sigRawKESSignature :: SigKESSignature ,
105112 sigRawOpCertificate :: SigOpCertificate crypto ,
106- sigRawColdKey :: SigColdKey
113+ sigRawColdKey :: SigColdKey crypto ,
114+ sigRawExpiresAt :: POSIXTime ,
115+ sigRawKESSignature :: SigKESSignature crypto
116+ -- ^ KES signature of all previous fields.
117+ --
118+ -- NOTE: this field must be lazy, otetherwise tests will fail.
107119 }
108120
109121deriving instance ( DSIGNAlgorithm (KES. DSIGN crypto )
110122 , Show (VerKeyKES (KES crypto ))
123+ , Show (SigKES (KES crypto ))
111124 )
112125 => Show (SigRaw crypto )
113126deriving instance ( DSIGNAlgorithm (KES. DSIGN crypto )
114127 , Eq (VerKeyKES (KES crypto ))
128+ , Eq (SigKES (KES crypto ))
115129 )
116130 => Eq (SigRaw crypto )
117131
@@ -151,17 +165,20 @@ data SigRawWithSignedBytes crypto = SigRawWithSignedBytes {
151165
152166deriving instance ( DSIGNAlgorithm (KES. DSIGN crypto )
153167 , Show (VerKeyKES (KES crypto ))
168+ , Show (SigKES (KES crypto ))
154169 )
155170 => Show (SigRawWithSignedBytes crypto )
156171deriving instance ( DSIGNAlgorithm (KES. DSIGN crypto )
157172 , Eq (VerKeyKES (KES crypto ))
173+ , Eq (SigKES (KES crypto ))
158174 )
159175 => Eq (SigRawWithSignedBytes crypto )
160176
161177instance Crypto crypto
162178 => ToJSON (SigRawWithSignedBytes crypto ) where
163179 toJSON SigRawWithSignedBytes {sigRaw} = toJSON sigRaw
164180
181+
165182data Sig crypto = SigWithBytes {
166183 sigRawBytes :: LBS. ByteString ,
167184 -- ^ encoded `SigRaw` data type
@@ -171,10 +188,12 @@ data Sig crypto = SigWithBytes {
171188
172189deriving instance ( DSIGNAlgorithm (KES. DSIGN crypto )
173190 , Show (VerKeyKES (KES crypto ))
191+ , Show (SigKES (KES crypto ))
174192 )
175193 => Show (Sig crypto )
176194deriving instance ( DSIGNAlgorithm (KES. DSIGN crypto )
177195 , Eq (VerKeyKES (KES crypto ))
196+ , Eq (SigKES (KES crypto ))
178197 )
179198 => Eq (Sig crypto )
180199
@@ -187,10 +206,10 @@ instance Crypto crypto
187206pattern Sig
188207 :: SigId
189208 -> SigBody
190- -> SigKESSignature
191- -> SigKESPeriod
209+ -> SigKESSignature crypto
210+ -> KESPeriod
192211 -> SigOpCertificate crypto
193- -> SigColdKey
212+ -> SigColdKey crypto
194213 -> POSIXTime
195214 -> LBS. ByteString
196215 -> LBS. ByteString
@@ -253,6 +272,60 @@ pattern
253272
254273instance Typeable crypto => ShowProxy (Sig crypto ) where
255274
275+
276+ data SigValidationError =
277+ InvalidKESSignature KESPeriod KESPeriod String
278+ | InvalidSignatureOCERT
279+ ! Word64 -- OCert counter
280+ ! KESPeriod -- OCert KES period
281+ ! String -- DSIGN error message
282+ | KESBeforeStartOCERT KESPeriod KESPeriod
283+ | KESAfterEndOCERT KESPeriod KESPeriod
284+ deriving Show
285+
286+ validateSig :: forall crypto .
287+ ( Crypto crypto
288+ , ContextDSIGN (KES. DSIGN crypto ) ~ ()
289+ , DSIGN. Signable (DSIGN crypto ) (OCertSignable crypto )
290+ , ContextKES (KES crypto ) ~ ()
291+ , Signable (KES crypto ) ByteString
292+ )
293+ => Sig crypto
294+ -> Either SigValidationError ()
295+ validateSig Sig { sigSignedBytes = signedBytes,
296+ sigKESPeriod,
297+ sigOpCertificate = SigOpCertificate ocert@ OCert {
298+ ocertKESPeriod,
299+ ocertVkHot,
300+ ocertN
301+ },
302+ sigColdKey = SigColdKey coldKey,
303+ sigKESSignature = SigKESSignature kesSig
304+ }
305+ = do
306+ sigKESPeriod < endKESPeriod
307+ ?! KESAfterEndOCERT endKESPeriod sigKESPeriod
308+ sigKESPeriod >= startKESPeriod
309+ ?! KESBeforeStartOCERT startKESPeriod sigKESPeriod
310+
311+ -- validate OCert, which includes verifying its signature
312+ validateOCert coldKey ocertVkHot ocert
313+ ?!: InvalidSignatureOCERT ocertN sigKESPeriod
314+ -- validate KES signature of the payload
315+ verifyKES () ocertVkHot
316+ (unKESPeriod sigKESPeriod - unKESPeriod startKESPeriod)
317+ (LBS. toStrict signedBytes)
318+ kesSig
319+ ?!: InvalidKESSignature ocertKESPeriod sigKESPeriod
320+ where
321+ startKESPeriod , endKESPeriod :: KESPeriod
322+
323+ startKESPeriod = ocertKESPeriod
324+ -- TODO: is `totalPeriodsKES` the same as `praosMaxKESEvo`
325+ -- or `sgMaxKESEvolution` in the genesis file?
326+ endKESPeriod = KESPeriod $ unKESPeriod startKESPeriod
327+ + totalPeriodsKES (Proxy :: Proxy (KES crypto ))
328+
256329type SigSubmission crypto = TxSubmission2. TxSubmission2 SigId (Sig crypto )
257330
258331
@@ -267,3 +340,19 @@ newtype CBORBytes = CBORBytes { getCBORBytes :: LBS.ByteString }
267340
268341instance Show CBORBytes where
269342 show = LBS.Char8. unpack . LBS.Base16. encode . getCBORBytes
343+
344+
345+ --
346+ -- Utility functions
347+ --
348+
349+ (?!:) :: Either e1 a -> (e1 -> e2 ) -> Either e2 a
350+ (?!:) = flip first
351+
352+ infix 1 ?!:
353+
354+ (?!) :: Bool -> e -> Either e ()
355+ (?!) True _ = Right ()
356+ (?!) False e = Left e
357+
358+ infix 1 ?!
0 commit comments