]> Git — Sourcephile - majurity.git/blob - hjugement-protocol/tests/HUnit/Trustee/Indispensable.hs
protocol: replace reifyCrypto by groupDict
[majurity.git] / hjugement-protocol / tests / HUnit / Trustee / Indispensable.hs
1 {-# LANGUAGE DataKinds #-}
2 {-# LANGUAGE OverloadedStrings #-}
3 {-# LANGUAGE PatternSynonyms #-}
4 module HUnit.Trustee.Indispensable where
5
6 import Test.Tasty.HUnit
7 import qualified Data.Text as Text
8 import qualified System.Random as Random
9 import qualified Text.Printf as Printf
10
11 import Voting.Protocol
12
13 import Utils
14
15 hunit :: Reifies v Version => Proxy v -> TestTree
16 hunit v = testGroup "Indispensable" $
17 [ testGroup "verifyIndispensableTrusteePublicKey" $
18 [ testsVerifyIndispensableTrusteePublicKey v weakFFC
19 ]
20 , testGroup "verifyTally" $
21 [ testsVerifyTally v weakFFC
22 , testsVerifyTally v beleniosFFC
23 ]
24 ]
25
26 testsVerifyIndispensableTrusteePublicKey ::
27 Group crypto => Key crypto =>
28 Reifies v Version => Proxy v ->
29 crypto -> TestTree
30 testsVerifyIndispensableTrusteePublicKey v crypto =
31 testGroup (Text.unpack $ cryptoName crypto)
32 [ testVerifyIndispensableTrusteePublicKey v crypto 0 (Right ())
33 ]
34
35 testVerifyIndispensableTrusteePublicKey ::
36 forall crypto v.
37 Group crypto => Key crypto =>
38 Reifies v Version => Proxy v ->
39 crypto -> Int -> Either ErrorTrusteePublicKey () -> TestTree
40 testVerifyIndispensableTrusteePublicKey (_v::Proxy v) crypto seed exp =
41 reify crypto $ \case
42 (c::Proxy c) | Dict <- groupDict c ->
43 let got =
44 runExcept $
45 (`evalStateT` Random.mkStdGen seed) $ do
46 trusteeSecKey :: SecretKey crypto c <- randomSecretKey
47 trusteePubKey :: TrusteePublicKey crypto v c <- proveIndispensableTrusteePublicKey trusteeSecKey
48 lift $ verifyIndispensableTrusteePublicKey trusteePubKey
49 in
50 testCase (Text.unpack $ cryptoName @crypto crypto) $
51 got @?= exp
52
53 testsVerifyTally ::
54 Group crypto => Key crypto =>
55 Reifies v Version => Proxy v ->
56 crypto -> TestTree
57 testsVerifyTally v crypto =
58 testGroup (Text.unpack $ cryptoName crypto)
59 [ testVerifyTally v crypto 0 1 1 1
60 , testVerifyTally v crypto 0 2 1 1
61 , testVerifyTally v crypto 0 1 2 1
62 , testVerifyTally v crypto 0 2 2 1
63 , testVerifyTally v crypto 0 5 10 5
64 ]
65
66 testVerifyTally ::
67 Group crypto => Key crypto =>
68 Reifies v Version => Proxy v ->
69 crypto -> Int -> Natural -> Natural -> Natural -> TestTree
70 testVerifyTally (_v::Proxy v) crypto seed nTrustees nQuests nChoices =
71 let clearTallyResult = dummyTallyResult nQuests nChoices in
72 let decryptedTallyResult :: Either ErrorTally [[Natural]] =
73 reify crypto $ \case
74 (c::Proxy c) | Dict <- groupDict c ->
75 runExcept $
76 (`evalStateT` Random.mkStdGen seed) $ do
77 secKeyByTrustee :: [SecretKey crypto c] <-
78 replicateM (fromIntegral nTrustees) $ randomSecretKey
79 trusteePubKeys
80 :: [TrusteePublicKey crypto v c]
81 <- forM secKeyByTrustee $ proveIndispensableTrusteePublicKey
82 let pubKeyByTrustee = trustee_PublicKey <$> trusteePubKeys
83 let elecPubKey = combineIndispensableTrusteePublicKeys trusteePubKeys
84 (encTally, countMax) <- encryptTallyResult elecPubKey clearTallyResult
85 decShareByTrustee
86 :: [DecryptionShare crypto v c]
87 <- forM secKeyByTrustee $ proveDecryptionShare encTally
88 lift $ verifyDecryptionShareByTrustee encTally pubKeyByTrustee decShareByTrustee
89 tally@Tally{..} <- lift $
90 proveTally (encTally, countMax) decShareByTrustee $
91 combineIndispensableDecryptionShares pubKeyByTrustee
92 lift $ verifyTally tally $
93 combineIndispensableDecryptionShares pubKeyByTrustee
94 return tally_countByChoiceByQuest
95 in
96 testCase (Printf.printf "#T=%i,#Q=%i,#C=%i (%i maxCount)"
97 nTrustees nQuests nChoices
98 (dummyTallyCount nQuests nChoices)) $
99 decryptedTallyResult @?= Right clearTallyResult
100
101 dummyTallyCount :: Natural -> Natural -> Natural
102 dummyTallyCount quest choice = quest * choice
103
104 dummyTallyResult :: Natural -> Natural -> [[Natural]]
105 dummyTallyResult nQuests nChoices =
106 [ [ dummyTallyCount q c | c <- [1..nChoices] ]
107 | q <- [1..nQuests]
108 ]
109
110 encryptTallyResult ::
111 Reifies v Version =>
112 Reifies c crypto =>
113 Group crypto =>
114 Multiplicative (G crypto c) =>
115 Invertible (G crypto c) =>
116 Monad m => RandomGen r =>
117 PublicKey crypto c -> [[Natural]] -> StateT r m (EncryptedTally crypto v c, Natural)
118 encryptTallyResult pubKey countByChoiceByQuest =
119 (`runStateT` 0) $
120 forM countByChoiceByQuest $
121 mapM $ \count -> do
122 modify' $ max count
123 (_encNonce, enc) <- lift $ encrypt pubKey (fromNatural count)
124 return enc
125