diff --git a/Crypto/Number/F2m.hs b/Crypto/Number/F2m.hs index 274b8df..d86d7e9 100644 --- a/Crypto/Number/F2m.hs +++ b/Crypto/Number/F2m.hs @@ -13,6 +13,7 @@ module Crypto.Number.F2m ( BinaryPolynomial , addF2m , mulF2m + , squareF2m' , squareF2m , modF2m , invF2m @@ -64,11 +65,11 @@ mulF2m fx n1 n2 = modF2m fx -- Multiplication table? C? squareF2m :: BinaryPolynomial -- ^ Irreducible binary polynomial -> Integer -> Integer -squareF2m fx = modF2m fx . square +squareF2m fx = modF2m fx . squareF2m' {-# INLINE squareF2m #-} -square :: Integer -> Integer -square n1 = go n1 ln1 +squareF2m' :: Integer -> Integer +squareF2m' n1 = go n1 ln1 where ln1 = log2 n1 go n s | s == 0 = n @@ -76,7 +77,7 @@ square n1 = go n1 ln1 where x = shift (shift n (2 * (s - ln1) - 1)) (2 * (ln1 - s) + 2) y = n .&. (shift 1 (2 * (ln1 - s) + 1) - 1) -{-# INLINE square #-} +{-# INLINE squareF2m' #-} -- | Inversion of @n over F₂m using extended Euclidean algorithm. -- diff --git a/cryptonite.cabal b/cryptonite.cabal index 2450f0a..c2dc811 100644 --- a/cryptonite.cabal +++ b/cryptonite.cabal @@ -308,8 +308,10 @@ Test-Suite test-cryptonite KAT_Camellia KAT_Curve25519 KAT_DES + KAT_Ed448 KAT_Ed25519 KAT_CMAC + KAT_HKDF KAT_HMAC KAT_MiyaguchiPreneel KAT_PBKDF2 @@ -323,6 +325,10 @@ Test-Suite test-cryptonite KAT_RC4 KAT_Scrypt KAT_TripleDES + ChaChaPoly1305 + Number + Number.F2m + Padding Poly1305 Salsa Utils diff --git a/tests/Number/F2m.hs b/tests/Number/F2m.hs new file mode 100644 index 0000000..afa6e50 --- /dev/null +++ b/tests/Number/F2m.hs @@ -0,0 +1,83 @@ +module Number.F2m (tests) where + +import Imports hiding ((.&.)) +import Data.Bits +import Crypto.Number.Basic (log2) +import Crypto.Number.F2m + +addTests = testGroup "addF2m" + [ testProperty "commutative" + $ \a b -> a `addF2m` b == b `addF2m` a + , testProperty "associative" + $ \a b c -> (a `addF2m` b) `addF2m` c == a `addF2m` (b `addF2m` c) + , testProperty "0 is neutral" + $ \a -> a `addF2m` 0 == a + , testProperty "nullable" + $ \a -> a `addF2m` a == 0 + , testProperty "works per bit" + $ \a b -> (a `addF2m` b) .&. b == (a .&. b) `addF2m` b + ] + +modTests = testGroup "modF2m" + [ testProperty "idempotent" + $ \(Positive m) (NonNegative a) -> modF2m m a == modF2m m (modF2m m a) + , testProperty "upper bound" + $ \(Positive m) (NonNegative a) -> modF2m m a < 2 ^ log2 m + , testProperty "reach upper" + $ \(Positive m) -> let a = 2 ^ log2 m - 1 in modF2m m (m `addF2m` a) == a + , testProperty "lower bound" + $ \(Positive m) (NonNegative a) -> modF2m m a >= 0 + , testProperty "reach lower" + $ \(Positive m) -> modF2m m m == 0 + , testProperty "additive" + $ \(Positive m) (NonNegative a) (NonNegative b) + -> modF2m m a `addF2m` modF2m m b == modF2m m (a `addF2m` b) + ] + +mulTests = testGroup "mulF2m" + [ testProperty "commutative" + $ \(Positive m) (NonNegative a) (NonNegative b) -> mulF2m m a b == mulF2m m b a + , testProperty "associative" + $ \(Positive m) (NonNegative a) (NonNegative b) (NonNegative c) + -> mulF2m m (mulF2m m a b) c == mulF2m m a (mulF2m m b c) + , testProperty "1 is neutral" + $ \(Positive m) (NonNegative a) -> mulF2m m a 1 == modF2m m a + , testProperty "0 is annihilator" + $ \(Positive m) (NonNegative a) -> mulF2m m a 0 == 0 + , testProperty "distributive" + $ \(Positive m) (NonNegative a) (NonNegative b) (NonNegative c) + -> mulF2m m a (b `addF2m` c) == mulF2m m a b `addF2m` mulF2m m a c + ] + +squareTests = testGroup "squareF2m" + [ testProperty "sqr(a) == a * a" + $ \(Positive m) (NonNegative a) -> mulF2m m a a == squareF2m m a + ] + +invTests = testGroup "invF2m" + [ testProperty "1 / a * a == 1" + $ \(Positive m) (NonNegative a) + -> maybe True (\c -> mulF2m m c a == modF2m m 1) (invF2m m a) + , testProperty "1 / a == a (mod a^2-1)" + $ \(NonNegative a) -> a < 2 || invF2m (squareF2m' a `addF2m` 1) a == Just a + ] + +divTests = testGroup "divF2m" + [ testProperty "1 / a == inv a" + $ \(Positive m) (NonNegative a) -> divF2m m 1 a == invF2m m a + , testProperty "a / b == a * inv b" + $ \(Positive m) (NonNegative a) (NonNegative b) + -> divF2m m a b == (mulF2m m a <$> invF2m m b) + , testProperty "a * b / b == a" + $ \(Positive m) (NonNegative a) (NonNegative b) + -> invF2m m b == Nothing || divF2m m (mulF2m m a b) b == Just (modF2m m a) + ] + +tests = testGroup "number.F2m" + [ addTests + , modTests + , mulTests + , squareTests + , invTests + , divTests + ] diff --git a/tests/Tests.hs b/tests/Tests.hs index 9d2c017..1ab9ea5 100644 --- a/tests/Tests.hs +++ b/tests/Tests.hs @@ -4,6 +4,7 @@ module Main where import Imports import qualified Number +import qualified Number.F2m import qualified BCrypt import qualified Hash import qualified Poly1305 @@ -33,6 +34,7 @@ import qualified Padding tests = testGroup "cryptonite" [ Number.tests + , Number.F2m.tests , Hash.tests , Padding.tests , testGroup "ConstructHash"