Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype F p = F {}
- inF :: forall p i. PrimeField p => Integral i => i -> F p
- class PrimeField p where
- class Additive a where
- class Additive a => Negable a where
- class Multiplicative a where
- class Multiplicative a => Invertible a where
- newtype G q = G {}
- natG :: SubGroup q => G q -> Natural
- class (PrimeField (P q), Multiplicative (F (P q))) => SubGroup q where
- type P q :: *
- groupGen :: G q
- groupOrder :: F (P q)
- groupGenInverses :: [G q]
- hash :: SubGroup q => ByteString -> [G q] -> E q
- newtype E q = E {}
- inE :: forall q i. SubGroup q => Integral i => i -> E q
- natE :: forall q. SubGroup q => E q -> Natural
- (^) :: SubGroup q => G q -> E q -> G q
- type RandomGen = RandomGen
- randomR :: Monad m => RandomGen r => Random i => Negable i => Multiplicative i => i -> StateT r m i
- random :: Monad m => RandomGen r => Random i => Negable i => Multiplicative i => StateT r m i
- data WeakParams
- data BeleniosParams
Type F
The type of the elements of a PrimeField
.
A field must satisfy the following properties:
(f, (
forms an abelian group, called the+
),zero
)Additive
group off
.(
forms an abelian group, called theNonNull
f, (*
),one
)Multiplicative
group off
.- (
*
) is associative:(a
and*
b)*
c == a*
(b*
c)a
.*
(b*
c) == (a*
b)*
c - (
*
) and (+
) are both commutative:a
and*
b == b*
aa
+
b == b+
a - (
*
) and (+
) are both left and right distributive:a
and*
(b+
c) == (a*
b)+
(a*
c)(a
+
b)*
c == (a*
c)+
(b*
c)
The Natural
is always within [0..
.fieldCharac
-1]
Class PrimeField
class PrimeField p where Source #
Parameter for a prime field.
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 # | |
Defined in Protocol.Arithmetic | |
PrimeField WeakParams Source # | |
Defined in Protocol.Arithmetic |
Class Additive
class Additive a where Source #
Instances
Additive Int Source # | |
Additive Integer Source # | |
Additive Natural Source # | |
(SubGroup q, Additive (F (P q))) => Additive (E q) Source # | |
PrimeField p => Additive (F p) Source # | |
SubGroup q => Additive (Encryption q) Source # | Additive homomorphism.
Using the fact that: |
Defined in Protocol.Election zero :: Encryption q Source # (+) :: Encryption q -> Encryption q -> Encryption q Source # sum :: Foldable f => f (Encryption q) -> Encryption q Source # |
Class Negable
Class Multiplicative
class Multiplicative a where Source #
Instances
Multiplicative Int Source # | |
Multiplicative Integer Source # | |
Multiplicative Natural Source # | |
(SubGroup q, Multiplicative (F (P q))) => Multiplicative (E q) Source # | |
(SubGroup q, Multiplicative (F (P q))) => Multiplicative (G q) Source # | |
PrimeField p => Multiplicative (F p) Source # | |
Class Invertible
class Multiplicative a => Invertible a where Source #
Type G
The type of the elements of a Multiplicative
SubGroup
of a PrimeField
.
natG :: SubGroup q => G q -> Natural Source #
(
returns the element of the natG
g)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).
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 (
to ensure that ensures that ElGamal is secure in terms
of the DDH assumption.fieldCharac
-1)
groupGenInverses :: [G q] Source #
groupGenInverses
returns the infinite list
of inv
erse powers of groupGen
:
[
,
but by computing each value from the previous one.groupGen
^
neg
i | i <- [0..]]
NOTE: groupGenInverses
is in the SubGroup
class in order to keep
computed terms in memory accross calls to groupGenInverses
.
Used by validableEncryption
.
Instances
SubGroup BeleniosParams Source # | |
Defined in Protocol.Arithmetic type P BeleniosParams :: Type Source # groupGen :: G BeleniosParams Source # groupOrder :: F (P BeleniosParams) Source # | |
SubGroup WeakParams Source # | |
Defined in Protocol.Arithmetic type P WeakParams :: Type Source # groupGen :: G WeakParams Source # groupOrder :: F (P WeakParams) Source # groupGenInverses :: [G WeakParams] Source # |
hash :: SubGroup q => ByteString -> [G q] -> E q Source #
(
returns as a number in hash
prefix gs)(
the SHA256 of the given F
p)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
An exponent of a (necessarily cyclic) SubGroup
of a PrimeField
.
The value is always in [0..
.groupOrder
-1]
Instances
SubGroup q => Enum (E q) Source # | |
Eq (E q) Source # | |
Ord (E q) Source # | |
Show (E q) Source # | |
SubGroup q => Random (E q) Source # | |
(SubGroup q, Multiplicative (F (P q))) => Multiplicative (E q) Source # | |
(SubGroup q, Negable (F (P q))) => Negable (E q) Source # | |
(SubGroup q, Additive (F (P q))) => Additive (E q) Source # | |
(^) :: SubGroup q => G q -> E q -> G q infixr 8 Source #
(b
returns the modular exponentiation of base ^
e)b
by exponent e
.
Type RandomGen
randomR :: Monad m => RandomGen r => Random i => Negable i => Multiplicative i => i -> StateT r m i Source #
(
returns a random integer in randomR
i)[0..i-1]
.
random :: Monad m => RandomGen r => Random i => Negable i => Multiplicative i => StateT r m i Source #
(
returns a random integer
in the range determined by its type.random
)
Groups
Type WeakParams
data WeakParams Source #
Weak parameters for debugging purposes only.
Instances
SubGroup WeakParams Source # | |
Defined in Protocol.Arithmetic type P WeakParams :: Type Source # groupGen :: G WeakParams Source # groupOrder :: F (P WeakParams) Source # groupGenInverses :: [G WeakParams] Source # | |
PrimeField WeakParams Source # | |
Defined in Protocol.Arithmetic | |
type P WeakParams Source # | |
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
.
Instances
SubGroup BeleniosParams Source # | |
Defined in Protocol.Arithmetic type P BeleniosParams :: Type Source # groupGen :: G BeleniosParams Source # groupOrder :: F (P BeleniosParams) Source # | |
PrimeField BeleniosParams Source # | |
Defined in Protocol.Arithmetic | |
type P BeleniosParams Source # | |
Defined in Protocol.Arithmetic |