commit befd3bdb19cfbe0d965fd67837f6d12d521cf550
parent b27a5d079113939782e288954d9de30f037b3d8e
Author: Jared Tobin <jared@jtobin.io>
Date: Tue, 23 Dec 2025 13:11:36 -0330
lib: more hardening of montgomery modules
Diffstat:
3 files changed, 17 insertions(+), 11 deletions(-)
diff --git a/lib/Numeric/Montgomery/Secp256k1/Curve.hs b/lib/Numeric/Montgomery/Secp256k1/Curve.hs
@@ -55,7 +55,7 @@ module Numeric.Montgomery.Secp256k1.Curve (
, sqrt#
, exp
, odd#
- , odd
+ , odd_vartime
) where
import Control.DeepSeq
@@ -66,7 +66,7 @@ import qualified Data.Word.Wide as W
import Data.Word.Wider (Wider(..))
import qualified Data.Word.Wider as WW
import GHC.Exts (Word(..))
-import Prelude hiding (or, and, not, sqrt, exp, odd)
+import Prelude hiding (or, and, not, sqrt, exp)
-- montgomery arithmetic, specialized to the secp256k1 field prime modulus
-- 0xFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFEFFFFFC2F
@@ -1538,18 +1538,21 @@ exp (Montgomery b) (Wider e) =
odd# :: (# Limb, Limb, Limb, Limb #) -> C.Choice
odd# = WW.odd#
-{-# INLINE odd #-}
+{-# INLINE odd# #-}
-- | Check if a 'Montgomery' value is odd.
--
+-- Note that the comparison is performed in constant time, but we
+-- branch when converting to 'Bool'.
+--
-- >>> odd 1
-- True
-- >>> odd 2
-- False
-- >>> Data.Word.Wider.odd (retr 3) -- parity is preserved
-- True
-odd :: Montgomery -> Bool
-odd (Montgomery m) = C.decide (odd# m)
+odd_vartime :: Montgomery -> Bool
+odd_vartime (Montgomery m) = C.decide (odd# m)
-- constant-time selection ----------------------------------------------------
diff --git a/lib/Numeric/Montgomery/Secp256k1/Scalar.hs b/lib/Numeric/Montgomery/Secp256k1/Scalar.hs
@@ -53,7 +53,7 @@ module Numeric.Montgomery.Secp256k1.Scalar (
, inv#
, exp
, odd#
- , odd
+ , odd_vartime
) where
import Control.DeepSeq
@@ -64,7 +64,7 @@ import qualified Data.Word.Wide as W
import Data.Word.Wider (Wider(..))
import qualified Data.Word.Wider as WW
import GHC.Exts (Word(..))
-import Prelude hiding (or, and, not, exp, odd)
+import Prelude hiding (or, and, not, exp)
-- montgomery arithmetic, specialized to the secp256k1 scalar group order
-- 0xFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFFEBAAEDCE6AF48A03BBFD25E8CD0364141
@@ -964,18 +964,21 @@ exp (Montgomery b) (Wider e) =
odd# :: (# Limb, Limb, Limb, Limb #) -> C.Choice
odd# = WW.odd#
-{-# INLINE odd #-}
+{-# INLINE odd# #-}
-- | Check if a 'Montgomery' value is odd.
--
+-- Note that the comparison is performed in constant time, but we
+-- branch when converting to 'Bool'.
+--
-- >>> odd 1
-- True
-- >>> odd 2
-- False
-- >>> Data.Word.Wider.odd (retr 3) -- parity is preserved
-- True
-odd :: Montgomery -> Bool
-odd (Montgomery m) = C.decide (odd# m)
+odd_vartime :: Montgomery -> Bool
+odd_vartime (Montgomery m) = C.decide (odd# m)
-- constant-time selection ----------------------------------------------------
diff --git a/test/Montgomery/Curve.hs b/test/Montgomery/Curve.hs
@@ -169,7 +169,7 @@ inv_valid (Q.NonZero s) = C.eq_vartime (C.inv s * s) 1
odd_correct :: C.Montgomery -> Bool
odd_correct w =
- C.odd w == I.integerTestBit (W.from_vartime (C.from_vartime w)) 0
+ C.odd_vartime w == I.integerTestBit (W.from_vartime (C.from_vartime w)) 0
tests :: TestTree
tests = testGroup "montgomery tests (curve)" [