elliptic-curve: Elliptic curve library

[ cryptography, library, mit ] [ Propose Tags ]

An extensible library of elliptic curves used in cryptography research


[Skip to Readme]

Modules

[Index] [Quick Jump]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0, 0.2.1, 0.2.2, 0.3.0
Change log ChangeLog.md
Dependencies base (>=4.10 && <5), galois-field (>=1 && <2), groups, MonadRandom, protolude (>=0.2 && <0.3), tasty-quickcheck, text, wl-pprint-text [details]
License MIT
Author
Maintainer Adjoint Inc (info@adjoint.io)
Category Cryptography
Home page https://github.com/adjoint-io/elliptic-curve#readme
Bug tracker https://github.com/adjoint-io/elliptic-curve/issues
Source repo head: git clone https://github.com/adjoint-io/elliptic-curve
Uploaded by sdiehl at 2019-09-27T15:22:08Z
Distributions
Reverse Dependencies 5 direct, 6 indirect [details]
Downloads 2067 total (16 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2019-09-27 [all 1 reports]

Readme for elliptic-curve-0.3.0

[back to package description]

Adjoint Logo

Elliptic Curve

An extensible library of elliptic curves used in cryptography research.

Curve representations

An elliptic curve E(K) over a field K is a smooth projective plane algebraic cubic curve with a specified base point O, and the points on E(K) form an algebraic group with identity point O. By the Riemann-Roch theorem, any elliptic curve is isomorphic to a cubic curve of the form

E(K) = {(x, y) | y^2 + a1xy + a3y = x^3 + a2x^2 + a4x + a6} U {O}

where O is the point at infinity, and a1, a2, a3, a4, a6 are K-rational coefficients that satisfy a non-zero discriminant condition. For cryptographic computational purposes, elliptic curves are represented in several different forms.

Weierstrass curves

A (short) Weierstrass curve is an elliptic curve over GF(p) for some prime p, and is of the form

E(GF(p)) = {(x, y) | y^2 = x^3 + Ax^2 + B} U {O}

where A and B are K-rational coefficients such that 4A^3 + 27B^2 is non-zero. Weierstrass curves are the most common representations of elliptic curves, as any elliptic curve over a field of characteristic greater than 3 is isomorphic to a Weierstrass curve.

Binary curves

A (short Weierstrass) binary curve is an elliptic curve over GF(2^m) for some positive m, and is of the form

E(GF(2^m)) = {(x, y) | y^2 = x^3 + Ax + B} U {O}

where A and B are K-rational coefficients such that B is non-zero. Binary curves have field elements represented by binary integers for efficient arithmetic, and are special cases of long Weierstrass curves over a field of characteristic 2.

Montgomery curves

A Montgomery curve is an elliptic curve over GF(p) for some prime p, and is of the form

E(GF(p)) = {(x, y) | By^2 = x^3 + Ax^2 + x} U {O}

where A and B are K-rational coefficients such that B(A^2 - 4) is non-zero. Montgomery curves only use the first affine coordinate for computations, and can utilise the Montgomery ladder for efficient multiplication.

Edwards curves

A (twisted) Edwards curve is an elliptic curve over GF(p) for some prime p, and is of the form

E(GF(p)) = {(x, y) | Ax^2 + y^2 = 1 + Dx^2y^2}

where A and D are K-rational coefficients such that D(1 - D) is non-zero. Edwards curves have no point at infinity, and their addition and doubling formulae converge.

Curve usage

This library is open for new curve representations and curve implementations through pull requests. These should ideally be executed by replicating and modifying existing curve files, for ease, quickcheck testing, and formatting consistency, but a short description of the file organisation is provided here for clarity. Note that it also has a dependency on the Galois field library and its required language extensions.

Representing a new curve using the curve class

Import the following modules.

import Curve (Curve(..))
import GaloisField (GaloisField)

Create a phantom representation of Weierstrass curves.

data W

Create a synonym for the points on Weierstrass curves.

type WPoint = Point W

Create a class for Weierstrass curves and their parameters.

class Curve W c k => WCurve c k where
  a_ :: c -> k
  b_ :: c -> k
  g_ :: WPoint c k

Create an instance of Weierstrass curves with their operations.

instance (GaloisField k, WCurve c k) => Curve W c k where

  data instance Point W c k = A k k
                            | O
    deriving (Eq, Show)

  def O       = True
  def (A x y) = y * y == x ^ 3 + a * x ^ 2 + b
    where
      a = a_ (undefined :: c)
      b = b_ (undefined :: c)

  ...

Export the following data types.

module Weierstrass
  ( Point(..)
  , WCurve(..)
  , WPoint
  ) where

Implementing a new curve using a curve representation

Import a curve representation and a suitable Galois field.

import Curve.Weierstrass (Point(..), WCurve(..), WPoint)
import PrimeField (PrimeField)

Create a phantom representation of the Anomalous curve.

data Anomalous

Create a synonym for the field of the Anomalous curve.

type Fp = PrimeField 0xb0000000000000000000000953000000000000000000001f9d7

Create a synonym for the points on the Anomalous curve.

type P = WPoint Anomalous Fp

Create constants for the parameters of the Anomalous curve.

_a :: Fp
_a = 0x98d0fac687d6343eb1a1f595283eb1a1f58d0fac687d635f5e4

_b :: Fp
_b = 0x4a1f58d0fac687d6343eb1a5e2d6343eb1a1f58d0fac688ab3f

_g :: P
_g = A
     0x101efb35fd1963c4871a2d17edaafa7e249807f58f8705126c6
     0x22389a3954375834304ba1d509a97de6c07148ea7f5951b20e7

...

Create an instance of the Anomalous curve with its parameters.

instance WCurve Anomalous Fp where
  a_ = const _a
  b_ = const _b
  g_ = _g

Export the following data types and constants.

module Curve.Weierstrass.Anomalous
  ( Fp
  , P
  , _a
  , _b
  , _g
  , ...
  ) where

Using an implemented curve

Import the curve class and a curve implementation.

import Curve
import qualified Curve.Weierstrass.Anomalous as Anomalous

The data types and constants can then be accessed readily as Anomalous.P and Anomalous._g.

Curve implementations

The following curves have already been implemented.

Binary curves

Edwards curves

Montgomery curves

Weierstrass curves