aboutsummaryrefslogtreecommitdiffstats
path: root/ecc.hs
blob: 56a306770cba95b517135562d94f23c0415eafaa (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
{-# LANGUAGE FlexibleInstances #-}

data FieldElement a = FieldElement
  { number :: a
  , prime  :: a
  }
  deriving Eq

instance (Num a, Show a) => Show (FieldElement a) where
  show a = "FieldElement_" ++ show (prime a) ++ " " ++ show (number a)

instance Integral a => Num (FieldElement a) where
  (FieldElement a b) + (FieldElement c d)
    | b /= d    = error "Distinct Fields"
    | otherwise = FieldElement (mod (a + c) b) b
  (FieldElement a b) * (FieldElement c d)
    | b /= d    = error "Distinct Fields"
    | otherwise = FieldElement (mod (a * c) b) b
  abs a = a
  signum _ = 1
  negate (FieldElement a b) = FieldElement (mod (b - a) b) b
  fromInteger _ = error "can't transform"

instance (Integral a) => Fractional (FieldElement a) where
  recip a = a ^ (prime a - 2)
  fromRational _ = error "can't transform"

assert :: Bool -> Bool
assert False = error "WRONG"
assert x     = x

aa =
  let a = FieldElement 2 31
      b = FieldElement 15 31
  in  assert
        (  (a + b == FieldElement 17 31)
        && (a /= b)
        && (a - b == FieldElement 18 31)
        )

bb =
  let a = FieldElement 19 31
      b = FieldElement 24 31
  in  a * b

data ECPoint a
  = Infinity
  | ECPoint
      { x :: a
      , y :: a
      , a :: a
      , b :: a
      }
  deriving (Eq )

rmul :: Integral a => a -> FieldElement a -> FieldElement a
a `rmul` (FieldElement v p) = FieldElement (mod (a * v) p) p

instance Show a => Show (ECPoint (FieldElement a)) where
  show Infinity = "ECPoint(Infinity)"
  show p        = "ECPoint_" ++ show (prime (x p)) ++ points ++ params
   where
    points = "(" ++ show (number (x p)) ++ ", " ++ show (number (y p)) ++ ")"
    params = "a_" ++ show (number (a p)) ++ "|b_" ++ show (number (b p))


validECPoint :: (Eq a, Num a) => ECPoint a -> Bool
validECPoint Infinity = True
validECPoint p        = y p ^ 2 == x p ^ 3 + a p * x p + b p

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)


cc =
  let a = ECPoint 3 (-7) 5 7
      b = ECPoint 18 77 5 7
      c = ECPoint (-1) (-1) 5 7
  in  ( validECPoint a
      , validECPoint b
      , validECPoint c
      , a /= b
      , a == a
      , add Infinity          a
      , add a                 (ECPoint 3 7 5 7)
      , add (ECPoint 3 7 5 7) c
      , add c                 c
      )

dd =
  let prime = 223
      a     = FieldElement 0 prime
      b     = FieldElement 7 prime
      x     = FieldElement 192 prime
      y     = FieldElement 105 prime
      point = ECPoint x y a b
  in  validECPoint point