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

Safe HaskellNone
LanguageHaskell2010

Pairing.Fq

Description

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

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

Documentation

newtype Fq Source #

Prime field with characteristic _q

Constructors

Fq Integer

Use new instead of this constructor

Instances
Eq Fq Source # 
Instance details

Defined in Pairing.Fq

Methods

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

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

Fractional Fq Source # 
Instance details

Defined in Pairing.Fq

Methods

(/) :: Fq -> Fq -> Fq #

recip :: Fq -> Fq #

fromRational :: Rational -> Fq #

Num Fq Source # 
Instance details

Defined in Pairing.Fq

Methods

(+) :: Fq -> Fq -> Fq #

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

(*) :: Fq -> Fq -> Fq #

negate :: Fq -> Fq #

abs :: Fq -> Fq #

signum :: Fq -> Fq #

fromInteger :: Integer -> Fq #

Ord Fq Source # 
Instance details

Defined in Pairing.Fq

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 #

Show Fq Source # 
Instance details

Defined in Pairing.Fq

Methods

showsPrec :: Int -> Fq -> ShowS #

show :: Fq -> String #

showList :: [Fq] -> ShowS #

Generic Fq Source # 
Instance details

Defined in Pairing.Fq

Associated Types

type Rep Fq :: Type -> Type #

Methods

from :: Fq -> Rep Fq x #

to :: Rep Fq x -> Fq #

Semigroup G1 Source # 
Instance details

Defined in Pairing.Group

Methods

(<>) :: G1 -> G1 -> G1 #

sconcat :: NonEmpty G1 -> G1 #

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

Monoid G1 Source # 
Instance details

Defined in Pairing.Group

Methods

mempty :: G1 #

mappend :: G1 -> G1 -> G1 #

mconcat :: [G1] -> G1 #

Bits Fq Source # 
Instance details

Defined in Pairing.Fq

Methods

(.&.) :: Fq -> Fq -> Fq #

(.|.) :: Fq -> Fq -> Fq #

xor :: Fq -> Fq -> Fq #

complement :: Fq -> Fq #

shift :: Fq -> Int -> Fq #

rotate :: Fq -> Int -> Fq #

zeroBits :: Fq #

bit :: Int -> Fq #

setBit :: Fq -> Int -> Fq #

clearBit :: Fq -> Int -> Fq #

complementBit :: Fq -> Int -> Fq #

testBit :: Fq -> Int -> Bool #

bitSizeMaybe :: Fq -> Maybe Int #

bitSize :: Fq -> Int #

isSigned :: Fq -> Bool #

shiftL :: Fq -> Int -> Fq #

unsafeShiftL :: Fq -> Int -> Fq #

shiftR :: Fq -> Int -> Fq #

unsafeShiftR :: Fq -> Int -> Fq #

rotateL :: Fq -> Int -> Fq #

rotateR :: Fq -> Int -> Fq #

popCount :: Fq -> Int #

NFData Fq Source # 
Instance details

Defined in Pairing.Fq

Methods

rnf :: Fq -> () #

ByteRepr Fq Source # 
Instance details

Defined in Pairing.Fq

Validate G1 Source # 
Instance details

Defined in Pairing.Group

FromX Fq Source # 
Instance details

Defined in Pairing.Fq

Methods

yFromX :: Fq -> LargestY -> Maybe Fq Source #

isLargestY :: Fq -> Bool Source #

CyclicGroup G1 Source # 
Instance details

Defined in Pairing.Group

AsInteger Fq Source # 
Instance details

Defined in Pairing.Fq

Methods

asInteger :: Fq -> Integer Source #

ToUncompressedForm G1 Source # 
Instance details

Defined in Pairing.Group

ToCompressedForm G1 Source # 
Instance details

Defined in Pairing.Group

Arbitrary (Point Fq) Source # 
Instance details

Defined in Pairing.Group

Methods

arbitrary :: Gen (Point Fq) #

shrink :: Point Fq -> [Point Fq] #

type Rep Fq Source # 
Instance details

Defined in Pairing.Fq

type Rep Fq = D1 (MetaData "Fq" "Pairing.Fq" "pairing-0.3.1-JhhvluXyNup3CB27ybng3m" True) (C1 (MetaCons "Fq" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer)))

new :: Integer -> Fq Source #

Turn an integer into an Fq number, should be used instead of the Fq constructor.

fqInv :: Fq -> Fq Source #

Multiplicative inverse

fqZero :: Fq Source #

Additive identity

fqOne :: Fq Source #

Multiplicative identity

fqNqr :: Fq Source #

Quadratic non-residue

fqPow :: Integral e => Fq -> e -> Fq Source #