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

Safe HaskellNone
LanguageHaskell2010

Protocol.Arithmetic

Contents

Synopsis

Type F

newtype F p Source #

The type of the elements of a PrimeField.

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].

Constructors

F 

Fields

Instances
Eq (F p) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

(==) :: F p -> F p -> Bool #

(/=) :: F p -> F p -> Bool #

Ord (F p) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

compare :: F p -> F p -> Ordering #

(<) :: F p -> F p -> Bool #

(<=) :: F p -> F p -> Bool #

(>) :: F p -> F p -> Bool #

(>=) :: F p -> F p -> Bool #

max :: F p -> F p -> F p #

min :: F p -> F p -> F p #

Show (F p) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

showsPrec :: Int -> F p -> ShowS #

show :: F p -> String #

showList :: [F p] -> ShowS #

PrimeField p => Random (F p) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

randomR :: RandomGen g => (F p, F p) -> g -> (F p, g) #

random :: RandomGen g => g -> (F p, g) #

randomRs :: RandomGen g => (F p, F p) -> g -> [F p] #

randoms :: RandomGen g => g -> [F p] #

randomRIO :: (F p, F p) -> IO (F p) #

randomIO :: IO (F p) #

PrimeField p => Multiplicative (F p) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

one :: F p Source #

(*) :: F p -> F p -> F p Source #

PrimeField p => Negable (F p) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

neg :: F p -> F p Source #

(-) :: F p -> F p -> F p Source #

PrimeField p => Additive (F p) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

zero :: F p Source #

(+) :: F p -> F p -> F p Source #

sum :: Foldable f => f (F p) -> F p Source #

inF :: forall p i. PrimeField p => Integral i => i -> F p Source #

Class PrimeField

class PrimeField p where Source #

Parameter for a prime field.

Methods

fieldCharac :: Natural Source #

The prime number characteristic of a PrimeField.

ElGamal's hardness to decrypt requires a large prime number to form the Multiplicative SubGroup.

Instances
PrimeField BeleniosParams Source # 
Instance details

Defined in Protocol.Arithmetic

PrimeField WeakParams Source # 
Instance details

Defined in Protocol.Arithmetic

Class Additive

class Additive a where Source #

Minimal complete definition

zero, (+)

Methods

zero :: a Source #

(+) :: a -> a -> a infixl 6 Source #

sum :: Foldable f => f a -> a Source #

Instances
Additive Int Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

zero :: Int Source #

(+) :: Int -> Int -> Int Source #

sum :: Foldable f => f Int -> Int Source #

Additive Integer Source # 
Instance details

Defined in Protocol.Arithmetic

Additive Natural Source # 
Instance details

Defined in Protocol.Arithmetic

(SubGroup q, Additive (F (P q))) => Additive (E q) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

zero :: E q Source #

(+) :: E q -> E q -> E q Source #

sum :: Foldable f => f (E q) -> E q Source #

PrimeField p => Additive (F p) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

zero :: F p Source #

(+) :: F p -> F p -> F p Source #

sum :: Foldable f => f (F p) -> F p Source #

SubGroup q => Additive (Encryption q) Source #

Additive homomorphism. Using the fact that: groupGen ^x * groupGen ^y == groupGen ^(x+y).

Instance details

Defined in Protocol.Election

Class Negable

class Additive a => Negable a where Source #

Minimal complete definition

neg

Methods

neg :: a -> a Source #

(-) :: a -> a -> a infixl 6 Source #

Instances
Negable Int Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

neg :: Int -> Int Source #

(-) :: Int -> Int -> Int Source #

Negable Integer Source # 
Instance details

Defined in Protocol.Arithmetic

(SubGroup q, Negable (F (P q))) => Negable (E q) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

neg :: E q -> E q Source #

(-) :: E q -> E q -> E q Source #

PrimeField p => Negable (F p) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

neg :: F p -> F p Source #

(-) :: F p -> F p -> F p Source #

Class Multiplicative

class Multiplicative a where Source #

Methods

one :: a Source #

(*) :: a -> a -> a infixl 7 Source #

Instances
Multiplicative Int Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

one :: Int Source #

(*) :: Int -> Int -> Int Source #

Multiplicative Integer Source # 
Instance details

Defined in Protocol.Arithmetic

Multiplicative Natural Source # 
Instance details

Defined in Protocol.Arithmetic

(SubGroup q, Multiplicative (F (P q))) => Multiplicative (E q) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

one :: E q Source #

(*) :: E q -> E q -> E q Source #

(SubGroup q, Multiplicative (F (P q))) => Multiplicative (G q) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

one :: G q Source #

(*) :: G q -> G q -> G q Source #

PrimeField p => Multiplicative (F p) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

one :: F p Source #

(*) :: F p -> F p -> F p Source #

Class Invertible

class Multiplicative a => Invertible a where Source #

Minimal complete definition

inv

Methods

inv :: a -> a Source #

(/) :: a -> a -> a infixl 7 Source #

Instances
(SubGroup q, Multiplicative (F (P q))) => Invertible (G q) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

inv :: G q -> G q Source #

(/) :: G q -> G q -> G q Source #

Type G

newtype G q Source #

The type of the elements of a Multiplicative SubGroup of a PrimeField.

Constructors

G 

Fields

Instances
Eq (G q) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

(==) :: G q -> G q -> Bool #

(/=) :: G q -> G q -> Bool #

Ord (G q) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

compare :: G q -> G q -> Ordering #

(<) :: G q -> G q -> Bool #

(<=) :: G q -> G q -> Bool #

(>) :: G q -> G q -> Bool #

(>=) :: G q -> G q -> Bool #

max :: G q -> G q -> G q #

min :: G q -> G q -> G q #

