]> Git — Sourcephile - majurity.git/blob - hjugement-protocol/src/Voting/Protocol/Trustee/Indispensable.hs
protocol: replace F by G
[majurity.git] / hjugement-protocol / src / Voting / Protocol / Trustee / Indispensable.hs
1 {-# LANGUAGE DeriveAnyClass #-}
2 {-# LANGUAGE DeriveGeneric #-}
3 {-# LANGUAGE OverloadedStrings #-}
4 {-# LANGUAGE UndecidableInstances #-} -- for Reifies instances
5 module Voting.Protocol.Trustee.Indispensable where
6
7 import Control.DeepSeq (NFData)
8 import Control.Monad (Monad(..), foldM, unless)
9 import Control.Monad.Trans.Except (ExceptT(..), throwE)
10 import Data.Aeson (ToJSON(..),FromJSON(..),(.:),(.=))
11 import Data.Eq (Eq(..))
12 import Data.Function (($))
13 import Data.Functor ((<$>))
14 import Data.Maybe (maybe)
15 import Data.Reflection (Reifies(..))
16 import Data.Semigroup (Semigroup(..))
17 import Data.Tuple (fst)
18 import GHC.Generics (Generic)
19 import System.Random (RandomGen)
20 import Text.Show (Show(..))
21 import qualified Control.Monad.Trans.State.Strict as S
22 import qualified Data.Aeson as JSON
23 import qualified Data.ByteString as BS
24 import qualified Data.List as List
25
26 import Voting.Protocol.Utils
27 import Voting.Protocol.Arith
28 import Voting.Protocol.Credential
29 import Voting.Protocol.Election
30 import Voting.Protocol.Tally
31
32 -- * Type 'TrusteePublicKey'
33 data TrusteePublicKey crypto v c = TrusteePublicKey
34 { trustee_PublicKey :: !(PublicKey crypto c)
35 , trustee_SecretKeyProof :: !(Proof crypto v c)
36 -- ^ NOTE: It is important to ensure
37 -- that each trustee generates its key pair independently
38 -- of the 'PublicKey's published by the other trustees.
39 -- Otherwise, a dishonest trustee could publish as 'PublicKey'
40 -- its genuine 'PublicKey' divided by the 'PublicKey's of the other trustees.
41 -- This would then lead to the 'election_PublicKey'
42 -- being equal to this dishonest trustee's 'PublicKey',
43 -- which means that knowing its 'SecretKey' would be sufficient
44 -- for decrypting messages encrypted to the 'election_PublicKey'.
45 -- To avoid this attack, each trustee publishing a 'PublicKey'
46 -- must 'prove' knowledge of the corresponding 'SecretKey'.
47 -- Which is done in 'proveIndispensableTrusteePublicKey'
48 -- and 'verifyIndispensableTrusteePublicKey'.
49 } deriving (Generic)
50 deriving instance Eq (G crypto c) => Eq (TrusteePublicKey crypto v c)
51 deriving instance (Show (G crypto c), Show (PublicKey crypto c)) => Show (TrusteePublicKey crypto v c)
52 deriving instance NFData (G crypto c) => NFData (TrusteePublicKey crypto v c)
53 instance
54 ( Group crypto
55 , ToJSON (G crypto c)
56 ) => ToJSON (TrusteePublicKey crypto v c) where
57 toJSON TrusteePublicKey{..} =
58 JSON.object
59 [ "pok" .= trustee_SecretKeyProof
60 , "public_key" .= trustee_PublicKey
61 ]
62 toEncoding TrusteePublicKey{..} =
63 JSON.pairs
64 ( "pok" .= trustee_SecretKeyProof
65 <> "public_key" .= trustee_PublicKey
66 )
67 instance
68 ( Reifies c crypto
69 , Group crypto
70 , FromJSON (PublicKey crypto c)
71 ) => FromJSON (TrusteePublicKey crypto v c) where
72 parseJSON = JSON.withObject "TrusteePublicKey" $ \o -> do
73 trustee_PublicKey <- o .: "public_key"
74 trustee_SecretKeyProof <- o .: "pok"
75 return TrusteePublicKey{..}
76
77 -- ** Generating a 'TrusteePublicKey'
78
79 -- | @('proveIndispensableTrusteePublicKey' trustSecKey)@
80 -- returns the 'PublicKey' associated to 'trustSecKey'
81 -- and a 'Proof' of its knowledge.
82 proveIndispensableTrusteePublicKey ::
83 Reifies v Version =>
84 Reifies c crypto =>
85 Group crypto =>
86 Key crypto =>
87 Multiplicative (G crypto c) =>
88 Invertible (G crypto c) =>
89 ToNatural (G crypto c) =>
90 Monad m => RandomGen r =>
91 SecretKey crypto c -> S.StateT r m (TrusteePublicKey crypto v c)
92 proveIndispensableTrusteePublicKey trustSecKey = do
93 let trustee_PublicKey = publicKey trustSecKey
94 trustee_SecretKeyProof <-
95 prove trustSecKey [groupGen] $
96 hash (indispensableTrusteePublicKeyStatement trustee_PublicKey)
97 return TrusteePublicKey{..}
98
99 -- ** Checking a 'TrusteePublicKey' before incorporating it into the 'Election''s 'PublicKey'
100
101 -- | @('verifyIndispensableTrusteePublicKey' trustPubKey)@
102 -- returns 'True' iif. the given 'trustee_SecretKeyProof'
103 -- does 'prove' that the 'SecretKey' associated with
104 -- the given 'trustee_PublicKey' is known by the trustee.
105 verifyIndispensableTrusteePublicKey ::
106 Reifies v Version =>
107 Reifies c crypto =>
108 Group crypto =>
109 Multiplicative (G crypto c) =>
110 Invertible (G crypto c) =>
111 ToNatural (G crypto c) =>
112 Monad m =>
113 TrusteePublicKey crypto v c ->
114 ExceptT ErrorTrusteePublicKey m ()
115 verifyIndispensableTrusteePublicKey TrusteePublicKey{..} =
116 unless (
117 proof_challenge trustee_SecretKeyProof == hash
118 (indispensableTrusteePublicKeyStatement trustee_PublicKey)
119 [commit trustee_SecretKeyProof groupGen trustee_PublicKey]
120 ) $
121 throwE ErrorTrusteePublicKey_WrongProof
122
123 -- ** Type 'ErrorTrusteePublicKey'
124 data ErrorTrusteePublicKey
125 = ErrorTrusteePublicKey_WrongProof
126 -- ^ The 'trustee_SecretKeyProof' is wrong.
127 deriving (Eq,Show)
128
129 -- ** Hashing
130 indispensableTrusteePublicKeyStatement ::
131 Reifies c crypto =>
132 ToNatural (G crypto c) =>
133 PublicKey crypto c -> BS.ByteString
134 indispensableTrusteePublicKeyStatement trustPubKey =
135 "pok|"<>bytesNat trustPubKey<>"|"
136
137 -- * 'Election''s 'PublicKey'
138
139 -- ** Generating an 'Election''s 'PublicKey' from multiple 'TrusteePublicKey's.
140
141 combineIndispensableTrusteePublicKeys ::
142 Reifies c crypto =>
143 Multiplicative (G crypto c) =>
144 Invertible (G crypto c) =>
145 ToNatural (G crypto c) =>
146 [TrusteePublicKey crypto v c] -> PublicKey crypto c
147 combineIndispensableTrusteePublicKeys =
148 List.foldr (\TrusteePublicKey{..} -> (trustee_PublicKey *)) one
149
150 -- ** Checking the trustee's 'DecryptionShare's before decrypting an 'EncryptedTally'.
151
152 verifyIndispensableDecryptionShareByTrustee ::
153 Reifies v Version =>
154 Reifies c crypto =>
155 Group crypto =>
156 Multiplicative (G crypto c) =>
157 Invertible (G crypto c) =>
158 ToNatural (G crypto c) =>
159 Monad m =>
160 EncryptedTally crypto v c -> [PublicKey crypto c] -> [DecryptionShare crypto v c] ->
161 ExceptT ErrorTally m ()
162 verifyIndispensableDecryptionShareByTrustee encByChoiceByQuest =
163 isoZipWithM_ (throwE $ ErrorTally_NumberOfTrustees)
164 (verifyDecryptionShare encByChoiceByQuest)
165
166 -- ** Decrypting an 'EncryptedTally' from multiple 'TrusteePublicKey's.
167
168 -- | @('combineDecryptionShares' pubKeyByTrustee decShareByTrustee)@
169 -- returns the 'DecryptionFactor's by choice by 'Question'
170 combineIndispensableDecryptionShares ::
171 Reifies v Version =>
172 Reifies c crypto =>
173 Group crypto =>
174 Multiplicative (G crypto c) =>
175 Invertible (G crypto c) =>
176 ToNatural (G crypto c) =>
177 [PublicKey crypto c] -> DecryptionShareCombinator crypto v c
178 combineIndispensableDecryptionShares
179 pubKeyByTrustee
180 encByChoiceByQuest
181 decByChoiceByQuestByTrustee = do
182 verifyIndispensableDecryptionShareByTrustee
183 encByChoiceByQuest
184 pubKeyByTrustee
185 decByChoiceByQuestByTrustee
186 (DecryptionShare dec0,decs) <-
187 maybe (throwE ErrorTally_NumberOfTrustees) return $
188 List.uncons decByChoiceByQuestByTrustee
189 foldM (isoZipWithM (throwE ErrorTally_NumberOfQuestions)
190 (maybe (throwE ErrorTally_NumberOfChoices) return `o2`
191 isoZipWith (\a (decFactor, _proof) -> a * decFactor)))
192 ((fst <$>) <$> dec0) (unDecryptionShare <$> decs)