hjugement-protocol-0.0.10.20191104: A cryptographic protocol for the Majority Judgment.

Safe HaskellNone
LanguageHaskell2010

Voting.Protocol.Trustee.Indispensable

Contents

Synopsis

Type TrusteePublicKey

data TrusteePublicKey crypto v c Source #

Constructors

TrusteePublicKey 

Fields

Instances
Eq (G crypto c) => Eq (TrusteePublicKey crypto v c) Source # 
Instance details

Defined in Voting.Protocol.Trustee.Indispensable

Methods

(==) :: TrusteePublicKey crypto v c -> TrusteePublicKey crypto v c -> Bool #

(/=) :: TrusteePublicKey crypto v c -> TrusteePublicKey crypto v c -> Bool #

(Show (G crypto c), Show (PublicKey crypto c)) => Show (TrusteePublicKey crypto v c) Source # 
Instance details

Defined in Voting.Protocol.Trustee.Indispensable

Methods

showsPrec :: Int -> TrusteePublicKey crypto v c -> ShowS #

show :: TrusteePublicKey crypto v c -> String #

showList :: [TrusteePublicKey crypto v c] -> ShowS #

Generic (TrusteePublicKey crypto v c) Source # 
Instance details

Defined in Voting.Protocol.Trustee.Indispensable

Associated Types

type Rep (TrusteePublicKey crypto v c) :: Type -> Type #

Methods

from :: TrusteePublicKey crypto v c -> Rep (TrusteePublicKey crypto v c) x #

to :: Rep (TrusteePublicKey crypto v c) x -> TrusteePublicKey crypto v c #

(Reifies v Version, ToJSON (G crypto c)) => ToJSON (TrusteePublicKey crypto v c) Source # 
Instance details

Defined in Voting.Protocol.Trustee.Indispensable

Methods

toJSON :: TrusteePublicKey crypto v c -> Value #

toEncoding :: TrusteePublicKey crypto v c -> Encoding #

toJSONList :: [TrusteePublicKey crypto v c] -> Value #

toEncodingList :: [TrusteePublicKey crypto v c] -> Encoding #

(Reifies v Version, CryptoParams crypto c) => FromJSON (TrusteePublicKey crypto v c) Source # 
Instance details

Defined in Voting.Protocol.Trustee.Indispensable

Methods

parseJSON :: Value -> Parser (TrusteePublicKey crypto v c) #

parseJSONList :: Value -> Parser [TrusteePublicKey crypto v c] #

NFData (G crypto c) => NFData (TrusteePublicKey crypto v c) Source # 
Instance details

Defined in Voting.Protocol.Trustee.Indispensable

Methods

rnf :: TrusteePublicKey crypto v c -> () #

type Rep (TrusteePublicKey crypto v c) Source # 
Instance details

Defined in Voting.Protocol.Trustee.Indispensable

type Rep (TrusteePublicKey crypto v c) = D1 (MetaData "TrusteePublicKey" "Voting.Protocol.Trustee.Indispensable" "hjugement-protocol-0.0.10.20191104-EAw7qkvTkg3AkEmPDQjrRv" False) (C1 (MetaCons "TrusteePublicKey" PrefixI True) (S1 (MetaSel (Just "trustee_PublicKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (PublicKey crypto c)) :*: S1 (MetaSel (Just "trustee_SecretKeyProof") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Proof crypto v c))))

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 #

(proveIndispensableTrusteePublicKey trustSecKey) returns the 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 #

(verifyIndispensableTrusteePublicKey trustPubKey) returns True iif. the given trustee_SecretKeyProof does prove that the SecretKey associated with the given trustee_PublicKey is known by the trustee.

Type ErrorTrusteePublicKey

Hashing

Election's PublicKey

Generating an Election's PublicKey from multiple TrusteePublicKeys.

Checking the trustee's DecryptionShares before decrypting an EncryptedTally.

Decrypting an EncryptedTally from multiple TrusteePublicKeys.

combineIndispensableDecryptionShares :: Reifies v Version => CryptoParams crypto c => [PublicKey crypto c] -> DecryptionShareCombinator crypto v c Source #

(combineDecryptionShares pubKeyByTrustee decShareByTrustee) returns the DecryptionFactors by choice by Question