Show (G q) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

showsPrec :: Int -> G q -> ShowS #

show :: G q -> String #

showList :: [G q] -> ShowS #

(SubGroup q, Multiplicative (F (P q))) => Invertible (G q) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

inv :: G q -> G q Source #

(/) :: G q -> G q -> G q Source #

(SubGroup q, Multiplicative (F (P q))) => Multiplicative (G q) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

one :: G q Source #

(*) :: G q -> G q -> G q Source #

natG :: SubGroup q => G q -> Natural Source #

(natG g) returns the element of the SubGroup g as an Natural within [0..fieldCharac-1].

Class SubGroup

class (PrimeField (P q), Multiplicative (F (P q))) => SubGroup q where Source #

A SubGroup of a PrimeField. Used for signing (Schnorr) and encrypting (ElGamal).

Minimal complete definition

groupGen, groupOrder

Associated Types

type P q :: * Source #

Setting q determines p, equals to P q.

Methods

groupGen :: G q Source #

A generator of the SubGroup. NOTE: since F p is a PrimeField, 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.

groupOrder :: F (P q) Source #

The order of the SubGroup.

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

groupGenInverses :: [G q] Source #

groupGenInverses returns the infinite list of inverse powers of groupGen: [groupGen ^ neg i | i <- [0..]], but by computing each value from the previous one.

NOTE: groupGenInverses is in the SubGroup class in order to keep computed terms in memory accross calls to groupGenInverses.

Used by validableEncryption.

hash :: SubGroup q => ByteString -> [G q] -> E q Source #

(hash prefix gs) returns as a number in (F p) the SHA256 of the given prefix prefixing the decimal representation of given SubGroup elements gs, each one postfixed with a comma (",").

Used by proveEncryption and validateEncryption, where the prefix contains the statement to be proven, and the gs contains the commitments.

Type E

newtype E q Source #

An exponent of a (necessarily cyclic) SubGroup of a PrimeField. The value is always in [0..groupOrder-1].

Constructors

E 

Fields

Instances
SubGroup q => Enum (E q) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

succ :: E q -> E q #

pred :: E q -> E q #

toEnum :: Int -> E q #

fromEnum :: E q -> Int #

enumFrom :: E q -> [E q] #

enumFromThen :: E q -> E q -> [E q] #

enumFromTo :: E q -> E q -> [E q] #

enumFromThenTo :: E q -> E q -> E q -> [E q] #

Eq (E q) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

(==) :: E q -> E q -> Bool #

(/=) :: E q -> E q -> Bool #

Ord (E q) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

compare :: E q -> E q -> Ordering #

(<) :: E q -> E q -> Bool #

(<=) :: E q -> E q -> Bool #

(>) :: E q -> E q -> Bool #

(>=) :: E q -> E q -> Bool #

max :: E q -> E q -> E q #

min :: E q -> E q -> E q #

Show (E q) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

showsPrec :: Int -> E q -> ShowS #

show :: E q -> String #

showList :: [E q] -> ShowS #

SubGroup q => Random (E q) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

randomR :: RandomGen g => (E q, E q) -> g -> (E q, g) #

random :: RandomGen g => g -> (E q, g) #

randomRs :: RandomGen g => (E q, E q) -> g -> [E q] #

randoms :: RandomGen g => g -> [E q] #

randomRIO :: (E q, E q) -> IO (E q) #

randomIO :: IO (E q) #

(SubGroup q, Multiplicative (F (P q))) => Multiplicative (E q) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

one :: E q Source #

(*) :: E q -> E q -> E q Source #

(SubGroup q, Negable (F (P q))) => Negable (E q) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

neg :: E q -> E q Source #

(-) :: E q -> E q -> E q Source #

(SubGroup q, Additive (F (P q))) => Additive (E q) Source # 
Instance details

Defined in Protocol.Arithmetic

Methods

zero :: E q Source #

(+) :: E q -> E q -> E q Source #

sum :: Foldable f => f (E q) -> E q Source #

inE :: forall q i. SubGroup q => Integral i => i -> E q Source #

natE :: forall q. SubGroup q => E q -> Natural Source #

(^) :: SubGroup q => G q -> E q -> G q infixr 8 Source #

(b ^ e) returns the modular exponentiation of base b by exponent e.

Type RandomGen

randomR :: Monad m => RandomGen r => Random i => Negable i => Multiplicative i => i -> StateT r m i Source #

(randomR i) returns a random integer in [0..i-1].

random :: Monad m => RandomGen r => Random i => Negable i => Multiplicative i => StateT r m i Source #

(random) returns a random integer in the range determined by its type.

Groups

Type WeakParams

data WeakParams Source #

Weak parameters for debugging purposes only.

Instances
SubGroup WeakParams Source # 
Instance details

Defined in Protocol.Arithmetic

Associated Types

type P WeakParams :: Type Source #

PrimeField WeakParams Source # 
Instance details

Defined in Protocol.Arithmetic

type P WeakParams Source # 
Instance details

Defined in Protocol.Arithmetic

Type BeleniosParams

data BeleniosParams Source #

Parameters used in Belenios. A 2048-bit fieldCharac of a PrimeField, with a 256-bit groupOrder for a Multiplicative SubGroup generated by groupGen.

Orphan instances

Random Natural Source # 
Instance details

Methods

randomR :: RandomGen g => (Natural, Natural) -> g -> (Natural, g) #

random :: RandomGen g => g -> (Natural, g) #

randomRs :: RandomGen g => (Natural, Natural) -> g -> [Natural] #

randoms :: RandomGen g => g -> [Natural] #

randomRIO :: (Natural, Natural) -> IO Natural #

randomIO :: IO Natural #