diff options
author | joe <joe@jerkface.net> | 2017-07-08 22:10:40 -0400 |
---|---|---|
committer | joe <joe@jerkface.net> | 2017-07-08 22:10:40 -0400 |
commit | 8fe93b8e1d1d968bdf0b8a35335b060d92a9d7d7 (patch) | |
tree | 6e9a4b35f11de5ad0e4f422e0a6d268b5270befd /src/Crypto/ECC/Class.hs | |
parent | f75d515bc0100e5ca372d592aa2f5f4ff2fc858c (diff) |
WIP: Tox encryption.
Diffstat (limited to 'src/Crypto/ECC/Class.hs')
-rw-r--r-- | src/Crypto/ECC/Class.hs | 127 |
1 files changed, 127 insertions, 0 deletions
diff --git a/src/Crypto/ECC/Class.hs b/src/Crypto/ECC/Class.hs new file mode 100644 index 00000000..16b2cc15 --- /dev/null +++ b/src/Crypto/ECC/Class.hs | |||
@@ -0,0 +1,127 @@ | |||
1 | -- | | ||
2 | -- Module : Crypto.ECC.Class | ||
3 | -- License : BSD-style | ||
4 | -- Stability : experimental | ||
5 | -- Portability : unknown | ||
6 | -- | ||
7 | -- Elliptic Curve Cryptography | ||
8 | -- | ||
9 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | ||
10 | {-# LANGUAGE TypeFamilies #-} | ||
11 | {-# LANGUAGE ScopedTypeVariables #-} | ||
12 | module Crypto.ECC.Class | ||
13 | ( Curve_X25519(..) | ||
14 | , EllipticCurve(..) | ||
15 | , EllipticCurveDH(..) | ||
16 | , EllipticCurveArith(..) | ||
17 | , KeyPair(..) | ||
18 | , SharedSecret(..) | ||
19 | ) where | ||
20 | |||
21 | import qualified Crypto.ECC.Simple.Types as Simple | ||
22 | import qualified Crypto.ECC.Simple.Prim as Simple | ||
23 | import Crypto.Random | ||
24 | -- import Crypto.Error | ||
25 | import Crypto.Error.Types | ||
26 | -- import Crypto.Internal.Proxy | ||
27 | import Data.Typeable | ||
28 | import Crypto.Internal.ByteArray (ByteArray, ByteArrayAccess, ScrubbedBytes) | ||
29 | import qualified Crypto.Internal.ByteArray as B | ||
30 | import Crypto.Number.Serialize (i2ospOf_, os2ip) | ||
31 | import qualified Crypto.PubKey.Curve25519 as X25519 | ||
32 | import Data.ByteArray (convert) | ||
33 | |||
34 | -- | An elliptic curve key pair composed of the private part (a scalar), and | ||
35 | -- the associated point. | ||
36 | data KeyPair curve = KeyPair | ||
37 | { keypairGetPublic :: !(Point curve) | ||
38 | , keypairGetPrivate :: !(Scalar curve) | ||
39 | } | ||
40 | |||
41 | newtype SharedSecret = SharedSecret ScrubbedBytes | ||
42 | deriving (Eq, ByteArrayAccess) | ||
43 | |||
44 | class EllipticCurve curve where | ||
45 | -- | Point on an Elliptic Curve | ||
46 | type Point curve :: * | ||
47 | |||
48 | -- | Scalar in the Elliptic Curve domain | ||
49 | type Scalar curve :: * | ||
50 | |||
51 | -- | Generate a new random scalar on the curve. | ||
52 | -- The scalar will represent a number between 1 and the order of the curve non included | ||
53 | curveGenerateScalar :: MonadRandom randomly => proxy curve -> randomly (Scalar curve) | ||
54 | |||
55 | -- | Generate a new random keypair | ||
56 | curveGenerateKeyPair :: MonadRandom randomly => proxy curve -> randomly (KeyPair curve) | ||
57 | |||
58 | -- | Get the curve size in bits | ||
59 | curveSizeBits :: proxy curve -> Int | ||
60 | |||
61 | -- | Encode a elliptic curve point into binary form | ||
62 | encodePoint :: ByteArray bs => proxy curve -> Point curve -> bs | ||
63 | |||
64 | -- | Try to decode the binary form of an elliptic curve point | ||
65 | decodePoint :: ByteArray bs => proxy curve -> bs -> CryptoFailable (Point curve) | ||
66 | |||
67 | class EllipticCurve curve => EllipticCurveDH curve where | ||
68 | -- | Generate a Diffie hellman secret value. | ||
69 | -- | ||
70 | -- This is generally just the .x coordinate of the resulting point, that | ||
71 | -- is not hashed. | ||
72 | -- | ||
73 | -- use `pointSmul` to keep the result in Point format. | ||
74 | ecdh :: proxy curve -> Scalar curve -> Point curve -> SharedSecret | ||
75 | |||
76 | class EllipticCurve curve => EllipticCurveArith curve where | ||
77 | -- | Add points on a curve | ||
78 | pointAdd :: proxy curve -> Point curve -> Point curve -> Point curve | ||
79 | |||
80 | -- | Scalar Multiplication on a curve | ||
81 | pointSmul :: proxy curve -> Scalar curve -> Point curve -> Point curve | ||
82 | |||
83 | -- -- | Scalar Inverse | ||
84 | -- scalarInverse :: Scalar curve -> Scalar curve | ||
85 | |||
86 | data Curve_X25519 = Curve_X25519 | ||
87 | |||
88 | instance EllipticCurve Curve_X25519 where | ||
89 | type Point Curve_X25519 = X25519.PublicKey | ||
90 | type Scalar Curve_X25519 = X25519.SecretKey | ||
91 | curveSizeBits _ = 255 | ||
92 | curveGenerateScalar _ = X25519.generateSecretKey | ||
93 | curveGenerateKeyPair _ = do | ||
94 | s <- X25519.generateSecretKey | ||
95 | return $ KeyPair (X25519.toPublic s) s | ||
96 | encodePoint _ p = B.convert p | ||
97 | decodePoint _ bs = X25519.publicKey bs | ||
98 | |||
99 | instance EllipticCurveDH Curve_X25519 where | ||
100 | ecdh _ s p = SharedSecret $ convert secret | ||
101 | where secret = X25519.dh p s | ||
102 | |||
103 | encodeECPoint :: forall curve bs . (Simple.Curve curve, ByteArray bs) => Simple.Point curve -> bs | ||
104 | encodeECPoint Simple.PointO = error "encodeECPoint: cannot serialize point at infinity" | ||
105 | encodeECPoint (Simple.Point x y) = B.concat [uncompressed,xb,yb] | ||
106 | where | ||
107 | size = Simple.curveSizeBytes (Proxy :: Proxy curve) | ||
108 | uncompressed, xb, yb :: bs | ||
109 | uncompressed = B.singleton 4 | ||
110 | xb = i2ospOf_ size x | ||
111 | yb = i2ospOf_ size y | ||
112 | |||
113 | decodeECPoint :: (Simple.Curve curve, ByteArray bs) => bs -> CryptoFailable (Simple.Point curve) | ||
114 | decodeECPoint mxy = case B.uncons mxy of | ||
115 | Nothing -> CryptoFailed $ CryptoError_PointSizeInvalid | ||
116 | Just (m,xy) | ||
117 | -- uncompressed | ||
118 | | m == 4 -> | ||
119 | let siz = B.length xy `div` 2 | ||
120 | (xb,yb) = B.splitAt siz xy | ||
121 | x = os2ip xb | ||
122 | y = os2ip yb | ||
123 | in Simple.pointFromIntegers (x,y) | ||
124 | | otherwise -> CryptoFailed $ CryptoError_PointFormatInvalid | ||
125 | |||
126 | curveSizeBytes :: EllipticCurve c => Proxy c -> Int | ||
127 | curveSizeBytes proxy = (curveSizeBits proxy + 7) `div` 8 | ||