| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Voting.Protocol.Election
Contents
Synopsis
- data Question v = Question {
- question_text :: !Text
- question_choices :: ![Text]
- question_mini :: !Natural
- question_maxi :: !Natural
- data Answer crypto v c = Answer {
- answer_opinions :: ![(Encryption crypto v c, DisjProof crypto v c)]
- answer_sumProof :: !(DisjProof crypto v c)
- encryptAnswer :: Reifies v Version => CryptoParams crypto c => Monad m => RandomGen r => PublicKey crypto c -> ZKP -> Question v -> [Bool] -> StateT r (ExceptT ErrorAnswer m) (Answer crypto v c)
- verifyAnswer :: Reifies v Version => CryptoParams crypto c => PublicKey crypto c -> ZKP -> Question v -> Answer crypto v c -> Bool
- data ErrorAnswer
- type Opinion = E
- data Election crypto v c = Election {
- election_name :: !Text
- election_description :: !Text
- election_questions :: ![Question v]
- election_uuid :: !UUID
- election_hash :: Base64SHA256
- election_crypto :: !crypto
- election_version :: !(Maybe Version)
- election_public_key :: !(PublicKey crypto c)
- hashElection :: Reifies v Version => CryptoParams crypto c => ToJSON crypto => Election crypto v c -> Base64SHA256
- readElection :: forall crypto r. FromJSON crypto => ReifyCrypto crypto => FilePath -> (forall v c. Reifies v Version => CryptoParams crypto c => Election crypto v c -> r) -> ExceptT String IO r
- data Ballot crypto v c = Ballot {
- ballot_answers :: ![Answer crypto v c]
- ballot_signature :: !(Maybe (Signature crypto v c))
- ballot_election_uuid :: !UUID
- ballot_election_hash :: !Base64SHA256
- encryptBallot :: Reifies v Version => CryptoParams crypto c => Key crypto => Monad m => RandomGen r => Election crypto v c -> Maybe (SecretKey crypto c) -> [[Bool]] -> StateT r (ExceptT ErrorBallot m) (Ballot crypto v c)
- verifyBallot :: Reifies v Version => CryptoParams crypto c => Election crypto v c -> Ballot crypto v c -> Bool
- data ErrorBallot
- ballotStatement :: CryptoParams crypto c => [Answer crypto v c] -> [G crypto c]
- ballotCommitments :: CryptoParams crypto c => ToNatural (G crypto c) => ZKP -> Commitment crypto c -> ByteString
Type Question
Constructors
| Question | |
Fields
| |
Instances
| Eq (Question v) Source # | |
| Show (Question v) Source # | |
| Generic (Question v) Source # | |
| Reifies v Version => ToJSON (Question v) Source # | |
Defined in Voting.Protocol.Election | |
| Reifies v Version => FromJSON (Question v) Source # | |
| NFData (Question v) Source # | |
Defined in Voting.Protocol.Election | |
| type Rep (Question v) Source # | |
Defined in Voting.Protocol.Election type Rep (Question v) = D1 (MetaData "Question" "Voting.Protocol.Election" "hjugement-protocol-0.0.10.20191104-EAw7qkvTkg3AkEmPDQjrRv" False) (C1 (MetaCons "Question" PrefixI True) ((S1 (MetaSel (Just "question_text") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "question_choices") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Text])) :*: (S1 (MetaSel (Just "question_mini") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Natural) :*: S1 (MetaSel (Just "question_maxi") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Natural)))) | |
Type Answer
data Answer crypto v c Source #
Constructors
| Answer | |
Fields
| |
Instances
| Eq (G crypto c) => Eq (Answer crypto v c) Source # | |
| (Show (G crypto c), Show (G crypto c)) => Show (Answer crypto v c) Source # | |
| Generic (Answer crypto v c) Source # | |
| (Reifies v Version, CryptoParams crypto c) => ToJSON (Answer crypto v c) Source # | |
Defined in Voting.Protocol.Election | |
| (Reifies v Version, CryptoParams crypto c) => FromJSON (Answer crypto v c) Source # | |
| NFData (G crypto c) => NFData (Answer crypto v c) Source # | |
Defined in Voting.Protocol.Election | |
| type Rep (Answer crypto v c) Source # | |
Defined in Voting.Protocol.Election type Rep (Answer crypto v c) = D1 (MetaData "Answer" "Voting.Protocol.Election" "hjugement-protocol-0.0.10.20191104-EAw7qkvTkg3AkEmPDQjrRv" False) (C1 (MetaCons "Answer" PrefixI True) (S1 (MetaSel (Just "answer_opinions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [(Encryption crypto v c, DisjProof crypto v c)]) :*: S1 (MetaSel (Just "answer_sumProof") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (DisjProof crypto v c)))) | |
encryptAnswer :: Reifies v Version => CryptoParams crypto c => Monad m => RandomGen r => PublicKey crypto c -> ZKP -> Question v -> [Bool] -> StateT r (ExceptT ErrorAnswer m) (Answer crypto v c) Source #
(
returns an encryptAnswer elecPubKey zkp quest opinions)Answer validable by verifyAnswer,
unless an ErrorAnswer is returned.
verifyAnswer :: Reifies v Version => CryptoParams crypto c => PublicKey crypto c -> ZKP -> Question v -> Answer crypto v c -> Bool Source #
Type ErrorAnswer
data ErrorAnswer Source #
Error raised by encryptAnswer.
Constructors
| ErrorAnswer_WrongNumberOfOpinions Natural Natural | When the number of opinions is different than
the number of choices ( |
| ErrorAnswer_WrongSumOfOpinions Natural Natural Natural | When the sum of opinions is not within the bounds
of |
Instances
Type Opinion
Index of a Disjunction within a list of them.
It is encrypted as a GroupExponent by encrypt.
Type Election
data Election crypto v c Source #
Constructors
| Election | |
Fields
| |
Instances
hashElection :: Reifies v Version => CryptoParams crypto c => ToJSON crypto => Election crypto v c -> Base64SHA256 Source #
readElection :: forall crypto r. FromJSON crypto => ReifyCrypto crypto => FilePath -> (forall v c. Reifies v Version => CryptoParams crypto c => Election crypto v c -> r) -> ExceptT String IO r Source #
Type Ballot
data Ballot crypto v c Source #
Constructors
| Ballot | |
Fields
| |
Instances
encryptBallot :: Reifies v Version => CryptoParams crypto c => Key crypto => Monad m => RandomGen r => Election crypto v c -> Maybe (SecretKey crypto c) -> [[Bool]] -> StateT r (ExceptT ErrorBallot m) (Ballot crypto v c) Source #
(
returns a encryptBallot c (Just ballotSecKey) opinionsByQuest)Ballot signed by secKey (the voter's secret key)
where opinionsByQuest is a list of Opinions
on each question_choices of each election_questions.
verifyBallot :: Reifies v Version => CryptoParams crypto c => Election crypto v c -> Ballot crypto v c -> Bool Source #
Type ErrorBallot
data ErrorBallot Source #
Error raised by encryptBallot.
Constructors
| ErrorBallot_WrongNumberOfAnswers Natural Natural | When the number of answers is different than the number of questions. |
| ErrorBallot_Answer ErrorAnswer | When |
| ErrorBallot_Wrong | TODO: to be more precise. |
Instances
Hashing
ballotStatement :: CryptoParams crypto c => [Answer crypto v c] -> [G crypto c] Source #
(
returns the encrypted material to be signed:
all the ballotStatement ballot)encryption_nonces and encryption_vaults of the given ballot_answers.
ballotCommitments :: CryptoParams crypto c => ToNatural (G crypto c) => ZKP -> Commitment crypto c -> ByteString Source #
(ballotCommitments voterZKP commitment)