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

Safe HaskellNone
LanguageHaskell2010

Pairing.Fq2

Description

First 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 following "Multiplication and Squaring on Pairing-Friendly Fields" by Devigili, hEigeartaigh, Scott and Dahab.

Synopsis

Documentation

data Fq2 Source #

Quadratic extension of Fq defined as Fq[u]/x^2 + 1

Constructors

Fq2

Use new instead of this contructor

Fields

Instances
Eq Fq2 Source # 
Instance details

Defined in Pairing.Fq2

Methods

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

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

Fractional Fq2 Source # 
Instance details

Defined in Pairing.Fq2

Methods

(/) :: Fq2 -> Fq2 -> Fq2 #

recip :: Fq2 -> Fq2 #

fromRational :: Rational -> Fq2 #

Num Fq2 Source # 
Instance details

Defined in Pairing.Fq2

Methods

(+) :: Fq2 -> Fq2 -> Fq2 #

(-) :: Fq2 -> Fq2 -> Fq2 #

(*) :: Fq2 -> Fq2 -> Fq2 #

negate :: Fq2 -> Fq2 #

abs :: Fq2 -> Fq2 #

signum :: Fq2 -> Fq2 #

fromInteger :: Integer -> Fq2 #

Show Fq2 Source # 
Instance details

Defined in Pairing.Fq2

Methods

showsPrec :: Int -> Fq2 -> ShowS #

show :: Fq2 -> String #

showList :: [Fq2] -> ShowS #

Generic Fq2 Source # 
Instance details

Defined in Pairing.Fq2

Associated Types

type Rep Fq2 :: Type -> Type #

Methods

from :: Fq2 -> Rep Fq2 x #

to :: Rep Fq2 x -> Fq2 #

Semigroup G2 Source # 
Instance details

Defined in Pairing.Group

Methods

(<>) :: G2 -> G2 -> G2 #

sconcat :: NonEmpty G2 -> G2 #

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

Monoid G2 Source # 
Instance details

Defined in Pairing.Group

Methods

mempty :: G2 #

mappend :: G2 -> G2 -> G2 #

mconcat :: [G2] -> G2 #

NFData Fq2 Source # 
Instance details

Defined in Pairing.Fq2

Methods

rnf :: Fq2 -> () #

CyclicGroup G2 Source # 
Instance details

Defined in Pairing.Group

Methods

generator :: G2 Source #

order :: Proxy G2 -> Integer Source #

expn :: AsInteger e => G2 -> e -> G2 Source #

inverse :: G2 -> G2 Source #

Arbitrary (Point Fq2) Source # 
Instance details

Defined in Pairing.Group

type Rep Fq2 Source # 
Instance details

Defined in Pairing.Fq2

type Rep Fq2 = D1 (MetaData "Fq2" "Pairing.Fq2" "pairing-0.1.1-LSMyNU2W24Y2zJo2MsJ5lB" False) (C1 (MetaCons "Fq2" PrefixI True) (S1 (MetaSel (Just "fq2x") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Fq) :*: S1 (MetaSel (Just "fq2y") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Fq)))

new :: Fq -> Fq -> Fq2 Source #

new x y creates a value representing x + y * u

fq2scalarMul :: Fq -> Fq2 -> Fq2 Source #

Multiplication by a scalar in Fq

fq2inv :: Fq2 -> Fq2 Source #

Multiplicative inverse

fq2one :: Fq2 Source #

Multiplicative identity

fq2zero :: Fq2 Source #

Additive identity

fq2conj :: Fq2 -> Fq2 Source #

Conjugation

fq2sqr :: Fq2 -> Fq2 Source #

Squaring operation

mulXi :: Fq2 -> Fq2 Source #

Multiply by xi

divXi :: Fq2 -> Fq2 Source #

Divide by xi

xi :: Fq2 Source #

Cubic non-residue in Fq2