diff --git a/Crypto/Cipher/Types/AEAD.hs b/Crypto/Cipher/Types/AEAD.hs index a6c41ad..2759dfc 100644 --- a/Crypto/Cipher/Types/AEAD.hs +++ b/Crypto/Cipher/Types/AEAD.hs @@ -7,53 +7,58 @@ -- -- AEAD cipher basic types -- +{-# LANGUAGE ExistentialQuantification #-} +{-# LANGUAGE Rank2Types #-} module Crypto.Cipher.Types.AEAD where -import Data.ByteString (ByteString) -import qualified Data.ByteString as B import Crypto.Cipher.Types.Base -import Crypto.Cipher.Types.Block import Crypto.Internal.ByteArray +import Crypto.Internal.Imports --- | Append associated data into the AEAD state -aeadAppendHeader :: BlockCipher a => AEAD a -> ByteString -> AEAD a -aeadAppendHeader (AEAD cipher (AEADState state)) bs = - AEAD cipher $ AEADState (aeadStateAppendHeader cipher state bs) +data AEADModeImpl st = AEADModeImpl + { aeadImplAppendHeader :: forall ba . ByteArrayAccess ba => st -> ba -> st + , aeadImplEncrypt :: forall ba . ByteArray ba => st -> ba -> (ba, st) + , aeadImplDecrypt :: forall ba . ByteArray ba => st -> ba -> (ba, st) + , aeadImplFinalize :: st -> Int -> AuthTag + } --- | Encrypt input and append into the AEAD state -aeadEncrypt :: BlockCipher a => AEAD a -> ByteString -> (ByteString, AEAD a) -aeadEncrypt (AEAD cipher (AEADState state)) input = (output, AEAD cipher (AEADState nst)) - where (output, nst) = aeadStateEncrypt cipher state input +-- | Authenticated Encryption with Associated Data algorithms +data AEAD cipher = forall st . AEAD + { aeadModeImpl :: AEADModeImpl st + , aeadState :: st + } --- | Decrypt input and append into the AEAD state -aeadDecrypt :: BlockCipher a => AEAD a -> ByteString -> (ByteString, AEAD a) -aeadDecrypt (AEAD cipher (AEADState state)) input = (output, AEAD cipher (AEADState nst)) - where (output, nst) = aeadStateDecrypt cipher state input +aeadAppendHeader :: ByteArrayAccess aad => AEAD cipher -> aad -> AEAD cipher +aeadAppendHeader (AEAD impl st) aad = AEAD impl $ (aeadImplAppendHeader impl) st aad --- | Finalize the AEAD state and create an authentification tag -aeadFinalize :: BlockCipher a => AEAD a -> Int -> AuthTag -aeadFinalize (AEAD cipher (AEADState state)) len = - aeadStateFinalize cipher state len +aeadEncrypt :: ByteArray ba => AEAD cipher -> ba -> (ba, AEAD cipher) +aeadEncrypt (AEAD impl st) ba = second (AEAD impl) $ (aeadImplEncrypt impl) st ba + +aeadDecrypt :: ByteArray ba => AEAD cipher -> ba -> (ba, AEAD cipher) +aeadDecrypt (AEAD impl st) ba = second (AEAD impl) $ (aeadImplDecrypt impl) st ba + +aeadFinalize :: AEAD cipher -> Int -> AuthTag +aeadFinalize (AEAD impl st) n = (aeadImplFinalize impl) st n -- | Simple AEAD encryption -aeadSimpleEncrypt :: BlockCipher a +aeadSimpleEncrypt :: (ByteArrayAccess aad, ByteArray ba) => AEAD a -- ^ A new AEAD Context - -> B.ByteString -- ^ Optional Authentified Header - -> B.ByteString -- ^ Optional Plaintext + -> aad -- ^ Optional Authentified Header + -> ba -- ^ Optional Plaintext -> Int -- ^ Tag length - -> (AuthTag, B.ByteString) -- ^ Authentification tag and ciphertext + -> (AuthTag, ba) -- ^ Authentification tag and ciphertext aeadSimpleEncrypt aeadIni header input taglen = (tag, output) where aead = aeadAppendHeader aeadIni header (output, aeadFinal) = aeadEncrypt aead input tag = aeadFinalize aeadFinal taglen -- | Simple AEAD decryption -aeadSimpleDecrypt :: BlockCipher a +aeadSimpleDecrypt :: (ByteArrayAccess aad, ByteArray ba) => AEAD a -- ^ A new AEAD Context - -> B.ByteString -- ^ Optional Authentified Header - -> B.ByteString -- ^ Optional Plaintext + -> aad -- ^ Optional Authentified Header + -> ba -- ^ Optional Plaintext -> AuthTag -- ^ Tag length - -> Maybe B.ByteString -- ^ Plaintext + -> Maybe ba -- ^ Plaintext aeadSimpleDecrypt aeadIni header input authTag | tag == authTag = Just output | otherwise = Nothing diff --git a/Crypto/Cipher/Types/Block.hs b/Crypto/Cipher/Types/Block.hs index 8a8f060..24dad45 100644 --- a/Crypto/Cipher/Types/Block.hs +++ b/Crypto/Cipher/Types/Block.hs @@ -24,8 +24,12 @@ module Crypto.Cipher.Types.Block , XTS -- * AEAD , AEAD(..) - , AEADState(..) + -- , AEADState(..) , AEADModeImpl(..) + , aeadAppendHeader + , aeadEncrypt + , aeadDecrypt + , aeadFinalize -- * CFB 8 bits --, cfb8Encrypt --, cfb8Decrypt @@ -35,8 +39,10 @@ import Data.ByteString (ByteString) import qualified Data.ByteString as B import Data.Byteable import Data.Word +import Crypto.Error import Crypto.Cipher.Types.Base import Crypto.Cipher.Types.GF +import Crypto.Cipher.Types.AEAD import Crypto.Cipher.Types.Utils import Crypto.Internal.ByteArray @@ -110,8 +116,8 @@ class Cipher cipher => BlockCipher cipher where -- | Initialize a new AEAD State -- -- When Nothing is returns, it means the mode is not handled. - aeadInit :: Byteable iv => AEADMode -> cipher -> iv -> Maybe (AEAD cipher) - aeadInit _ _ _ = Nothing + aeadInit :: ByteArrayAccess iv => AEADMode -> cipher -> iv -> CryptoFailable (AEAD cipher) + aeadInit _ _ _ = CryptoFailed CryptoError_AEADModeNotSupported -- | class of block cipher with a 128 bits block size class BlockCipher cipher => BlockCipher128 cipher where @@ -139,19 +145,6 @@ class BlockCipher cipher => BlockCipher128 cipher where -> ba -- ^ Plaintext xtsDecrypt = xtsDecryptGeneric --- | Authenticated Encryption with Associated Data algorithms -data AEAD cipher = AEAD cipher (AEADState cipher) - --- | Wrapper for any AEADState -data AEADState cipher = forall st . AEADModeImpl cipher st => AEADState st - --- | Class of AEAD Mode implementation -class BlockCipher cipher => AEADModeImpl cipher state where - aeadStateAppendHeader :: cipher -> state -> ByteString -> state - aeadStateEncrypt :: cipher -> state -> ByteString -> (ByteString, state) - aeadStateDecrypt :: cipher -> state -> ByteString -> (ByteString, state) - aeadStateFinalize :: cipher -> state -> Int -> AuthTag - -- | Create an IV for a specified block cipher makeIV :: (Byteable b, BlockCipher c) => b -> Maybe (IV c) makeIV b = toIV undefined diff --git a/Crypto/Error/Types.hs b/Crypto/Error/Types.hs index 008bd21..368f5ef 100644 --- a/Crypto/Error/Types.hs +++ b/Crypto/Error/Types.hs @@ -28,6 +28,7 @@ data CryptoError = -- symmetric cipher errors CryptoError_KeySizeInvalid | CryptoError_IvSizeInvalid + | CryptoError_AEADModeNotSupported deriving (Show,Eq,Enum,Data,Typeable) instance E.Exception CryptoError diff --git a/tests/BlockCipher.hs b/tests/BlockCipher.hs index f52f2c7..5ea615a 100644 --- a/tests/BlockCipher.hs +++ b/tests/BlockCipher.hs @@ -57,7 +57,7 @@ data KAT_CFB = KAT_CFB data KAT_CTR = KAT_CTR { ctrKey :: ByteString -- ^ Key , ctrIV :: ByteString -- ^ IV (usually represented as a 128 bits integer) - , ctrPlaintext :: ByteString -- ^ Plaintext + , ctrPlaintext :: ByteString -- ^ Plaintext , ctrCiphertext :: ByteString -- ^ Ciphertext } deriving (Show,Eq) @@ -398,14 +398,16 @@ testBlockCipherAEAD cipher = toTests _ = testProperty_AEAD testProperty_AEAD mode (AEADUnit key testIV (unPlaintext -> aad) (unPlaintext -> plaintext)) = withCtx key $ \ctx -> case aeadInit mode ctx testIV of - Just iniAead -> + CryptoPassed iniAead -> let aead = aeadAppendHeader iniAead aad (eText, aeadE) = aeadEncrypt aead plaintext (dText, aeadD) = aeadDecrypt aead eText eTag = aeadFinalize aeadE (blockSize ctx) dTag = aeadFinalize aeadD (blockSize ctx) in (plaintext `assertEq` dText) && (eTag `byteArrayEq` dTag) - Nothing -> True + CryptoFailed err + | err == CryptoError_AEADModeNotSupported -> True + | otherwise -> error ("testProperty_AEAD: " ++ show err) withCtx :: Cipher c => Key c -> (c -> a) -> a withCtx (Key key) f =