move core to map over Word64 view of a byte array directly.
this bring a massive speedup and adapt the core blowfish encryption and decryption to work on any bytearray without creating a bytestring.
This commit is contained in:
parent
3b966c0995
commit
a1c21f130c
@ -39,8 +39,8 @@ instance Cipher Blowfish where
|
||||
|
||||
instance BlockCipher Blowfish where
|
||||
blockSize _ = 8
|
||||
ecbEncrypt (Blowfish bf) = ecbEncryptLegacy encrypt bf
|
||||
ecbDecrypt (Blowfish bf) = ecbDecryptLegacy decrypt bf
|
||||
ecbEncrypt (Blowfish bf) = encrypt bf
|
||||
ecbDecrypt (Blowfish bf) = decrypt bf
|
||||
|
||||
#define INSTANCE_CIPHER(CSTR, NAME, KEYSIZE) \
|
||||
instance Cipher CSTR where \
|
||||
|
||||
@ -23,12 +23,13 @@ import qualified Data.ByteString as B
|
||||
|
||||
import Crypto.Error
|
||||
import Crypto.Internal.ByteArray
|
||||
import Crypto.Internal.Words
|
||||
import Crypto.Cipher.Blowfish.Box
|
||||
|
||||
-- | variable keyed blowfish state
|
||||
data Context = BF Pbox Sbox Sbox Sbox Sbox
|
||||
|
||||
encrypt, decrypt :: Context -> B.ByteString -> B.ByteString
|
||||
encrypt, decrypt :: ByteArray ba => Context -> ba -> ba
|
||||
encrypt = cipher . selectEncrypt
|
||||
decrypt = cipher . selectDecrypt
|
||||
|
||||
@ -36,11 +37,11 @@ selectEncrypt, selectDecrypt :: Context -> (Pbox, Context)
|
||||
selectEncrypt x@(BF p _ _ _ _) = (p, x)
|
||||
selectDecrypt x@(BF p _ _ _ _) = (V.reverse p, x)
|
||||
|
||||
cipher :: (Pbox, Context) -> B.ByteString -> B.ByteString
|
||||
cipher :: ByteArray ba => (Pbox, Context) -> ba -> ba
|
||||
cipher (p, bs) b
|
||||
| B.length b == 0 = B.empty
|
||||
| B.length b `mod` 8 /= 0 = error "invalid data length"
|
||||
| otherwise = B.concat $ doChunks 8 (fromW32Pair . coreCrypto p bs . toW32Pair) b
|
||||
| byteArrayLength b == 0 = empty
|
||||
| byteArrayLength b `mod` 8 /= 0 = error "invalid data length"
|
||||
| otherwise = byteArrayMapAsWord64 (coreCrypto p bs) b
|
||||
|
||||
initBlowfish :: ByteArray key => key -> CryptoFailable Context
|
||||
initBlowfish key
|
||||
@ -62,15 +63,16 @@ keyFromByteString k
|
||||
(fromIntegral d) ) : w8tow32 xs
|
||||
w8tow32 _ = error $ "internal error: Crypto.Cipher.Blowfish:keyFromByteString"
|
||||
|
||||
coreCrypto :: Pbox -> Context -> (Word32, Word32) -> (Word32, Word32)
|
||||
coreCrypto p bs i = (\(l,r) -> (r `xor` p!17, l `xor` p!16))
|
||||
$ V.foldl' (doRound bs) i (V.take 16 p)
|
||||
coreCrypto :: Pbox -> Context -> Word64 -> Word64
|
||||
coreCrypto p bs input = (\x -> let (l,r) = w64to32 x in w32to64 (r `xor` p!17, l `xor` p!16))
|
||||
$ V.foldl' (doRound bs) input (V.take 16 p)
|
||||
where
|
||||
doRound :: Context -> (Word32, Word32) -> Word32 -> (Word32, Word32)
|
||||
doRound (BF _ s0 s1 s2 s3) (l,r) pv =
|
||||
doRound :: Context -> Word64 -> Word32 -> Word64
|
||||
doRound (BF _ s0 s1 s2 s3) i pv =
|
||||
let (l,r) = w64to32 i in
|
||||
let newr = l `xor` pv
|
||||
newl = r `xor` (f newr)
|
||||
in (newl, newr)
|
||||
in w32to64 (newl, newr)
|
||||
where
|
||||
f :: Word32 -> Word32
|
||||
f t = let a = s0 ! (fromIntegral $ (t `shiftR` 24) .&. 0xff)
|
||||
@ -80,12 +82,13 @@ coreCrypto p bs i = (\(l,r) -> (r `xor` p!17, l `xor` p!16))
|
||||
in ((a + b) `xor` c) + d
|
||||
|
||||
bfMakeKey :: Vector Word32 -> Context
|
||||
bfMakeKey k = procKey (0,0) (BF (V.zipWith xor k iPbox) iSbox0 iSbox1 iSbox2 iSbox3) 0
|
||||
bfMakeKey k = procKey 0 (BF (V.zipWith xor k iPbox) iSbox0 iSbox1 iSbox2 iSbox3) 0
|
||||
|
||||
procKey :: (Word32, Word32) -> Context -> Int -> Context
|
||||
procKey :: Word64 -> Context -> Int -> Context
|
||||
procKey _ tpbf 1042 = tpbf
|
||||
procKey (l,r) tpbf@(BF p s0 s1 s2 s3) i = procKey (nl,nr) (newbf i) (i+2)
|
||||
where (nl,nr) = coreCrypto p tpbf (l,r)
|
||||
procKey input tpbf@(BF p s0 s1 s2 s3) i = procKey ni (newbf i) (i+2)
|
||||
where ni = coreCrypto p tpbf input
|
||||
(nl,nr) = w64to32 ni
|
||||
newbf x | x < 18 = (BF (p//[(x,nl),(x+1,nr)]) s0 s1 s2 s3)
|
||||
| x < 274 = (BF p (s0//[(x-18,nl),(x-17,nr)]) s1 s2 s3)
|
||||
| x < 530 = (BF p s0 (s1//[(x-274,nl),(x-273,nr)]) s2 s3)
|
||||
@ -93,43 +96,3 @@ procKey (l,r) tpbf@(BF p s0 s1 s2 s3) i = procKey (nl,nr) (newbf i) (i+2)
|
||||
| x < 1042 = (BF p s0 s1 s2 (s3//[(x-786,nl),(x-785,nr)]))
|
||||
| otherwise = error "internal error: Crypto.Cipher.Blowfish:procKey "
|
||||
|
||||
|
||||
doChunks :: Int -> (B.ByteString -> B.ByteString) -> B.ByteString -> [B.ByteString]
|
||||
doChunks n f b =
|
||||
let (x, rest) = B.splitAt n b in
|
||||
if B.length rest >= n
|
||||
then f x : doChunks n f rest
|
||||
else [ f x ]
|
||||
|
||||
toW32Pair :: B.ByteString -> (Word32, Word32)
|
||||
toW32Pair b = let (x1, x2) = B.splitAt 4 b
|
||||
w1 = decode32be x1
|
||||
w2 = decode32be x2
|
||||
in (w1,w2)
|
||||
|
||||
fromW32Pair :: (Word32, Word32) -> B.ByteString
|
||||
fromW32Pair (w1,w2)
|
||||
= let w1' = fromIntegral w1
|
||||
w2' = fromIntegral w2
|
||||
w = (w1' `shiftL` 32) .|. w2'
|
||||
in encode64be w
|
||||
|
||||
decode32be :: B.ByteString -> Word32
|
||||
decode32be s = id $!
|
||||
(fromIntegral (s `B.index` 0) `shiftL` 24) .|.
|
||||
(fromIntegral (s `B.index` 1) `shiftL` 16) .|.
|
||||
(fromIntegral (s `B.index` 2) `shiftL` 8) .|.
|
||||
(fromIntegral (s `B.index` 3) )
|
||||
|
||||
encode64be :: Word64 -> B.ByteString
|
||||
encode64be w = B.pack . map fromIntegral $
|
||||
[ (w `shiftR` 56) .&. 0xff
|
||||
, (w `shiftR` 48) .&. 0xff
|
||||
, (w `shiftR` 40) .&. 0xff
|
||||
, (w `shiftR` 32) .&. 0xff
|
||||
, (w `shiftR` 24) .&. 0xff
|
||||
, (w `shiftR` 16) .&. 0xff
|
||||
, (w `shiftR` 8) .&. 0xff
|
||||
, w .&. 0xff
|
||||
]
|
||||
|
||||
|
||||
Loading…
Reference in New Issue
Block a user