{-# LANGUAGE OverloadedStrings #-} module Voting.Protocol.Trustee.Indispensable where import Control.Monad (Monad(..), foldM, unless) import Control.Monad.Trans.Except (ExceptT(..), throwE) import Data.Eq (Eq(..)) import Data.Function (($)) import Data.Maybe (maybe) import Data.Semigroup (Semigroup(..)) import Text.Show (Show(..)) import qualified Control.Monad.Trans.State.Strict as S import qualified Data.ByteString as BS import qualified Data.List as List import Voting.Protocol.Utils import Voting.Protocol.Arithmetic import Voting.Protocol.Credential import Voting.Protocol.Election import Voting.Protocol.Tally -- * Type 'TrusteePublicKey' data TrusteePublicKey q = TrusteePublicKey { trustee_PublicKey :: PublicKey q , trustee_SecretKeyProof :: Proof q -- ^ NOTE: It is important to ensure -- that each trustee generates its key pair independently -- of the 'PublicKey's published by the other trustees. -- Otherwise, a dishonest trustee could publish as 'PublicKey' -- its genuine 'PublicKey' divided by the 'PublicKey's of the other trustees. -- This would then lead to the 'election_PublicKey' -- being equal to this dishonest trustee's 'PublicKey', -- which means that knowing its 'SecretKey' would be sufficient -- for decrypting messages encrypted to the 'election_PublicKey'. -- To avoid this attack, each trustee publishing a 'PublicKey' -- must 'prove' knowledge of the corresponding 'SecretKey'. -- Which is done in 'proveIndispensableTrusteePublicKey' -- and 'verifyIndispensableTrusteePublicKey'. } deriving (Eq,Show) -- ** Type 'ErrorTrusteePublicKey' data ErrorTrusteePublicKey = ErrorTrusteePublicKey_Wrong -- ^ The 'trustee_SecretKeyProof' is wrong. deriving (Eq,Show) -- | @('proveIndispensableTrusteePublicKey' trustSecKey)@ -- returns the 'PublicKey' associated to 'trustSecKey' -- and a 'Proof' of its knowledge. proveIndispensableTrusteePublicKey :: Monad m => RandomGen r => SubGroup q => SecretKey q -> S.StateT r m (TrusteePublicKey q) proveIndispensableTrusteePublicKey trustSecKey = do let trustee_PublicKey = publicKey trustSecKey trustee_SecretKeyProof <- prove trustSecKey [groupGen] $ hash (indispensableTrusteePublicKeyStatement trustee_PublicKey) return TrusteePublicKey{..} -- | @('verifyIndispensableTrusteePublicKey' trustPubKey)@ -- returns 'True' iif. the given 'trustee_SecretKeyProof' -- does 'prove' that the 'SecretKey' associated with -- the given 'trustee_PublicKey' is known by the trustee. verifyIndispensableTrusteePublicKey :: Monad m => SubGroup q => TrusteePublicKey q -> ExceptT ErrorTrusteePublicKey m () verifyIndispensableTrusteePublicKey TrusteePublicKey{..} = unless ((proof_challenge trustee_SecretKeyProof ==) $ hash (indispensableTrusteePublicKeyStatement trustee_PublicKey) [commit trustee_SecretKeyProof groupGen trustee_PublicKey]) $ throwE ErrorTrusteePublicKey_Wrong -- ** Hashing indispensableTrusteePublicKeyStatement :: PublicKey q -> BS.ByteString indispensableTrusteePublicKeyStatement trustPubKey = "pok|"<>bytesNat trustPubKey<>"|" -- * 'Election''s 'PublicKey' combineIndispensableTrusteePublicKeys :: SubGroup q => [TrusteePublicKey q] -> PublicKey q combineIndispensableTrusteePublicKeys = List.foldr (\TrusteePublicKey{..} -> (trustee_PublicKey *)) one verifyIndispensableDecryptionShareByTrustee :: SubGroup q => Monad m => EncryptedTally q -> [PublicKey q] -> [DecryptionShare q] -> ExceptT ErrorDecryptionShare m () verifyIndispensableDecryptionShareByTrustee encTally = isoZipWithM_ (throwE $ ErrorDecryptionShare_Invalid "verifyIndispensableDecryptionShareByTrustee") (verifyDecryptionShare encTally) -- | @('combineDecryptionShares' pubKeyByTrustee decShareByTrustee)@ -- returns the 'DecryptionFactor's by choice by 'Question' combineIndispensableDecryptionShares :: SubGroup q => [PublicKey q] -> EncryptedTally q -> DecryptionShareCombinator q combineIndispensableDecryptionShares pubKeyByTrustee encTally decShareByTrustee = do verifyIndispensableDecryptionShareByTrustee encTally pubKeyByTrustee decShareByTrustee (d0,ds) <- maybe err return $ List.uncons decShareByTrustee foldM (\decFactorByChoiceByQuest DecryptionShare{..} -> isoZipWithM err (\acc df -> maybe err return $ isoZipWith (*) acc df) decFactorByChoiceByQuest decryptionShare_factors) (decryptionShare_factors d0) ds where err = throwE $ ErrorDecryptionShare_Invalid "combineIndispensableDecryptionShares"