protocol: fix {encryt,verify}Ballot wrt. specs
authorJulien Moutinho <julm+hjugement@autogeree.net>
Thu, 15 Aug 2019 21:42:17 +0000 (21:42 +0000)
committerJulien Moutinho <julm+hjugement@autogeree.net>
Thu, 15 Aug 2019 21:42:17 +0000 (21:42 +0000)
hjugement-protocol/src/Voting/Protocol/Election.hs

index 1dc16db1f4208c35fa83488becc69e362abfe64c..740a4712f17ff66e2b387cef78d4643457a33581 100644 (file)
@@ -224,6 +224,21 @@ prove sec commitmentBases oracle = do
           -- TODO: switch (+) to (-) when 'commit' will switch (/) to (*).
         }
 
+-- | Like 'prove' but quicker. It chould replace 'prove' entirely
+-- when Helios-C specifications will be fixed.
+proveQuicker ::
+ Reifies c FFC =>
+ Monad m => RandomGen r => Functor list =>
+ E c -> list (G c) -> Oracle list c -> S.StateT r m (Proof c)
+proveQuicker sec commitmentBases oracle = do
+       nonce <- random
+       let commitments = (^ nonce) <$> commitmentBases
+       let proof_challenge = oracle commitments
+       return Proof
+        { proof_challenge
+        , proof_response = nonce - sec*proof_challenge
+        }
+
 -- | @('fakeProof')@ returns a 'Proof'
 -- whose 'proof_challenge' and 'proof_response' are uniformly chosen at random,
 -- instead of @('proof_challenge' '==' 'hash' statement commitments)@
@@ -259,6 +274,13 @@ commit Proof{..} base basePowSec =
   -- this would be compensated by using @('-')@ instead of @('+')@ in 'prove'.
 {-# INLINE commit #-}
 
+-- | Like 'commit' but quicker. It chould replace 'commit' entirely
+-- when Helios-C specifications will be fixed.
+commitQuicker :: Reifies c FFC => Proof c -> G c -> G c -> Commitment c
+commitQuicker Proof{..} base basePowSec =
+       base^proof_response *
+       basePowSec^proof_challenge
+
 -- * Type 'Disjunction'
 -- | A 'Disjunction' is an 'inv'ersed @('groupGen' '^'opinion)@
 -- it's used in 'proveEncryption' to generate a 'Proof'
@@ -522,7 +544,7 @@ data Election c = Election
  , election_crypto      :: !(ElectionCrypto c)
  , election_questions   :: ![Question]
  , election_uuid        :: !UUID
- , election_hash        :: !Hash
+ , election_hash        :: Base64SHA256
  } deriving (Eq,Show,Generic,NFData)
 
 instance ToJSON (Election c) where
@@ -655,7 +677,7 @@ encryptBallot Election{..} ballotSecKeyMay opinionsByQuest
         Nothing -> return Nothing
         Just (ballotSecKey, signature_publicKey) -> do
                signature_proof <-
-                       prove ballotSecKey (Identity groupGen) $
+                       proveQuicker ballotSecKey (Identity groupGen) $
                         \(Identity commitment) ->
                                hash
                                 -- NOTE: the order is unusual, the commitments are first
@@ -684,7 +706,7 @@ verifyBallot Election{..} Ballot{..} =
                        let zkp = ZKP (bytesNat signature_publicKey) in
                        (, zkp) $
                                proof_challenge signature_proof == hash
-                                (signatureCommitments zkp (commit signature_proof groupGen signature_publicKey))
+                                (signatureCommitments zkp (commitQuicker signature_proof groupGen signature_publicKey))
                                 (signatureStatement ballot_answers)
        in
        and $ isValidSign :