]> Git — Sourcephile - majurity.git/blob - hjugement-protocol/tests/HUnit/Trustee/Indispensable.hs
protocol: bring c from the method level to the class level
[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 Reifies v Version =>
28 ReifyCrypto crypto => Key crypto =>
29 Proxy v -> 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 ReifyCrypto crypto => Key crypto =>
38 Reifies v Version => Proxy v ->
39 crypto -> Int -> Either ErrorTrusteePublicKey () -> TestTree
40 testVerifyIndispensableTrusteePublicKey (_v::Proxy v) crypto seed exp =
41 reifyCrypto crypto $ \(_c::Proxy c) ->
42 let got =
43 runExcept $
44 (`evalStateT` Random.mkStdGen seed) $ do
45 trusteeSecKey :: SecretKey crypto c <- randomSecretKey
46 trusteePubKey :: TrusteePublicKey crypto v c <- proveIndispensableTrusteePublicKey trusteeSecKey
47 lift $ verifyIndispensableTrusteePublicKey trusteePubKey
48 in
49 testCase (Text.unpack $ cryptoName @crypto crypto) $
50 got @?= exp
51
52 testsVerifyTally ::
53 ReifyCrypto crypto => Key crypto =>
54 Reifies v Version => Proxy v ->
55 crypto -> TestTree
56 testsVerifyTally v crypto =
57 testGroup (Text.unpack $ cryptoName crypto)
58 [ testVerifyTally v crypto 0 1 1 1
59 , testVerifyTally v crypto 0 2 1 1
60 , testVerifyTally v crypto 0 1 2 1
61 , testVerifyTally v crypto 0 2 2 1
62 , testVerifyTally v crypto 0 5 10 5
63 ]
64
65 testVerifyTally ::
66 Reifies v Version =>
67 ReifyCrypto crypto => Key crypto =>
68 Proxy v -> crypto -> Int -> Natural -> Natural -> Natural -> TestTree
69 testVerifyTally (_v::Proxy v) crypto seed nTrustees nQuests nChoices =
70 let clearTallyResult = dummyTallyResult nQuests nChoices in
71 let decryptedTallyResult :: Either ErrorTally [[Natural]] =
72 reifyCrypto crypto $ \(_c::Proxy c) ->
73 runExcept $
74 (`evalStateT` Random.mkStdGen seed) $ do
75 secKeyByTrustee :: [SecretKey crypto c] <-
76 replicateM (fromIntegral nTrustees) $ randomSecretKey
77 trusteePubKeys
78 :: [TrusteePublicKey crypto v c]
79 <- forM secKeyByTrustee $ proveIndispensableTrusteePublicKey
80 let pubKeyByTrustee = trustee_PublicKey <$> trusteePubKeys
81 let elecPubKey = combineIndispensableTrusteePublicKeys trusteePubKeys
82 (encTally, countMax) <- encryptTallyResult elecPubKey clearTallyResult
83 decShareByTrustee
84 :: [DecryptionShare crypto v c]
85 <- forM secKeyByTrustee $ proveDecryptionShare encTally
86 lift $ verifyDecryptionShareByTrustee encTally pubKeyByTrustee decShareByTrustee
87 tally@Tally{..} <- lift $
88 proveTally (encTally, countMax) decShareByTrustee $
89 combineIndispensableDecryptionShares pubKeyByTrustee
90 lift $ verifyTally tally $
91 combineIndispensableDecryptionShares pubKeyByTrustee
92 return tally_countByChoiceByQuest
93 in
94 testCase (Printf.printf "#T=%i,#Q=%i,#C=%i (%i maxCount)"
95 nTrustees nQuests nChoices
96 (dummyTallyCount nQuests nChoices)) $
97 decryptedTallyResult @?= Right clearTallyResult
98
99 dummyTallyCount :: Natural -> Natural -> Natural
100 dummyTallyCount quest choice = quest * choice
101
102 dummyTallyResult :: Natural -> Natural -> [[Natural]]
103 dummyTallyResult nQuests nChoices =
104 [ [ dummyTallyCount q c | c <- [1..nChoices] ]
105 | q <- [1..nQuests]
106 ]
107
108 encryptTallyResult ::
109 Reifies v Version =>
110 GroupParams crypto c =>
111 Monad m => RandomGen r =>
112 PublicKey crypto c -> [[Natural]] -> StateT r m (EncryptedTally crypto v c, Natural)
113 encryptTallyResult pubKey countByChoiceByQuest =
114 (`runStateT` 0) $
115 forM countByChoiceByQuest $
116 mapM $ \count -> do
117 modify' $ max count
118 (_encNonce, enc) <- lift $ encrypt pubKey (fromNatural count)
119 return enc
120