elliptic-curve-0.2.2: Elliptic curve library

Safe HaskellNone
LanguageHaskell2010

Curve.Binary

Contents

Synopsis

Documentation

class GaloisField k => PrimeField' k Source #

Minimal complete definition

toInt'

Instances
KnownNat p => PrimeField' (PrimeField p) Source # 
Instance details

Defined in Curve

data Coordinates Source #

Curve coordinates.

Constructors

Affine 
Jacobian 
Projective 

data Form Source #

Curve forms.

class (GaloisField q, PrimeField' r, Group (Point f c e q r)) => Curve (f :: Form) (c :: Coordinates) e q r where Source #

Elliptic curves.

Minimal complete definition

char, cof, disc, fromA, point, pointX, toA, yX

Associated Types

data Point f c e q r :: * Source #

Curve point.

Methods

char :: Point f c e q r -> Integer Source #

Curve characteristic.

cof :: Point f c e q r -> Integer Source #

Curve cofactor.

disc :: Point f c e q r -> q Source #

Curve discriminant.

mul :: Point f c e q r -> r -> Point f c e q r Source #

Curve point multiplication.

point :: q -> q -> Maybe (Point f c e q r) Source #

Get point from X and Y coordinates.

pointX :: q -> Maybe (Point f c e q r) Source #

Get point from X coordinate.

yX :: Point f c e q r -> q -> Maybe q Source #

Get Y coordinate from X coordinate.

fromA :: Point f Affine e q r -> Point f c e q r Source #

Transform from affine coordinates.

toA :: Point f c e q r -> Point f Affine e q r Source #

Transform to affine coordinates.

Instances
WACurve e q r => Curve Weierstrass Affine (e :: k) q r Source # 
Instance details

Defined in Curve.Weierstrass

Associated Types

data Point Weierstrass Affine e q r :: Type Source #

WJCurve e q r => Curve Weierstrass Jacobian (e :: k) q r Source # 
Instance details

Defined in Curve.Weierstrass

Associated Types

data Point Weierstrass Jacobian e q r :: Type Source #

WPCurve e q r => Curve Weierstrass Projective (e :: k) q r Source # 
Instance details

Defined in Curve.Weierstrass

Associated Types

data Point Weierstrass Projective e q r :: Type Source #

MACurve e q r => Curve Montgomery Affine (e :: k) q r Source # 
Instance details

Defined in Curve.Montgomery

Associated Types

data Point Montgomery Affine e q r :: Type Source #

EACurve e q r => Curve Edwards Affine (e :: k) q r Source # 
Instance details

Defined in Curve.Edwards

Associated Types

data Point Edwards Affine e q r :: Type Source #

EPCurve e q r => Curve Edwards Projective (e :: k) q r Source # 
Instance details

Defined in Curve.Edwards

Associated Types

data Point Edwards Projective e q r :: Type Source #

BACurve e q r => Curve Binary Affine (e :: k) q r Source # 
Instance details

Defined in Curve.Binary

Associated Types

data Point Binary Affine e q r :: Type Source #

BPCurve e q r => Curve Binary Projective (e :: k) q r Source # 
Instance details

Defined in Curve.Binary

Associated Types

data Point Binary Projective e q r :: Type Source #

class BCurve Projective e q r => BPCurve e q r where Source #

Binary projective curves y^2z + xyz = x^3 + Ax^2z + Bz.

Methods

gP_ Source #

Arguments

:: BPPoint e q r

Curve generator.

Instances
BPCurve SECT571R1 F2m Fr Source #

Projective SECT571R1 curve is a binary projective curve.

Instance details

Defined in Curve.Binary.SECT571R1

BPCurve SECT571K1 F2m Fr Source #

Projective SECT571K1 curve is a binary projective curve.

Instance details

Defined in Curve.Binary.SECT571K1

BPCurve SECT409R1 F2m Fr Source #

Projective SECT409R1 curve is a binary projective curve.

Instance details

Defined in Curve.Binary.SECT409R1

BPCurve SECT409K1 F2m Fr Source #

Projective SECT409K1 curve is a binary projective curve.

Instance details

Defined in Curve.Binary.SECT409K1

BPCurve SECT283R1 F2m Fr Source #

Projective SECT283R1 curve is a binary projective curve.

Instance details

Defined in Curve.Binary.SECT283R1

BPCurve SECT283K1 F2m Fr Source #

Projective SECT283K1 curve is a binary projective curve.

Instance details

Defined in Curve.Binary.SECT283K1

BPCurve SECT239K1 F2m Fr Source #

Projective SECT239K1 curve is a binary projective curve.

Instance details

Defined in Curve.Binary.SECT239K1

BPCurve SECT233R1 F2m Fr Source #

Projective SECT233R1 curve is a binary projective curve.

Instance details

Defined in Curve.Binary.SECT233R1

BPCurve SECT233K1 F2m Fr Source #

Projective SECT233K1 curve is a binary projective curve.

Instance details

Defined in Curve.Binary.SECT233K1

BPCurve SECT193R2 F2m Fr Source #

Projective SECT193R2 curve is a binary projective curve.

Instance details

Defined in Curve.Binary.SECT193R2

BPCurve SECT193R1 F2m Fr Source #

Projective SECT193R1 curve is a binary projective curve.

Instance details

Defined in Curve.Binary.SECT193R1

BPCurve SECT163R2 F2m Fr Source #

Projective SECT163R2 curve is a binary projective curve.

Instance details

Defined in Curve.Binary.SECT163R2

BPCurve SECT163R1 F2m Fr Source #

Projective SECT163R1 curve is a binary projective curve.

Instance details

Defined in Curve.Binary.SECT163R1

BPCurve SECT163K1 F2m Fr Source #

Projective SECT163K1 curve is a binary projective curve.

Instance details

Defined in Curve.Binary.SECT163K1

BPCurve SECT131R2 F2m Fr Source #

Projective SECT131R2 curve is a binary projective curve.

Instance details

Defined in Curve.Binary.SECT131R2

BPCurve SECT131R1 F2m Fr Source #

Projective SECT131R1 curve is a binary projective curve.

Instance details

Defined in Curve.Binary.SECT131R1

BPCurve SECT113R2 F2m Fr Source #

Projective SECT113R2 curve is a binary projective curve.

Instance details

Defined in Curve.Binary.SECT113R2

BPCurve SECT113R1 F2m Fr Source #

Projective SECT113R1 curve is a binary projective curve.

Instance details

Defined in Curve.Binary.SECT113R1

type BPPoint = BPoint Projective Source #

Binary projective points.

class BCurve Affine e q r => BACurve e q r where Source #

Binary affine curves y^2 + xy = x^3 + Ax^2 + B.

Methods

gA_ Source #

Arguments

:: BAPoint e q r

Curve generator.

Instances
BACurve SECT571R1 F2m Fr Source #

Affine SECT571R1 curve is a binary affine curve.

Instance details

Defined in Curve.Binary.SECT571R1

BACurve SECT571K1 F2m Fr Source #

Affine SECT571K1 curve is a binary affine curve.

Instance details

Defined in Curve.Binary.SECT571K1

BACurve SECT409R1 F2m Fr Source #

Affine SECT409R1 curve is a binary affine curve.

Instance details

Defined in Curve.Binary.SECT409R1

BACurve SECT409K1 F2m Fr Source #

Affine SECT409K1 curve is a binary affine curve.

Instance details

Defined in Curve.Binary.SECT409K1

BACurve SECT283R1 F2m Fr Source #

Affine SECT283R1 curve is a binary affine curve.

Instance details

Defined in Curve.Binary.SECT283R1

BACurve SECT283K1 F2m Fr Source #

Affine SECT283K1 curve is a binary affine curve.

Instance details

Defined in Curve.Binary.SECT283K1

BACurve SECT239K1 F2m Fr Source #

Affine SECT239K1 curve is a binary affine curve.

Instance details

Defined in Curve.Binary.SECT239K1

BACurve SECT233R1 F2m Fr Source #

Affine SECT233R1 curve is a binary affine curve.

Instance details

Defined in Curve.Binary.SECT233R1

BACurve SECT233K1 F2m Fr Source #

Affine SECT233K1 curve is a binary affine curve.

Instance details

Defined in Curve.Binary.SECT233K1

BACurve SECT193R2 F2m Fr Source #

Affine SECT193R2 curve is a binary affine curve.

Instance details

Defined in Curve.Binary.SECT193R2

BACurve SECT193R1 F2m Fr Source #

Affine SECT193R1 curve is a binary affine curve.

Instance details

Defined in Curve.Binary.SECT193R1

BACurve SECT163R2 F2m Fr Source #

Affine SECT163R2 curve is a binary affine curve.

Instance details

Defined in Curve.Binary.SECT163R2

BACurve SECT163R1 F2m Fr Source #

Affine SECT163R1 curve is a binary affine curve.

Instance details

Defined in Curve.Binary.SECT163R1

BACurve SECT163K1 F2m Fr Source #

Affine SECT163K1 curve is a binary affine curve.

Instance details

Defined in Curve.Binary.SECT163K1

BACurve SECT131R2 F2m Fr Source #

Affine SECT131R2 curve is a binary affine curve.

Instance details

Defined in Curve.Binary.SECT131R2

BACurve SECT131R1 F2m Fr Source #

Affine SECT131R1 curve is a binary affine curve.

Instance details

Defined in Curve.Binary.SECT131R1

BACurve SECT113R2 F2m Fr Source #

Affine SECT113R2 curve is a binary affine curve.

Instance details

Defined in Curve.Binary.SECT113R2

BACurve SECT113R1 F2m Fr Source #

Affine SECT113R1 curve is a binary affine curve.

Instance details

Defined in Curve.Binary.SECT113R1

type BAPoint = BPoint Affine Source #

Binary affine points.

class (GaloisField q, PrimeField' r, Curve Binary c e q r) => BCurve c e q r where Source #

Binary curves.

Methods

a_ Source #

Arguments

:: BPoint c e q r 
-> q

Coefficient A.

b_ Source #

Arguments

:: BPoint c e q r 
-> q

Coefficient B.

h_ Source #

Arguments

:: BPoint c e q r 
-> Integer

Curve cofactor.

p_ Source #

Arguments

:: BPoint c e q r 
-> Integer

Curve polynomial.

r_ Source #

Arguments

:: BPoint c e q r 
-> Integer

Curve order.

x_ Source #

Arguments

:: BPoint c e q r 
-> q

Coordinate X.

y_ Source #

Arguments

:: BPoint c e q r 
-> q

Coordinate Y.

Instances
Curve Binary c SECT571R1 F2m Fr => BCurve c SECT571R1 F2m Fr Source #

SECT571R1 curve is a binary curve.

Instance details

Defined in Curve.Binary.SECT571R1

Curve Binary c SECT571K1 F2m Fr => BCurve c SECT571K1 F2m Fr Source #

SECT571K1 curve is a binary curve.

Instance details

Defined in Curve.Binary.SECT571K1

Curve Binary c SECT409R1 F2m Fr => BCurve c SECT409R1 F2m Fr Source #

SECT409R1 curve is a binary curve.

Instance details

Defined in Curve.Binary.SECT409R1

Curve Binary c SECT409K1 F2m Fr => BCurve c SECT409K1 F2m Fr Source #

SECT409K1 curve is a binary curve.

Instance details

Defined in Curve.Binary.SECT409K1

Curve Binary c SECT283R1 F2m Fr => BCurve c SECT283R1 F2m Fr Source #

SECT283R1 curve is a binary curve.

Instance details

Defined in Curve.Binary.SECT283R1

Curve Binary c SECT283K1 F2m Fr => BCurve c SECT283K1 F2m Fr Source #

SECT283K1 curve is a binary curve.

Instance details

Defined in Curve.Binary.SECT283K1

Curve Binary c SECT239K1 F2m Fr => BCurve c SECT239K1 F2m Fr Source #

SECT239K1 curve is a binary curve.

Instance details

Defined in Curve.Binary.SECT239K1

Curve Binary c SECT233R1 F2m Fr => BCurve c SECT233R1 F2m Fr Source #

SECT233R1 curve is a binary curve.

Instance details

Defined in Curve.Binary.SECT233R1

Curve Binary c SECT233K1 F2m Fr => BCurve c SECT233K1 F2m Fr Source #

SECT233K1 curve is a binary curve.

Instance details

Defined in Curve.Binary.SECT233K1

Curve Binary c SECT193R2 F2m Fr => BCurve c SECT193R2 F2m Fr Source #

SECT193R2 curve is a binary curve.

Instance details

Defined in Curve.Binary.SECT193R2

Curve Binary c SECT193R1 F2m Fr => BCurve c SECT193R1 F2m Fr Source #

SECT193R1 curve is a binary curve.

Instance details

Defined in Curve.Binary.SECT193R1

Curve Binary c SECT163R2 F2m Fr => BCurve c SECT163R2 F2m Fr Source #

SECT163R2 curve is a binary curve.

Instance details

Defined in Curve.Binary.SECT163R2

Curve Binary c SECT163R1 F2m Fr => BCurve c SECT163R1 F2m Fr Source #

SECT163R1 curve is a binary curve.

Instance details

Defined in Curve.Binary.SECT163R1

Curve Binary c SECT163K1 F2m Fr => BCurve c SECT163K1 F2m Fr Source #

SECT163K1 curve is a binary curve.

Instance details

Defined in Curve.Binary.SECT163K1

Curve Binary c SECT131R2 F2m Fr => BCurve c SECT131R2 F2m Fr Source #

SECT131R2 curve is a binary curve.

Instance details

Defined in Curve.Binary.SECT131R2

Curve Binary c SECT131R1 F2m Fr => BCurve c SECT131R1 F2m Fr Source #

SECT131R1 curve is a binary curve.

Instance details

Defined in Curve.Binary.SECT131R1

Curve Binary c SECT113R2 F2m Fr => BCurve c SECT113R2 F2m Fr Source #

SECT113R2 curve is a binary curve.

Instance details

Defined in Curve.Binary.SECT113R2

Curve Binary c SECT113R1 F2m Fr => BCurve c SECT113R1 F2m Fr Source #

SECT113R1 curve is a binary curve.

Instance details

Defined in Curve.Binary.SECT113R1

type BPoint = Point Binary Source #

Binary points.

class (Arbitrary g, Eq g, Generic g, Monoid g, Pretty g, Random g, Show g) => Group g where Source #

Groups.

Minimal complete definition

add, dbl, def, gen, id, inv, order

Methods

add :: g -> g -> g Source #

Element addition.

dbl :: g -> g Source #

Element doubling.

def :: g -> Bool Source #

Check well-defined.

gen :: g Source #

Group generator.

id :: g Source #

Identity element.

inv :: g -> g Source #

Element inversion.

mul' :: g -> Integer -> g Source #

Element multiplication.

order :: g -> Integer Source #

Curve order.

rnd :: MonadRandom m => m g Source #

Random element.

Instances
FGroup r q => Group (Element r q) Source # 
Instance details

Defined in Group.Field

Methods

add :: Element r q -> Element r q -> Element r q Source #

dbl :: Element r q -> Element r q Source #

def :: Element r q -> Bool Source #

gen :: Element r q Source #

id :: Element r q Source #

inv :: Element r q -> Element r q Source #

mul' :: Element r q -> Integer -> Element r q Source #

order :: Element r q -> Integer Source #

rnd :: MonadRandom m => m (Element r q) Source #

WPCurve e q r => Group (WPPoint e q r) Source # 
Instance details

Defined in Curve.Weierstrass

Methods

add :: WPPoint e q r -> WPPoint e q r -> WPPoint e q r Source #

dbl :: WPPoint e q r -> WPPoint e q r Source #

def :: WPPoint e q r -> Bool Source #

gen :: WPPoint e q r Source #

id :: WPPoint e q r Source #

inv :: WPPoint e q r -> WPPoint e q r Source #

mul' :: WPPoint e q r -> Integer -> WPPoint e q r Source #

order :: WPPoint e q r -> Integer Source #

rnd :: MonadRandom m => m (WPPoint e q r) Source #

WJCurve e q r => Group (WJPoint e q r) Source # 
Instance details

Defined in Curve.Weierstrass

Methods

add :: WJPoint e q r -> WJPoint e q r -> WJPoint e q r Source #

dbl :: WJPoint e q r -> WJPoint e q r Source #

def :: WJPoint e q r -> Bool Source #

gen :: WJPoint e q r Source #

id :: WJPoint e q r Source #

inv :: WJPoint e q r -> WJPoint e q r Source #

mul' :: WJPoint e q r -> Integer -> WJPoint e q r Source #

order :: WJPoint e q r -> Integer Source #

rnd :: MonadRandom m => m (WJPoint e q r) Source #

WACurve e q r => Group (WAPoint e q r) Source # 
Instance details

Defined in Curve.Weierstrass

Methods

add :: WAPoint e q r -> WAPoint e q r -> WAPoint e q r Source #

dbl :: WAPoint e q r -> WAPoint e q r Source #

def :: WAPoint e q r -> Bool Source #

gen :: WAPoint e q r Source #

id :: WAPoint e q r Source #

inv :: WAPoint e q r -> WAPoint e q r Source #

mul' :: WAPoint e q r -> Integer -> WAPoint e q r Source #

order :: WAPoint e q r -> Integer Source #

rnd :: MonadRandom m => m (WAPoint e q r) Source #

MACurve e q r => Group (MAPoint e q r) Source # 
Instance details

Defined in Curve.Montgomery

Methods

add :: MAPoint e q r -> MAPoint e q r -> MAPoint e q r Source #

dbl :: MAPoint e q r -> MAPoint e q r Source #

def :: MAPoint e q r -> Bool Source #

gen :: MAPoint e q r Source #

id :: MAPoint e q r Source #

inv :: MAPoint e q r -> MAPoint e q r Source #

mul' :: MAPoint e q r -> Integer -> MAPoint e q r Source #

order :: MAPoint e q r -> Integer Source #

rnd :: MonadRandom m => m (MAPoint e q r) Source #

EPCurve e q r => Group (EPPoint e q r) Source # 
Instance details

Defined in Curve.Edwards

Methods

add :: EPPoint e q r -> EPPoint e q r -> EPPoint e q r Source #

dbl :: EPPoint e q r -> EPPoint e q r Source #

def :: EPPoint e q r -> Bool Source #

gen :: EPPoint e q r Source #

id :: EPPoint e q r Source #

inv :: EPPoint e q r -> EPPoint e q r Source #

mul' :: EPPoint e q r -> Integer -> EPPoint e q r Source #

order :: EPPoint e q r -> Integer Source #

rnd :: MonadRandom m => m (EPPoint e q r) Source #

EACurve e q r => Group (EAPoint e q r) Source # 
Instance details

Defined in Curve.Edwards

Methods

add :: EAPoint e q r -> EAPoint e q r -> EAPoint e q r Source #

dbl :: EAPoint e q r -> EAPoint e q r Source #

def :: EAPoint e q r -> Bool Source #

gen :: EAPoint e q r Source #

id :: EAPoint e q r Source #

inv :: EAPoint e q r -> EAPoint e q r Source #

mul' :: EAPoint e q r -> Integer -> EAPoint e q r Source #

order :: EAPoint e q r -> Integer Source #

rnd :: MonadRandom m => m (EAPoint e q r) Source #

BPCurve e q r => Group (BPPoint e q r) Source # 
Instance details

Defined in Curve.Binary

Methods

add :: BPPoint e q r -> BPPoint e q r -> BPPoint e q r Source #

dbl :: BPPoint e q r -> BPPoint e q r Source #

def :: BPPoint e q r -> Bool Source #

gen :: BPPoint e q r Source #

id :: BPPoint e q r Source #

inv :: BPPoint e q r -> BPPoint e q r Source #

mul' :: BPPoint e q r -> Integer -> BPPoint e q r Source #

order :: BPPoint e q r -> Integer Source #

rnd :: MonadRandom m => m (BPPoint e q r) Source #

BACurve e q r => Group (BAPoint e q r) Source # 
Instance details

Defined in Curve.Binary

Methods

add :: BAPoint e q r -> BAPoint e q r -> BAPoint e q r Source #

dbl :: BAPoint e q r -> BAPoint e q r Source #

def :: BAPoint e q r -> Bool Source #

gen :: BAPoint e q r Source #

id :: BAPoint e q r Source #

inv :: BAPoint e q r -> BAPoint e q r Source #

mul' :: BAPoint e q r -> Integer -> BAPoint e q r Source #

order :: BAPoint e q r -> Integer Source #

rnd :: MonadRandom m => m (BAPoint e q r) Source #

Orphan instances

BACurve e q r => Curve Binary Affine (e :: k) q r Source # 
Instance details

Associated Types

data Point Binary Affine e q r :: Type Source #

BPCurve e q r => Curve Binary Projective (e :: k) q r Source # 
Instance details

Associated Types

data Point Binary Projective e q r :: Type Source #

BPCurve e q r => Eq (BPPoint e q r) Source # 
Instance details

Methods

(==) :: BPPoint e q r -> BPPoint e q r -> Bool #

(/=) :: BPPoint e q r -> BPPoint e q r -> Bool #

BPCurve e q r => Pretty (BPPoint e q r) Source # 
Instance details

Methods

pretty :: BPPoint e q r -> Doc #

prettyList :: [BPPoint e q r] -> Doc #

BACurve e q r => Pretty (BAPoint e q r) Source # 
Instance details

Methods

pretty :: BAPoint e q r -> Doc #

prettyList :: [BAPoint e q r] -> Doc #

BPCurve e q r => Group (BPPoint e q r) Source # 
Instance details

Methods

add :: BPPoint e q r -> BPPoint e q r -> BPPoint e q r Source #

dbl :: BPPoint e q r -> BPPoint e q r Source #

def :: BPPoint e q r -> Bool Source #

gen :: BPPoint e q r Source #

id :: BPPoint e q r Source #

inv :: BPPoint e q r -> BPPoint e q r Source #

mul' :: BPPoint e q r -> Integer -> BPPoint e q r Source #

order :: BPPoint e q r -> Integer Source #

rnd :: MonadRandom m => m (BPPoint e q r) Source #

BACurve e q r => Group (BAPoint e q r) Source # 
Instance details

Methods

add :: BAPoint e q r -> BAPoint e q r -> BAPoint e q r Source #

dbl :: BAPoint e q r -> BAPoint e q r Source #

def :: BAPoint e q r -> Bool Source #

gen :: BAPoint e q r Source #

id :: BAPoint e q r Source #

inv :: BAPoint e q r -> BAPoint e q r Source #

mul' :: BAPoint e q r -> Integer -> BAPoint e q r Source #

order :: BAPoint e q r -> Integer Source #

rnd :: MonadRandom m => m (BAPoint e q r) Source #

Eq q => Eq (Point Binary Affine e q r) Source # 
Instance details

Methods

(==) :: Point Binary Affine e q r -> Point Binary Affine e q r -> Bool #

(/=) :: Point Binary Affine e q r -> Point Binary Affine e q r -> Bool #

Read q => Read (Point Binary Affine e q r) Source # 
Instance details

Read q => Read (Point Binary Projective e q r) Source # 
Instance details

Show q => Show (Point Binary Affine e q r) Source # 
Instance details

Methods

showsPrec :: Int -> Point Binary Affine e q r -> ShowS #

show :: Point Binary Affine e q r -> String #

showList :: [Point Binary Affine e q r] -> ShowS #

Show q => Show (Point Binary Projective e q r) Source # 
Instance details

Generic (Point Binary Affine e q r) Source # 
Instance details

Associated Types

type Rep (Point Binary Affine e q r) :: Type -> Type #

Methods

from :: Point Binary Affine e q r -> Rep (Point Binary Affine e q r) x #

to :: Rep (Point Binary Affine e q r) x -> Point Binary Affine e q r #

Generic (Point Binary Projective e q r) Source # 
Instance details

Associated Types

type Rep (Point Binary Projective e q r) :: Type -> Type #

Methods

from :: Point Binary Projective e q r -> Rep (Point Binary Projective e q r) x #

to :: Rep (Point Binary Projective e q r) x -> Point Binary Projective e q r #

NFData q => NFData (Point Binary Affine e q r) Source # 
Instance details

Methods

rnf :: Point Binary Affine e q r -> () #

NFData q => NFData (Point Binary Projective e q r) Source # 
Instance details

Methods

rnf :: Point Binary Projective e q r -> () #