1{-# LANGUAGE ExistentialQuantification #-}
2{-# LANGUAGE FlexibleContexts #-}
3{-# LANGUAGE OverloadedStrings #-}
4module ECC (tests) where
5
6import           Crypto.Error
7import qualified Crypto.ECC as ECC
8
9import           Data.ByteArray.Encoding
10
11import Imports
12
13data Curve = forall curve. (ECC.EllipticCurveDH curve, Show curve, Eq (ECC.Point curve)) => Curve curve
14
15instance Show Curve where
16    showsPrec d (Curve curve) = showsPrec d curve
17
18instance Arbitrary Curve where
19    arbitrary = elements
20        [ Curve ECC.Curve_P256R1
21        , Curve ECC.Curve_P384R1
22        , Curve ECC.Curve_P521R1
23        , Curve ECC.Curve_X25519
24        , Curve ECC.Curve_X448
25        ]
26
27data VectorPoint = VectorPoint
28    { vpCurve :: Curve
29    , vpHex   :: ByteString
30    , vpError :: Maybe CryptoError
31    }
32
33vectorsPoint =
34    [ VectorPoint
35        { vpCurve = Curve ECC.Curve_P256R1
36        , vpHex   = ""
37        , vpError = Just CryptoError_PointSizeInvalid
38        }
39    , VectorPoint
40        { vpCurve = Curve ECC.Curve_P256R1
41        , vpHex   = "00"
42        , vpError = Just CryptoError_PointFormatInvalid
43        }
44    , VectorPoint
45        { vpCurve = Curve ECC.Curve_P256R1
46        , vpHex   = "0408edd7b50085a952172228aca391beebe9ba942a0ae9eb15bcc8d50795d1a5505221c7b9b3bb4310f165fc3ac3114339db8170ceae6697e0f9736698b33551b8"
47        , vpError = Nothing
48        }
49    , VectorPoint
50        { vpCurve = Curve ECC.Curve_P256R1
51        , vpHex   = "04216f25b00717d46deef3402628f6abf265bfa12aea515ae8f100ce415e251e72cd5cd8f47f613a0f4e0f4f9410dd9c85c149cffcb320c2d52bf550a397ec92e5"
52        , vpError = Nothing
53        }
54    , VectorPoint
55        { vpCurve = Curve ECC.Curve_P256R1
56        , vpHex   = "0421eba6080610926609bb8d52afd3331ed1b07e0ba4c1441a118b62497d3e85f39a50c865027cdd84298cdf094b7818f2a65ae59f46c971a32ab4ea3c2c93c959"
57        , vpError = Nothing
58        }
59    , VectorPoint
60        { vpCurve = Curve ECC.Curve_P256R1
61        , vpHex   = "0400d7fc4050dfe73475502d5d1fadc105d7725508f48da2cd4729bf191fd6490a0001a16f417a27530e756efeb4a228f02db878072b9f833e99a2821d85fa78fc"
62        , vpError = Nothing
63        }
64    , VectorPoint
65        { vpCurve = Curve ECC.Curve_P256R1
66        , vpHex   = "040000fc4050dfe73475502d5d1fadc105d7725508f48da2cd4729bf191fd6490a0001a16f417a27530e756efeb4a228f02db878072b9f833e99a2821d85fa78fc"
67        , vpError = Just CryptoError_PointCoordinatesInvalid
68        }
69    , VectorPoint
70        { vpCurve = Curve ECC.Curve_P256R1
71        , vpHex   = "04d7fc4050dfe73475502d5d1fadc105d7725508f48da2cd4729bf191fd6490a01a16f417a27530e756efeb4a228f02db878072b9f833e99a2821d85fa78fc"
72        , vpError = Just CryptoError_PublicKeySizeInvalid -- tests leading zeros
73        }
74    , VectorPoint
75        { vpCurve = Curve ECC.Curve_P256R1
76        , vpHex   = "040000d7fc4050dfe73475502d5d1fadc105d7725508f48da2cd4729bf191fd6490a000001a16f417a27530e756efeb4a228f02db878072b9f833e99a2821d85fa78fc"
77        , vpError = Just CryptoError_PublicKeySizeInvalid -- tests leading zeros
78        }
79    , VectorPoint
80        { vpCurve = Curve ECC.Curve_P384R1
81        , vpHex   = ""
82        , vpError = Just CryptoError_PointSizeInvalid
83        }
84    , VectorPoint
85        { vpCurve = Curve ECC.Curve_P384R1
86        , vpHex   = "00"
87        , vpError = Just CryptoError_PointFormatInvalid
88        }
89    , VectorPoint
90        { vpCurve = Curve ECC.Curve_P384R1
91        , vpHex   = "0409281a103fb1773445e16eec86adb095e32928ccc9c806bd210c649712813bdb6cab40163a8cb163b578ea8dda5eb32cfb5208ebf0d31a6c590fa92f5a61f32dbc0d518b166ea5a9adf9dd21c1bd09932ca21c6a5725ca89542ac57b6a9eca6f"
92        , vpError = Nothing
93        }
94    , VectorPoint
95        { vpCurve = Curve ECC.Curve_P384R1
96        , vpHex   = "040c7b3fb575c1db7bc61fe7a456cc34a8289f41e167938a56e5ba2787723f3de2c645112705e13ed24f477730173935ca4e0ff468e7e0acf78a9f59dadff8193a0e23789eb3737730c089b27a0f94de7d95b8db4466d017fb21a5710d6ca85775"
97        , vpError = Nothing
98        }
99    , VectorPoint
100        { vpCurve = Curve ECC.Curve_P384R1
101        , vpHex   = "0438e7705220b60460194be63d21c8945be2a211957168fa60f26b2ad4e8f5cd96a7779e7edff4deda9ded63243c2127e273d4444edaaba03b79b6caafc5033432af13776f851c0c7e1080c60d7ee3b61740720ab98461813dab5fb8c31bfa9ed9"
102        , vpError = Nothing
103        }
104    , VectorPoint
105        { vpCurve = Curve ECC.Curve_P384R1
106        , vpHex   = "04000836bf09614bf5b3c0ffe9b0822a2cc109a90b13d4d3510ce14f766e7d90875ec4bc8d6bee11fc1fdf97473a67884c00b1e2685367bdb846c95181b0f35a35cfbee04451122cc55a1e363acaa6c002e71b0b6ff7d0f5dc830a32f0e5086189"
107        , vpError = Nothing
108        }
109    , VectorPoint
110        { vpCurve = Curve ECC.Curve_P384R1
111        , vpHex   = "04000036bf09614bf5b3c0ffe9b0822a2cc109a90b13d4d3510ce14f766e7d90875ec4bc8d6bee11fc1fdf97473a67884c00b1e2685367bdb846c95181b0f35a35cfbee04451122cc55a1e363acaa6c002e71b0b6ff7d0f5dc830a32f0e5086189"
112        , vpError = Just CryptoError_PointCoordinatesInvalid
113        }
114    , VectorPoint
115        { vpCurve = Curve ECC.Curve_P384R1
116        , vpHex   = "040836bf09614bf5b3c0ffe9b0822a2cc109a90b13d4d3510ce14f766e7d90875ec4bc8d6bee11fc1fdf97473a67884cb1e2685367bdb846c95181b0f35a35cfbee04451122cc55a1e363acaa6c002e71b0b6ff7d0f5dc830a32f0e5086189"
117        , vpError = Nothing -- ignores leading zeros
118        }
119    , VectorPoint
120        { vpCurve = Curve ECC.Curve_P384R1
121        , vpHex   = "0400000836bf09614bf5b3c0ffe9b0822a2cc109a90b13d4d3510ce14f766e7d90875ec4bc8d6bee11fc1fdf97473a67884c0000b1e2685367bdb846c95181b0f35a35cfbee04451122cc55a1e363acaa6c002e71b0b6ff7d0f5dc830a32f0e5086189"
122        , vpError = Nothing -- ignores leading zeros
123        }
124    , VectorPoint
125        { vpCurve = Curve ECC.Curve_P521R1
126        , vpHex   = ""
127        , vpError = Just CryptoError_PointSizeInvalid
128        }
129    , VectorPoint
130        { vpCurve = Curve ECC.Curve_P521R1
131        , vpHex   = "00"
132        , vpError = Just CryptoError_PointFormatInvalid
133        }
134    , VectorPoint
135        { vpCurve = Curve ECC.Curve_P521R1
136        , vpHex   = "04000ce5c207335134567026063743df82c1b551a009cf616471f0e23fa9767a50cc7f8771ef13a65c49ce7e1cd1ac3ad721dcc3ddd35f98ae5d380a0832f87a9f0ca4012914911d6bea7f3c481d694fb1645be27c7b66b09b28e261f8030b3fb8206f6a95f6ad73db755765b64f592a799234f8f451cb787abe95b1a54991a799ad0d69da"
137        , vpError = Nothing
138        }
139    , VectorPoint
140        { vpCurve = Curve ECC.Curve_P521R1
141        , vpHex   = "04003a5e6c1ce3a6a323757005da17b357db991bd1ad835e6201411f458b5c2edb3c66786b727b7e15fbad7dd74a4b0eb542183b5242e5952061cb85e7229353eb0dc300aac2dbd5232d582481ba7a59a993eb04c4466a1b17ba0015b65c616ce8703e70880969d8d58e633acb29c3ca017eb1b88649387b867466090ce1a57c2b4f8376bb"
142        , vpError = Nothing
143        }
144    , VectorPoint
145        { vpCurve = Curve ECC.Curve_P521R1
146        , vpHex   = "04003e0659fe9498695a3d8c88b8e25fa8133c30ab10eccbe9094344c99924f89fb69d9b3acf03bf438328f9cba55fa28a05be9a7e18780706b3728abfee2592aeb86d0001ea5ff64f2ca7a6453c79f80550e971843e073f4f8fec75bad2e52a4483ebf1f16f43d0de27e1967ea22f9722527652fa74439fdc03a569fba29e2d6f7c012db6"
147        , vpError = Nothing
148        }
149    , VectorPoint
150        { vpCurve = Curve ECC.Curve_P521R1
151        , vpHex   = "040043f91fd92d9ccd6d5584b265a2a775d222f4a41ff98190677d985e0889737cbe631d525835fe04faffcdebeccb783538280f4600ae82347b0470583abd9def306000a2e9bdc34f42b134517fc1e961befea0affd1f9666361a039192082a892dd722931d5865b62b69d7369e74895120e540cb10030cccb6049d809fbcf3f54537b378"
152        , vpError = Nothing
153        }
154    , VectorPoint
155        { vpCurve = Curve ECC.Curve_P521R1
156        , vpHex   = "040000f91fd92d9ccd6d5584b265a2a775d222f4a41ff98190677d985e0889737cbe631d525835fe04faffcdebeccb783538280f4600ae82347b0470583abd9def306000a2e9bdc34f42b134517fc1e961befea0affd1f9666361a039192082a892dd722931d5865b62b69d7369e74895120e540cb10030cccb6049d809fbcf3f54537b378"
157        , vpError = Just CryptoError_PointCoordinatesInvalid
158        }
159    , VectorPoint
160        { vpCurve = Curve ECC.Curve_P521R1
161        , vpHex   = "0443f91fd92d9ccd6d5584b265a2a775d222f4a41ff98190677d985e0889737cbe631d525835fe04faffcdebeccb783538280f4600ae82347b0470583abd9def3060a2e9bdc34f42b134517fc1e961befea0affd1f9666361a039192082a892dd722931d5865b62b69d7369e74895120e540cb10030cccb6049d809fbcf3f54537b378"
162        , vpError = Nothing -- ignores leading zeros
163        }
164    , VectorPoint
165        { vpCurve = Curve ECC.Curve_P521R1
166        , vpHex   = "04000043f91fd92d9ccd6d5584b265a2a775d222f4a41ff98190677d985e0889737cbe631d525835fe04faffcdebeccb783538280f4600ae82347b0470583abd9def30600000a2e9bdc34f42b134517fc1e961befea0affd1f9666361a039192082a892dd722931d5865b62b69d7369e74895120e540cb10030cccb6049d809fbcf3f54537b378"
167        , vpError = Nothing -- ignores leading zeros
168        }
169    , VectorPoint
170        { vpCurve = Curve ECC.Curve_X25519
171        , vpHex   = ""
172        , vpError = Just CryptoError_PublicKeySizeInvalid
173        }
174    , VectorPoint
175        { vpCurve = Curve ECC.Curve_X25519
176        , vpHex   = "22cd98c65fb50db3be0d6d359456c0cd3516952a6e7229ff672893944f703f10"
177        , vpError = Nothing
178        }
179    , VectorPoint
180        { vpCurve = Curve ECC.Curve_X25519
181        , vpHex   = "23cd98c65fb50db3be0d6d359456c0cd3516952a6e7229ff672893944f703f10"
182        , vpError = Nothing
183        }
184    , VectorPoint
185        { vpCurve = Curve ECC.Curve_X25519
186        , vpHex   = "0023cd98c65fb50db3be0d6d359456c0cd3516952a6e7229ff672893944f703f10"
187        , vpError = Just CryptoError_PublicKeySizeInvalid
188        }
189    , VectorPoint
190        { vpCurve = Curve ECC.Curve_X448
191        , vpHex   = ""
192        , vpError = Just CryptoError_PublicKeySizeInvalid
193        }
194    , VectorPoint
195        { vpCurve = Curve ECC.Curve_X448
196        , vpHex   = "2b162c2fef165ecbb203e40975ae4424f0f8db25ab582cb96b2e5ffe90a31798b35480b594c99dc32b437e61a74f792d8ecf5fc3e8cfeb75"
197        , vpError = Nothing
198        }
199    , VectorPoint
200        { vpCurve = Curve ECC.Curve_X448
201        , vpHex   = "2c162c2fef165ecbb203e40975ae4424f0f8db25ab582cb96b2e5ffe90a31798b35480b594c99dc32b437e61a74f792d8ecf5fc3e8cfeb75"
202        , vpError = Nothing
203        }
204    , VectorPoint
205        { vpCurve = Curve ECC.Curve_X448
206        , vpHex   = "002c162c2fef165ecbb203e40975ae4424f0f8db25ab582cb96b2e5ffe90a31798b35480b594c99dc32b437e61a74f792d8ecf5fc3e8cfeb75"
207        , vpError = Just CryptoError_PublicKeySizeInvalid
208        }
209    ]
210
211vectorsWeakPoint =
212    [ VectorPoint
213        { vpCurve = Curve ECC.Curve_X25519
214        , vpHex   = "0000000000000000000000000000000000000000000000000000000000000000"
215        , vpError = Just CryptoError_ScalarMultiplicationInvalid
216        }
217    , VectorPoint
218        { vpCurve = Curve ECC.Curve_X25519
219        , vpHex   = "0100000000000000000000000000000000000000000000000000000000000000"
220        , vpError = Just CryptoError_ScalarMultiplicationInvalid
221        }
222    , VectorPoint
223        { vpCurve = Curve ECC.Curve_X25519
224        , vpHex   = "e0eb7a7c3b41b8ae1656e3faf19fc46ada098deb9c32b1fd866205165f49b800"
225        , vpError = Just CryptoError_ScalarMultiplicationInvalid
226        }
227    , VectorPoint
228        { vpCurve = Curve ECC.Curve_X25519
229        , vpHex   = "5f9c95bca3508c24b1d0b1559c83ef5b04445cc4581c8e86d8224eddd09f1157"
230        , vpError = Just CryptoError_ScalarMultiplicationInvalid
231        }
232    , VectorPoint
233        { vpCurve = Curve ECC.Curve_X25519
234        , vpHex   = "ecffffffffffffffffffffffffffffffffffffffffffffffffffffffffffff7f"
235        , vpError = Just CryptoError_ScalarMultiplicationInvalid
236        }
237    , VectorPoint
238        { vpCurve = Curve ECC.Curve_X25519
239        , vpHex   = "edffffffffffffffffffffffffffffffffffffffffffffffffffffffffffff7f"
240        , vpError = Just CryptoError_ScalarMultiplicationInvalid
241        }
242    , VectorPoint
243        { vpCurve = Curve ECC.Curve_X25519
244        , vpHex   = "eeffffffffffffffffffffffffffffffffffffffffffffffffffffffffffff7f"
245        , vpError = Just CryptoError_ScalarMultiplicationInvalid
246        }
247    , VectorPoint
248        { vpCurve = Curve ECC.Curve_X448
249        , vpHex   = "0000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000"
250        , vpError = Just CryptoError_ScalarMultiplicationInvalid
251        }
252    , VectorPoint
253        { vpCurve = Curve ECC.Curve_X448
254        , vpHex   = "0100000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000"
255        , vpError = Just CryptoError_ScalarMultiplicationInvalid
256        }
257    ]
258
259vpEncodedPoint :: VectorPoint -> ByteString
260vpEncodedPoint vector = let Right bs = convertFromBase Base16 (vpHex vector) in bs
261
262cryptoError :: CryptoFailable a -> Maybe CryptoError
263cryptoError = onCryptoFailure Just (const Nothing)
264
265doPointDecodeTest (i, vector) =
266    case vpCurve vector of
267        Curve curve ->
268            let prx = Just curve -- using Maybe as Proxy
269             in testCase (show i) (vpError vector @=? cryptoError (ECC.decodePoint prx $ vpEncodedPoint vector))
270
271doWeakPointECDHTest (i, vector) =
272    case vpCurve vector of
273        Curve curve -> testCase (show i) $ do
274            let prx = Just curve -- using Maybe as Proxy
275                CryptoPassed public = ECC.decodePoint prx $ vpEncodedPoint vector
276            keyPair <- ECC.curveGenerateKeyPair prx
277            vpError vector @=? cryptoError (ECC.ecdh prx (ECC.keypairGetPrivate keyPair) public)
278
279tests = testGroup "ECC"
280    [ testGroup "decodePoint" $ map doPointDecodeTest (zip [katZero..] vectorsPoint)
281    , testGroup "ECDH weak points" $ map doWeakPointECDHTest (zip [katZero..] vectorsWeakPoint)
282    , testGroup "property"
283        [ testProperty "decodePoint.encodePoint==id" $ \testDRG (Curve curve) -> do
284            let prx = Just curve -- using Maybe as Proxy
285                keyPair = withTestDRG testDRG $ ECC.curveGenerateKeyPair prx
286                p1 = ECC.keypairGetPublic keyPair
287                bs = ECC.encodePoint prx p1 :: ByteString
288                p2 = ECC.decodePoint prx bs
289             in CryptoPassed p1 == p2
290        , localOption (QuickCheckTests 20) $ testProperty "ECDH commutes" $ \testDRG (Curve curve) ->
291            let prx = Just curve -- using Maybe as Proxy
292                (alice, bob) = withTestDRG testDRG $
293                                   (,) <$> ECC.curveGenerateKeyPair prx
294                                       <*> ECC.curveGenerateKeyPair prx
295                aliceShared  = ECC.ecdh    prx (ECC.keypairGetPrivate alice) (ECC.keypairGetPublic bob)
296                bobShared    = ECC.ecdh    prx (ECC.keypairGetPrivate bob) (ECC.keypairGetPublic alice)
297                aliceShared' = ECC.ecdhRaw prx (ECC.keypairGetPrivate alice) (ECC.keypairGetPublic bob)
298                bobShared'   = ECC.ecdhRaw prx (ECC.keypairGetPrivate bob) (ECC.keypairGetPublic alice)
299             in aliceShared == bobShared && aliceShared == CryptoPassed aliceShared'
300                                         && bobShared   == CryptoPassed bobShared'
301        ]
302    ]
303