pairing-0.4.1: Bilinear pairings

Safe HaskellNone
LanguageHaskell2010

Pairing.Fq

Contents

Description

Prime field with characteristic _q, over which the elliptic curve is defined and the other finite field extensions.

  • Fq
  • Fq2 := Fq[u]/u^2 + 1
  • Fq6 := Fq2[v]/v^3 - (9 + u)
  • Fq12 := Fq6[w]/w^2 - v
Synopsis

Documentation

type Fq = PrimeField 21888242871839275222246405745257275088696311157297823662689037894645226208583 Source #

Prime field Fq with characteristic _q

type Fq2 = ExtensionField Fq PolynomialU Source #

Quadratic extension field of Fq defined as Fq2 = Fq[u]/f(u)

type Fq6 = ExtensionField Fq2 PolynomialV Source #

Cubic extension field of Fq2 defined as Fq6 = Fq2[v]/g(v)

type Fq12 = ExtensionField Fq6 PolynomialW Source #

Quadratic extension field of Fq6 defined as Fq12 = Fq6[w]/h(w)

fqSqrt :: (Fq -> Fq -> Fq) -> Fq -> Maybe Fq Source #

fq2Sqrt :: Fq2 -> Maybe Fq2 Source #

Square root of Fq2 are specified by https://eprint.iacr.org/2012/685.pdf, Algorithm 9 with lots of help from https://docs.rs/pairing/0.14.1/src/pairing/bls12_381/fq2.rs.html#162-222 This implementation appears to return the larger square root so check the return value and negate as necessary

fqYforX :: Fq -> (Fq -> Fq -> Fq) -> Maybe Fq Source #

fq2YforX :: Fq2 -> (Fq2 -> Fq2 -> Fq2) -> Maybe Fq2 Source #

fqNqr :: Fq Source #

Quadratic non-residue

xi :: Fq2 Source #

Cubic non-residue in Fq2

mulXi :: Fq6 -> Fq6 Source #

Multiply by xi (cubic nonresidue in Fq2) and reorder coefficients

fq2Conj :: Fq2 -> Fq2 Source #

Conjugation

fq2ScalarMul :: Fq -> Fq2 -> Fq2 Source #

Multiplication by a scalar in Fq

construct :: [Fq] -> Fq12 Source #

Create a new value in Fq12 by providing a list of twelve coefficients in Fq, should be used instead of the Fq12 constructor.

deconstruct :: Fq12 -> [Fq] Source #

Deconstruct a value in Fq12 into a list of twelve coefficients in Fq.

fq12Conj :: Fq12 -> Fq12 Source #

Conjugation

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

Iterated Frobenius automorphism

Orphan instances

Ord Fq Source # 
Instance details

Methods

compare :: Fq -> Fq -> Ordering #

(<) :: Fq -> Fq -> Bool #

(<=) :: Fq -> Fq -> Bool #

(>) :: Fq -> Fq -> Bool #

(>=) :: Fq -> Fq -> Bool #

max :: Fq -> Fq -> Fq #

min :: Fq -> Fq -> Fq #

ByteRepr Fq Source # 
Instance details

FromX Fq Source # 
Instance details

Methods

yFromX :: Fq -> (Fq -> Fq -> Fq) -> Maybe Fq Source #

isOdd :: Fq -> Bool Source #