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

Safe HaskellNone
LanguageHaskell2010

Voting.Protocol.FFC

Contents

Description

Finite Field Cryptography (FFC) is a method of implementing discrete logarithm cryptography using finite field mathematics.

Synopsis

Type FFC

data FFC Source #

Mutiplicative subgroup of a Finite Prime Field.

NOTE: an FFC term-value is brought into the context of many functions through a type-variable c whose Reifies constraint enables to reflect that FFC at the term-level (a surprising technique but a very useful one). Doing like this is simpler than working in a Monad (like a Reader), and enables that FFC term to be used simply in instances' methods not supporting an inner Monad, like parseJSON, randomR, fromEnum or arbitrary. Aside from that, the sharing of FFC amongst several types is encoded at the type-level by including c as a phantom type of F, G and E.

Constructors

FFC 

Fields

  • ffc_name :: !Text
     
  • ffc_fieldCharac :: !Natural

    The prime number characteristic of a Finite Prime Field.

    ElGamal's hardness to decrypt requires a large prime number to form the multiplicative subgroup.

  • ffc_groupGen :: !Natural

    A generator of the multiplicative subgroup of the Finite Prime Field.

    NOTE: since ffc_fieldCharac is prime, the multiplicative subgroup is cyclic, and there are phi(fieldCharac-1) many choices for the generator of the group, where phi is the Euler totient function.

  • ffc_groupOrder :: !Natural

    The order of the subgroup.

    WARNING: ffc_groupOrder MUST be a prime number dividing (ffc_fieldCharac-1) to ensure that ElGamal is secure in terms of the DDH assumption.

Instances
Eq FFC Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

(==) :: FFC -> FFC -> Bool #

(/=) :: FFC -> FFC -> Bool #

Show FFC Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

showsPrec :: Int -> FFC -> ShowS #

show :: FFC -> String #

showList :: [FFC] -> ShowS #

Generic FFC Source # 
Instance details

Defined in Voting.Protocol.FFC

Associated Types

type Rep FFC :: Type -> Type #

Methods

from :: FFC -> Rep FFC x #

to :: Rep FFC x -> FFC #

ToJSON FFC Source # 
Instance details

Defined in Voting.Protocol.FFC

FromJSON FFC Source # 
Instance details

Defined in Voting.Protocol.FFC

NFData FFC Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

rnf :: FFC -> () #

ReifyCrypto FFC Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

reifyCrypto :: FFC -> (forall c. (Reifies c FFC, CryptoParams FFC c) => Proxy c -> r) -> r Source #

Key FFC Source # 
Instance details

Defined in Voting.Protocol.FFC

Reifies c FFC => CryptoParams FFC c Source # 
Instance details

Defined in Voting.Protocol.FFC

Eq (G FFC c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

(==) :: G FFC c -> G FFC c -> Bool #

(/=) :: G FFC c -> G FFC c -> Bool #

Ord (G FFC c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

compare :: G FFC c -> G FFC c -> Ordering #

(<) :: G FFC c -> G FFC c -> Bool #

(<=) :: G FFC c -> G FFC c -> Bool #

(>) :: G FFC c -> G FFC c -> Bool #

(>=) :: G FFC c -> G FFC c -> Bool #

max :: G FFC c -> G FFC c -> G FFC c #

min :: G FFC c -> G FFC c -> G FFC c #

Show (G FFC c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

showsPrec :: Int -> G FFC c -> ShowS #

show :: G FFC c -> String #

showList :: [G FFC c] -> ShowS #

ToJSON (G FFC c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

toJSON :: G FFC c -> Value #

toEncoding :: G FFC c -> Encoding #

toJSONList :: [G FFC c] -> Value #

toEncodingList :: [G FFC c] -> Encoding #

Reifies c FFC => FromJSON (G FFC c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

parseJSON :: Value -> Parser (G FFC c) #

parseJSONList :: Value -> Parser [G FFC c] #

NFData (G FFC c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

rnf :: G FFC c -> () #

Reifies c FFC => Random (G FFC c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

randomR :: RandomGen g => (G FFC c, G FFC c) -> g -> (G FFC c, g) #

random :: RandomGen g => g -> (G FFC c, g) #

randomRs :: RandomGen g => (G FFC c, G FFC c) -> g -> [G FFC c] #

randoms :: RandomGen g => g -> [G FFC c] #

randomRIO :: (G FFC c, G FFC c) -> IO (G FFC c) #

randomIO :: IO (G FFC c) #

ToNatural (G FFC c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

nat :: G FFC c -> Natural Source #

Reifies c FFC => FromNatural (G FFC c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

fromNatural :: Natural -> G FFC c Source #

Reifies c FFC => EuclideanRing (G FFC c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

inverse :: G FFC c -> G FFC c Source #

(/) :: G FFC c -> G FFC c -> G FFC c Source #

Reifies c FFC => Ring (G FFC c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

negate :: G FFC c -> G FFC c Source #

(-) :: G FFC c -> G FFC c -> G FFC c Source #

Reifies c FFC => Semiring (G FFC c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

one :: G FFC c Source #

(*) :: G FFC c -> G FFC c -> G FFC c Source #

Reifies c FFC => Additive (G FFC c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

zero :: G FFC c Source #

(+) :: G FFC c -> G FFC c -> G FFC c Source #

sum :: Foldable f => f (G FFC c) -> G FFC c Source #

type Rep FFC Source # 
Instance details

Defined in Voting.Protocol.FFC

type Rep FFC = D1 (MetaData "FFC" "Voting.Protocol.FFC" "hjugement-protocol-0.0.10.20191104-EAw7qkvTkg3AkEmPDQjrRv" False) (C1 (MetaCons "FFC" PrefixI True) ((S1 (MetaSel (Just "ffc_name") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "ffc_fieldCharac") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Natural)) :*: (S1 (MetaSel (Just "ffc_groupGen") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Natural) :*: S1 (MetaSel (Just "ffc_groupOrder") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Natural))))
type FieldElement FFC Source #

The type of the elements of a Finite Prime Field.

A field must satisfy the following properties:

  • (f, (+), zero) forms an abelian group, called the additive group of f.
  • (NonNull f, (*), one) forms an abelian group, called the multiplicative group of f.
  • (*) is associative: (a*b)*c == a*(b*c) and a*(b*c) == (a*b)*c.
  • (*) and (+) are both commutative: a*b == b*a and a+b == b+a
  • (*) and (+) are both left and right distributive: a*(b+c) == (a*b) + (a*c) and (a+b)*c == (a*c) + (b*c)

The Natural is always within [0..fieldCharac-1].

Instance details

Defined in Voting.Protocol.FFC

Examples

weakFFC :: FFC Source #

Weak parameters for debugging purposes only.

beleniosFFC :: FFC Source #

Parameters used in Belenios. A 2048-bit fieldCharac of a Finite Prime Field, with a 256-bit groupOrder for a multiplicative subgroup generated by groupGen.