Skip to content

Commit 7767396

Browse files
sig validation
1 parent 664a68c commit 7767396

File tree

3 files changed

+183
-80
lines changed

3 files changed

+183
-80
lines changed

dmq-node/dmq-node.cabal

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -71,6 +71,7 @@ library
7171
DMQ.Protocol.LocalMsgSubmission.Type
7272
DMQ.Protocol.SigSubmission.Codec
7373
DMQ.Protocol.SigSubmission.Type
74+
DMQ.Protocol.SigSubmission.Validate
7475
DMQ.Tracer
7576

7677
build-depends:
@@ -84,6 +85,7 @@ library
8485
cardano-crypto-class,
8586
cardano-crypto-wrapper,
8687
cardano-ledger-byron,
88+
cardano-ledger-core,
8789
cardano-ledger-shelley,
8890
cardano-slotting,
8991
cborg >=0.2.1 && <0.3,
@@ -113,6 +115,7 @@ library
113115
text >=1.2.4 && <2.2,
114116
time ^>=1.12,
115117
transformers,
118+
transformers-except,
116119
typed-protocols:{typed-protocols, cborg} ^>=1.1,
117120

118121
hs-source-dirs: src

dmq-node/src/DMQ/Protocol/SigSubmission/Type.hs

Lines changed: 4 additions & 80 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@
55
{-# LANGUAGE PatternSynonyms #-}
66
{-# LANGUAGE ScopedTypeVariables #-}
77
{-# LANGUAGE StandaloneDeriving #-}
8+
{-# LANGUAGE TypeFamilies #-}
89
{-# LANGUAGE TypeOperators #-}
910
{-# LANGUAGE UndecidableInstances #-}
1011

@@ -19,27 +20,22 @@ module DMQ.Protocol.SigSubmission.Type
1920
, SigRaw (..)
2021
, SigRawWithSignedBytes (..)
2122
, Sig (Sig, SigWithBytes, sigRawWithSignedBytes, sigRawBytes, sigId, sigBody, sigExpiresAt, sigOpCertificate, sigKESPeriod, sigKESSignature, sigColdKey, sigSignedBytes, sigBytes)
22-
, validateSig
2323
-- * `TxSubmission` mini-protocol
2424
, SigSubmission
2525
, module SigSubmission
2626
-- * Re-exports from `kes-agent`
2727
, KESPeriod (..)
2828
) where
2929

30-
import Data.Bifunctor (first)
3130
import Data.ByteString (ByteString)
3231
import Data.ByteString.Lazy qualified as LBS
3332
import Data.Time.Clock.POSIX (POSIXTime)
3433
import Data.Typeable
35-
import Data.Word (Word64)
3634

37-
import Cardano.Crypto.DSIGN.Class (ContextDSIGN, DSIGNAlgorithm, VerKeyDSIGN)
38-
import Cardano.Crypto.DSIGN.Class qualified as DSIGN
39-
import Cardano.Crypto.KES.Class (KESAlgorithm (..), Signable)
35+
import Cardano.Crypto.DSIGN.Class (DSIGNAlgorithm, VerKeyDSIGN)
36+
import Cardano.Crypto.KES.Class (KESAlgorithm (..))
4037
import Cardano.KESAgent.KES.Crypto as KES
41-
import Cardano.KESAgent.KES.OCert (KESPeriod (..), OCert (..), OCertSignable,
42-
validateOCert)
38+
import Cardano.KESAgent.KES.OCert (KESPeriod (..), OCert (..))
4339

4440
import Ouroboros.Network.Protocol.TxSubmission2.Type as SigSubmission hiding
4541
(TxSubmission2)
@@ -225,76 +221,4 @@ pattern
225221
instance Typeable crypto => ShowProxy (Sig crypto) where
226222

227223

228-
data SigValidationError =
229-
InvalidKESSignature KESPeriod KESPeriod String
230-
| InvalidSignatureOCERT
231-
!Word64 -- OCert counter
232-
!KESPeriod -- OCert KES period
233-
!String -- DSIGN error message
234-
| KESBeforeStartOCERT KESPeriod KESPeriod
235-
| KESAfterEndOCERT KESPeriod KESPeriod
236-
deriving Show
237-
238-
-- TODO:
239-
-- We don't validate ocert numbers, since we might not have necessary
240-
-- information to do so, but we can validate that they are growing.
241-
validateSig :: forall crypto.
242-
( Crypto crypto
243-
, ContextDSIGN (KES.DSIGN crypto) ~ ()
244-
, DSIGN.Signable (DSIGN crypto) (OCertSignable crypto)
245-
, ContextKES (KES crypto) ~ ()
246-
, Signable (KES crypto) ByteString
247-
)
248-
=> Sig crypto
249-
-> Either SigValidationError ()
250-
validateSig Sig { sigSignedBytes = signedBytes,
251-
sigKESPeriod,
252-
sigOpCertificate = SigOpCertificate ocert@OCert {
253-
ocertKESPeriod,
254-
ocertVkHot,
255-
ocertN
256-
},
257-
sigColdKey = SigColdKey coldKey,
258-
sigKESSignature = SigKESSignature kesSig
259-
}
260-
= do
261-
sigKESPeriod < endKESPeriod
262-
?! KESAfterEndOCERT endKESPeriod sigKESPeriod
263-
sigKESPeriod >= startKESPeriod
264-
?! KESBeforeStartOCERT startKESPeriod sigKESPeriod
265-
266-
-- validate OCert, which includes verifying its signature
267-
validateOCert coldKey ocertVkHot ocert
268-
?!: InvalidSignatureOCERT ocertN sigKESPeriod
269-
-- validate KES signature of the payload
270-
verifyKES () ocertVkHot
271-
(unKESPeriod sigKESPeriod - unKESPeriod startKESPeriod)
272-
(LBS.toStrict signedBytes)
273-
kesSig
274-
?!: InvalidKESSignature ocertKESPeriod sigKESPeriod
275-
where
276-
startKESPeriod, endKESPeriod :: KESPeriod
277-
278-
startKESPeriod = ocertKESPeriod
279-
-- TODO: is `totalPeriodsKES` the same as `praosMaxKESEvo`
280-
-- or `sgMaxKESEvolution` in the genesis file?
281-
endKESPeriod = KESPeriod $ unKESPeriod startKESPeriod
282-
+ totalPeriodsKES (Proxy :: Proxy (KES crypto))
283-
284224
type SigSubmission crypto = TxSubmission2.TxSubmission2 SigId (Sig crypto)
285-
286-
287-
--
288-
-- Utility functions
289-
--
290-
291-
(?!:) :: Either e1 a -> (e1 -> e2) -> Either e2 a
292-
(?!:) = flip first
293-
294-
infix 1 ?!:
295-
296-
(?!) :: Bool -> e -> Either e ()
297-
(?!) True _ = Right ()
298-
(?!) False e = Left e
299-
300-
infix 1 ?!
Lines changed: 176 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,176 @@
1+
{-# LANGUAGE DataKinds #-}
2+
{-# LANGUAGE FlexibleInstances #-}
3+
{-# LANGUAGE StandaloneDeriving #-}
4+
{-# LANGUAGE TypeFamilies #-}
5+
{-# LANGUAGE TypeOperators #-}
6+
7+
-- | Encapsulates signature validation utilities leveraged by the mempool writer
8+
--
9+
module DMQ.Protocol.SigSubmission.Validate where
10+
11+
import Control.Exception
12+
import Control.Monad.Class.MonadTime.SI
13+
import Control.Monad.Trans.Except
14+
import Control.Monad.Trans.Except.Extra
15+
import Data.ByteString (ByteString)
16+
import Data.ByteString.Lazy qualified as LBS
17+
import Data.Map.Strict qualified as Map
18+
import Data.Maybe (isNothing)
19+
import Data.Text (Text)
20+
import Data.Text qualified as Text
21+
import Data.Typeable
22+
import Data.Word
23+
import Text.Printf
24+
25+
import Cardano.Crypto.DSIGN.Class (ContextDSIGN)
26+
import Cardano.Crypto.DSIGN.Class qualified as DSIGN
27+
import Cardano.Crypto.KES.Class (KESAlgorithm (..))
28+
import Cardano.KESAgent.KES.Crypto as KES
29+
import Cardano.KESAgent.KES.OCert (OCert (..), OCertSignable, validateOCert)
30+
import Cardano.Ledger.BaseTypes.NonZero
31+
import Cardano.Ledger.Hashes
32+
33+
import DMQ.Diffusion.NodeKernel (PoolValidationCtx (..))
34+
import DMQ.Protocol.SigSubmission.Type
35+
import Ouroboros.Consensus.Shelley.Ledger.Query
36+
import Ouroboros.Network.TxSubmission.Mempool.Simple
37+
import Ouroboros.Network.Util.ShowProxy
38+
39+
40+
-- | The type of non-fatal failures reported by the mempool writer
41+
-- for invalid messages
42+
--
43+
data instance MempoolAddFail (Sig crypto) =
44+
SigInvalid Text
45+
| SigDuplicate
46+
| SigExpired
47+
| SigResultOther Text
48+
deriving (Eq, Show)
49+
50+
instance (Typeable crypto) => ShowProxy (MempoolAddFail (Sig crypto))
51+
52+
-- | The type of exception raised by the mempool writer for invalid messages
53+
-- as determined by the validation procedure and severity policy
54+
--
55+
newtype instance InvalidTxsError SigValidationError = InvalidTxsError SigValidationError
56+
57+
deriving instance Show (InvalidTxsError SigValidationError)
58+
instance Exception (InvalidTxsError SigValidationError)
59+
60+
-- | The policy which is realized by the mempool writer when encountering
61+
-- an invalid message.
62+
--
63+
data ValidationSeverity =
64+
FailDefault | FailSoft
65+
66+
data SigValidationError =
67+
InvalidKESSignature KESPeriod KESPeriod String
68+
| InvalidSignatureOCERT
69+
!Word64 -- OCert counter
70+
!KESPeriod -- OCert KES period
71+
!String -- DSIGN error message
72+
| KESBeforeStartOCERT KESPeriod KESPeriod
73+
| KESAfterEndOCERT KESPeriod KESPeriod
74+
| UnrecognizedPool
75+
| NotInitialized
76+
| ClockSkew
77+
deriving Show
78+
79+
-- TODO fine tune policy
80+
sigValidationPolicy
81+
:: SigValidationError
82+
-> Either (MempoolAddFail (Sig crypto)) (MempoolAddFail (Sig crypto))
83+
sigValidationPolicy sve = case sve of
84+
InvalidKESSignature {} -> Left . SigInvalid . Text.pack . show $ sve
85+
InvalidSignatureOCERT {} -> Left . SigInvalid . Text.pack . show $ sve
86+
KESAfterEndOCERT {} -> Left SigExpired
87+
KESBeforeStartOCERT start sig ->
88+
Left . SigResultOther . Text.pack
89+
$ printf "KESBeforeStartOCERT %s %s" (show start) (show sig)
90+
UnrecognizedPool -> Left . SigInvalid $ Text.pack "unrecognized pool id"
91+
ClockSkew -> Left . SigInvalid $ Text.pack "clock skew out of range"
92+
NotInitialized -> Right . SigResultOther $ Text.pack "not initialized yet"
93+
94+
-- TODO:
95+
-- We don't validate ocert numbers, since we might not have necessary
96+
-- information to do so, but we can validate that they are growing.
97+
validateSig :: forall crypto.
98+
( Crypto crypto
99+
, ContextDSIGN (KES.DSIGN crypto) ~ ()
100+
, DSIGN.Signable (DSIGN crypto) (OCertSignable crypto)
101+
, ContextKES (KES crypto) ~ ()
102+
, Signable (KES crypto) ByteString
103+
)
104+
=> ValidationSeverity
105+
-> (DSIGN.VerKeyDSIGN (DSIGN crypto) -> KeyHash StakePool)
106+
-> [Sig crypto]
107+
-> PoolValidationCtx
108+
-- ^ cardano pool id verification
109+
-> Except (InvalidTxsError SigValidationError) [Either (MempoolAddFail (Sig crypto)) ()]
110+
validateSig severity verKeyHashingFn sigs ctx = firstExceptT InvalidTxsError $ traverse process sigs
111+
where
112+
DMQPoolValidationCtx now mNextEpoch pools = ctx
113+
114+
process Sig { sigSignedBytes = signedBytes,
115+
sigKESPeriod,
116+
sigOpCertificate = SigOpCertificate ocert@OCert {
117+
ocertKESPeriod,
118+
ocertVkHot,
119+
ocertN
120+
},
121+
sigColdKey = SigColdKey coldKey,
122+
sigKESSignature = SigKESSignature kesSig
123+
} = do
124+
e1 <- sigKESPeriod < endKESPeriod
125+
?! KESAfterEndOCERT endKESPeriod sigKESPeriod
126+
e2 <- sigKESPeriod >= startKESPeriod
127+
?! KESBeforeStartOCERT startKESPeriod sigKESPeriod
128+
e3 <- case Map.lookup (verKeyHashingFn coldKey) pools of
129+
Nothing | isNothing mNextEpoch -> classifyError NotInitialized
130+
| otherwise -> classifyError UnrecognizedPool
131+
Just ss | not (isZero (ssSetPool ss)) -> right $ Right ()
132+
| not (isZero (ssMarkPool ss))
133+
, Just nextEpoch <- mNextEpoch
134+
-- TODO make this a constant
135+
, diffUTCTime nextEpoch now <= 5 -> right $ Right ()
136+
| otherwise -> classifyError ClockSkew
137+
-- validate OCert, which includes verifying its signature
138+
e4 <- validateOCert coldKey ocertVkHot ocert
139+
?!: InvalidSignatureOCERT ocertN sigKESPeriod
140+
-- validate KES signature of the payload
141+
e5 <- verifyKES () ocertVkHot
142+
(unKESPeriod sigKESPeriod - unKESPeriod startKESPeriod)
143+
(LBS.toStrict signedBytes)
144+
kesSig
145+
?!: InvalidKESSignature ocertKESPeriod sigKESPeriod
146+
-- for eg. remember to run all results with possibly non-fatal errors
147+
right $ e1 >> e2 >> e3 >> e4 >> e5
148+
where
149+
startKESPeriod, endKESPeriod :: KESPeriod
150+
151+
startKESPeriod = ocertKESPeriod
152+
-- TODO: is `totalPeriodsKES` the same as `praosMaxKESEvo`
153+
-- or `sgMaxKESEvolution` in the genesis file?
154+
endKESPeriod = KESPeriod $ unKESPeriod startKESPeriod
155+
+ totalPeriodsKES (Proxy :: Proxy (KES crypto))
156+
157+
classifyError sigValidationError = case severity of
158+
FailSoft ->
159+
let mempoolAddFail = either id id (sigValidationPolicy sigValidationError)
160+
in right . Left $ mempoolAddFail
161+
FailDefault ->
162+
either (const $ throwE sigValidationError) (right . Left)
163+
(sigValidationPolicy sigValidationError)
164+
165+
(?!:) :: Either e1 ()
166+
-> (e1 -> SigValidationError)
167+
-> Except SigValidationError (Either (MempoolAddFail (Sig crypto)) ())
168+
(?!:) = (handleE classifyError .) . flip firstExceptT . hoistEither . fmap Right
169+
170+
(?!) :: Bool
171+
-> SigValidationError
172+
-> Except SigValidationError (Either (MempoolAddFail (Sig crypto)) ())
173+
(?!) flag sve = if flag then right $ Right () else classifyError sve
174+
175+
infix 1 ?!
176+
infix 1 ?!:

0 commit comments

Comments
 (0)