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

Safe HaskellNone
LanguageHaskell2010

Pairing.Point

Description

Affine point arithmetic defining the group operation on an elliptic curve E(F), for some field F. In our case the field F is given as some type t with Num and Fractional instances.

Synopsis

Documentation

data Point a Source #

Points on a curve over a field a represented as either affine coordinates or as a point at infinity.

Constructors

Point a a

Affine point

Infinity

Point at infinity

Instances
Functor Point Source # 
Instance details

Defined in Pairing.Point

Methods

fmap :: (a -> b) -> Point a -> Point b #

(<$) :: a -> Point b -> Point a #

Semigroup G2 Source # 
Instance details

Defined in Pairing.Group

Methods

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

sconcat :: NonEmpty G2 -> G2 #

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

Semigroup G1 Source # 
Instance details

Defined in Pairing.Group

Methods

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

sconcat :: NonEmpty G1 -> G1 #

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

Monoid G2 Source # 
Instance details

Defined in Pairing.Group

Methods

mempty :: G2 #

mappend :: G2 -> G2 -> G2 #

mconcat :: [G2] -> G2 #

Monoid G1 Source # 
Instance details

Defined in Pairing.Group

Methods

mempty :: G1 #

mappend :: G1 -> G1 -> G1 #

mconcat :: [G1] -> G1 #

Validate G2 Source # 
Instance details

Defined in Pairing.Group

Validate G1 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

ToUncompressedForm G2 Source # 
Instance details

Defined in Pairing.Group

ToUncompressedForm G1 Source # 
Instance details

Defined in Pairing.Group

ToCompressedForm G2 Source # 
Instance details

Defined in Pairing.Group

ToCompressedForm G1 Source # 
Instance details

Defined in Pairing.Group

Eq a => Eq (Point a) Source # 
Instance details

Defined in Pairing.Point

Methods

(==) :: Point a -> Point a -> Bool #

(/=) :: Point a -> Point a -> Bool #

Ord a => Ord (Point a) Source # 
Instance details

Defined in Pairing.Point

Methods

compare :: Point a -> Point a -> Ordering #

(<) :: Point a -> Point a -> Bool #

(<=) :: Point a -> Point a -> Bool #

(>) :: Point a -> Point a -> Bool #

(>=) :: Point a -> Point a -> Bool #

max :: Point a -> Point a -> Point a #

min :: Point a -> Point a -> Point a #

Show a => Show (Point a) Source # 
Instance details

Defined in Pairing.Point

Methods

showsPrec :: Int -> Point a -> ShowS #

show :: Point a -> String #

showList :: [Point a] -> ShowS #

Generic (Point a) Source # 
Instance details

Defined in Pairing.Point

Associated Types

type Rep (Point a) :: Type -> Type #

Methods

from :: Point a -> Rep (Point a) x #

to :: Rep (Point a) x -> Point a #

Arbitrary (Point Fq) Source # 
Instance details

Defined in Pairing.Group

Methods

arbitrary :: Gen (Point Fq) #

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

Arbitrary (Point Fq2) Source # 
Instance details

Defined in Pairing.Group

NFData a => NFData (Point a) Source # 
Instance details

Defined in Pairing.Point

Methods

rnf :: Point a -> () #

type Rep (Point a) Source # 
Instance details

Defined in Pairing.Point

type Rep (Point a) = D1 (MetaData "Point" "Pairing.Point" "pairing-0.3.1-JhhvluXyNup3CB27ybng3m" False) (C1 (MetaCons "Point" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :+: C1 (MetaCons "Infinity" PrefixI False) (U1 :: Type -> Type))

gDouble :: (Fractional t, Eq t) => Point t -> Point t Source #

Point doubling

gAdd :: (Fractional t, Eq t) => Point t -> Point t -> Point t Source #

Point addition, provides a group structure on an elliptic curve with the point at infinity as its unit.

gNeg :: (Fractional t, Eq t) => Point t -> Point t Source #

Negation (flipping the y component)

gMul :: (Eq t, Integral a, Fractional t) => Point t -> a -> Point t Source #

Multiplication by a scalar