1-- | 2-- Module : Crypto.PubKey.Ed448 3-- License : BSD-style 4-- Maintainer : Olivier Chéron <olivier.cheron@gmail.com> 5-- Stability : experimental 6-- Portability : unknown 7-- 8-- Ed448 support 9-- 10-- Internally uses Decaf point compression to omit the cofactor 11-- and implementation by Mike Hamburg. Externally API and 12-- data types are compatible with the encoding specified in RFC 8032. 13-- 14{-# LANGUAGE BangPatterns #-} 15{-# LANGUAGE GeneralizedNewtypeDeriving #-} 16module Crypto.PubKey.Ed448 17 ( SecretKey 18 , PublicKey 19 , Signature 20 -- * Size constants 21 , publicKeySize 22 , secretKeySize 23 , signatureSize 24 -- * Smart constructors 25 , signature 26 , publicKey 27 , secretKey 28 -- * Methods 29 , toPublic 30 , sign 31 , verify 32 , generateSecretKey 33 ) where 34 35import Data.Word 36import Foreign.C.Types 37import Foreign.Ptr 38 39import Crypto.Error 40import Crypto.Internal.ByteArray (ByteArrayAccess, Bytes, 41 ScrubbedBytes, withByteArray) 42import qualified Crypto.Internal.ByteArray as B 43import Crypto.Internal.Compat 44import Crypto.Internal.Imports 45import Crypto.Random 46 47-- | An Ed448 Secret key 48newtype SecretKey = SecretKey ScrubbedBytes 49 deriving (Show,Eq,ByteArrayAccess,NFData) 50 51-- | An Ed448 public key 52newtype PublicKey = PublicKey Bytes 53 deriving (Show,Eq,ByteArrayAccess,NFData) 54 55-- | An Ed448 signature 56newtype Signature = Signature Bytes 57 deriving (Show,Eq,ByteArrayAccess,NFData) 58 59-- | Try to build a public key from a bytearray 60publicKey :: ByteArrayAccess ba => ba -> CryptoFailable PublicKey 61publicKey bs 62 | B.length bs == publicKeySize = 63 CryptoPassed $ PublicKey $ B.copyAndFreeze bs (\_ -> return ()) 64 | otherwise = 65 CryptoFailed $ CryptoError_PublicKeySizeInvalid 66 67-- | Try to build a secret key from a bytearray 68secretKey :: ByteArrayAccess ba => ba -> CryptoFailable SecretKey 69secretKey bs 70 | B.length bs == secretKeySize = unsafeDoIO $ withByteArray bs initialize 71 | otherwise = CryptoFailed CryptoError_SecretKeyStructureInvalid 72 where 73 initialize inp = do 74 valid <- isValidPtr inp 75 if valid 76 then (CryptoPassed . SecretKey) <$> B.copy bs (\_ -> return ()) 77 else return $ CryptoFailed CryptoError_SecretKeyStructureInvalid 78 isValidPtr _ = 79 return True 80{-# NOINLINE secretKey #-} 81 82-- | Try to build a signature from a bytearray 83signature :: ByteArrayAccess ba => ba -> CryptoFailable Signature 84signature bs 85 | B.length bs == signatureSize = 86 CryptoPassed $ Signature $ B.copyAndFreeze bs (\_ -> return ()) 87 | otherwise = 88 CryptoFailed CryptoError_SecretKeyStructureInvalid 89 90-- | Create a public key from a secret key 91toPublic :: SecretKey -> PublicKey 92toPublic (SecretKey sec) = PublicKey <$> 93 B.allocAndFreeze publicKeySize $ \result -> 94 withByteArray sec $ \psec -> 95 decaf_ed448_derive_public_key result psec 96{-# NOINLINE toPublic #-} 97 98-- | Sign a message using the key pair 99sign :: ByteArrayAccess ba => SecretKey -> PublicKey -> ba -> Signature 100sign secret public message = 101 Signature $ B.allocAndFreeze signatureSize $ \sig -> 102 withByteArray secret $ \sec -> 103 withByteArray public $ \pub -> 104 withByteArray message $ \msg -> 105 decaf_ed448_sign sig sec pub msg (fromIntegral msgLen) 0 no_context 0 106 where 107 !msgLen = B.length message 108 109-- | Verify a message 110verify :: ByteArrayAccess ba => PublicKey -> ba -> Signature -> Bool 111verify public message signatureVal = unsafeDoIO $ 112 withByteArray signatureVal $ \sig -> 113 withByteArray public $ \pub -> 114 withByteArray message $ \msg -> do 115 r <- decaf_ed448_verify sig pub msg (fromIntegral msgLen) 0 no_context 0 116 return (r /= 0) 117 where 118 !msgLen = B.length message 119 120-- | Generate a secret key 121generateSecretKey :: MonadRandom m => m SecretKey 122generateSecretKey = SecretKey <$> getRandomBytes secretKeySize 123 124-- | A public key is 57 bytes 125publicKeySize :: Int 126publicKeySize = 57 127 128-- | A secret key is 57 bytes 129secretKeySize :: Int 130secretKeySize = 57 131 132-- | A signature is 114 bytes 133signatureSize :: Int 134signatureSize = 114 135 136no_context :: Ptr Word8 137no_context = nullPtr -- not supported yet 138 139foreign import ccall "cryptonite_decaf_ed448_derive_public_key" 140 decaf_ed448_derive_public_key :: Ptr PublicKey -- public key 141 -> Ptr SecretKey -- secret key 142 -> IO () 143 144foreign import ccall "cryptonite_decaf_ed448_sign" 145 decaf_ed448_sign :: Ptr Signature -- signature 146 -> Ptr SecretKey -- secret 147 -> Ptr PublicKey -- public 148 -> Ptr Word8 -- message 149 -> CSize -- message len 150 -> Word8 -- prehashed 151 -> Ptr Word8 -- context 152 -> Word8 -- context len 153 -> IO () 154 155foreign import ccall "cryptonite_decaf_ed448_verify" 156 decaf_ed448_verify :: Ptr Signature -- signature 157 -> Ptr PublicKey -- public 158 -> Ptr Word8 -- message 159 -> CSize -- message len 160 -> Word8 -- prehashed 161 -> Ptr Word8 -- context 162 -> Word8 -- context len 163 -> IO CInt 164