When merging the last two posts, I immediately run into serious difficulties. Haskell's type system just made my work harder(well my ignorance did). Until I could come up with a solution, I could not appreciate how the strictness of the type system actually gives flexibility.
Rewrite the finite field
Previously I used a type that stored the number and the order of the field. That was the solution of the Python code from the Book[1]. It is how I would have done it in any other language I know. However, that was a limitation, for example when writing the instance for Num
, I could not define the function fromInteger
. Researching how could I work with finite fields in Haskell I found a package for exactly this use: finite-field. However, reading that code was too much of a challenge for me. Luckily, I also found this stackoverflow question "Prime finite field (Z/pZ) in Haskell with Operator Overloading". That gave me a workable solution. I can encode the order of the field as part of the type. That is really cool!
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
import GHC.TypeLits
newtype FieldElement (n :: Nat) = FieldElement Integer deriving Eq
This turned very quickly into quite advanced Haskell. You need 2 language extensions that I don't yet know what they mean, but the compiler kindly tells you, you need them. Importing GHC.TypeLits
lets you work with natural numbers as part of the types. With this, FieldElement
only wraps an Integer
and derives the Integer equality. You can use newtype
to define the type, because there is only one constructor, with one field. The cool new stuff happens left of the =
, when defining the type, constraining it to n :: Nat
, this n
, that represents the order of the field, must be a natural number.
Now, make FieldElement
an instance of Num
as before, yet with this new definition, you don't need to check the order of the field for each operation, since it is given by the type. The type system will now check that you don't mix FieldElement
of different orders, because they are now objects of different types.
You first need another language extension and a new import. Place them on the top of the file.
{-# LANGUAGE ScopedTypeVariables #-}
import Data.Proxy
The instance is Num (FieldElement n)
and you need to make sure that n
is an instance of KnownNat
. With that you can use the function natVal
to recover the value of the order of field from the type and use it for all the functions in Num
. fromInteger
takes all the management of the field order. In the last post I could not implement that function and now it is doing all the work.
instance KnownNat n => Num (FieldElement n) where
FieldElement x + FieldElement y = fromInteger $ x + y
FieldElement x * FieldElement y = fromInteger $ x * y
abs x = x
signum _ = 1
negate (FieldElement x) = fromInteger $ negate x
fromInteger a = FieldElement (mod a n)
where n = natVal (Proxy :: Proxy n)
Using the same trick with natVal
create the instance of Fractional
and Show
.
instance KnownNat n => Fractional (FieldElement n) where
recip a = a ^ (n - 2) where n = natVal (Proxy :: Proxy n)
fromRational r = error "cant transform"
instance KnownNat n => Show (FieldElement n) where
show (FieldElement a) = "FieldElement_" ++ show n ++ " " ++ show a
where n = natVal (Proxy :: Proxy n)
You can then define a number (e.g. 3) in the prime field (e.g 17) in this way:
three = FieldElement 3 :: FieldElement 17
Generalizing the elliptic curves over finite fields
In the last post I described the elliptic curve over the reals, more accurately over floating point numbers of type Double
. Mathematically, it is also possible to describe the elliptic curve over finite fields. The extension requires no work on the mathematical side, it just works. In our case, you do need to remove the explicit Type dependence to Double
to make things more general.
This means ECPoint
now needs a type parameter, which defines the field over which the points are defined. It could be Double
as previously, but now it can also be FieldElement n
. It can take anything type, but it is over those two that things will be defined and usable as some type constrains do come up in later definitions.
data ECPoint a
= Infinity
| ECPoint
{ x :: a
, y :: a
, a :: a
, b :: a
}
deriving (Eq)
I could define the constants a
and b
also as part of the type, yet for the Moment I'm lazy to implement that and I still don't find the need to do so as with finite fields.
To validate a point, the function is the same, yet type constrains already start to show up. Eq
is still mostly defined for all types, yet Num
already constrains the usable ones.
validECPoint :: (Eq a, Num a) => ECPoint a -> Bool
validECPoint Infinity = True
validECPoint (ECPoint x y a b) = y ^ 2 == x ^ 3 + a * x + b
Defining addition of points in the elliptic curve requires no change in the code, only the enforcement of the type constraints.
add :: (Eq a, Fractional a) => ECPoint a -> ECPoint a -> ECPoint a
add Infinity p = p
add p Infinity = p
add p q
| a p /= a q || b p /= b q = error "point not on same curve"
| x p == x q && y p /= y q = Infinity
| x p /= x q = new_point $ (y q - y p) / (x q - x p)
| x p == x q && y p == 0 = Infinity
| p == q = new_point $ (3 * x p ^ 2 + a p) / (2 * y p)
| otherwise = error "Unexpected case of points"
where
new_point slope =
let new_x = slope ^ 2 - x p - x q
new_y = slope * (x p - new_x) - y p
in ECPoint new_x new_y (a p) (b p)
Finally to get things to show up nicely on the console, I prepare the instances of show. In this case I learned again about a new language pragma. I wanted to show the ECPoint
as before for other Double
type and then be more specific when dealing with finite fields. Implementing this too instances got the compiler to complain and so I learned about overlapping instances. First you need the language extension FlexibleInstances
. Then using the OVERLAPPABLE
pragma when defining the most generic Show
instance, which only requires the type to be instance of Num
. That covers the instance of Double
. Because, FieldElement n
is an instance of Num
the problem of overlapping arose, with the pragma OVERLAPPING
, it is now allowed as it is more specific than the Num
case, and it will be used for the field elements.
{-# LANGUAGE FlexibleInstances #-}
import Text.Printf (PrintfArg, printf)
instance {-# OVERLAPPABLE #-} (PrintfArg a, Num a) => Show (ECPoint a) where
show Infinity = "ECPoint(Infinity)"
show p = printf "ECPoint(%f, %f)_%f_%f" (x p) (y p) (a p) (b p)
instance {-# OVERLAPPING #-} KnownNat n => Show (ECPoint (FieldElement n)) where
show Infinity = "ECPoint(Infinity)"
show p = "ECPoint_" ++ show n ++ points ++ params
where
n = natVal (Proxy :: Proxy n)
points = "(" ++ si (x p) ++ ", " ++ si (y p) ++ ")"
params = "a_" ++ si (a p) ++ "|b_" ++ si (b p)
si (FieldElement r) = show r
I can define a point like this
dd =
let a = FieldElement 0 :: FieldElement 223
b = FieldElement 7
x = FieldElement 192
y = FieldElement 105
in ECPoint x y a b
Haskell's compiler will infer the field order for the variables b
, x
and y
, to be also FieldElement 223
. Because ECPoint
requires all arguments to be of the same type. As a matter of fact, because I defined fromInteger
earlier in Num
for FieldElement
, I can define that point like this too:
ee = ECPoint 192 105 (FieldElement 0 :: FieldElement 223) 7
ff = ECPoint 192 105 0 7 :: ECPoint (FieldElement 223)
Scalar multiplication
Having addition already defined over points on the elliptic curve with the function add
, it is also useful to use multiplication as an abbreviated sum. That is
5 A = A + A + A + A + A
Very naively that can be implemented as:
aPoint = ECPoint 192 105 0 7 :: ECPoint (FieldElement 223)
total = add aPoint $ add aPoint $ add aPoint $ add aPoint aPoint
That looks like a job for foldr
totalfoldr = foldr add Infinity $ replicate 5 aPoint
However, the process of adding each term as many times as the factor we are using is very CPU time consuming. When working on very large fields and with very large factors, the individual sum becomes unfeasible. However, we can shorten the multiplication by using a binary expansion, using the accumulated sum of A
, in powers of two. Which is possible because addition on elliptic curves is associative and commutative.
This binary expansion and the corresponding scalar product can be implemented using Haskell's library for bitwise operations Data.Bits
.
import Data.Bits
binaryExpansion :: (Eq a, Fractional a) => Integer -> ECPoint a -> ECPoint a -> ECPoint a
binaryExpansion m value result | m == 0 = result
| otherwise = binaryExpansion (m `shiftR` 1) (add value value) accumulator
where
accumulator = if m .&. 1 == 1 then add result value else result
scalarProduct :: (Eq a, Fractional a) => Integer -> ECPoint a -> ECPoint a
scalarProduct m ec = binaryExpansion m ec Infinity
This way that product can be calculated as:
totalbin = scalarProduct 5 aPoint
Instantiating the monoid type class for ECPoint
By now you might have noticed that points on the elliptic curve are also monoids, and thus just for completeness we can implement it.
instance (Eq a, Fractional a) => Semigroup (ECPoint a) where
(<>) = add
instance (Eq a, Fractional a) => Monoid (ECPoint a) where
mempty = Infinity
This way we create another way of expressing the multiplication:
totalmconcat = mconcat $ replicate 5 aPoint
And also even a more general way of representing the binaryExpansion
expansion.
binaryExpansion :: (Semigroup a) => Integer -> a -> a -> a
binaryExpansion m value result | m == 0 = result
| otherwise = binaryExpansion (m `shiftR` 1) (value <> value) accumulator
where
accumulator = if m .&. 1 == 1 then result <> value else result
That is awesome, now it has become a quite generic function, as it should, because the binary expansion is a very generic procedure.
Conclusion
This was a fascinating learning experience. It was a lot more than just translating Python code to Haskell. Haskell made it difficult to just take the Python solution, and at the same time it forced me to investigate a lot more on its capabilities. Trying to compile this small program and having error messages that at least hint me to my next web search was of enormous help.
I find it fantastic that learning Haskell also forces you to think about properties of the objects you are dealing with. It was only through Haskell, that I thought of points on the elliptic curve to be monoids, and that by recognizing that property as a consequence my code can be refactored to be more generic.
Jimmy Song, Programming Bitcoin, O'Reilly Media, Inc. ISBN: 9781492031499, 2019 ↩
Congratulations @titan-c! You have completed the following achievement on the Hive blockchain and have been rewarded with new badge(s) :
Your next target is to reach 91000 upvotes.
You can view your badges on your board and compare yourself to others in the Ranking
If you no longer want to receive notifications, reply to this comment with the word
STOP
To support your work, I also upvoted your post!