]> Git — Sourcephile - majurity.git/blob - hjugement-protocol/src/Voting/Protocol/Trustee/Indispensable.hs
protocol: bring c from the method level to the class level
[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 ToJSON (G crypto c) => ToJSON (TrusteePublicKey crypto v c) where
54 toJSON TrusteePublicKey{..} =
55 JSON.object
56 [ "pok" .= trustee_SecretKeyProof
57 , "public_key" .= trustee_PublicKey
58 ]
59 toEncoding TrusteePublicKey{..} =
60 JSON.pairs
61 ( "pok" .= trustee_SecretKeyProof
62 <> "public_key" .= trustee_PublicKey
63 )
64 instance GroupParams crypto c => FromJSON (TrusteePublicKey crypto v c) where
65 parseJSON = JSON.withObject "TrusteePublicKey" $ \o -> do
66 trustee_PublicKey <- o .: "public_key"
67 trustee_SecretKeyProof <- o .: "pok"
68 return TrusteePublicKey{..}
69
70 -- ** Generating a 'TrusteePublicKey'
71
72 -- | @('proveIndispensableTrusteePublicKey' trustSecKey)@
73 -- returns the 'PublicKey' associated to 'trustSecKey'
74 -- and a 'Proof' of its knowledge.
75 proveIndispensableTrusteePublicKey ::
76 Reifies v Version =>
77 GroupParams crypto c =>
78 Key crypto =>
79 Monad m => RandomGen r =>
80 SecretKey crypto c -> S.StateT r m (TrusteePublicKey crypto v c)
81 proveIndispensableTrusteePublicKey trustSecKey = do
82 let trustee_PublicKey = publicKey trustSecKey
83 trustee_SecretKeyProof <-
84 prove trustSecKey [groupGen] $
85 hash (indispensableTrusteePublicKeyStatement trustee_PublicKey)
86 return TrusteePublicKey{..}
87
88 -- ** Checking a 'TrusteePublicKey' before incorporating it into the 'Election''s 'PublicKey'
89
90 -- | @('verifyIndispensableTrusteePublicKey' trustPubKey)@
91 -- returns 'True' iif. the given 'trustee_SecretKeyProof'
92 -- does 'prove' that the 'SecretKey' associated with
93 -- the given 'trustee_PublicKey' is known by the trustee.
94 verifyIndispensableTrusteePublicKey ::
95 Reifies v Version =>
96 GroupParams crypto c =>
97 Monad m =>
98 TrusteePublicKey crypto v c ->
99 ExceptT ErrorTrusteePublicKey m ()
100 verifyIndispensableTrusteePublicKey TrusteePublicKey{..} =
101 unless (
102 proof_challenge trustee_SecretKeyProof == hash
103 (indispensableTrusteePublicKeyStatement trustee_PublicKey)
104 [commit trustee_SecretKeyProof groupGen trustee_PublicKey]
105 ) $
106 throwE ErrorTrusteePublicKey_WrongProof
107
108 -- ** Type 'ErrorTrusteePublicKey'
109 data ErrorTrusteePublicKey
110 = ErrorTrusteePublicKey_WrongProof
111 -- ^ The 'trustee_SecretKeyProof' is wrong.
112 deriving (Eq,Show)
113
114 -- ** Hashing
115 indispensableTrusteePublicKeyStatement ::
116 GroupParams crypto c =>
117 PublicKey crypto c -> BS.ByteString
118 indispensableTrusteePublicKeyStatement trustPubKey =
119 "pok|"<>bytesNat trustPubKey<>"|"
120
121 -- * 'Election''s 'PublicKey'
122
123 -- ** Generating an 'Election''s 'PublicKey' from multiple 'TrusteePublicKey's.
124
125 combineIndispensableTrusteePublicKeys ::
126 GroupParams crypto c =>
127 [TrusteePublicKey crypto v c] -> PublicKey crypto c
128 combineIndispensableTrusteePublicKeys =
129 List.foldr (\TrusteePublicKey{..} -> (trustee_PublicKey *)) one
130
131 -- ** Checking the trustee's 'DecryptionShare's before decrypting an 'EncryptedTally'.
132
133 verifyIndispensableDecryptionShareByTrustee ::
134 Reifies v Version =>
135 GroupParams crypto c =>
136 Monad m =>
137 EncryptedTally crypto v c -> [PublicKey crypto c] -> [DecryptionShare crypto v c] ->
138 ExceptT ErrorTally m ()
139 verifyIndispensableDecryptionShareByTrustee encByChoiceByQuest =
140 isoZipWithM_ (throwE $ ErrorTally_NumberOfTrustees)
141 (verifyDecryptionShare encByChoiceByQuest)
142
143 -- ** Decrypting an 'EncryptedTally' from multiple 'TrusteePublicKey's.
144
145 -- | @('combineDecryptionShares' pubKeyByTrustee decShareByTrustee)@
146 -- returns the 'DecryptionFactor's by choice by 'Question'
147 combineIndispensableDecryptionShares ::
148 Reifies v Version =>
149 GroupParams crypto c =>
150 [PublicKey crypto c] -> DecryptionShareCombinator crypto v c
151 combineIndispensableDecryptionShares
152 pubKeyByTrustee
153 encByChoiceByQuest
154 decByChoiceByQuestByTrustee = do
155 verifyIndispensableDecryptionShareByTrustee
156 encByChoiceByQuest
157 pubKeyByTrustee
158 decByChoiceByQuestByTrustee
159 (DecryptionShare dec0,decs) <-
160 maybe (throwE ErrorTally_NumberOfTrustees) return $
161 List.uncons decByChoiceByQuestByTrustee
162 foldM (isoZipWithM (throwE ErrorTally_NumberOfQuestions)
163 (maybe (throwE ErrorTally_NumberOfChoices) return `o2`
164 isoZipWith (\a (decFactor, _proof) -> a * decFactor)))
165 ((fst <$>) <$> dec0) (unDecryptionShare <$> decs)