pairing-0.2: Optimal ate pairing over Barreto-Naehrig curves

Safe HaskellNone
LanguageHaskell2010

Pairing.Fq12

Description

Final quadratic extension of the tower:

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

Implementation follows "Multiplication and Squaring on Pairing-Friendly Fields" by Devigili, hEigeartaigh, Scott and Dahab.

Synopsis

Documentation

data Fq12 Source #

Field extension defined as Fq6[w]/w^2 - v

Constructors

Fq12

Use new instead of this constructor

Fields

Instances
Eq Fq12 Source # 
Instance details

Defined in Pairing.Fq12

Methods

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

(/=) :: Fq12 -> Fq12 -> Bool #

Fractional Fq12 Source # 
Instance details

Defined in Pairing.Fq12

Methods

(/) :: Fq12 -> Fq12 -> Fq12 #

recip :: Fq12 -> Fq12 #

fromRational :: Rational -> Fq12 #

Num Fq12 Source # 
Instance details

Defined in Pairing.Fq12

Methods

(+) :: Fq12 -> Fq12 -> Fq12 #

(-) :: Fq12 -> Fq12 -> Fq12 #

(*) :: Fq12 -> Fq12 -> Fq12 #

negate :: Fq12 -> Fq12 #

abs :: Fq12 -> Fq12 #

signum :: Fq12 -> Fq12 #

fromInteger :: Integer -> Fq12 #

Show Fq12 Source # 
Instance details

Defined in Pairing.Fq12

Methods

showsPrec :: Int -> Fq12 -> ShowS #

show :: Fq12 -> String #

showList :: [Fq12] -> ShowS #

Semigroup GT Source # 
Instance details

Defined in Pairing.Group

Methods

(<>) :: GT -> GT -> GT #

sconcat :: NonEmpty GT -> GT #

stimes :: Integral b => b -> GT -> GT #

Monoid GT Source # 
Instance details

Defined in Pairing.Group

Methods

mempty :: GT #

mappend :: GT -> GT -> GT #

mconcat :: [GT] -> GT #

CyclicGroup GT Source # 
Instance details

Defined in Pairing.Group

new :: [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.

fq12inv :: Fq12 -> Fq12 Source #

Multiplicative inverse

fq12one :: Fq12 Source #

Multiplicative identity

fq12zero :: Fq12 Source #

Additive identity

fq12conj :: Fq12 -> Fq12 Source #

Conjugation

fq12frobenius :: Int -> Fq12 -> Fq12 Source #

Iterated Frobenius automorphism