[DES] fix serialization
This commit is contained in:
parent
7a85896359
commit
bc306afc1b
@ -13,7 +13,6 @@ import Data.Word
|
||||
import Crypto.Error
|
||||
import Crypto.Cipher.Types
|
||||
import Crypto.Cipher.DES.Primitive
|
||||
import Crypto.Cipher.DES.Serialization
|
||||
import Crypto.Internal.ByteArray
|
||||
|
||||
-- | DES Context
|
||||
@ -27,8 +26,8 @@ instance Cipher DES where
|
||||
|
||||
instance BlockCipher DES where
|
||||
blockSize _ = 8
|
||||
ecbEncrypt (DES key) = unblockify . map (encrypt key) . blockify
|
||||
ecbDecrypt (DES key) = unblockify . map (decrypt key) . blockify
|
||||
ecbEncrypt (DES key) = byteArrayMapAsWord64 (unBlock . encrypt key . Block)
|
||||
ecbDecrypt (DES key) = byteArrayMapAsWord64 (unBlock . decrypt key . Block)
|
||||
|
||||
initDES :: ByteArray key => key -> CryptoFailable DES
|
||||
initDES k
|
||||
|
||||
@ -16,7 +16,7 @@ module Crypto.Cipher.DES.Primitive (encrypt, decrypt, Block(..)) where
|
||||
import Data.Word
|
||||
import Data.Bits
|
||||
|
||||
newtype Block = Block Word64
|
||||
newtype Block = Block { unBlock :: Word64 }
|
||||
|
||||
type Rotation = Int
|
||||
type Key = Word64
|
||||
|
||||
@ -9,8 +9,6 @@
|
||||
--
|
||||
module Crypto.Cipher.DES.Serialization
|
||||
( toBS
|
||||
, blockify
|
||||
, unblockify
|
||||
) where
|
||||
|
||||
import qualified Data.ByteString as B
|
||||
@ -23,72 +21,5 @@ import Data.Word (Word64)
|
||||
import Foreign.Storable
|
||||
import Foreign.Ptr (castPtr, plusPtr, Ptr)
|
||||
|
||||
{-
|
||||
#ifdef ARCH_IS_LITTLE_ENDIAN
|
||||
-- | convert a 8 byte bytestring big endian to a host one
|
||||
toW64 :: B.ByteString -> Block
|
||||
toW64 b = Block $ B.inlinePerformIO $ withBytePtr b $ \ptr -> (be64 `fmap` peek (castPtr ptr))
|
||||
|
||||
-- | convert a word64 to a bytestring in big endian format
|
||||
toBS :: Block -> B.ByteString
|
||||
toBS (Block w) = B.unsafeCreate 8 $ \ptr -> poke (castPtr ptr) (be64 w)
|
||||
|
||||
-- | Create a strict bytestring out of DES blocks
|
||||
unblockify :: [Block] -> B.ByteString
|
||||
unblockify blocks = B.unsafeCreate (nbBlocks * 8) $ \initPtr -> pokeTo (castPtr initPtr) blocks
|
||||
where nbBlocks = length blocks
|
||||
pokeTo :: Ptr Word64 -> [Block] -> IO ()
|
||||
pokeTo _ [] = return ()
|
||||
pokeTo ptr (Block x:xs) = poke ptr (be64 x) >> pokeTo (ptr `plusPtr` 8) xs
|
||||
|
||||
be64 :: Word64 -> Word64
|
||||
be64 w =
|
||||
(w `shiftR` 56) .|. (w `shiftL` 56)
|
||||
.|. ((w `shiftR` 40) .&. 0xff00) .|. ((w .&. 0xff00) `shiftL` 40)
|
||||
.|. ((w `shiftR` 24) .&. 0xff0000) .|. ((w .&. 0xff0000) `shiftL` 24)
|
||||
.|. ((w `shiftR` 8) .&. 0xff000000) .|. ((w .&. 0xff000000) `shiftL` 8)
|
||||
#else
|
||||
-- | convert a 8 byte bytestring to a little endian word64
|
||||
toW64 :: B.ByteString -> Block
|
||||
toW64 bs = Block $ case B.unpack bs of
|
||||
[a,b,c,d,e,f,g,h] -> shl h 0 .|. shl g 8 .|. shl f 16 .|. shl e 24 .|.
|
||||
shl d 32 .|. shl c 40 .|. shl b 48 .|. shl a 56
|
||||
_ -> 0
|
||||
where shl w n = fromIntegral w `shiftL` n
|
||||
|
||||
-- | convert a word64 to a bytestring in little endian format
|
||||
toBS :: Block -> B.ByteString
|
||||
toBS (Block b) = B.pack $ map (shr b) [56,48,40,32,24,16,8,0]
|
||||
where shr w n = fromIntegral (w `shiftR` n)
|
||||
|
||||
-- | Create a strict bytestring out of DES blocks
|
||||
unblockify :: [Block] -> B.ByteString
|
||||
unblockify = B.concat . map toBS
|
||||
#endif
|
||||
-}
|
||||
|
||||
-- | create DES blocks from a strict bytestring
|
||||
blockify :: ByteArrayAccess ba => ba -> [Block]
|
||||
blockify s
|
||||
| len `mod` 8 /= 0 = error "invalid block"
|
||||
| otherwise = loop 0
|
||||
where
|
||||
len = byteArrayLength s
|
||||
loop i
|
||||
| i == len = []
|
||||
| otherwise = Block (byteArrayToW64BE s i) : loop (i+8)
|
||||
|
||||
unblockify :: ByteArray ba => [Block] -> ba
|
||||
unblockify blocks = byteArrayAllocAndFreeze (nbBlocks * 8) $ \initPtr -> pokeTo (castPtr initPtr) blocks
|
||||
where nbBlocks = length blocks
|
||||
pokeTo :: Ptr Word64 -> [Block] -> IO ()
|
||||
pokeTo _ [] = return ()
|
||||
pokeTo ptr (Block x:xs) = poke ptr (toBE64 x) >> pokeTo (ptr `plusPtr` 8) xs
|
||||
|
||||
toBS :: Block -> B.ByteString
|
||||
toBS (Block w) = byteArrayAllocAndFreeze 8 $ \ptr -> poke ptr (toBE64 w)
|
||||
{-
|
||||
blockify s | B.null s = []
|
||||
| otherwise = let (s1,s2) = B.splitAt 8 s
|
||||
in toW64 s1:blockify s2
|
||||
-}
|
||||
|
||||
@ -13,10 +13,9 @@ module Crypto.Cipher.TripleDES
|
||||
|
||||
import Data.Word
|
||||
import Crypto.Error
|
||||
import Crypto.Internal.ByteArray
|
||||
import Crypto.Cipher.Types
|
||||
import Crypto.Cipher.DES.Serialization
|
||||
import Crypto.Cipher.DES.Primitive
|
||||
import Crypto.Internal.ByteArray
|
||||
|
||||
-- | 3DES with 3 different keys used all in the same direction
|
||||
data DES_EEE3 = DES_EEE3 Word64 Word64 Word64
|
||||
@ -56,23 +55,23 @@ instance Cipher DES_EEE2 where
|
||||
|
||||
instance BlockCipher DES_EEE3 where
|
||||
blockSize _ = 8
|
||||
ecbEncrypt (DES_EEE3 k1 k2 k3) = unblockify . map (encrypt k3 . encrypt k2 . encrypt k1) . blockify
|
||||
ecbDecrypt (DES_EEE3 k1 k2 k3) = unblockify . map (decrypt k1 . decrypt k2 . decrypt k3) . blockify
|
||||
ecbEncrypt (DES_EEE3 k1 k2 k3) = byteArrayMapAsWord64 (unBlock . (encrypt k3 . encrypt k2 . encrypt k1) . Block)
|
||||
ecbDecrypt (DES_EEE3 k1 k2 k3) = byteArrayMapAsWord64 (unBlock . (decrypt k1 . decrypt k2 . decrypt k3) . Block)
|
||||
|
||||
instance BlockCipher DES_EDE3 where
|
||||
blockSize _ = 8
|
||||
ecbEncrypt (DES_EDE3 k1 k2 k3) = unblockify . map (encrypt k3 . decrypt k2 . encrypt k1) . blockify
|
||||
ecbDecrypt (DES_EDE3 k1 k2 k3) = unblockify . map (decrypt k1 . encrypt k2 . decrypt k3) . blockify
|
||||
ecbEncrypt (DES_EDE3 k1 k2 k3) = byteArrayMapAsWord64 (unBlock . (encrypt k3 . decrypt k2 . encrypt k1) . Block)
|
||||
ecbDecrypt (DES_EDE3 k1 k2 k3) = byteArrayMapAsWord64 (unBlock . (decrypt k1 . encrypt k2 . decrypt k3) . Block)
|
||||
|
||||
instance BlockCipher DES_EEE2 where
|
||||
blockSize _ = 8
|
||||
ecbEncrypt (DES_EEE2 k1 k2) = unblockify . map (encrypt k1 . encrypt k2 . encrypt k1) . blockify
|
||||
ecbDecrypt (DES_EEE2 k1 k2) = unblockify . map (decrypt k1 . decrypt k2 . decrypt k1) . blockify
|
||||
ecbEncrypt (DES_EEE2 k1 k2) = byteArrayMapAsWord64 (unBlock . (encrypt k1 . encrypt k2 . encrypt k1) . Block)
|
||||
ecbDecrypt (DES_EEE2 k1 k2) = byteArrayMapAsWord64 (unBlock . (decrypt k1 . decrypt k2 . decrypt k1) . Block)
|
||||
|
||||
instance BlockCipher DES_EDE2 where
|
||||
blockSize _ = 8
|
||||
ecbEncrypt (DES_EDE2 k1 k2) = unblockify . map (encrypt k1 . decrypt k2 . encrypt k1) . blockify
|
||||
ecbDecrypt (DES_EDE2 k1 k2) = unblockify . map (decrypt k1 . encrypt k2 . decrypt k1) . blockify
|
||||
ecbEncrypt (DES_EDE2 k1 k2) = byteArrayMapAsWord64 (unBlock . (encrypt k1 . decrypt k2 . encrypt k1) . Block)
|
||||
ecbDecrypt (DES_EDE2 k1 k2) = byteArrayMapAsWord64 (unBlock . (decrypt k1 . encrypt k2 . decrypt k1) . Block)
|
||||
|
||||
init3DES :: ByteArray key => (Word64 -> Word64 -> Word64 -> a) -> key -> CryptoFailable a
|
||||
init3DES constr k
|
||||
|
||||
@ -25,6 +25,7 @@ module Crypto.Internal.ByteArray
|
||||
, byteArrayFromBS
|
||||
, byteArrayToW64BE
|
||||
, byteArrayToW64LE
|
||||
, byteArrayMapAsWord64
|
||||
, byteArrayMapAsWord128
|
||||
) where
|
||||
|
||||
@ -198,3 +199,17 @@ byteArrayMapAsWord128 f bs =
|
||||
poke d (toBE64 r1)
|
||||
poke (d `plusPtr` 8) (toBE64 r2)
|
||||
loop (i-1) (d `plusPtr` 16) (s `plusPtr` 16)
|
||||
|
||||
byteArrayMapAsWord64 :: ByteArray bs => (Word64 -> Word64) -> bs -> bs
|
||||
byteArrayMapAsWord64 f bs =
|
||||
byteArrayAllocAndFreeze len $ \dst ->
|
||||
withByteArray bs $ \src ->
|
||||
loop (len `div` 8) dst src
|
||||
where
|
||||
len = byteArrayLength bs
|
||||
loop 0 _ _ = return ()
|
||||
loop i d s = do
|
||||
w <- peek s
|
||||
let r = f (fromBE64 w)
|
||||
poke d (toBE64 r)
|
||||
loop (i-1) (d `plusPtr` 8) (s `plusPtr` 8)
|
||||
|
||||
@ -21,6 +21,7 @@ import qualified KAT_Blowfish
|
||||
import qualified KAT_Camellia
|
||||
import qualified KAT_DES
|
||||
import qualified KAT_RC4
|
||||
import qualified KAT_TripleDES
|
||||
import qualified KAT_AFIS
|
||||
|
||||
b8_128_k0_i0 = "\xe2\x8a\x5f\xa4\xa6\x7f\x8c\x5d\xef\xed\x3e\x6f\xb7\x30\x34\x86\xaa\x84\x27\xd3\x14\x19\xa7\x29\x57\x2d\x77\x79\x53\x49\x11\x20\xb6\x4a\xb8\xe7\x2b\x8d\xeb\x85\xcd\x6a\xea\x7c\xb6\x08\x9a\x10\x18\x24\xbe\xeb\x08\x81\x4a\x42\x8a\xab\x1f\xa2\xc8\x16\x08\x1b\x8a\x26\xaf\x44\x8a\x1b\xa9\x06\x36\x8f\xd8\xc8\x38\x31\xc1\x8c\xec\x8c\xed\x81\x1a\x02\x8e\x67\x5b\x8d\x2b\xe8\xfc\xe0\x81\x16\x5c\xea\xe9\xf1\xd1\xb7\xa9\x75\x49\x77\x49\x48\x05\x69\xce\xb8\x3d\xe6\xa0\xa5\x87\xd4\x98\x4f\x19\x92\x5f\x5d\x33\x8e\x43\x0d"
|
||||
@ -83,6 +84,7 @@ tests = testGroup "cryptonite"
|
||||
, KAT_Camellia.tests
|
||||
, KAT_DES.tests
|
||||
, KAT_RC4.tests
|
||||
, KAT_TripleDES.tests
|
||||
, KAT_AFIS.tests
|
||||
]
|
||||
where chachaRunSimple expected rounds klen nonceLen =
|
||||
|
||||
Loading…
Reference in New Issue
Block a user