]> Git — Sourcephile - majurity.git/blob - hjugement-protocol/tests/HUnit/Election.hs
protocol: add Trustee.Indispensable
[majurity.git] / hjugement-protocol / tests / HUnit / Election.hs
1 {-# LANGUAGE AllowAmbiguousTypes #-}
2 {-# LANGUAGE DataKinds #-}
3 {-# LANGUAGE OverloadedStrings #-}
4 {-# LANGUAGE PatternSynonyms #-}
5 module HUnit.Election where
6
7 import Test.Tasty.HUnit
8 import qualified Data.List as List
9 import qualified System.Random as Random
10
11 import Voting.Protocol
12
13 import Utils
14
15 hunit :: TestTree
16 hunit = testGroup "Election"
17 [ testGroup "groupGenInverses"
18 [ testCase "WeakParams" $
19 List.take 10 (groupGenInverses @WeakParams) @?=
20 [groupGen^neg (fromNatural n) | n <- [0..9]]
21 , testCase "BeleniosParams" $
22 List.take 10 (groupGenInverses @BeleniosParams) @?=
23 [groupGen^neg (fromNatural n) | n <- [0..9]]
24 ]
25 , testGroup "encryptBallot" $
26 [ testsEncryptBallot @WeakParams
27 , testsEncryptBallot @BeleniosParams
28 ]
29 ]
30
31 testsEncryptBallot :: forall q. Params q => TestTree
32 testsEncryptBallot =
33 testGroup (paramsName @q)
34 [ testEncryptBallot @q 0
35 [Question "q1" ["a1","a2","a3"] zero one]
36 [[True, False, False]]
37 (Right True)
38 , testEncryptBallot @q 0
39 [Question "q1" ["a1","a2","a3"] zero one]
40 [[False, False, False]]
41 (Right True)
42 , testEncryptBallot @q 0
43 [Question "q1" ["a1","a2","a3"] zero one]
44 [[False, False, False]]
45 (Right True)
46 , testEncryptBallot @q 0
47 [Question "q1" [] zero one]
48 []
49 (Left (ErrorBallot_WrongNumberOfAnswers 0 1))
50 , testEncryptBallot @q 0
51 [Question "q1" ["a1","a2"] one one]
52 [[True]]
53 (Left (ErrorBallot_Answer (ErrorAnswer_WrongNumberOfOpinions 1 2)))
54 , testEncryptBallot @q 0
55 [Question "q1" ["a1","a2","a3"] zero one]
56 [[True, True, False]]
57 (Left (ErrorBallot_Answer (ErrorAnswer_WrongSumOfOpinions 2 0 1)))
58 , testEncryptBallot @q 0
59 [Question "q1" ["a1","a2","a3"] one one]
60 [[False, False, False]]
61 (Left (ErrorBallot_Answer (ErrorAnswer_WrongSumOfOpinions 0 1 1)))
62 , testEncryptBallot @q 0
63 [Question "q1" ["a1","a2"] one one]
64 [[False, False, True]]
65 (Left (ErrorBallot_Answer (ErrorAnswer_WrongNumberOfOpinions 3 2)))
66 , testEncryptBallot @q 0
67 [ Question "q1" ["a11","a12","a13"] zero (one+one)
68 , Question "q2" ["a21","a22","a23"] one one
69 ]
70 [ [True, False, True]
71 , [False, True, False] ]
72 (Right True)
73 ]
74
75 testEncryptBallot ::
76 forall q. SubGroup q =>
77 Int -> [Question q] -> [[Bool]] ->
78 Either ErrorBallot Bool ->
79 TestTree
80 testEncryptBallot seed quests opins exp =
81 let got =
82 runExcept $
83 (`evalStateT` Random.mkStdGen seed) $ do
84 uuid <- randomUUID
85 cred <- randomCredential
86 let ballotSecKey = credentialSecretKey @q uuid cred
87 elecPubKey <- publicKey <$> randomSecretKey
88 let elec = Election
89 { election_name = "election"
90 , election_description = "description"
91 , election_PublicKey = elecPubKey
92 , election_questions = quests
93 , election_uuid = uuid
94 , election_hash = Hash "" -- FIXME: when implemented
95 }
96 verifyBallot elec
97 <$> encryptBallot elec (Just ballotSecKey) opins
98 in
99 testCase (show opins) $
100 got @?= exp