protocol: change F to be a Natural, not an Integer.
authorJulien Moutinho <julm+hjugement@autogeree.net>
Wed, 24 Apr 2019 21:50:32 +0000 (21:50 +0000)
committerJulien Moutinho <julm+hjugement@autogeree.net>
Wed, 24 Apr 2019 21:51:02 +0000 (21:51 +0000)
hjugement-protocol/Protocol/Arithmetic.hs
hjugement-protocol/Protocol/Election.hs

index 142f549c98fb4b54274b40f293912c96f43e63e9..9ac6ea93a4a40126e63e4534d79d901a550a4885 100644 (file)
@@ -46,8 +46,8 @@ import qualified System.Random as Random
 --   @a'*'(b'+'c) == (a'*'b) '+' (a'*'c)@ and
 --   @(a'+'b)'*'c == (a'*'c) '+' (b'*'c)@
 --
--- The 'Integer' is always within @[0..'fieldCharac'-1]@.
-newtype F p = F { unF :: Integer }
+-- The 'Natural' is always within @[0..'fieldCharac'-1]@.
+newtype F p = F { unF :: Natural }
  deriving (Eq,Ord,Show)
 
 inF :: forall p i. PrimeField p => Integral i => i -> F p
@@ -60,7 +60,7 @@ instance PrimeField p => Additive (F p) where
        F x + F y = F ((x + y) `mod` fieldCharac @p)
 instance PrimeField p => Negable (F p) where
        neg (F x) | x == 0 = zero
-                 | otherwise = F (N.negate x + fieldCharac @p)
+                 | otherwise = F (fromIntegral (N.negate (toInteger x) + toInteger (fieldCharac @p)))
 instance PrimeField p => Multiplicative (F p) where
        one = F 1
        -- | Because 'fieldCharac' is prime,
@@ -68,9 +68,11 @@ instance PrimeField p => Multiplicative (F p) where
        F x * F y = F ((x * y) `mod` fieldCharac @p)
 instance PrimeField p => Random.Random (F p) where
        randomR (F lo, F hi) =
-               first F . Random.randomR
-                (max 0 lo, min hi (fieldCharac @p - 1))
-       random = first F . Random.randomR (0, fieldCharac @p - 1)
+               first (F . fromIntegral) .
+               Random.randomR
+                ( 0`max`toInteger lo
+                , toInteger hi`min`(toInteger (fieldCharac @p) - 1))
+       random = first (F . fromIntegral) . Random.randomR (0, toInteger (fieldCharac @p) - 1)
 
 -- ** Class 'PrimeField'
 -- | Parameter for a prime field.
@@ -79,7 +81,7 @@ class PrimeField p where
        --
        -- ElGamal's hardness to decrypt requires a large prime number
        -- to form the 'Multiplicative' 'SubGroup'.
-       fieldCharac :: Integer
+       fieldCharac :: Natural
 
 -- ** Class 'Additive'
 class Additive a where
@@ -87,13 +89,13 @@ class Additive a where
        (+) :: a -> a -> a; infixl 6 +
        sum :: Foldable f => f a -> a
        sum = foldl' (+) zero
-instance Additive Integer where
+instance Additive Natural where
        zero = 0
        (+)  = (N.+)
-instance Additive Int where
+instance Additive Integer where
        zero = 0
        (+)  = (N.+)
-instance Additive Natural where
+instance Additive Int where
        zero = 0
        (+)  = (N.+)
 
@@ -111,6 +113,9 @@ instance Negable Int where
 class Multiplicative a where
        one :: a
        (*) :: a -> a -> a; infixl 7 *
+instance Multiplicative Natural where
+       one = 1
+       (*) = (N.*)
 instance Multiplicative Integer where
        one = 1
        (*) = (N.*)
@@ -129,10 +134,10 @@ class Multiplicative a => Invertible a where
 newtype G q = G { unG :: F (P q) }
  deriving (Eq,Ord,Show)
 
--- | @('intG' g)@ returns the element of the 'SubGroup' 'g'
--- as an 'Integer' within @[0..'fieldCharac'-1]@.
-intG :: SubGroup q => G q -> Integer
-intG = unF . unG
+-- | @('natG' g)@ returns the element of the 'SubGroup' 'g'
+-- as an 'Natural' within @[0..'fieldCharac'-1]@.
+natG :: SubGroup q => G q -> Natural
+natG = unF . unG
 
 instance (SubGroup q, Multiplicative (F (P q))) => Multiplicative (G q) where
        one = G one
