summaryrefslogtreecommitdiff
path: root/cryptonite-backport/Crypto/PubKey
diff options
context:
space:
mode:
authorjoe <joe@jerkface.net>2017-09-15 04:40:28 -0400
committerjoe <joe@jerkface.net>2017-09-15 04:40:28 -0400
commit9605ede14705ef81dde2ff58ecddd66cf3adb13f (patch)
treed708c4088eae04825cbbabd99958ef593560a62b /cryptonite-backport/Crypto/PubKey
parentd830e5d9a18646e8f9fecf4ce74ac0250a3e9021 (diff)
Separated back-ported cryptonite files.
Diffstat (limited to 'cryptonite-backport/Crypto/PubKey')
-rw-r--r--cryptonite-backport/Crypto/PubKey/Curve25519.hs131
1 files changed, 131 insertions, 0 deletions
diff --git a/cryptonite-backport/Crypto/PubKey/Curve25519.hs b/cryptonite-backport/Crypto/PubKey/Curve25519.hs
new file mode 100644
index 00000000..42878691
--- /dev/null
+++ b/cryptonite-backport/Crypto/PubKey/Curve25519.hs
@@ -0,0 +1,131 @@
1-- |
2-- Module : Crypto.PubKey.Curve25519
3-- License : BSD-style
4-- Maintainer : Vincent Hanquez <vincent@snarc.org>
5-- Stability : experimental
6-- Portability : unknown
7--
8-- Curve25519 support
9--
10{-# LANGUAGE GeneralizedNewtypeDeriving #-}
11{-# LANGUAGE MagicHash #-}
12{-# LANGUAGE ScopedTypeVariables #-}
13module Crypto.PubKey.Curve25519
14 ( SecretKey
15 , PublicKey
16 , DhSecret
17 -- * Smart constructors
18 , dhSecret
19 , publicKey
20 , secretKey
21 -- * methods
22 , dh
23 , toPublic
24 , generateSecretKey
25 ) where
26
27import Data.Bits
28import Data.Word
29import Foreign.Ptr
30import Foreign.Storable
31import GHC.Ptr
32
33-- import Crypto.Error
34import Crypto.Error.Types
35import Crypto.Internal.Compat
36import Crypto.Internal.Imports
37import Crypto.Internal.ByteArray (ByteArrayAccess, ByteArray, ScrubbedBytes, Bytes, withByteArray)
38import qualified Crypto.Internal.ByteArray as B
39-- import Crypto.Error (CryptoFailable(..))
40import Crypto.Random
41
42-- | A Curve25519 Secret key
43newtype SecretKey = SecretKey ScrubbedBytes
44 deriving (Show,Eq,ByteArrayAccess,NFData)
45
46-- | A Curve25519 public key
47newtype PublicKey = PublicKey Bytes
48 deriving (Show,Eq,ByteArrayAccess,NFData)
49
50-- | A Curve25519 Diffie Hellman secret related to a
51-- public key and a secret key.
52newtype DhSecret = DhSecret ScrubbedBytes
53 deriving (Show,Eq,ByteArrayAccess,NFData)
54
55-- | Try to build a public key from a bytearray
56publicKey :: ByteArrayAccess bs => bs -> CryptoFailable PublicKey
57publicKey bs
58 | B.length bs == 32 = CryptoPassed $ PublicKey $ B.copyAndFreeze bs (\_ -> return ())
59 | otherwise = CryptoFailed CryptoError_PublicKeySizeInvalid
60
61-- | Try to build a secret key from a bytearray
62secretKey :: ByteArrayAccess bs => bs -> CryptoFailable SecretKey
63secretKey bs
64 | B.length bs == 32 = unsafeDoIO $ do
65 withByteArray bs $ \inp -> do
66 valid <- isValidPtr inp
67 if valid
68 then (CryptoPassed . SecretKey) <$> B.copy bs (\_ -> return ())
69 else return $ CryptoFailed CryptoError_SecretKeyStructureInvalid
70 | otherwise = CryptoFailed CryptoError_SecretKeySizeInvalid
71 where
72 -- e[0] &= 0xf8;
73 -- e[31] &= 0x7f;
74 -- e[31] |= 40;
75 isValidPtr :: Ptr Word8 -> IO Bool
76 isValidPtr _ = do
77 --b0 <- peekElemOff inp 0
78 --b31 <- peekElemOff inp 31
79 return True
80{-
81 return $ and [ testBit b0 0 == False
82 , testBit b0 1 == False
83 , testBit b0 2 == False
84 , testBit b31 7 == False
85 , testBit b31 6 == True
86 ]
87-}
88{-# NOINLINE secretKey #-}
89
90-- | Create a DhSecret from a bytearray object
91dhSecret :: ByteArrayAccess b => b -> CryptoFailable DhSecret
92dhSecret bs
93 | B.length bs == 32 = CryptoPassed $ DhSecret $ B.copyAndFreeze bs (\_ -> return ())
94 | otherwise = CryptoFailed CryptoError_SharedSecretSizeInvalid
95
96-- | Compute the Diffie Hellman secret from a public key and a secret key
97dh :: PublicKey -> SecretKey -> DhSecret
98dh (PublicKey pub) (SecretKey sec) = DhSecret <$>
99 B.allocAndFreeze 32 $ \result ->
100 withByteArray sec $ \psec ->
101 withByteArray pub $ \ppub ->
102 ccryptonite_curve25519 result psec ppub
103{-# NOINLINE dh #-}
104
105-- | Create a public key from a secret key
106toPublic :: SecretKey -> PublicKey
107toPublic (SecretKey sec) = PublicKey <$>
108 B.allocAndFreeze 32 $ \result ->
109 withByteArray sec $ \psec ->
110 ccryptonite_curve25519 result psec basePoint
111 where
112 basePoint = Ptr "\x09\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"#
113{-# NOINLINE toPublic #-}
114
115-- | Generate a secret key.
116generateSecretKey :: MonadRandom m => m SecretKey
117generateSecretKey = tweakToSecretKey <$> getRandomBytes 32
118 where
119 tweakToSecretKey :: ScrubbedBytes -> SecretKey
120 tweakToSecretKey bin = SecretKey $ B.copyAndFreeze bin $ \inp -> do
121 modifyByte inp 0 (\e0 -> e0 .&. 0xf8)
122 modifyByte inp 31 (\e31 -> (e31 .&. 0x7f) .|. 0x40)
123
124 modifyByte :: Ptr Word8 -> Int -> (Word8 -> Word8) -> IO ()
125 modifyByte p n f = peekByteOff p n >>= pokeByteOff p n . f
126
127foreign import ccall "cryptonite_curve25519_donna"
128 ccryptonite_curve25519 :: Ptr Word8 -- ^ public
129 -> Ptr Word8 -- ^ secret
130 -> Ptr Word8 -- ^ basepoint
131 -> IO ()