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

Safe HaskellNone
LanguageHaskell2010

Voting.Protocol.Arith

Contents

Description

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

Synopsis

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 Voting.Protocol.Arith

Methods

zero :: Int Source #

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

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

Additive Integer Source # 
Instance details

Defined in Voting.Protocol.Arith

Additive Natural Source # 
Instance details

Defined in Voting.Protocol.Arith

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

Defined in Voting.Protocol.FFC

Methods

zero :: F c Source #

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

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

(Reifies c crypto, Group crypto) => Additive (E crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

zero :: E crypto c Source #

(+) :: E crypto c -> E crypto c -> E crypto c Source #

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

(Reifies c crypto, Multiplicative (FieldElement crypto c)) => Additive (Encryption crypto v c) Source #

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

Instance details

Defined in Voting.Protocol.Election

Methods

zero :: Encryption crypto v c Source #

(+) :: Encryption crypto v c -> Encryption crypto v c -> Encryption crypto v c Source #

sum :: Foldable f => f (Encryption crypto v c) -> Encryption crypto v c Source #

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 Voting.Protocol.Arith

Methods

neg :: Int -> Int Source #

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

Negable Integer Source # 
Instance details

Defined in Voting.Protocol.Arith

Reifies c FFC => Negable (F c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

neg :: F c -> F c Source #

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

(Reifies c crypto, Group crypto) => Negable (E crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

neg :: E crypto c -> E crypto c Source #

(-) :: E crypto c -> E crypto c -> E crypto c 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 Voting.Protocol.Arith

Methods

one :: Int Source #

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

Multiplicative Integer Source # 
Instance details

Defined in Voting.Protocol.Arith

Multiplicative Natural Source # 
Instance details

Defined in Voting.Protocol.Arith

Reifies c FFC => Multiplicative (F c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

one :: F c Source #

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

(Reifies c crypto, Group crypto) => Multiplicative (E crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

one :: E crypto c Source #

(*) :: E crypto c -> E crypto c -> E crypto c Source #

Multiplicative (FieldElement crypto c) => Multiplicative (G crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

one :: G crypto c Source #

(*) :: G crypto c -> G crypto c -> G crypto c 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
(Reifies c crypto, Group crypto, Multiplicative (FieldElement crypto c)) => Invertible (G crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

inv :: G crypto c -> G crypto c Source #

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

(^) :: Reifies c crypto => Multiplicative (FieldElement crypto c) => G crypto c -> E crypto c -> G crypto c infixr 8 Source #

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

groupGenInverses :: forall crypto c. Reifies c crypto => Group crypto => Multiplicative (FieldElement crypto c) => [G crypto c] 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.

Used by intervalDisjunctions.

groupGenPowers :: forall crypto c. Reifies c crypto => Group crypto => Multiplicative (FieldElement crypto c) => [G crypto c] Source #

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.

Type family FieldElement

type family FieldElement crypto :: * -> * Source #

Instances
type FieldElement FFC Source # 
Instance details

Defined in Voting.Protocol.FFC

Class Group where

class Group crypto where Source #

Methods

groupGen :: Reifies c crypto => G crypto c Source #

groupOrder :: Reifies c crypto => Proxy c -> Natural Source #

Instances
Group FFC Source # 
Instance details

Defined in Voting.Protocol.FFC

Type G

newtype G crypto c Source #

The type of the elements of a subgroup of a field.

Constructors

G 

Fields

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

Defined in Voting.Protocol.Arith

Methods

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

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

Ord (FieldElement crypto c) => Ord (G crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

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

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

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

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

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

max :: G crypto c -> G crypto c -> G crypto c #

min :: G crypto c -> G crypto c -> G crypto c #

Show (FieldElement crypto c) => Show (G crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

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

show :: G crypto c -> String #

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

ToJSON (FieldElement crypto c) => ToJSON (G crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

toJSON :: G crypto c -> Value #

toEncoding :: G crypto c -> Encoding #

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

toEncodingList :: [G crypto 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 (FieldElement crypto c) => NFData (G crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

rnf :: G crypto c -> () #

ToNatural (FieldElement crypto c) => ToNatural (G crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

nat :: G crypto c -> Natural Source #

FromNatural (FieldElement crypto c) => FromNatural (G crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

fromNatural :: Natural -> G crypto c Source #

(Reifies c crypto, Group crypto, Multiplicative (FieldElement crypto c)) => Invertible (G crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

inv :: G crypto c -> G crypto c Source #

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

Multiplicative (FieldElement crypto c) => Multiplicative (G crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

one :: G crypto c Source #

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

Type E

newtype E crypto c Source #

An exponent of a (cyclic) subgroup of a field. The value is always in [0..groupOrder-1].

Constructors

E 

Fields

Instances
(Reifies c crypto, Group crypto) => Enum (E crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

succ :: E crypto c -> E crypto c #

pred :: E crypto c -> E crypto c #

toEnum :: Int -> E crypto c #

fromEnum :: E crypto c -> Int #

enumFrom :: E crypto c -> [E crypto c] #

enumFromThen :: E crypto c -> E crypto c -> [E crypto c] #

enumFromTo :: E crypto c -> E crypto c -> [E crypto c] #

enumFromThenTo :: E crypto c -> E crypto c -> E crypto c -> [E crypto c] #

Eq (E crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

(==) :: E crypto c -> E crypto c -> Bool #

(/=) :: E crypto c -> E crypto c -> Bool #

Ord (E crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

compare :: E crypto c -> E crypto c -> Ordering #

(<) :: E crypto c -> E crypto c -> Bool #

(<=) :: E crypto c -> E crypto c -> Bool #

(>) :: E crypto c -> E crypto c -> Bool #

(>=) :: E crypto c -> E crypto c -> Bool #

max :: E crypto c -> E crypto c -> E crypto c #

min :: E crypto c -> E crypto c -> E crypto c #

Show (E crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

showsPrec :: Int -> E crypto c -> ShowS #

show :: E crypto c -> String #

showList :: [E crypto c] -> ShowS #

ToJSON (E crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

toJSON :: E crypto c -> Value #

toEncoding :: E crypto c -> Encoding #

toJSONList :: [E crypto c] -> Value #

toEncodingList :: [E crypto c] -> Encoding #

(Reifies c crypto, Group crypto) => FromJSON (E crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

parseJSON :: Value -> Parser (E crypto c) #

parseJSONList :: Value -> Parser [E crypto c] #

NFData (E crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

rnf :: E crypto c -> () #

(Reifies c crypto, Group crypto) => Random (E crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

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

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

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

randoms :: RandomGen g => g -> [E crypto c] #

randomRIO :: (E crypto c, E crypto c) -> IO (E crypto c) #

randomIO :: IO (E crypto c) #

ToNatural (E crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

nat :: E crypto c -> Natural Source #

(Reifies c crypto, Group crypto) => FromNatural (E crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

fromNatural :: Natural -> E crypto c Source #

(Reifies c crypto, Group crypto) => Multiplicative (E crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

one :: E crypto c Source #

(*) :: E crypto c -> E crypto c -> E crypto c Source #

(Reifies c crypto, Group crypto) => Negable (E crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

neg :: E crypto c -> E crypto c Source #

(-) :: E crypto c -> E crypto c -> E crypto c Source #

(Reifies c crypto, Group crypto) => Additive (E crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

zero :: E crypto c Source #

(+) :: E crypto c -> E crypto c -> E crypto c Source #

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

Class FromNatural

class FromNatural a where Source #

Methods

fromNatural :: Natural -> a Source #

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

Defined in Voting.Protocol.FFC

Methods

fromNatural :: Natural -> F c Source #

(Reifies c crypto, Group crypto) => FromNatural (E crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

fromNatural :: Natural -> E crypto c Source #

FromNatural (FieldElement crypto c) => FromNatural (G crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

fromNatural :: Natural -> G crypto c Source #

Class ToNatural

class ToNatural a where Source #

Methods

nat :: a -> Natural Source #

Instances
ToNatural Natural Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

nat :: Natural -> Natural Source #

ToNatural (F c) Source # 
Instance details

Defined in Voting.Protocol.FFC

Methods

nat :: F c -> Natural Source #

ToNatural (E crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

nat :: E crypto c -> Natural Source #

ToNatural (FieldElement crypto c) => ToNatural (G crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

nat :: G crypto c -> Natural Source #

bytesNat :: ToNatural n => n -> ByteString Source #

(bytesNat x) returns the serialization of x.

Type Hash

newtype Hash crypto c Source #

Constructors

Hash (E crypto c) 
Instances
Eq (Hash crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

(==) :: Hash crypto c -> Hash crypto c -> Bool #

(/=) :: Hash crypto c -> Hash crypto c -> Bool #

Ord (Hash crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

compare :: Hash crypto c -> Hash crypto c -> Ordering #

(<) :: Hash crypto c -> Hash crypto c -> Bool #

(<=) :: Hash crypto c -> Hash crypto c -> Bool #

(>) :: Hash crypto c -> Hash crypto c -> Bool #

(>=) :: Hash crypto c -> Hash crypto c -> Bool #

max :: Hash crypto c -> Hash crypto c -> Hash crypto c #

min :: Hash crypto c -> Hash crypto c -> Hash crypto c #

Show (Hash crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

showsPrec :: Int -> Hash crypto c -> ShowS #

show :: Hash crypto c -> String #

showList :: [Hash crypto c] -> ShowS #

NFData (Hash crypto c) Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

rnf :: Hash crypto c -> () #

hash :: Reifies c crypto => Group crypto => ToNatural (FieldElement crypto c) => ByteString -> [G crypto c] -> E crypto c Source #

(hash bs gs) returns as a number in GroupExponent the SHA256 hash of the given ByteString bs prefixing the decimal representation of given subgroup elements gs, with a comma (",") intercalated between them.

NOTE: to avoid any collision when the hash function is used in different contexts, a message gs is actually prefixed by a bs indicating the context.

Used by proveEncryption and verifyEncryption, where the bs usually contains the statement to be proven, and the gs contains the commitments.

decodeBigEndian :: ByteString -> Natural Source #

(decodeBigEndian bs) interpret bs as big-endian number.

Type Base64SHA256

newtype Base64SHA256 Source #

Constructors

Base64SHA256 Text 
Instances
Eq Base64SHA256 Source # 
Instance details

Defined in Voting.Protocol.Arith

Ord Base64SHA256 Source # 
Instance details

Defined in Voting.Protocol.Arith

Show Base64SHA256 Source # 
Instance details

Defined in Voting.Protocol.Arith

Generic Base64SHA256 Source # 
Instance details

Defined in Voting.Protocol.Arith

Associated Types

type Rep Base64SHA256 :: Type -> Type #

ToJSON Base64SHA256 Source # 
Instance details

Defined in Voting.Protocol.Arith

FromJSON Base64SHA256 Source # 
Instance details

Defined in Voting.Protocol.Arith

NFData Base64SHA256 Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

rnf :: Base64SHA256 -> () #

type Rep Base64SHA256 Source # 
Instance details

Defined in Voting.Protocol.Arith

type Rep Base64SHA256 = D1 (MetaData "Base64SHA256" "Voting.Protocol.Arith" "hjugement-protocol-0.0.8.20191027-9HiW8HrEuPGHgxG7ahMSfc" True) (C1 (MetaCons "Base64SHA256" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

base64SHA256 :: ByteString -> Base64SHA256 Source #

(base64SHA256 bs) returns the SHA256 hash of the given ByteString bs, as a Text escaped in base64 encoding (RFC 4648).

Type HexSHA256

newtype HexSHA256 Source #

Constructors

HexSHA256 Text 
Instances
Eq HexSHA256 Source # 
Instance details

Defined in Voting.Protocol.Arith

Ord HexSHA256 Source # 
Instance details

Defined in Voting.Protocol.Arith

Show HexSHA256 Source # 
Instance details

Defined in Voting.Protocol.Arith

Generic HexSHA256 Source # 
Instance details

Defined in Voting.Protocol.Arith

Associated Types

type Rep HexSHA256 :: Type -> Type #

ToJSON HexSHA256 Source # 
Instance details

Defined in Voting.Protocol.Arith

FromJSON HexSHA256 Source # 
Instance details

Defined in Voting.Protocol.Arith

NFData HexSHA256 Source # 
Instance details

Defined in Voting.Protocol.Arith

Methods

rnf :: HexSHA256 -> () #

type Rep HexSHA256 Source # 
Instance details

Defined in Voting.Protocol.Arith

type Rep HexSHA256 = D1 (MetaData "HexSHA256" "Voting.Protocol.Arith" "hjugement-protocol-0.0.8.20191027-9HiW8HrEuPGHgxG7ahMSfc" True) (C1 (MetaCons "HexSHA256" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

hexSHA256 :: ByteString -> Text Source #

(hexSHA256 bs) returns the SHA256 hash of the given ByteString bs, escaped in hexadecimal into a Text of 32 lowercase characters.

Used (in retro-dependencies of this library) to hash the PublicKey of a voter or a trustee.

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 #