pairing-0.5.0: Bilinear pairings

Safe HaskellNone
LanguageHaskell2010

Pairing.Curve

Contents

Synopsis

Galois fields

type Fq = Fq Source #

Prime field Fq.

type Fq2 = Fq2 Source #

Quadratic extension field of Fq defined as Fq2 = Fq[u]/+ 1.

type Fq6 = Fq6 Source #

Cubic extension field of Fq2 defined as Fq6 = Fq2[v]/- (9 + u).

type Fq12 = Fq12 Source #

Quadratic extension field of Fq6 defined as Fq12 = Fq6[w]/- v.

type Fr = Fr Source #

Prime field Fr.

Elliptic curves

type G1 = PA Source #

G1 is E(Fq) defined by y^2 = x^3 + b.

type G2 = PA Source #

G2 is E'(Fq2) defined by y^2 = x^3 + b / xi.

type G2' = PJ Source #

G2' is G2 in Jacobian coordinates.

type GT = P Source #

GT is subgroup of r-th roots of unity of the multiplicative group of Fq12.

gG1 :: G1 Source #

Generator of G1.

gG2 :: G2 Source #

Generator of G2.

gGT :: GT Source #

Generator of GT.

rG1 :: Integer Source #

Order of G1.

rG2 :: Integer Source #

Order of G2.

rGT :: Integer Source #

Order of GT.

Parameters

_a :: Fq Source #

Elliptic curve E(Fq) coefficient A, with y = x^3 + Ax + B.

_a' :: Fq2 Source #

Elliptic curve E(Fq2) coefficient A', with y = x^3 + A'x + B'.

_b :: Fq Source #

Elliptic curve E(Fq) coefficient B, with y = x^3 + Ax + B.

_b' :: Fq2 Source #

Elliptic curve E(Fq2) coefficient B', with y = x^3 + A'x + B'.

_k :: Integer Source #

Embedding degree.

_nqr :: Integer Source #

Quadratic nonresidue in Fq.

_q :: Integer Source #

Characteristic of finite fields.

_r :: Integer Source #

Order of G1 and characteristic of prime field of exponents.

_t :: Integer Source #

BN parameter that determines the prime _q.

_xi :: Fq2 Source #

Parameter of twisted curve over Fq.

Miscellaneous functions

conj :: forall k im. IrreducibleMonic k im => ExtensionField k im -> ExtensionField k im Source #

Conjugation.

getYfromX :: Curve f c e q r => Point f c e q r -> (q -> q -> q) -> q -> Maybe q Source #

Get Y coordinate from X coordinate given a curve and a choice function.

scale :: IrreducibleMonic k im => k -> ExtensionField k im -> ExtensionField k im Source #

Scalar multiplication.

mulXi :: Fq6 -> Fq6 Source #

Multiply by _xi (cubic nonresidue in Fq2) and reorder coefficients.

fq12Frobenius :: Int -> Fq12 -> Fq12 Source #

Iterated Frobenius automorphism in Fq12.

isRootOfUnity :: Integer -> Fr -> Bool Source #

Check if an element is a root of unity.

isPrimitiveRootOfUnity :: Integer -> Fr -> Bool Source #

Check if an element is a primitive root of unity.

primitiveRootOfUnity :: Int -> Fr Source #

Compute primitive roots of unity for 2^0, 2^1, ..., 2^28. (2^28 is the largest power of two that divides _r - 1, therefore there are no primitive roots of unity for higher powers of 2 in Fr.)

precompRootOfUnity :: Int -> Fr Source #

Precompute roots of unity.