diff --git a/Crypto/PubKey/Curve448.hs b/Crypto/PubKey/Curve448.hs new file mode 100644 index 0000000..a9237b1 --- /dev/null +++ b/Crypto/PubKey/Curve448.hs @@ -0,0 +1,108 @@ +-- | +-- Module : Crypto.PubKey.Curve448 +-- License : BSD-style +-- Maintainer : John Galt +-- Stability : experimental +-- Portability : unknown +-- +-- Curve448 support +-- +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{-# LANGUAGE MagicHash #-} +module Crypto.PubKey.Curve448 + ( SecretKey + , PublicKey + , DhSecret + -- * Smart constructors + , dhSecret + , publicKey + , secretKey + -- * methods + , dh + , toPublic + , generateSecretKey + ) where + +import Data.Word +import Foreign.Ptr +import GHC.Ptr + +import Crypto.Error +import Crypto.Random +import Crypto.Internal.Compat +import Crypto.Internal.Imports +import Crypto.Internal.ByteArray (ByteArrayAccess, ScrubbedBytes, Bytes, withByteArray) +import qualified Crypto.Internal.ByteArray as B + +-- | A Curve448 Secret key +newtype SecretKey = SecretKey ScrubbedBytes + deriving (Show,Eq,ByteArrayAccess,NFData) + +-- | A Curve448 public key +newtype PublicKey = PublicKey Bytes + deriving (Show,Eq,ByteArrayAccess,NFData) + +-- | A Curve448 Diffie Hellman secret related to a +-- public key and a secret key. +newtype DhSecret = DhSecret ScrubbedBytes + deriving (Show,Eq,ByteArrayAccess,NFData) + +-- | Try to build a public key from a bytearray +publicKey :: ByteArrayAccess bs => bs -> CryptoFailable PublicKey +publicKey bs + | B.length bs == x448_bytes = CryptoPassed $ PublicKey $ B.copyAndFreeze bs (\_ -> return ()) + | otherwise = CryptoFailed CryptoError_PublicKeySizeInvalid + +-- | Try to build a secret key from a bytearray +secretKey :: ByteArrayAccess bs => bs -> CryptoFailable SecretKey +secretKey bs + | B.length bs == x448_bytes = unsafeDoIO $ + withByteArray bs $ \inp -> do + valid <- isValidPtr inp + if valid + then (CryptoPassed . SecretKey) <$> B.copy bs (\_ -> return ()) + else return $ CryptoFailed CryptoError_SecretKeyStructureInvalid + | otherwise = CryptoFailed CryptoError_SecretKeySizeInvalid + where + isValidPtr :: Ptr Word8 -> IO Bool + isValidPtr _ = + return True +{-# NOINLINE secretKey #-} + +-- | Create a DhSecret from a bytearray object +dhSecret :: ByteArrayAccess b => b -> CryptoFailable DhSecret +dhSecret bs + | B.length bs == x448_bytes = CryptoPassed $ DhSecret $ B.copyAndFreeze bs (\_ -> return ()) + | otherwise = CryptoFailed CryptoError_SharedSecretSizeInvalid + +-- | Compute the Diffie Hellman secret from a public key and a secret key +dh :: PublicKey -> SecretKey -> DhSecret +dh (PublicKey pub) (SecretKey sec) = DhSecret <$> + B.allocAndFreeze x448_bytes $ \result -> + withByteArray sec $ \psec -> + withByteArray pub $ \ppub -> + ccryptonite_ed448 result psec ppub +{-# NOINLINE dh #-} + +-- | Create a public key from a secret key +toPublic :: SecretKey -> PublicKey +toPublic (SecretKey sec) = PublicKey <$> + B.allocAndFreeze x448_bytes $ \result -> + withByteArray sec $ \psec -> + ccryptonite_ed448 result psec basePoint + where + basePoint = Ptr "\x05\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"# +{-# NOINLINE toPublic #-} + +-- | Generate a secret key. +generateSecretKey :: MonadRandom m => m SecretKey +generateSecretKey = SecretKey <$> getRandomBytes x448_bytes + +x448_bytes :: Int +x448_bytes = 448 `quot` 8 + +foreign import ccall "cryptonite_x448" + ccryptonite_ed448 :: Ptr Word8 -- ^ public + -> Ptr Word8 -- ^ secret + -> Ptr Word8 -- ^ basepoint + -> IO () diff --git a/Crypto/PubKey/Ed448.hs b/Crypto/PubKey/Ed448.hs index 33c969a..9efc6a5 100644 --- a/Crypto/PubKey/Ed448.hs +++ b/Crypto/PubKey/Ed448.hs @@ -7,102 +7,14 @@ -- -- Ed448 support -- +-- /Functions and types exported here will be DEPRECATED in a future version./ +-- For Diffie-Hellman over curve448 please use module "Crypto.PubKey.Curve448" +-- instead. +-- {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE MagicHash #-} module Crypto.PubKey.Ed448 - ( SecretKey - , PublicKey - , DhSecret - -- * Smart constructors - , dhSecret - , publicKey - , secretKey - -- * methods - , dh - , toPublic - , generateSecretKey + ( module Crypto.PubKey.Curve448 ) where -import Data.Word -import Foreign.Ptr -import GHC.Ptr - -import Crypto.Error -import Crypto.Random -import Crypto.Internal.Compat -import Crypto.Internal.Imports -import Crypto.Internal.ByteArray (ByteArrayAccess, ScrubbedBytes, Bytes, withByteArray) -import qualified Crypto.Internal.ByteArray as B - --- | A Ed448 Secret key -newtype SecretKey = SecretKey ScrubbedBytes - deriving (Show,Eq,ByteArrayAccess,NFData) - --- | A Ed448 public key -newtype PublicKey = PublicKey Bytes - deriving (Show,Eq,ByteArrayAccess,NFData) - --- | A Ed448 Diffie Hellman secret related to a --- public key and a secret key. -newtype DhSecret = DhSecret ScrubbedBytes - deriving (Show,Eq,ByteArrayAccess,NFData) - --- | Try to build a public key from a bytearray -publicKey :: ByteArrayAccess bs => bs -> CryptoFailable PublicKey -publicKey bs - | B.length bs == x448_bytes = CryptoPassed $ PublicKey $ B.copyAndFreeze bs (\_ -> return ()) - | otherwise = CryptoFailed CryptoError_PublicKeySizeInvalid - --- | Try to build a secret key from a bytearray -secretKey :: ByteArrayAccess bs => bs -> CryptoFailable SecretKey -secretKey bs - | B.length bs == x448_bytes = unsafeDoIO $ - withByteArray bs $ \inp -> do - valid <- isValidPtr inp - if valid - then (CryptoPassed . SecretKey) <$> B.copy bs (\_ -> return ()) - else return $ CryptoFailed CryptoError_SecretKeyStructureInvalid - | otherwise = CryptoFailed CryptoError_SecretKeySizeInvalid - where - isValidPtr :: Ptr Word8 -> IO Bool - isValidPtr _ = - return True -{-# NOINLINE secretKey #-} - --- | Create a DhSecret from a bytearray object -dhSecret :: ByteArrayAccess b => b -> CryptoFailable DhSecret -dhSecret bs - | B.length bs == x448_bytes = CryptoPassed $ DhSecret $ B.copyAndFreeze bs (\_ -> return ()) - | otherwise = CryptoFailed CryptoError_SharedSecretSizeInvalid - --- | Compute the Diffie Hellman secret from a public key and a secret key -dh :: PublicKey -> SecretKey -> DhSecret -dh (PublicKey pub) (SecretKey sec) = DhSecret <$> - B.allocAndFreeze x448_bytes $ \result -> - withByteArray sec $ \psec -> - withByteArray pub $ \ppub -> - ccryptonite_ed448 result psec ppub -{-# NOINLINE dh #-} - --- | Create a public key from a secret key -toPublic :: SecretKey -> PublicKey -toPublic (SecretKey sec) = PublicKey <$> - B.allocAndFreeze x448_bytes $ \result -> - withByteArray sec $ \psec -> - ccryptonite_ed448 result psec basePoint - where - basePoint = Ptr "\x05\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\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00\x00"# -{-# NOINLINE toPublic #-} - --- | Generate a secret key. -generateSecretKey :: MonadRandom m => m SecretKey -generateSecretKey = SecretKey <$> getRandomBytes x448_bytes - -x448_bytes :: Int -x448_bytes = 448 `quot` 8 - -foreign import ccall "cryptonite_x448" - ccryptonite_ed448 :: Ptr Word8 -- ^ public - -> Ptr Word8 -- ^ secret - -> Ptr Word8 -- ^ basepoint - -> IO () +import Crypto.PubKey.Curve448 diff --git a/cryptonite.cabal b/cryptonite.cabal index 6a0d081..2d1d020 100644 --- a/cryptonite.cabal +++ b/cryptonite.cabal @@ -10,7 +10,7 @@ Description: . * MAC: HMAC, Poly1305 . - * Asymmetric crypto: DSA, RSA, DH, ECDH, ECDSA, ECC, Curve25519, Ed25519, Ed448 + * Asymmetric crypto: DSA, RSA, DH, ECDH, ECDSA, ECC, Curve25519, Curve448, Ed25519 . * Key Derivation Function: PBKDF2, Scrypt, HKDF . @@ -126,6 +126,7 @@ Library Crypto.Hash.IO Crypto.Hash.Algorithms Crypto.PubKey.Curve25519 + Crypto.PubKey.Curve448 Crypto.PubKey.MaskGenFunction Crypto.PubKey.DH Crypto.PubKey.DSA @@ -324,8 +325,8 @@ Test-Suite test-cryptonite KAT_Blowfish KAT_Camellia KAT_Curve25519 + KAT_Curve448 KAT_DES - KAT_Ed448 KAT_Ed25519 KAT_CMAC KAT_HKDF diff --git a/tests/KAT_Curve448.hs b/tests/KAT_Curve448.hs new file mode 100644 index 0000000..5f66ac9 --- /dev/null +++ b/tests/KAT_Curve448.hs @@ -0,0 +1,25 @@ +{-# LANGUAGE OverloadedStrings #-} +module KAT_Curve448 ( tests ) where + +import Crypto.Error +import qualified Crypto.PubKey.Ed448 as Curve448 +import Data.ByteArray as B +import Imports + +alicePrivate = throwCryptoError $ Curve448.secretKey ("\x9a\x8f\x49\x25\xd1\x51\x9f\x57\x75\xcf\x46\xb0\x4b\x58\x00\xd4\xee\x9e\xe8\xba\xe8\xbc\x55\x65\xd4\x98\xc2\x8d\xd9\xc9\xba\xf5\x74\xa9\x41\x97\x44\x89\x73\x91\x00\x63\x82\xa6\xf1\x27\xab\x1d\x9a\xc2\xd8\xc0\xa5\x98\x72\x6b" :: ByteString) +alicePublic = throwCryptoError $ Curve448.publicKey ("\x9b\x08\xf7\xcc\x31\xb7\xe3\xe6\x7d\x22\xd5\xae\xa1\x21\x07\x4a\x27\x3b\xd2\xb8\x3d\xe0\x9c\x63\xfa\xa7\x3d\x2c\x22\xc5\xd9\xbb\xc8\x36\x64\x72\x41\xd9\x53\xd4\x0c\x5b\x12\xda\x88\x12\x0d\x53\x17\x7f\x80\xe5\x32\xc4\x1f\xa0" :: ByteString) +bobPrivate = throwCryptoError $ Curve448.secretKey ("\x1c\x30\x6a\x7a\xc2\xa0\xe2\xe0\x99\x0b\x29\x44\x70\xcb\xa3\x39\xe6\x45\x37\x72\xb0\x75\x81\x1d\x8f\xad\x0d\x1d\x69\x27\xc1\x20\xbb\x5e\xe8\x97\x2b\x0d\x3e\x21\x37\x4c\x9c\x92\x1b\x09\xd1\xb0\x36\x6f\x10\xb6\x51\x73\x99\x2d" :: ByteString) +bobPublic = throwCryptoError $ Curve448.publicKey ("\x3e\xb7\xa8\x29\xb0\xcd\x20\xf5\xbc\xfc\x0b\x59\x9b\x6f\xec\xcf\x6d\xa4\x62\x71\x07\xbd\xb0\xd4\xf3\x45\xb4\x30\x27\xd8\xb9\x72\xfc\x3e\x34\xfb\x42\x32\xa1\x3c\xa7\x06\xdc\xb5\x7a\xec\x3d\xae\x07\xbd\xc1\xc6\x7b\xf3\x36\x09" :: ByteString) +aliceMultBob = "\x07\xff\xf4\x18\x1a\xc6\xcc\x95\xec\x1c\x16\xa9\x4a\x0f\x74\xd1\x2d\xa2\x32\xce\x40\xa7\x75\x52\x28\x1d\x28\x2b\xb6\x0c\x0b\x56\xfd\x24\x64\xc3\x35\x54\x39\x36\x52\x1c\x24\x40\x30\x85\xd5\x9a\x44\x9a\x50\x37\x51\x4a\x87\x9d" :: ByteString + +katTests :: [TestTree] +katTests = + [ testCase "0" (aliceMultBob @=? B.convert (Curve448.dh alicePublic bobPrivate)) + , testCase "1" (aliceMultBob @=? B.convert (Curve448.dh bobPublic alicePrivate)) + , testCase "2" (alicePublic @=? Curve448.toPublic alicePrivate) + , testCase "3" (bobPublic @=? Curve448.toPublic bobPrivate) + ] + +tests = testGroup "Curve448" + [ testGroup "KATs" katTests + ] diff --git a/tests/KAT_Ed448.hs b/tests/KAT_Ed448.hs deleted file mode 100644 index cbc8756..0000000 --- a/tests/KAT_Ed448.hs +++ /dev/null @@ -1,25 +0,0 @@ -{-# LANGUAGE OverloadedStrings #-} -module KAT_Ed448 ( tests ) where - -import Crypto.Error -import qualified Crypto.PubKey.Ed448 as Ed448 -import Data.ByteArray as B -import Imports - -alicePrivate = throwCryptoError $ Ed448.secretKey ("\x9a\x8f\x49\x25\xd1\x51\x9f\x57\x75\xcf\x46\xb0\x4b\x58\x00\xd4\xee\x9e\xe8\xba\xe8\xbc\x55\x65\xd4\x98\xc2\x8d\xd9\xc9\xba\xf5\x74\xa9\x41\x97\x44\x89\x73\x91\x00\x63\x82\xa6\xf1\x27\xab\x1d\x9a\xc2\xd8\xc0\xa5\x98\x72\x6b" :: ByteString) -alicePublic = throwCryptoError $ Ed448.publicKey ("\x9b\x08\xf7\xcc\x31\xb7\xe3\xe6\x7d\x22\xd5\xae\xa1\x21\x07\x4a\x27\x3b\xd2\xb8\x3d\xe0\x9c\x63\xfa\xa7\x3d\x2c\x22\xc5\xd9\xbb\xc8\x36\x64\x72\x41\xd9\x53\xd4\x0c\x5b\x12\xda\x88\x12\x0d\x53\x17\x7f\x80\xe5\x32\xc4\x1f\xa0" :: ByteString) -bobPrivate = throwCryptoError $ Ed448.secretKey ("\x1c\x30\x6a\x7a\xc2\xa0\xe2\xe0\x99\x0b\x29\x44\x70\xcb\xa3\x39\xe6\x45\x37\x72\xb0\x75\x81\x1d\x8f\xad\x0d\x1d\x69\x27\xc1\x20\xbb\x5e\xe8\x97\x2b\x0d\x3e\x21\x37\x4c\x9c\x92\x1b\x09\xd1\xb0\x36\x6f\x10\xb6\x51\x73\x99\x2d" :: ByteString) -bobPublic = throwCryptoError $ Ed448.publicKey ("\x3e\xb7\xa8\x29\xb0\xcd\x20\xf5\xbc\xfc\x0b\x59\x9b\x6f\xec\xcf\x6d\xa4\x62\x71\x07\xbd\xb0\xd4\xf3\x45\xb4\x30\x27\xd8\xb9\x72\xfc\x3e\x34\xfb\x42\x32\xa1\x3c\xa7\x06\xdc\xb5\x7a\xec\x3d\xae\x07\xbd\xc1\xc6\x7b\xf3\x36\x09" :: ByteString) -aliceMultBob = "\x07\xff\xf4\x18\x1a\xc6\xcc\x95\xec\x1c\x16\xa9\x4a\x0f\x74\xd1\x2d\xa2\x32\xce\x40\xa7\x75\x52\x28\x1d\x28\x2b\xb6\x0c\x0b\x56\xfd\x24\x64\xc3\x35\x54\x39\x36\x52\x1c\x24\x40\x30\x85\xd5\x9a\x44\x9a\x50\x37\x51\x4a\x87\x9d" :: ByteString - -katTests :: [TestTree] -katTests = - [ testCase "0" (aliceMultBob @=? B.convert (Ed448.dh alicePublic bobPrivate)) - , testCase "1" (aliceMultBob @=? B.convert (Ed448.dh bobPublic alicePrivate)) - , testCase "2" (alicePublic @=? Ed448.toPublic alicePrivate) - , testCase "3" (bobPublic @=? Ed448.toPublic bobPrivate) - ] - -tests = testGroup "Ed448" - [ testGroup "KATs" katTests - ] diff --git a/tests/Tests.hs b/tests/Tests.hs index a576535..5db110b 100644 --- a/tests/Tests.hs +++ b/tests/Tests.hs @@ -18,7 +18,7 @@ import qualified KAT_HMAC import qualified KAT_HKDF import qualified KAT_PBKDF2 import qualified KAT_Curve25519 -import qualified KAT_Ed448 +import qualified KAT_Curve448 import qualified KAT_Ed25519 import qualified KAT_PubKey import qualified KAT_Scrypt @@ -47,7 +47,7 @@ tests = testGroup "cryptonite" , KAT_HMAC.tests ] , KAT_Curve25519.tests - , KAT_Ed448.tests + , KAT_Curve448.tests , KAT_Ed25519.tests , KAT_PubKey.tests , testGroup "KDF"