diff --git a/Crypto/Cipher/Types.hs b/Crypto/Cipher/Types.hs index 9a7043f..f200a22 100644 --- a/Crypto/Cipher/Types.hs +++ b/Crypto/Cipher/Types.hs @@ -16,18 +16,14 @@ module Crypto.Cipher.Types , StreamCipher(..) , DataUnitOffset , KeySizeSpecifier(..) - , KeyError(..) , AEAD(..) , AEADState(..) , AEADMode(..) , AEADModeImpl(..) - , cfb8Encrypt - , cfb8Decrypt + -- , cfb8Encrypt + -- , cfb8Decrypt -- * AEAD functions , module Crypto.Cipher.Types.AEAD - -- * Key type and constructor - , Key - , makeKey -- * Initial Vector type and constructor , IV , makeIV @@ -37,24 +33,7 @@ module Crypto.Cipher.Types , AuthTag(..) ) where -import Data.SecureMem -import Data.Byteable import Crypto.Cipher.Types.Base import Crypto.Cipher.Types.Block import Crypto.Cipher.Types.Stream import Crypto.Cipher.Types.AEAD - --- | Create a Key for a specified cipher -makeKey :: (ToSecureMem b, Cipher c) => b -> Either KeyError (Key c) -makeKey b = toKey undefined - where sm = toSecureMem b - smLen = byteableLength sm - toKey :: Cipher c => c -> Either KeyError (Key c) - toKey cipher = case cipherKeySize cipher of - KeySizeRange mi ma | smLen < mi -> Left KeyErrorTooSmall - | smLen > ma -> Left KeyErrorTooBig - | otherwise -> Right $ Key sm - KeySizeEnum l | smLen `elem` l -> Right $ Key sm - | otherwise -> Left $ KeyErrorInvalid ("valid size: " ++ show l) - KeySizeFixed v | smLen == v -> Right $ Key sm - | otherwise -> Left $ KeyErrorInvalid ("valid size: " ++ show v) diff --git a/Crypto/Cipher/Types/Base.hs b/Crypto/Cipher/Types/Base.hs index baa9827..3843a6c 100644 --- a/Crypto/Cipher/Types/Base.hs +++ b/Crypto/Cipher/Types/Base.hs @@ -7,10 +7,9 @@ -- -- symmetric cipher basic types -- +{-# LANGUAGE ExistentialQuantification #-} module Crypto.Cipher.Types.Base - ( KeyError(..) - , KeySizeSpecifier(..) - , Key(..) + ( KeySizeSpecifier(..) , IV(..) , Cipher(..) , AuthTag(..) @@ -23,12 +22,8 @@ import Data.SecureMem import Data.Word import Data.ByteString (ByteString) --- | Possible Error that can be reported when initializating a key -data KeyError = - KeyErrorTooSmall - | KeyErrorTooBig - | KeyErrorInvalid String - deriving (Show,Eq) +import Crypto.Internal.ByteArray +import Crypto.Error -- | Different specifier for key size in bytes data KeySizeSpecifier = @@ -40,19 +35,10 @@ data KeySizeSpecifier = -- | Offset inside an XTS data unit, measured in block size. type DataUnitOffset = Word32 --- | a Key parametrized by the cipher -newtype Key c = Key SecureMem deriving (Eq) - -instance ToSecureMem (Key c) where - toSecureMem (Key sm) = sm -instance Byteable (Key c) where - toBytes (Key sm) = toBytes sm - -- | an IV parametrized by the cipher -newtype IV c = IV ByteString deriving (Eq) +data IV c = forall byteArray . ByteArray byteArray => IV byteArray -instance Byteable (IV c) where - toBytes (IV sm) = sm +instance ByteArray (IV c) where -- | Authentification Tag for AE cipher mode newtype AuthTag = AuthTag ByteString @@ -75,7 +61,7 @@ data AEADMode = -- | Symmetric cipher class. class Cipher cipher where -- | Initialize a cipher context from a key - cipherInit :: Key cipher -> cipher + cipherInit :: ByteArray key => key -> CryptoFailable cipher -- | Cipher name cipherName :: cipher -> String -- | return the size of the key required for this cipher. diff --git a/Crypto/Cipher/Types/Block.hs b/Crypto/Cipher/Types/Block.hs index 2edc20e..20c9c39 100644 --- a/Crypto/Cipher/Types/Block.hs +++ b/Crypto/Cipher/Types/Block.hs @@ -26,8 +26,8 @@ module Crypto.Cipher.Types.Block , AEADState(..) , AEADModeImpl(..) -- * CFB 8 bits - , cfb8Encrypt - , cfb8Decrypt + --, cfb8Encrypt + --, cfb8Decrypt ) where import Data.ByteString (ByteString) @@ -39,6 +39,9 @@ import Data.Bits (shiftR) import Crypto.Cipher.Types.Base import Crypto.Cipher.Types.GF import Crypto.Cipher.Types.Utils + +import Crypto.Internal.ByteArray + import Foreign.Ptr import Foreign.Storable @@ -56,33 +59,33 @@ class Cipher cipher => BlockCipher cipher where -- | Encrypt blocks -- -- the input string need to be multiple of the block size - ecbEncrypt :: cipher -> ByteString -> ByteString + ecbEncrypt :: ByteArray ba => cipher -> ba -> ba -- | Decrypt blocks -- -- the input string need to be multiple of the block size - ecbDecrypt :: cipher -> ByteString -> ByteString + ecbDecrypt :: ByteArray ba => cipher -> ba -> ba -- | encrypt using the CBC mode. -- -- input need to be a multiple of the blocksize - cbcEncrypt :: cipher -> IV cipher -> ByteString -> ByteString + cbcEncrypt :: ByteArray ba => cipher -> IV cipher -> ba -> ba cbcEncrypt = cbcEncryptGeneric -- | decrypt using the CBC mode. -- -- input need to be a multiple of the blocksize - cbcDecrypt :: cipher -> IV cipher -> ByteString -> ByteString + cbcDecrypt :: ByteArray ba => cipher -> IV cipher -> ba -> ba cbcDecrypt = cbcDecryptGeneric -- | encrypt using the CFB mode. -- -- input need to be a multiple of the blocksize - cfbEncrypt :: cipher -> IV cipher -> ByteString -> ByteString + cfbEncrypt :: ByteArray ba => cipher -> IV cipher -> ba -> ba cfbEncrypt = cfbEncryptGeneric -- | decrypt using the CFB mode. -- -- input need to be a multiple of the blocksize - cfbDecrypt :: cipher -> IV cipher -> ByteString -> ByteString + cfbDecrypt :: ByteArray ba => cipher -> IV cipher -> ba -> ba cfbDecrypt = cfbDecryptGeneric -- | combine using the CTR mode. @@ -93,9 +96,17 @@ class Cipher cipher => BlockCipher cipher where -- encryption and decryption are the same operation. -- -- input can be of any size - ctrCombine :: cipher -> IV cipher -> ByteString -> ByteString + ctrCombine :: ByteArray ba => cipher -> IV cipher -> ba -> ba ctrCombine = ctrCombineGeneric + -- | 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 + +-- | class of block cipher with a 128 bits block size +class BlockCipher cipher => BlockCipher128 cipher where -- | encrypt using the XTS mode. -- -- input need to be a multiple of the blocksize, and the cipher @@ -105,7 +116,7 @@ class Cipher cipher => BlockCipher cipher where -> DataUnitOffset -- ^ Offset in the data unit in number of blocks -> ByteString -- ^ Plaintext -> ByteString -- ^ Ciphertext - xtsEncrypt = xtsEncryptGeneric + xtsEncrypt = undefined -- xtsEncryptGeneric -- | decrypt using the XTS mode. -- @@ -116,13 +127,7 @@ class Cipher cipher => BlockCipher cipher where -> DataUnitOffset -- ^ Offset in the data unit in number of blocks -> ByteString -- ^ Ciphertext -> ByteString -- ^ Plaintext - xtsDecrypt = xtsDecryptGeneric - - -- | 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 + xtsDecrypt = undefined -- xtsDecryptGeneric -- | Authenticated Encryption with Associated Data algorithms data AEAD cipher = AEAD cipher (AEADState cipher) @@ -156,6 +161,8 @@ nullIV = toIV undefined -- -- Assume the IV is in Big Endian format. ivAdd :: BlockCipher c => IV c -> Int -> IV c +ivAdd i _ = i +{- ivAdd (IV b) i = IV $ snd $ B.mapAccumR addCarry i b where addCarry :: Int -> Word8 -> (Int, Word8) addCarry acc w @@ -163,49 +170,54 @@ ivAdd (IV b) i = IV $ snd $ B.mapAccumR addCarry i b | otherwise = let (hi,lo) = acc `divMod` 256 nw = lo + (fromIntegral w) in (hi + (nw `shiftR` 8), fromIntegral nw) +-} -cbcEncryptGeneric :: BlockCipher cipher => cipher -> IV cipher -> ByteString -> ByteString -cbcEncryptGeneric cipher (IV ivini) input = B.concat $ doEnc ivini $ chunk (blockSize cipher) input +cbcEncryptGeneric :: (ByteArray ba, BlockCipher cipher) => cipher -> IV cipher -> ba -> ba +cbcEncryptGeneric cipher ivini input = byteArrayConcat $ doEnc ivini $ chunk (blockSize cipher) input where doEnc _ [] = [] doEnc iv (i:is) = - let o = ecbEncrypt cipher $ bxor iv i - in o : doEnc o is + let o = ecbEncrypt cipher $ byteArrayXor iv i + in o : doEnc (IV o) is -cbcDecryptGeneric :: BlockCipher cipher => cipher -> IV cipher -> ByteString -> ByteString -cbcDecryptGeneric cipher (IV ivini) input = B.concat $ doDec ivini $ chunk (blockSize cipher) input - where doDec _ [] = [] +cbcDecryptGeneric :: (ByteArray ba, BlockCipher cipher) => cipher -> IV cipher -> ba -> ba +cbcDecryptGeneric cipher ivini input = byteArrayConcat $ doDec ivini $ chunk (blockSize cipher) input + where + doDec _ [] = [] doDec iv (i:is) = - let o = bxor iv $ ecbDecrypt cipher i - in o : doDec i is + let o = byteArrayXor iv $ ecbDecrypt cipher i + in o : doDec (IV i) is -cfbEncryptGeneric :: BlockCipher cipher => cipher -> IV cipher -> ByteString -> ByteString -cfbEncryptGeneric cipher (IV ivini) input = B.concat $ doEnc ivini $ chunk (blockSize cipher) input - where doEnc _ [] = [] +cfbEncryptGeneric :: (ByteArray ba, BlockCipher cipher) => cipher -> IV cipher -> ba -> ba +cfbEncryptGeneric cipher ivini input = byteArrayConcat $ doEnc ivini $ chunk (blockSize cipher) input + where + doEnc _ [] = [] doEnc iv (i:is) = - let o = bxor i $ ecbEncrypt cipher iv - in o : doEnc o is + let o = byteArrayXor i $ ecbEncrypt cipher iv + in o : doEnc (IV o) is -cfbDecryptGeneric :: BlockCipher cipher => cipher -> IV cipher -> ByteString -> ByteString -cfbDecryptGeneric cipher (IV ivini) input = B.concat $ doDec ivini $ chunk (blockSize cipher) input - where doDec _ [] = [] +cfbDecryptGeneric :: (ByteArray ba, BlockCipher cipher) => cipher -> IV cipher -> ba -> ba +cfbDecryptGeneric cipher ivini input = byteArrayConcat $ doDec ivini $ chunk (blockSize cipher) input + where + doDec _ [] = [] doDec iv (i:is) = - let o = bxor i $ ecbEncrypt cipher iv - in o : doDec i is + let o = byteArrayXor i $ ecbEncrypt cipher iv + in o : doDec (IV i) is -ctrCombineGeneric :: BlockCipher cipher => cipher -> IV cipher -> ByteString -> ByteString -ctrCombineGeneric cipher ivini input = B.concat $ doCnt ivini $ chunk (blockSize cipher) input +ctrCombineGeneric :: (ByteArray ba, BlockCipher cipher) => cipher -> IV cipher -> ba -> ba +ctrCombineGeneric cipher ivini input = byteArrayConcat $ doCnt ivini $ chunk (blockSize cipher) input where doCnt _ [] = [] doCnt iv (i:is) = - let ivEnc = ecbEncrypt cipher (toBytes iv) - in bxor i ivEnc : doCnt (ivAdd iv 1) is + let ivEnc = ecbEncrypt cipher iv + in byteArrayXor i ivEnc : doCnt (ivAdd iv 1) is -xtsEncryptGeneric :: BlockCipher cipher => XTS cipher +{- +xtsEncryptGeneric :: BlockCipher128 cipher => XTS cipher xtsEncryptGeneric = xtsGeneric ecbEncrypt -xtsDecryptGeneric :: BlockCipher cipher => XTS cipher +xtsDecryptGeneric :: BlockCipher128 cipher => XTS cipher xtsDecryptGeneric = xtsGeneric ecbDecrypt -xtsGeneric :: BlockCipher cipher +xtsGeneric :: BlockCipher128 cipher => (cipher -> B.ByteString -> B.ByteString) -> (cipher, cipher) -> IV cipher @@ -214,14 +226,16 @@ xtsGeneric :: BlockCipher cipher -> ByteString xtsGeneric f (cipher, tweakCipher) iv sPoint input | blockSize cipher /= 16 = error "XTS mode is only available with cipher that have a block size of 128 bits" - | otherwise = B.concat $ doXts iniTweak $ chunk (blockSize cipher) input - where encTweak = ecbEncrypt tweakCipher (toBytes iv) + | otherwise = byteArrayConcat $ doXts iniTweak $ chunk (blockSize cipher) input + where encTweak = ecbEncrypt tweakCipher iv iniTweak = iterate xtsGFMul encTweak !! fromIntegral sPoint doXts _ [] = [] doXts tweak (i:is) = let o = bxor (f cipher $ bxor i tweak) tweak in o : doXts (xtsGFMul tweak) is +-} +{- -- | Encrypt using CFB mode in 8 bit output -- -- Effectively turn a Block cipher in CFB mode into a Stream cipher @@ -251,3 +265,4 @@ cfb8Decrypt ctx origIv msg = B.unsafeCreate (B.length msg) $ \dst -> loop dst or r = cfbDecrypt ctx iv m' out = B.head r ni = IV (B.drop 1 i `B.snoc` B.head m') +-} diff --git a/Crypto/Cipher/Types/Utils.hs b/Crypto/Cipher/Types/Utils.hs index 21ddf40..408989a 100644 --- a/Crypto/Cipher/Types/Utils.hs +++ b/Crypto/Cipher/Types/Utils.hs @@ -9,16 +9,11 @@ -- module Crypto.Cipher.Types.Utils where -import Data.Bits (xor) -import Data.ByteString (ByteString) -import qualified Data.ByteString as B +import Crypto.Internal.ByteArray -chunk :: Int -> ByteString -> [ByteString] +chunk :: ByteArray b => Int -> b -> [b] chunk sz bs = split bs - where split b | B.length b <= sz = [b] + where split b | byteArrayLength b <= sz = [b] | otherwise = - let (b1, b2) = B.splitAt sz b + let (b1, b2) = byteArraySplit sz b in b1 : split b2 - -bxor :: ByteString -> ByteString -> ByteString -bxor src dst = B.pack $ B.zipWith xor src dst