web: fix purescript environment
[majurity.git] / hjugement-protocol / src / Voting / Protocol / FFC.hs
index e4d6ddd95f98a9408f7211b0a5d99cce9b087ce2..3041df8ef31bd13d0f03cfe2d2ed794e7d2dc7be 100644 (file)
@@ -14,7 +14,7 @@ module Voting.Protocol.FFC where
 import Control.Arrow (first)
 import Control.DeepSeq (NFData)
 import Control.Monad (Monad(..), unless)
-import Data.Aeson (ToJSON(..),FromJSON(..),(.:),(.:?),(.=))
+import Data.Aeson (ToJSON(..), FromJSON(..), (.:), (.:?), (.=))
 import Data.Bool
 import Data.Either (Either(..))
 import Data.Eq (Eq(..))
@@ -24,7 +24,7 @@ import Data.Maybe (Maybe(..), fromMaybe, fromJust)
 import Data.Monoid (Monoid(..))
 import Data.Ord (Ord(..))
 import Data.Proxy (Proxy(..))
-import Data.Reflection (Reifies(..))
+import Data.Reflection (Reifies(..), reify)
 import Data.Semigroup (Semigroup(..))
 import Data.Text (Text)
 import GHC.Generics (Generic)
@@ -41,7 +41,8 @@ import qualified Data.Text as Text
 import qualified Data.Text.Encoding as Text
 import qualified System.Random as Random
 
-import Voting.Protocol.Arith
+import Voting.Protocol.Arithmetic
+import Voting.Protocol.Cryptography
 import Voting.Protocol.Credential
 
 -- * Type 'FFC'
@@ -62,12 +63,12 @@ data FFC = FFC
      -- ^ The prime number characteristic of a Finite Prime Field.
      --
      -- ElGamal's hardness to decrypt requires a large prime number
-     -- to form the 'Multiplicative' subgroup.
+     -- to form the multiplicative subgroup.
  ,   ffc_groupGen :: !Natural
-     -- ^ A generator of the 'Multiplicative' subgroup of the Finite Prime Field.
+     -- ^ A generator of the multiplicative subgroup of the Finite Prime Field.
      --
      -- NOTE: since 'ffc_fieldCharac' is prime,
-     -- the 'Multiplicative' subgroup is cyclic,
+     -- the multiplicative subgroup is cyclic,
      -- and there are phi('fieldCharac'-1) many choices for the generator of the group,
      -- where phi is the Euler totient function.
  ,   ffc_groupOrder :: !Natural
@@ -116,13 +117,11 @@ instance FromJSON FFC where
                unless (fromJust (ffc_fieldCharac`minusNaturalMaybe`one) `rem` ffc_groupOrder == 0) $
                        JSON.typeMismatch "FFC: groupOrder does not divide fieldCharac-1" (JSON.Object o)
                return FFC{..}
-instance Group FFC where
-       groupGen :: forall c. Reifies c FFC => G FFC c
+instance Reifies c FFC => CryptoParams FFC c where
        groupGen = G $ ffc_groupGen $ reflect (Proxy::Proxy c)
-       groupOrder :: forall c. Reifies c FFC => Proxy c -> Natural
        groupOrder c = ffc_groupOrder $ reflect c
-       -- groupDict Proxy = Dict
-       groupReify c k = k
+instance ReifyCrypto FFC where
+       reifyCrypto = reify
 instance Key FFC where
        cryptoType _ = "FFC"
        cryptoName = ffc_name
@@ -153,7 +152,7 @@ weakFFC = FFC
 
 -- | Parameters used in Belenios.
 -- A 2048-bit 'fieldCharac' of a Finite Prime Field,
--- with a 256-bit 'groupOrder' for a 'Multiplicative' subgroup
+-- with a 256-bit 'groupOrder' for a multiplicative subgroup
 -- generated by 'groupGen'.
 beleniosFFC :: FFC
 beleniosFFC = FFC
@@ -168,10 +167,10 @@ beleniosFFC = FFC
 -- A field must satisfy the following properties:
 --
 -- * @(f, ('+'), 'zero')@ forms an abelian group,
---   called the 'Additive' group of 'f'.
+--   called the additive group of 'f'.
 --
 -- * @('NonNull' f, ('*'), 'one')@ forms an abelian group,
---   called the 'Multiplicative' group of 'f'.
+--   called the multiplicative group of 'f'.
 --
 -- * ('*') is associative:
 --   @(a'*'b)'*'c == a'*'(b'*'c)@ and
@@ -214,13 +213,16 @@ instance ToNatural (G FFC c) where
 instance Reifies c FFC => Additive (G FFC c) where
        zero = G 0
        G x + G y = G $ (x + y) `mod` fieldCharac @c
-instance Reifies c FFC => Negable (G FFC c) where
-       neg (G x)
-        | x == 0 = zero
-        | otherwise = G $ fromJust $ nat (fieldCharac @c)`minusNaturalMaybe`x
-instance Reifies c FFC => Multiplicative (G FFC c) where
+instance Reifies c FFC => Semiring (G FFC c) where
        one = G 1
        G x * G y = G $ (x * y) `mod` fieldCharac @c
+instance Reifies c FFC => Ring (G FFC c) where
+       negate (G x)
+        | x == 0 = zero
+        | otherwise = G $ fromJust $ nat (fieldCharac @c)`minusNaturalMaybe`x
+instance Reifies c FFC => EuclideanRing (G FFC c) where
+       -- | NOTE: add 'groupOrder' so the exponent given to (^) is positive.
+       inverse = (^ E (fromJust $ groupOrder @FFC (Proxy @c)`minusNaturalMaybe`1))
 instance Reifies c FFC => Random.Random (G FFC c) where
        randomR (G lo, G hi) =
                first (G . fromIntegral) .
@@ -230,6 +232,3 @@ instance Reifies c FFC => Random.Random (G FFC c) where
        random =
                first (G . fromIntegral) .
                Random.randomR (0, toInteger (fieldCharac @c) - 1)
-instance Reifies c FFC => Invertible (G FFC c) where
-       -- | NOTE: add 'groupOrder' so the exponent given to (^) is positive.
-       inv = (^ E (fromJust $ groupOrder @FFC (Proxy @c)`minusNaturalMaybe`1))