Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data TrusteePublicKey crypto v c = TrusteePublicKey {
- trustee_PublicKey :: !(PublicKey crypto c)
- trustee_SecretKeyProof :: !(Proof crypto v c)
- proveIndispensableTrusteePublicKey :: Reifies v Version => CryptoParams crypto c => Key crypto => Monad m => RandomGen r => SecretKey crypto c -> StateT r m (TrusteePublicKey crypto v c)
- verifyIndispensableTrusteePublicKey :: Reifies v Version => CryptoParams crypto c => Monad m => TrusteePublicKey crypto v c -> ExceptT ErrorTrusteePublicKey m ()
- data ErrorTrusteePublicKey = ErrorTrusteePublicKey_WrongProof
- indispensableTrusteePublicKeyStatement :: CryptoParams crypto c => PublicKey crypto c -> ByteString
- combineIndispensableTrusteePublicKeys :: CryptoParams crypto c => [TrusteePublicKey crypto v c] -> PublicKey crypto c
- verifyIndispensableDecryptionShareByTrustee :: Reifies v Version => CryptoParams crypto c => Monad m => EncryptedTally crypto v c -> [PublicKey crypto c] -> [DecryptionShare crypto v c] -> ExceptT ErrorTally m ()
- combineIndispensableDecryptionShares :: Reifies v Version => CryptoParams crypto c => [PublicKey crypto c] -> DecryptionShareCombinator crypto v c
Type TrusteePublicKey
data TrusteePublicKey crypto v c Source #
TrusteePublicKey | |
|
Instances
Generating a TrusteePublicKey
proveIndispensableTrusteePublicKey :: Reifies v Version => CryptoParams crypto c => Key crypto => Monad m => RandomGen r => SecretKey crypto c -> StateT r m (TrusteePublicKey crypto v c) Source #
(
returns the proveIndispensableTrusteePublicKey
trustSecKey)PublicKey
associated to trustSecKey
and a Proof
of its knowledge.
Checking a TrusteePublicKey
before incorporating it into the Election'
s PublicKey
verifyIndispensableTrusteePublicKey :: Reifies v Version => CryptoParams crypto c => Monad m => TrusteePublicKey crypto v c -> 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.
Type ErrorTrusteePublicKey
data ErrorTrusteePublicKey Source #
ErrorTrusteePublicKey_WrongProof | 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 # |
Hashing
indispensableTrusteePublicKeyStatement :: CryptoParams crypto c => PublicKey crypto c -> ByteString Source #
Election'
s PublicKey
Generating an Election'
s PublicKey
from multiple TrusteePublicKey
s.
combineIndispensableTrusteePublicKeys :: CryptoParams crypto c => [TrusteePublicKey crypto v c] -> PublicKey crypto c Source #
Checking the trustee's DecryptionShare
s before decrypting an EncryptedTally
.
verifyIndispensableDecryptionShareByTrustee :: Reifies v Version => CryptoParams crypto c => Monad m => EncryptedTally crypto v c -> [PublicKey crypto c] -> [DecryptionShare crypto v c] -> ExceptT ErrorTally m () Source #
Decrypting an EncryptedTally
from multiple TrusteePublicKey
s.
combineIndispensableDecryptionShares :: Reifies v Version => CryptoParams crypto c => [PublicKey crypto c] -> DecryptionShareCombinator crypto v c Source #
(
returns the combineDecryptionShares
pubKeyByTrustee decShareByTrustee)DecryptionFactor
s by choice by Question