Twofish 192 and 256 bit key support
This commit is contained in:
parent
b658c8a99b
commit
762d818ec0
@ -14,6 +14,7 @@ module Crypto.Cipher.AES
|
||||
|
||||
import Crypto.Error
|
||||
import Crypto.Cipher.Types
|
||||
import Crypto.Cipher.Utils
|
||||
import Crypto.Cipher.Types.Block
|
||||
import Crypto.Cipher.AES.Primitive
|
||||
import Crypto.Internal.Imports
|
||||
@ -47,15 +48,6 @@ instance Cipher AES256 where
|
||||
cipherKeySize _ = KeySizeFixed 32
|
||||
cipherInit k = AES256 <$> (initAES =<< validateKeySize (undefined :: AES256) k)
|
||||
|
||||
validateKeySize :: (ByteArrayAccess key, Cipher cipher) => cipher -> key -> CryptoFailable key
|
||||
validateKeySize c k = if validKeyLength
|
||||
then CryptoPassed k
|
||||
else CryptoFailed CryptoError_KeySizeInvalid
|
||||
where keyLength = BA.length k
|
||||
validKeyLength = case cipherKeySize c of
|
||||
KeySizeRange low high -> keyLength >= low && keyLength <= high
|
||||
KeySizeEnum lengths -> keyLength `elem` lengths
|
||||
KeySizeFixed s -> keyLength == s
|
||||
|
||||
#define INSTANCE_BLOCKCIPHER(CSTR) \
|
||||
instance BlockCipher CSTR where \
|
||||
|
||||
@ -1,18 +1,45 @@
|
||||
module Crypto.Cipher.Twofish
|
||||
( Twofish128
|
||||
, Twofish192
|
||||
, Twofish256
|
||||
) where
|
||||
|
||||
import Crypto.Cipher.Twofish.Primitive
|
||||
import Crypto.Cipher.Types
|
||||
import Crypto.Cipher.Utils
|
||||
|
||||
newtype Twofish128 = Twofish128 Twofish
|
||||
|
||||
instance Cipher Twofish128 where
|
||||
cipherName _ = "Twofish128"
|
||||
cipherKeySize _ = KeySizeFixed 16
|
||||
cipherInit key = Twofish128 `fmap` initTwofish key
|
||||
cipherInit key = Twofish128 <$> (initTwofish =<< validateKeySize (undefined :: Twofish128) key)
|
||||
|
||||
instance BlockCipher Twofish128 where
|
||||
blockSize _ = 16
|
||||
blockSize _ = 16
|
||||
ecbEncrypt (Twofish128 key) = encrypt key
|
||||
ecbDecrypt (Twofish128 key) = decrypt key
|
||||
ecbDecrypt (Twofish128 key) = decrypt key
|
||||
|
||||
newtype Twofish192 = Twofish192 Twofish
|
||||
|
||||
instance Cipher Twofish192 where
|
||||
cipherName _ = "Twofish192"
|
||||
cipherKeySize _ = KeySizeFixed 24
|
||||
cipherInit key = Twofish192 <$> (initTwofish =<< validateKeySize (undefined :: Twofish192) key)
|
||||
|
||||
instance BlockCipher Twofish192 where
|
||||
blockSize _ = 16
|
||||
ecbEncrypt (Twofish192 key) = encrypt key
|
||||
ecbDecrypt (Twofish192 key) = decrypt key
|
||||
|
||||
newtype Twofish256 = Twofish256 Twofish
|
||||
|
||||
instance Cipher Twofish256 where
|
||||
cipherName _ = "Twofish256"
|
||||
cipherKeySize _ = KeySizeFixed 32
|
||||
cipherInit key = Twofish256 <$> (initTwofish =<< validateKeySize (undefined :: Twofish256) key)
|
||||
|
||||
instance BlockCipher Twofish256 where
|
||||
blockSize _ = 16
|
||||
ecbEncrypt (Twofish256 key) = encrypt key
|
||||
ecbDecrypt (Twofish256 key) = decrypt key
|
||||
|
||||
@ -33,19 +33,30 @@ rsPolynomial = 0x14d -- x^8 + x^6 + x^3 + x^2 + 1, see [TWOFISH] 4.3
|
||||
data Twofish = Twofish { s :: (Array32, Array32, Array32, Array32)
|
||||
, k :: Array32 }
|
||||
|
||||
-- | Initialize a 128-bit key
|
||||
data ByteSize = Bytes16 | Bytes24 | Bytes32 deriving (Eq)
|
||||
|
||||
data KeyPackage ba = KeyPackage { rawKeyBytes :: ba
|
||||
, byteSize :: ByteSize }
|
||||
|
||||
buildPackage :: ByteArray ba => ba -> Maybe (KeyPackage ba)
|
||||
buildPackage key
|
||||
| B.length key == 16 = return $ KeyPackage key Bytes16
|
||||
| B.length key == 24 = return $ KeyPackage key Bytes24
|
||||
| B.length key == 32 = return $ KeyPackage key Bytes32
|
||||
| otherwise = Nothing
|
||||
|
||||
-- | Initialize a 128-bit, 192-bit, or 256-bit key
|
||||
--
|
||||
-- Return the initialized key or a error message if the given
|
||||
-- keyseed was not 16-bytes in length.
|
||||
initTwofish :: ByteArray key
|
||||
=> key -- ^ The key to create the camellia context
|
||||
=> key -- ^ The key to create the twofish context
|
||||
-> CryptoFailable Twofish
|
||||
initTwofish key
|
||||
| B.length key /= blockSize = CryptoFailed CryptoError_KeySizeInvalid
|
||||
| otherwise = CryptoPassed Twofish { k = generatedK, s = generatedS }
|
||||
where generatedK = array32 40 $ genK key
|
||||
generatedS = genSboxes $ sWords key
|
||||
|
||||
initTwofish key =
|
||||
case buildPackage key of Nothing -> CryptoFailed CryptoError_KeySizeInvalid
|
||||
Just keyPackage -> CryptoPassed Twofish { k = generatedK, s = generatedS }
|
||||
where generatedK = array32 40 $ genK keyPackage
|
||||
generatedS = genSboxes keyPackage $ sWords key
|
||||
|
||||
mapBlocks :: ByteArray ba => (ba -> ba) -> ba -> ba
|
||||
mapBlocks operation input
|
||||
@ -195,41 +206,79 @@ sWords key = sWord
|
||||
|
||||
data Column = Zero | One | Two | Three deriving (Show, Eq, Enum, Bounded)
|
||||
|
||||
-- Only implemented for 128-bit key (so far)
|
||||
genSboxes :: [Word8] -> (Array32, Array32, Array32, Array32)
|
||||
genSboxes ws = (mkArray b0, mkArray b1, mkArray b2, mkArray b3)
|
||||
genSboxes :: ByteArray ba => KeyPackage ba -> [Word8] -> (Array32, Array32, Array32, Array32)
|
||||
genSboxes keyPackage ws = (mkArray b0', mkArray b1', mkArray b2', mkArray b3')
|
||||
where range = [0..255]
|
||||
mkArray = array32 256
|
||||
[w0, w1, w2, w3, w4, w5, w6, w7] = take 8 ws
|
||||
b0 = fmap mapper range
|
||||
where mapper :: Int -> Word32
|
||||
mapper byte = mdsColumnMult ((sbox1 . fromIntegral) ((sbox0 . fromIntegral $ sbox0 byte `xor` w0) `xor` w4)) Zero
|
||||
b1 = fmap mapper range
|
||||
where mapper byte = mdsColumnMult ((sbox0 . fromIntegral) ((sbox0 . fromIntegral $ sbox1 byte `xor` w1) `xor` w5)) One
|
||||
b2 = fmap mapper range
|
||||
where mapper byte = mdsColumnMult ((sbox1 . fromIntegral) ((sbox1 . fromIntegral $ sbox0 byte `xor` w2) `xor` w6)) Two
|
||||
b3 = fmap mapper range
|
||||
where mapper byte = mdsColumnMult ((sbox0 . fromIntegral) ((sbox1 . fromIntegral $ sbox1 byte `xor` w3) `xor` w7)) Three
|
||||
[w0, w1, w2, w3, w4, w5, w6, w7, w8, w9, w10, w11, w12, w13, w14, w15] = take 16 ws
|
||||
(b0', b1', b2', b3') = sboxBySize $ byteSize keyPackage
|
||||
|
||||
genK :: (ByteArray ba) => ba -> [Word32]
|
||||
genK key = concatMap makeTuple [0..19]
|
||||
sboxBySize :: ByteSize -> ([Word32], [Word32], [Word32], [Word32])
|
||||
sboxBySize Bytes16 = (b0, b1, b2, b3)
|
||||
where !b0 = fmap mapper range
|
||||
where mapper :: Int -> Word32
|
||||
mapper byte = mdsColumnMult ((sbox1 . fromIntegral) ((sbox0 . fromIntegral $ sbox0 byte `xor` w0) `xor` w4)) Zero
|
||||
!b1 = fmap mapper range
|
||||
where mapper byte = mdsColumnMult ((sbox0 . fromIntegral) ((sbox0 . fromIntegral $ sbox1 byte `xor` w1) `xor` w5)) One
|
||||
!b2 = fmap mapper range
|
||||
where mapper byte = mdsColumnMult ((sbox1 . fromIntegral) ((sbox1 . fromIntegral $ sbox0 byte `xor` w2) `xor` w6)) Two
|
||||
!b3 = fmap mapper range
|
||||
where mapper byte = mdsColumnMult ((sbox0 . fromIntegral) ((sbox1 . fromIntegral $ sbox1 byte `xor` w3) `xor` w7)) Three
|
||||
|
||||
sboxBySize Bytes24 = (b0, b1, b2, b3)
|
||||
where !b0 = fmap mapper range
|
||||
where mapper byte = mdsColumnMult ((sbox1 . fromIntegral) ((sbox0 . fromIntegral) ((sbox0 . fromIntegral $ sbox1 byte `xor` w0) `xor` w4) `xor` w8)) Zero
|
||||
!b1 = fmap mapper range
|
||||
where mapper byte = mdsColumnMult ((sbox0 . fromIntegral) ((sbox0 . fromIntegral) ((sbox1 . fromIntegral $ sbox1 byte `xor` w1) `xor` w5) `xor` w9)) One
|
||||
!b2 = fmap mapper range
|
||||
where mapper byte = mdsColumnMult ((sbox1 . fromIntegral) ((sbox1 . fromIntegral) ((sbox0 . fromIntegral $ sbox0 byte `xor` w2) `xor` w6) `xor` w10)) Two
|
||||
!b3 = fmap mapper range
|
||||
where mapper byte = mdsColumnMult ((sbox0 . fromIntegral) ((sbox1 . fromIntegral) ((sbox1 . fromIntegral $ sbox0 byte `xor` w3) `xor` w7) `xor` w11)) Three
|
||||
|
||||
sboxBySize Bytes32 = (b0, b1, b2, b3)
|
||||
where !b0 = fmap mapper range
|
||||
where mapper byte = mdsColumnMult ((sbox1 . fromIntegral) ((sbox0 . fromIntegral) ((sbox0 . fromIntegral) ((sbox1 . fromIntegral $ sbox1 byte `xor` w0) `xor` w4) `xor` w8) `xor` w12)) Zero
|
||||
!b1 = fmap mapper range
|
||||
where mapper byte = mdsColumnMult ((sbox0 . fromIntegral) ((sbox0 . fromIntegral) ((sbox1 . fromIntegral) ((sbox1 . fromIntegral $ sbox0 byte `xor` w1) `xor` w5) `xor` w9) `xor` w13)) One
|
||||
!b2 = fmap mapper range
|
||||
where mapper byte = mdsColumnMult ((sbox1 . fromIntegral) ((sbox1 . fromIntegral) ((sbox0 . fromIntegral) ((sbox0 . fromIntegral $ sbox0 byte `xor` w2) `xor` w6) `xor` w10) `xor` w14)) Two
|
||||
!b3 = fmap mapper range
|
||||
where mapper byte = mdsColumnMult ((sbox0 . fromIntegral) ((sbox1 . fromIntegral) ((sbox1 . fromIntegral) ((sbox0 . fromIntegral $ sbox1 byte `xor` w3) `xor` w7) `xor` w11) `xor` w15)) Three
|
||||
|
||||
genK :: (ByteArray ba) => KeyPackage ba -> [Word32]
|
||||
genK keyPackage = concatMap makeTuple [0..19]
|
||||
where makeTuple :: Word8 -> [Word32]
|
||||
makeTuple idx = [a + b', rotateL (2 * b' + a) 9]
|
||||
where tmp1 = replicate 4 $ 2 * idx
|
||||
tmp2 = fmap (+1) tmp1
|
||||
a = h tmp1 key 0
|
||||
b = h tmp2 key 1
|
||||
a = h tmp1 keyPackage 0
|
||||
b = h tmp2 keyPackage 1
|
||||
b' = rotateL b 8
|
||||
|
||||
h :: (ByteArray ba) => [Word8] -> KeyPackage ba -> Int -> Word32
|
||||
h input keyPackage offset = foldl' xorMdsColMult 0 $ zip [y0f, y1f, y2f, y3f] $ enumFrom Zero
|
||||
where key = rawKeyBytes keyPackage
|
||||
[y0, y1, y2, y3] = take 4 input
|
||||
(!y0f, !y1f, !y2f, !y3f) = run (y0, y1, y2, y3) $ byteSize keyPackage
|
||||
|
||||
-- ONLY implemented for 128-bit key (so far)
|
||||
h :: (ByteArray ba) => [Word8] -> ba -> Int -> Word32
|
||||
h input key offset = foldl' xorMdsColMult 0 $ zip [y0', y1', y2', y3'] $ enumFrom Zero
|
||||
where [y0, y1, y2, y3] = take 4 input
|
||||
y0' = sbox1 . fromIntegral $ (sbox0 . fromIntegral $ (sbox0 (fromIntegral y0) `xor` B.index key (4 * (2 + offset) + 0))) `xor` B.index key (4 * (0 + offset) + 0) :: Word8
|
||||
y1' = sbox0 . fromIntegral $ (sbox0 . fromIntegral $ (sbox1 (fromIntegral y1) `xor` B.index key (4 * (2 + offset) + 1))) `xor` B.index key (4 * (0 + offset) + 1)
|
||||
y2' = sbox1 . fromIntegral $ (sbox1 . fromIntegral $ (sbox0 (fromIntegral y2) `xor` B.index key (4 * (2 + offset) + 2))) `xor` B.index key (4 * (0 + offset) + 2)
|
||||
y3' = sbox0 . fromIntegral $ (sbox1 . fromIntegral $ (sbox1 (fromIntegral y3) `xor` B.index key (4 * (2 + offset) + 3))) `xor` B.index key (4 * (0 + offset) + 3)
|
||||
run :: (Word8, Word8, Word8, Word8) -> ByteSize -> (Word8, Word8, Word8, Word8)
|
||||
run (!y0'', !y1'', !y2'', !y3'') Bytes32 = run (y0', y1', y2', y3') Bytes24
|
||||
where y0' = sbox1 (fromIntegral y0'') `xor` B.index key (4 * (6 + offset) + 0)
|
||||
y1' = sbox0 (fromIntegral y1'') `xor` B.index key (4 * (6 + offset) + 1)
|
||||
y2' = sbox0 (fromIntegral y2'') `xor` B.index key (4 * (6 + offset) + 2)
|
||||
y3' = sbox1 (fromIntegral y3'') `xor` B.index key (4 * (6 + offset) + 3)
|
||||
|
||||
run (!y0'', !y1'', !y2'', !y3'') Bytes24 = run (y0', y1', y2', y3') Bytes16
|
||||
where y0' = sbox1 (fromIntegral y0'') `xor` B.index key (4 * (4 + offset) + 0)
|
||||
y1' = sbox1 (fromIntegral y1'') `xor` B.index key (4 * (4 + offset) + 1)
|
||||
y2' = sbox0 (fromIntegral y2'') `xor` B.index key (4 * (4 + offset) + 2)
|
||||
y3' = sbox0 (fromIntegral y3'') `xor` B.index key (4 * (4 + offset) + 3)
|
||||
|
||||
run (!y0'', !y1'', !y2'', !y3'') Bytes16 = (y0', y1', y2', y3')
|
||||
where y0' = sbox1 . fromIntegral $ (sbox0 . fromIntegral $ (sbox0 (fromIntegral y0'') `xor` B.index key (4 * (2 + offset) + 0))) `xor` B.index key (4 * (0 + offset) + 0)
|
||||
y1' = sbox0 . fromIntegral $ (sbox0 . fromIntegral $ (sbox1 (fromIntegral y1'') `xor` B.index key (4 * (2 + offset) + 1))) `xor` B.index key (4 * (0 + offset) + 1)
|
||||
y2' = sbox1 . fromIntegral $ (sbox1 . fromIntegral $ (sbox0 (fromIntegral y2'') `xor` B.index key (4 * (2 + offset) + 2))) `xor` B.index key (4 * (0 + offset) + 2)
|
||||
y3' = sbox0 . fromIntegral $ (sbox1 . fromIntegral $ (sbox1 (fromIntegral y3'') `xor` B.index key (4 * (2 + offset) + 3))) `xor` B.index key (4 * (0 + offset) + 3)
|
||||
|
||||
xorMdsColMult :: Word32 -> (Word8, Column) -> Word32
|
||||
xorMdsColMult acc wordAndIndex = acc `xor` uncurry mdsColumnMult wordAndIndex
|
||||
|
||||
19
Crypto/Cipher/Utils.hs
Normal file
19
Crypto/Cipher/Utils.hs
Normal file
@ -0,0 +1,19 @@
|
||||
module Crypto.Cipher.Utils
|
||||
( validateKeySize
|
||||
) where
|
||||
|
||||
import Crypto.Error
|
||||
import Crypto.Cipher.Types
|
||||
import Crypto.Internal.Imports
|
||||
|
||||
import Data.ByteArray as BA
|
||||
|
||||
validateKeySize :: (ByteArrayAccess key, Cipher cipher) => cipher -> key -> CryptoFailable key
|
||||
validateKeySize c k = if validKeyLength
|
||||
then CryptoPassed k
|
||||
else CryptoFailed CryptoError_KeySizeInvalid
|
||||
where keyLength = BA.length k
|
||||
validKeyLength = case cipherKeySize c of
|
||||
KeySizeRange low high -> keyLength >= low && keyLength <= high
|
||||
KeySizeEnum lengths -> keyLength `elem` lengths
|
||||
KeySizeFixed s -> keyLength == s
|
||||
@ -110,6 +110,7 @@ Library
|
||||
Crypto.Cipher.TripleDES
|
||||
Crypto.Cipher.Twofish
|
||||
Crypto.Cipher.Types
|
||||
Crypto.Cipher.Utils
|
||||
Crypto.Cipher.XSalsa
|
||||
Crypto.ConstructHash.MiyaguchiPreneel
|
||||
Crypto.Data.AFIS
|
||||
|
||||
@ -14,6 +14,32 @@ vectors_twofish128 =
|
||||
(B.pack [0x01, 0x9F, 0x98, 0x09, 0xDE, 0x17, 0x11, 0x85, 0x8F, 0xAA, 0xC3, 0xA3, 0xBA, 0x20, 0xFB, 0xC3])
|
||||
]
|
||||
|
||||
kats128 = defaultKATs { kat_ECB = vectors_twofish128 }
|
||||
vectors_twofish192 =
|
||||
[ KAT_ECB (B.pack [0x01, 0x23, 0x45, 0x67, 0x89, 0xAB, 0xCD, 0xEF, 0xFE, 0xDC, 0xBA, 0x98, 0x76, 0x54, 0x32, 0x10,
|
||||
0x00, 0x11, 0x22, 0x33, 0x44, 0x55, 0x66, 0x77])
|
||||
(B.pack [0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00])
|
||||
(B.pack [0xCF, 0xD1, 0xD2, 0xE5, 0xA9, 0xBE, 0x9C, 0xDF, 0x50, 0x1F, 0x13, 0xB8, 0x92, 0xBD, 0x22, 0x48])
|
||||
, KAT_ECB (B.pack [0x88, 0xB2, 0xB2, 0x70, 0x6B, 0x10, 0x5E, 0x36, 0xB4, 0x46, 0xBB, 0x6D, 0x73, 0x1A, 0x1E, 0x88,
|
||||
0xEF, 0xA7, 0x1F, 0x78, 0x89, 0x65, 0xBD, 0x44])
|
||||
(B.pack [0x39, 0xDA, 0x69, 0xD6, 0xBA, 0x49, 0x97, 0xD5, 0x85, 0xB6, 0xDC, 0x07, 0x3C, 0xA3, 0x41, 0xB2])
|
||||
(B.pack [0x18, 0x2B, 0x02, 0xD8, 0x14, 0x97, 0xEA, 0x45, 0xF9, 0xDA, 0xAC, 0xDC, 0x29, 0x19, 0x3A, 0x65])]
|
||||
|
||||
vectors_twofish256 =
|
||||
[ KAT_ECB (B.pack [0x01, 0x23, 0x45, 0x67, 0x89, 0xAB, 0xCD, 0xEF, 0xFE, 0xDC, 0xBA, 0x98, 0x76, 0x54, 0x32, 0x10,
|
||||
0x00, 0x11, 0x22, 0x33, 0x44, 0x55, 0x66, 0x77, 0x88, 0x99, 0xAA, 0xBB, 0xCC, 0xDD, 0xEE, 0xFF])
|
||||
(B.pack [0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00, 0x00])
|
||||
(B.pack [0x37, 0x52, 0x7B, 0xE0, 0x05, 0x23, 0x34, 0xB8, 0x9F, 0x0C, 0xFC, 0xCA, 0xE8, 0x7C, 0xFA, 0x20])
|
||||
, KAT_ECB (B.pack [0xD4, 0x3B, 0xB7, 0x55, 0x6E, 0xA3, 0x2E, 0x46, 0xF2, 0xA2, 0x82, 0xB7, 0xD4, 0x5B, 0x4E, 0x0D,
|
||||
0x57, 0xFF, 0x73, 0x9D, 0x4D, 0xC9, 0x2C, 0x1B, 0xD7, 0xFC, 0x01, 0x70, 0x0C, 0xC8, 0x21, 0x6F])
|
||||
(B.pack [0x90, 0xAF, 0xE9, 0x1B, 0xB2, 0x88, 0x54, 0x4F, 0x2C, 0x32, 0xDC, 0x23, 0x9B, 0x26, 0x35, 0xE6])
|
||||
(B.pack [0x6C, 0xB4, 0x56, 0x1C, 0x40, 0xBF, 0x0A, 0x97, 0x05, 0x93, 0x1C, 0xB6, 0xD4, 0x08, 0xE7, 0xFA])]
|
||||
|
||||
kats128 = defaultKATs { kat_ECB = vectors_twofish128 }
|
||||
kats192 = defaultKATs { kat_ECB = vectors_twofish192 }
|
||||
kats256 = defaultKATs { kat_ECB = vectors_twofish256 }
|
||||
|
||||
tests = testGroup "Twofish"
|
||||
[ testBlockCipher kats128 (undefined :: Twofish128)
|
||||
, testBlockCipher kats192 (undefined :: Twofish192)
|
||||
, testBlockCipher kats256 (undefined :: Twofish256) ]
|
||||
|
||||
tests = testBlockCipher kats128 (undefined :: Twofish128)
|
||||
|
||||
Loading…
Reference in New Issue
Block a user