Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class (EuclideanRing (G crypto c), FromNatural (G crypto c), ToNatural (G crypto c), Eq (G crypto c), Ord (G crypto c), Show (G crypto c), NFData (G crypto c), FromJSON (G crypto c), ToJSON (G crypto c), Reifies c crypto) => CryptoParams crypto c where
- groupGen :: G crypto c
- groupOrder :: Proxy c -> Natural
- groupGenPowers :: [G crypto c]
- groupGenInverses :: [G crypto c]
- class ReifyCrypto crypto where
- reifyCrypto :: crypto -> (forall c. Reifies c crypto => CryptoParams crypto c => Proxy c -> r) -> r
- class Additive a where
- class Additive a => Semiring a where
- (^) :: forall crypto c. Reifies c crypto => Semiring (G crypto c) => G crypto c -> E crypto c -> G crypto c
- class Semiring a => Ring a where
- class Ring a => EuclideanRing a where
- newtype G crypto c = G {
- unG :: FieldElement crypto
- type family FieldElement crypto :: *
- newtype E crypto c = E {}
- class FromNatural a where
- fromNatural :: Natural -> a
- class ToNatural a where
- bytesNat :: ToNatural n => n -> ByteString
Class CryptoParams
where
class (EuclideanRing (G crypto c), FromNatural (G crypto c), ToNatural (G crypto c), Eq (G crypto c), Ord (G crypto c), Show (G crypto c), NFData (G crypto c), FromJSON (G crypto c), ToJSON (G crypto c), Reifies c crypto) => CryptoParams crypto c where Source #
groupGen :: G crypto c Source #
A generator of the subgroup.
groupOrder :: Proxy c -> Natural Source #
The order of the subgroup.
groupGenPowers :: [G crypto c] Source #
groupGenPowers
returns the infinite list
of powers of groupGen
.
NOTE: In the CryptoParams
class to keep
computed values in memory across calls to groupGenPowers
.
groupGenInverses :: [G crypto c] Source #
groupGenInverses
returns the infinite list
of inverse
powers of groupGen
:
[
,
but by computing each value from the previous one.groupGen
^
negate
i | i <- [0..]]
NOTE: In the CryptoParams
class to keep
computed values in memory across calls to groupGenInverses
.
Used by intervalDisjunctions
.
Class ReifyCrypto
class ReifyCrypto crypto where Source #
reifyCrypto :: crypto -> (forall c. Reifies c crypto => CryptoParams crypto c => Proxy c -> r) -> r Source #
Like reify
but augmented with the CryptoParams
constraint.
Instances
ReifyCrypto FFC Source # | |
Defined in Voting.Protocol.FFC reifyCrypto :: FFC -> (forall c. (Reifies c FFC, CryptoParams FFC c) => Proxy c -> r) -> r Source # |
Class Additive
class Additive a where Source #
An additive semigroup.
Instances
Additive Int Source # | |
Additive Integer Source # | |
Additive Natural Source # | |
CryptoParams crypto c => Additive (E crypto c) Source # | |
Reifies c FFC => Additive (G FFC c) Source # | |
CryptoParams crypto c => Additive (Encryption crypto v c) Source # | Additive homomorphism.
Using the fact that: |
Defined in Voting.Protocol.Cryptography 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 Semiring
class Additive a => Semiring a where Source #
A multiplicative semigroup, with an additive semigroup (aka. a semiring).
(^) :: forall crypto c. Reifies c crypto => Semiring (G crypto c) => G crypto c -> E crypto c -> G crypto c infixr 8 Source #
(b
returns the modular exponentiation of base ^
e)b
by exponent e
.
Class Ring
class Semiring a => Ring a where Source #
A semiring that support substraction (aka. a ring).
Class EuclideanRing
class Ring a => EuclideanRing a where Source #
A commutative ring that support division (aka. an euclidean ring).
Type G
The type of the elements of a subgroup of a field.
G | |
|
Instances
Eq (G FFC c) Source # | |
Ord (G FFC c) Source # | |
Show (G FFC c) Source # | |
ToJSON (G FFC c) Source # | |
Reifies c FFC => FromJSON (G FFC c) Source # | |
NFData (G FFC c) Source # | |
Defined in Voting.Protocol.FFC | |
Reifies c FFC => Random (G FFC c) Source # | |
ToNatural (G FFC c) Source # | |
Reifies c FFC => FromNatural (G FFC c) Source # | |
Defined in Voting.Protocol.FFC | |
Reifies c FFC => EuclideanRing (G FFC c) Source # | |
Reifies c FFC => Ring (G FFC c) Source # | |
Reifies c FFC => Semiring (G FFC c) Source # | |
Reifies c FFC => Additive (G FFC c) Source # | |
Type family FieldElement
type family FieldElement crypto :: * Source #
Instances
type FieldElement FFC Source # | The type of the elements of a Finite Prime Field. A field must satisfy the following properties:
The |
Defined in Voting.Protocol.FFC |
Type E
An exponent of a (cyclic) subgroup of a field.
The value is always in [0..
.groupOrder
-1]
Instances
CryptoParams crypto c => Bounded (E crypto c) Source # | |
Eq (E crypto c) Source # | |
Ord (E crypto c) Source # | |
Defined in Voting.Protocol.Arithmetic | |
Show (E crypto c) Source # | |
ToJSON (E crypto c) Source # | |
Defined in Voting.Protocol.Arithmetic | |
CryptoParams crypto c => FromJSON (E crypto c) Source # | |
NFData (E crypto c) Source # | |
Defined in Voting.Protocol.Arithmetic | |
CryptoParams crypto c => Random (E crypto c) Source # | |
ToNatural (E crypto c) Source # | |
CryptoParams crypto c => FromNatural (E crypto c) Source # | |
Defined in Voting.Protocol.Arithmetic fromNatural :: Natural -> E crypto c Source # | |
CryptoParams crypto c => Ring (E crypto c) Source # | |
CryptoParams crypto c => Semiring (E crypto c) Source # | |
CryptoParams crypto c => Additive (E crypto c) Source # | |
Class FromNatural
class FromNatural a where Source #
fromNatural :: Natural -> a Source #
Instances
FromNatural Natural Source # | |
Defined in Voting.Protocol.Arithmetic fromNatural :: Natural -> Natural Source # | |
CryptoParams crypto c => FromNatural (E crypto c) Source # | |
Defined in Voting.Protocol.Arithmetic fromNatural :: Natural -> E crypto c Source # | |
Reifies c FFC => FromNatural (G FFC c) Source # | |
Defined in Voting.Protocol.FFC |