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

Safe HaskellNone
LanguageHaskell2010

Pairing.Group

Contents

Description

Definitions of the groups the pairing is defined on

Synopsis

Documentation

class Monoid g => CyclicGroup g where Source #

Methods

generator :: g Source #

order :: Proxy g -> Integer Source #

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

inverse :: g -> g Source #

random :: MonadRandom m => g -> m g Source #

Instances
CyclicGroup GT Source # 
Instance details

Defined in Pairing.Group

CyclicGroup G2 Source # 
Instance details

Defined in Pairing.Group

CyclicGroup G1 Source # 
Instance details

Defined in Pairing.Group

type G1 = Point Fq Source #

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

type G2 = Point Fq2 Source #

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

type GT = Fq12 Source #

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

isOnCurveG1 :: G1 -> Bool Source #

Test whether a value in G1 satisfies the corresponding curve equation

isOnCurveG2 :: G2 -> Bool Source #

Test whether a value in G2 satisfies the corresponding curve equation

isInGT :: GT -> Bool Source #

Test whether a value is an _r-th root of unity

g1 :: G1 Source #

Generator for G1

g2 :: G2 Source #

Generator for G2

b1 :: Fq Source #

Parameter for curve on Fq

b2 :: Fq2 Source #

Parameter for twisted curve over Fq2

groupFromX :: (Validate (Point a), FromX a) => Bool -> a -> Maybe (Point a) Source #

Orphan instances

Semigroup GT Source # 
Instance details

Methods

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

sconcat :: NonEmpty GT -> GT #

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

Semigroup G2 Source # 
Instance details

Methods

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

sconcat :: NonEmpty G2 -> G2 #

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

Semigroup G1 Source # 
Instance details

Methods

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

sconcat :: NonEmpty G1 -> G1 #

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

Monoid GT Source # 
Instance details

Methods

mempty :: GT #

mappend :: GT -> GT -> GT #

mconcat :: [GT] -> GT #

Monoid G2 Source # 
Instance details

Methods

mempty :: G2 #

mappend :: G2 -> G2 -> G2 #

mconcat :: [G2] -> G2 #

Monoid G1 Source # 
Instance details

Methods

mempty :: G1 #

mappend :: G1 -> G1 -> G1 #

mconcat :: [G1] -> G1 #

Validate GT Source # 
Instance details

Validate G2 Source # 
Instance details

Validate G1 Source # 
Instance details

CyclicGroup GT Source # 
Instance details

CyclicGroup G2 Source # 
Instance details

CyclicGroup G1 Source # 
Instance details

ToUncompressedForm GT Source # 
Instance details

ToUncompressedForm G2 Source # 
Instance details

ToUncompressedForm G1 Source # 
Instance details

ToCompressedForm G2 Source # 
Instance details

ToCompressedForm G1 Source # 
Instance details

Arbitrary (Point Fq) Source # 
Instance details

Methods

arbitrary :: Gen (Point Fq) #

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

Arbitrary (Point Fq2) Source # 
Instance details