Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data TrusteePublicKey q = TrusteePublicKey {}
- data ErrorTrusteePublicKey = ErrorTrusteePublicKey_Wrong
- proveIndispensableTrusteePublicKey :: Monad m => RandomGen r => SubGroup q => SecretKey q -> StateT r m (TrusteePublicKey q)
- verifyIndispensableTrusteePublicKey :: Monad m => SubGroup q => TrusteePublicKey q -> ExceptT ErrorTrusteePublicKey m ()
- indispensableTrusteePublicKeyStatement :: PublicKey q -> ByteString
- combineIndispensableTrusteePublicKeys :: SubGroup q => [TrusteePublicKey q] -> PublicKey q
- verifyIndispensableDecryptionShareByTrustee :: SubGroup q => Monad m => EncryptedTally q -> [PublicKey q] -> [DecryptionShare q] -> ExceptT ErrorDecryptionShare m ()
- combineIndispensableDecryptionShares :: SubGroup q => [PublicKey q] -> EncryptedTally q -> DecryptionShareCombinator q
Type TrusteePublicKey
data TrusteePublicKey q Source #
TrusteePublicKey | |
|
Instances
Eq (TrusteePublicKey q) Source # | |
Defined in Voting.Protocol.Trustee.Indispensable (==) :: TrusteePublicKey q -> TrusteePublicKey q -> Bool # (/=) :: TrusteePublicKey q -> TrusteePublicKey q -> Bool # | |
Show (TrusteePublicKey q) Source # | |
Defined in Voting.Protocol.Trustee.Indispensable showsPrec :: Int -> TrusteePublicKey q -> ShowS # show :: TrusteePublicKey q -> String # showList :: [TrusteePublicKey q] -> ShowS # |
Type ErrorTrusteePublicKey
data ErrorTrusteePublicKey Source #
ErrorTrusteePublicKey_Wrong | The |
Instances
Eq ErrorTrusteePublicKey Source # | |
Defined in Voting.Protocol.Trustee.Indispensable (==) :: ErrorTrusteePublicKey -> ErrorTrusteePublicKey -> Bool # (/=) :: ErrorTrusteePublicKey -> ErrorTrusteePublicKey -> Bool # | |
Show ErrorTrusteePublicKey Source # | |
Defined in Voting.Protocol.Trustee.Indispensable showsPrec :: Int -> ErrorTrusteePublicKey -> ShowS # show :: ErrorTrusteePublicKey -> String # showList :: [ErrorTrusteePublicKey] -> ShowS # |
proveIndispensableTrusteePublicKey :: Monad m => RandomGen r => SubGroup q => SecretKey q -> StateT r m (TrusteePublicKey q) Source #
(
returns the proveIndispensableTrusteePublicKey
trustSecKey)PublicKey
associated to trustSecKey
and a Proof
of its knowledge.
verifyIndispensableTrusteePublicKey :: Monad m => SubGroup q => TrusteePublicKey q -> ExceptT ErrorTrusteePublicKey m () Source #
(
returns verifyIndispensableTrusteePublicKey
trustPubKey)True
iif. the given trustee_SecretKeyProof
does prove
that the SecretKey
associated with
the given trustee_PublicKey
is known by the trustee.
Hashing
Election'
s PublicKey
combineIndispensableTrusteePublicKeys :: SubGroup q => [TrusteePublicKey q] -> PublicKey q Source #
verifyIndispensableDecryptionShareByTrustee :: SubGroup q => Monad m => EncryptedTally q -> [PublicKey q] -> [DecryptionShare q] -> ExceptT ErrorDecryptionShare m () Source #
combineIndispensableDecryptionShares :: SubGroup q => [PublicKey q] -> EncryptedTally q -> DecryptionShareCombinator q Source #
(
returns the combineDecryptionShares
pubKeyByTrustee decShareByTrustee)DecryptionFactor
s by choice by Question