| Copyright | (c) Eric Schorn 2022 |
|---|---|
| License | MIT |
| Maintainer | eric.schorn@nccgroup.com |
| Stability | experimental |
| Portability | GHC |
| Safe Haskell | Safe |
| Language | Haskell2010 |
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
- type Fp = Fz 28948022309329048855892746252171976963363056481941560715954676764349967630337
- type Fq = Fz 28948022309329048855892746252171976963363056481941647379679742748393362948097
- type Pallas = Point 0 5 1 16529367526445723262478303825122581175399563069290091271396079358777790485830 Fp
- type Vesta = Point 0 5 1 17521115379873687012324543952179862442514855490857619866290295271833908843935 Fq
- class CurvePt a where
- base :: a
- fromBytesC :: ByteString -> Maybe a
- isOnCurve :: a -> Bool
- negatePt :: a -> a
- neutral :: a
- pointAdd :: a -> a -> a
- toBytesC :: a -> ByteString
- class (CurvePt a, Field b) => Curve a b where
- pointMul :: b -> a -> a
- mapToCurveSimpleSwu :: b -> b -> a
- hashToPallas :: ByteString -> Pallas
- hashToVesta :: ByteString -> Vesta
- rndPallas :: forall g. RandomGen g => g -> (g, Pallas)
- rndVesta :: forall g. RandomGen g => g -> (g, Vesta)
- class (Num a, Eq a) => Field a where
- fromBytesF :: ByteString -> Maybe a
- _fromBytesF :: ByteString -> a
- hash2Field :: ByteString -> String -> String -> (a, a)
- inv0 :: a -> a
- isSqr :: a -> Bool
- rndF :: RandomGen r => r -> (r, a)
- sgn0 :: a -> Integer
- shiftR1 :: a -> a
- sqrt :: a -> Maybe a
- toBytesF :: a -> ByteString
- toI :: a -> Integer
- pallasPrime :: Integer
- vestaPrime :: Integer
- exampleFp :: Fp
- exampleFq :: Fq
- examplePallasPt :: Pallas
- exampleVestaPt :: Vesta
- class Num a where
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
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.
The negatePt function negates a point.
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.
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).
rndPallas :: forall g. RandomGen g => g -> (g, Pallas) Source #
The rndPallas function returns a random Pallas point when given a StdGen.
rndVesta :: forall g. RandomGen g => g -> (g, Vesta) Source #
The rndVesta function returns a random Vests point when given a StdGen.
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.
The inv0 function returns the multiplicative inverse as calculated by Fermat's
Little Theorem (mapping 0 to 0).
The isSqr function indicates whether the operand has a square root.
rndF :: RandomGen r => r -> (r, a) Source #
The rndF function returns a random (invertible/non-zero) field element.
The sgn0 function returns the least significant bit of the field element as an
Integer.
The shiftR1 function shifts the field element one bit to the right, effectively
dividing it by two (and discarding the remainder).
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.
The toI function returns the field element as a properly reduced Integer.
pallasPrime :: Integer Source #
The Pallas field modulus https://neuromancer.sk/std/other/Pallas
vestaPrime :: Integer Source #
The Vesta field modulus https://neuromancer.sk/std/other/Vesta
examplePallasPt :: Pallas Source #
An example Pallas point generated by hashing a message.
exampleVestaPt :: Vesta Source #
An example Vesta point (base * 8).
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 + xis the additive identityfromInteger0x + fromInteger 0=xnegategives the additive inversex + negate x=fromInteger 0- Associativity of
(*) (x * y) * z=x * (y * z)is the multiplicative identityfromInteger1x * fromInteger 1=xandfromInteger 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.
Methods
Unary negation.
Absolute value.
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
| Num Word16 | Since: base-2.1 |
| Num Word32 | Since: base-2.1 |
| Num Word64 | Since: base-2.1 |
| Num Word8 | Since: base-2.1 |
| Num Integer | Since: base-2.1 |
| Num Natural | Note that Since: base-4.8.0.0 |
| Num Int | Since: base-2.1 |
| Num Word | Since: base-2.1 |
| Integral a => Num (Ratio a) | Since: base-2.0.1 |
| KnownNat n => Num (Zn n) | |
| (KnownNat n, NatWithinBound Word64 n) => Num (Zn64 n) | |
| Num (CountOf ty) | |
Defined in Basement.Types.OffsetSize | |
| Num (Offset ty) | |
Defined in Basement.Types.OffsetSize | |