pasta-curves-0.0.0.0: Provides the Pasta curves: Pallas, Vesta and their field elements Fp and Fq.
Copyright(c) Eric Schorn 2022
LicenseMIT
Maintainereric.schorn@nccgroup.com
Stabilityexperimental
PortabilityGHC
Safe HaskellSafe
LanguageHaskell2010

PastaCurves

Description

This module provides the Pasta Curves consisting of: the Pallas curve and its Fp field element, the Vesta curve and its Fq field element, and a variety of supporting functionality such as point/element arithmetic, serialization, and hash-to-curve. The algorithms are NOT constant time; Safety and simplicity are the top priorities.

\[ \text{Pallas: } y^2 = x^3 + 5 \text{ over } F_p(0x40000000000000000000000000000000224698fc094cf91b992d30ed00000001) \]

\[ \text{Vesta: } y^2 = x^3 + 5 \text{ over } F_q(0x40000000000000000000000000000000224698fc0994a8dd8c46eb2100000001) \]

The order of the Pallas curve is 0x40000000000000000000000000000000224698fc0994a8dd8c46eb2100000001.

The order of the Vesta curve is 0x40000000000000000000000000000000224698fc094cf91b992d30ed00000001.

The curves are designed such that the order of one matches the field characteristic of the other. For a brief introduction, see the Zcash blog titled "The Pasta Curves for Halo 2 and Beyond" at https://electriccoin.co/blog/the-pasta-curves-for-halo-2-and-beyond/. The reference Rust implementation (which inspired this implementation) can be found at: https://github.com/zcash/pasta_curves.

Example usage of this library implementation:

$ cabal repl

ghci> a = 9 :: Fp

ghci> a*a
0x0000000000000000000000000000000000000000000000000000000000000051

ghci> pointMul a base :: Vesta
Projective {_px = 0x3CDC6A090F2BB3B52714C083929B620FE24ADBCBBD420752108CD7C29E543E5E, 
            _py = 0x08795CD330B3CE5AA63BD2B18DE155AE3C96E8AF9DA2CC742C6BA1464E490161, 
            _pz = 0x1FA26F58F3A641ADFE81775D3D53378D6178B6CCBF14F9BD4AB5F10DEE28D878}
Synopsis

Documentation

type Fp = Fz 28948022309329048855892746252171976963363056481941560715954676764349967630337 Source #

Fp is the field element used as a coordinate in the Pallas elliptic curve. It is a type synonym for the internal Fz type, parameterized with the correct modulus. It is also typically used as a scalar to multiply a Vesta elliptic curve point. Note that pointMul does not enforce specific scalar/point combinations.

type Fq = Fz 28948022309329048855892746252171976963363056481941647379679742748393362948097 Source #

Fq is the field element used as a coordinate in the Vesta elliptic curve. It is a type synonym for the internal Fz type, parameterized with the correct modulus. It is also typically used as a scalar to multiply a Pallas elliptic curve point. Note that pointMul does not enforce specific scalar/point combinations.

type Pallas = Point 0 5 1 16529367526445723262478303825122581175399563069290091271396079358777790485830 Fp Source #

Pallas represents a point on the Pallas elliptic curve using Fp coordinates. The curve was designed to have the some order as the Fq element's modulus. It is a type synonym for the internal Point type, parameterized with the curves a and b values and the affine base point as base_x and base_y. The underlying point is of type Point a b base_x base_y field.

type Vesta = Point 0 5 1 17521115379873687012324543952179862442514855490857619866290295271833908843935 Fq Source #

Vesta represents a point on the Vesta elliptic curve using Fq coordinates. The curve was designed to have the some order as the Fp element's modulus. It is a type synonym for the internal Point type, parameterized with the curves a and b values and the affine base point as base_x and base_y. The underlying point is of type Point a b base_x base_y field.

class CurvePt a where Source #

The CurvePt class provides the bulk of the functionality related to operations involving points on the elliptic curve. It supports both the Pallas and Vesta curve point types, as well as any other curves (using the arbitrary curve parameters). The curve order must be prime.

Methods

base :: a Source #

Returns the (constant) base point.

fromBytesC :: ByteString -> Maybe a Source #

The fromBytesC function deserializes a compressed point from a ByteString. An invalid ByteString will return Nothing.

isOnCurve :: a -> Bool Source #

The isOnCurve function validates whether the point is on the curve. It is already utilized within fromBytesC deserialization, within hash-to-curve (for redundant safety) and within toBytesC serialization.

negatePt :: a -> a Source #

The negatePt function negates a point.

neutral :: a Source #

Returns the (constant) neutral point.

pointAdd :: a -> a -> a Source #

The pointAdd function adds two curve points on the same elliptic curve.

toBytesC :: a -> ByteString Source #

The toBytesC function serializes a point to a (compressed) ByteStream.

class (CurvePt a, Field b) => Curve a b where Source #

The Curve class provides the elliptic point multiplication operation involving one CurvePt point on an elliptic curve and another Field field element as the scalar operand. It also provides the mapToCurveSimpleSwu which is used in the later stages of hashing-to-curve. It supports both the Pallas and Vesta curve point type.

Methods

pointMul :: b -> a -> a Source #

The pointMul function multiplies a field element by a prime-order curve point. This, for example, could be a Fq field element scalar with a Pallas elliptic curve point (which happens to use Fp co-ordinates).

mapToCurveSimpleSwu :: b -> b -> a Source #

hashToPallas :: ByteString -> Pallas Source #