@@ -191,7 +196,7 @@ hash ::
 hash prefix gs =
        let s = prefix <> foldMap (\(G (F i)) -> fromString (show i) <> fromString ",") gs in
        let h = ByteArray.convert (Crypto.hashWith Crypto.SHA256 s) in
-       inE (BS.foldl' (\acc b -> acc`shiftL`3 + fromIntegral b) (0::Integer) h)
+       inE (BS.foldl' (\acc b -> acc`shiftL`3 + fromIntegral b) (0::Natural) h)
 
 -- * Type 'E'
 -- | An exponent of a (necessarily cyclic) 'SubGroup' of a 'PrimeField'.
@@ -204,26 +209,31 @@ inE i = E (F (abs (fromIntegral i `mod` unF (groupOrder @q))))
        where abs x | x < 0 = x + unF (groupOrder @q)
                    | otherwise = x
 
-intE :: forall q. SubGroup q => E q -> Integer
-intE = unF . unE
+natE :: forall q. SubGroup q => E q -> Natural
+natE = unF . unE
 
 instance (SubGroup q, Additive (F (P q))) => Additive (E q) where
        zero = E zero
        E (F x) + E (F y) = E (F ((x + y) `mod` unF (groupOrder @q)))
 instance (SubGroup q, Negable (F (P q))) => Negable (E q) where
        neg (E (F x)) | x == 0 = zero
-                     | otherwise = E (F (neg x + unF (groupOrder @q)))
+                     | otherwise = E (F (fromIntegral ( neg (toInteger x)
+                                                      + toInteger (unF (groupOrder @q)) )))
 instance (SubGroup q, Multiplicative (F (P q))) => Multiplicative (E q) where
        one = E one
        E (F x) * E (F y) = E (F ((x * y) `mod` unF (groupOrder @q)))
 instance SubGroup q => Random.Random (E q) where
        randomR (E (F lo), E (F hi)) =
-               first (E . F) . Random.randomR
-                (max 0 lo, min hi (unF (groupOrder @q) - 1))
-       random = first (E . F) . Random.randomR (0, unF (groupOrder @q) - 1)
+               first (E . F . fromIntegral) .
+               Random.randomR
+                ( 0`max`toInteger lo
+                , toInteger hi`min`(toInteger (unF (groupOrder @q)) - 1) )
+       random =
+               first (E . F . fromIntegral) .
+               Random.randomR (0, toInteger (unF (groupOrder @q)) - 1)
 instance SubGroup q => Enum (E q) where
        toEnum = inE
-       fromEnum = fromIntegral . intE
+       fromEnum = fromIntegral . natE
        enumFromTo lo hi = List.unfoldr
         (\i -> if i<=hi then Just (i, i+one) else Nothing) lo
 
@@ -261,6 +271,12 @@ random ::
  S.StateT r m i
 random = S.StateT $ return . Random.random
 
+instance Random.Random Natural where
+       randomR (mini,maxi) =
+               first (fromIntegral::Integer -> Natural) .
+               Random.randomR (fromIntegral mini, fromIntegral maxi)
+       random = first (fromIntegral::Integer -> Natural) . Random.random
+
 -- * Groups
 
 -- ** Type 'WeakParams'
index 071984fa33c46e3e222d3de8fdc15d0e54672bfc..b7cb69e4db4d4a8395eff79b83e32af4dcd41e5e 100644 (file)
@@ -150,8 +150,8 @@ newtype ValidityProof n q = ValidityProof (ML.MeasuredList n (Proof q))
 encryptionStatement :: SubGroup q => ZKP -> Encryption q -> BS.ByteString
 encryptionStatement zkp Encryption{..} =
        "prove|"<>zkp<>"|"<>
-       fromString (show (intG encryption_nonce))<>","<>
-       fromString (show (intG encryption_vault))<>"|"
+       fromString (show (natG encryption_nonce))<>","<>
+       fromString (show (natG encryption_vault))<>"|"
 
 proveEncryption ::
  forall ds m r q.