The hashToPallas function takes an arbitrary ByteString and maps it to a valid point on the Pallas elliptic curve (of unknown relation to the base point).

hashToVesta :: ByteString -> Vesta Source #

The hashToVesta function takes an arbitrary ByteString and maps it to a valid point on the Vesta elliptic curve (of unknown relation to the base point).

class (Num a, Eq a) => Field a where Source #

The Field class provides useful support functionality for field elements.

Methods

fromBytesF :: ByteString -> Maybe a Source #

The fromBytesF function is the primary deserialization constructor which consumes a big-endian ByteString sized to minimally contain the modulus and returns a field element. The deserialized integer must already be properly reduced to reside within [0..modulus), otherwise Nothing is returned.

_fromBytesF :: ByteString -> a Source #

The _fromBytesF function is the secondary deserialization constructor which consumes an unconstrained big-endian ByteString and returns a internally reduced field element. This function is useful for random testing and hash2Field-style functions.

hash2Field :: ByteString -> String -> String -> (a, a) Source #

The hash2Field function provides intermediate functionality that is suitable for ultimately supporting the hash2Curve function. This function returns a 2-tuple of field elements.

inv0 :: a -> a Source #

The inv0 function returns the multiplicative inverse as calculated by Fermat's Little Theorem (mapping 0 to 0).

isSqr :: a -> Bool Source #

The isSqr function indicates whether the operand has a square root.

sgn0 :: a -> Integer Source #

The sgn0 function returns the least significant bit of the field element as an Integer.

shiftR1 :: a -> a Source #

The shiftR1 function shifts the field element one bit to the right, effectively dividing it by two (and discarding the remainder).

sqrt :: a -> Maybe a Source #

The sqrt function implements the variable-time Tonelli-Shanks algorithm to calculate the operand's square root. The function returns Nothing in the event of a problem (such as the operand not being a square, the modulus is not prime, etc).

toBytesF :: a -> ByteString Source #

The toBytesF function serializes an element into a big-endian ByteString sized to minimally contain the modulus.

toI :: a -> Integer Source #

The toI function returns the field element as a properly reduced Integer.

exampleFp :: Fp Source #

An example Fp element (8).

exampleFq :: Fq Source #

An example Fq element (999).

examplePallasPt :: Pallas Source #

An example Pallas point generated by hashing a message.

exampleVestaPt :: Vesta Source #

An example Vesta point (base * 8).

class Num a where #

Basic numeric class.

The Haskell Report defines no laws for Num. However, (+) and (*) are customarily expected to define a ring and have the following properties:

Associativity of (+)
(x + y) + z = x + (y + z)
Commutativity of (+)
x + y = y + x
fromInteger 0 is the additive identity
x + fromInteger 0 = x
negate gives the additive inverse
x + negate x = fromInteger 0
Associativity of (*)
(x * y) * z = x * (y * z)
fromInteger 1 is the multiplicative identity
x * fromInteger 1 = x and fromInteger 1 * x = x
Distributivity of (*) with respect to (+)
a * (b + c) = (a * b) + (a * c) and (b + c) * a = (b * a) + (c * a)

Note that it isn't customarily expected that a type instance of both Num and Ord implement an ordered ring. Indeed, in base only Integer and Rational do.

Minimal complete definition

(+), (*), abs, signum, fromInteger, (negate | (-))

Methods

(+) :: a -> a -> a infixl 6 #

(-) :: a -> a -> a infixl 6 #

(*) :: a -> a -> a infixl 7 #

negate :: a -> a #

Unary negation.

abs :: a -> a #

Absolute value.

signum :: a -> a #

Sign of a number. The functions abs and signum should satisfy the law:

abs x * signum x == x

For real numbers, the signum is either -1 (negative), 0 (zero) or 1 (positive).

fromInteger :: Integer -> a #

Conversion from an Integer. An integer literal represents the application of the function fromInteger to the appropriate value of type Integer, so such literals have type (Num a) => a.

Instances

Instances details
Num Int

Since: base-2.1

Instance details

Defined in GHC.Num

Methods

(+) :: Int -> Int -> Int #

(-) :: Int -> Int -> Int #

(*) :: Int -> Int -> Int #

negate :: Int -> Int #

abs :: Int -> Int #

signum :: Int -> Int #

fromInteger :: Integer -> Int #

Num Integer

Since: base-2.1

Instance details

Defined in GHC.Num

Num Natural

Note that Natural's Num instance isn't a ring: no element but 0 has an additive inverse. It is a semiring though.

Since: base-4.8.0.0

Instance details

Defined in GHC.Num

Num Word

Since: base-2.1

Instance details

Defined in GHC.Num

Methods

(+) :: Word -> Word -> Word #

(-) :: Word -> Word -> Word #

(*) :: Word -> Word -> Word #

negate :: Word -> Word #

abs :: Word -> Word #

signum :: Word -> Word #

fromInteger :: Integer -> Word #

Num Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Num Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Num Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Num Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Integral a => Num (Ratio a)

Since: base-2.0.1

Instance details

Defined in GHC.Real

Methods

(+) :: Ratio a -> Ratio a -> Ratio a #

(-) :: Ratio a -> Ratio a -> Ratio a #

(*) :: Ratio a -> Ratio a -> Ratio a #

negate :: Ratio a -> Ratio a #

abs :: Ratio a -> Ratio a #

signum :: Ratio a -> Ratio a #

fromInteger :: Integer -> Ratio a #