[Blowfish] put all the boxes together so we don't need to concat them
also create the vector in one place when mixing with the key
This commit is contained in:
parent
51cdd1bcd8
commit
a2fb62ffd8
@ -5,13 +5,7 @@
|
||||
-- Portability : Good
|
||||
module Crypto.Cipher.Blowfish.Box
|
||||
( Pbox
|
||||
, Sbox
|
||||
, mkBox
|
||||
, iPbox
|
||||
, iSbox0
|
||||
, iSbox1
|
||||
, iSbox2
|
||||
, iSbox3
|
||||
, boxes
|
||||
) where
|
||||
|
||||
import Data.Bits
|
||||
@ -22,8 +16,6 @@ import qualified Data.Vector as V
|
||||
import qualified Data.ByteString as B
|
||||
|
||||
type Pbox = Vector Word32
|
||||
type Sbox = Vector Word32
|
||||
|
||||
|
||||
mkBox :: [Char] -> Vector Word32
|
||||
mkBox = V.fromList . map decode32be . doChunks 4 id . B.pack . map (fromIntegral . ord)
|
||||
@ -42,17 +34,13 @@ decode32be s = id $!
|
||||
(fromIntegral (s `B.index` 2) `shiftL` 8) .|.
|
||||
(fromIntegral (s `B.index` 3) )
|
||||
|
||||
iPbox :: Pbox
|
||||
iPbox = mkBox "\
|
||||
boxes :: Pbox
|
||||
boxes = mkBox "\
|
||||
\\x24\x3f\x6a\x88\x85\xa3\x08\xd3\x13\x19\x8a\x2e\x03\x70\x73\x44\
|
||||
\\xa4\x09\x38\x22\x29\x9f\x31\xd0\x08\x2e\xfa\x98\xec\x4e\x6c\x89\
|
||||
\\x45\x28\x21\xe6\x38\xd0\x13\x77\xbe\x54\x66\xcf\x34\xe9\x0c\x6c\
|
||||
\\xc0\xac\x29\xb7\xc9\x7c\x50\xdd\x3f\x84\xd5\xb5\xb5\x47\x09\x17\
|
||||
\\x92\x16\xd5\xd9\x89\x79\xfb\x1b\
|
||||
\"
|
||||
|
||||
iSbox0 :: Sbox
|
||||
iSbox0 = mkBox "\
|
||||
\\xd1\x31\x0b\xa6\x98\xdf\xb5\xac\x2f\xfd\x72\xdb\xd0\x1a\xdf\xb7\
|
||||
\\xb8\xe1\xaf\xed\x6a\x26\x7e\x96\xba\x7c\x90\x45\xf1\x2c\x7f\x99\
|
||||
\\x24\xa1\x99\x47\xb3\x91\x6c\xf7\x08\x01\xf2\xe2\x85\x8e\xfc\x16\
|
||||
@ -117,10 +105,6 @@ iSbox0 = mkBox "\
|
||||
\\x08\xba\x6f\xb5\x57\x1b\xe9\x1f\xf2\x96\xec\x6b\x2a\x0d\xd9\x15\
|
||||
\\xb6\x63\x65\x21\xe7\xb9\xf9\xb6\xff\x34\x05\x2e\xc5\x85\x56\x64\
|
||||
\\x53\xb0\x2d\x5d\xa9\x9f\x8f\xa1\x08\xba\x47\x99\x6e\x85\x07\x6a\
|
||||
\"
|
||||
|
||||
iSbox1 :: Sbox
|
||||
iSbox1 = mkBox "\
|
||||
\\x4b\x7a\x70\xe9\xb5\xb3\x29\x44\xdb\x75\x09\x2e\xc4\x19\x26\x23\
|
||||
\\xad\x6e\xa6\xb0\x49\xa7\xdf\x7d\x9c\xee\x60\xb8\x8f\xed\xb2\x66\
|
||||
\\xec\xaa\x8c\x71\x69\x9a\x17\xff\x56\x64\x52\x6c\xc2\xb1\x9e\xe1\
|
||||
@ -185,10 +169,6 @@ iSbox1 = mkBox "\
|
||||
\\xdb\x73\xdb\xd3\x10\x55\x88\xcd\x67\x5f\xda\x79\xe3\x67\x43\x40\
|
||||
\\xc5\xc4\x34\x65\x71\x3e\x38\xd8\x3d\x28\xf8\x9e\xf1\x6d\xff\x20\
|
||||
\\x15\x3e\x21\xe7\x8f\xb0\x3d\x4a\xe6\xe3\x9f\x2b\xdb\x83\xad\xf7\
|
||||
\"
|
||||
|
||||
iSbox2 :: Sbox
|
||||
iSbox2 = mkBox "\
|
||||
\\xe9\x3d\x5a\x68\x94\x81\x40\xf7\xf6\x4c\x26\x1c\x94\x69\x29\x34\
|
||||
\\x41\x15\x20\xf7\x76\x02\xd4\xf7\xbc\xf4\x6b\x2e\xd4\xa2\x00\x68\
|
||||
\\xd4\x08\x24\x71\x33\x20\xf4\x6a\x43\xb7\xd4\xb7\x50\x00\x61\xaf\
|
||||
@ -253,10 +233,6 @@ iSbox2 = mkBox "\
|
||||
\\x1e\x50\xef\x5e\xb1\x61\xe6\xf8\xa2\x85\x14\xd9\x6c\x51\x13\x3c\
|
||||
\\x6f\xd5\xc7\xe7\x56\xe1\x4e\xc4\x36\x2a\xbf\xce\xdd\xc6\xc8\x37\
|
||||
\\xd7\x9a\x32\x34\x92\x63\x82\x12\x67\x0e\xfa\x8e\x40\x60\x00\xe0\
|
||||
\"
|
||||
|
||||
iSbox3 :: Sbox
|
||||
iSbox3 = mkBox "\
|
||||
\\x3a\x39\xce\x37\xd3\xfa\xf5\xcf\xab\xc2\x77\x37\x5a\xc5\x2d\x1b\
|
||||
\\x5c\xb0\x67\x9e\x4f\xa3\x37\x42\xd3\x82\x27\x40\x99\xbc\x9b\xbe\
|
||||
\\xd5\x11\x8e\x9d\xbf\x0f\x73\x15\xd6\x2d\x1c\x7e\xc7\x00\xc4\x7b\
|
||||
|
||||
@ -18,6 +18,7 @@ module Crypto.Cipher.Blowfish.Primitive
|
||||
, decrypt
|
||||
) where
|
||||
|
||||
import Control.Monad (forM_)
|
||||
import Data.Vector (Vector, (!), (//))
|
||||
import qualified Data.Vector as V
|
||||
import qualified Data.Vector.Mutable as V (unsafeRead, unsafeWrite)
|
||||
@ -64,7 +65,7 @@ initBlowfish key
|
||||
keyFromByteString :: B.ByteString -> CryptoFailable Context
|
||||
keyFromByteString k
|
||||
| B.length k /= (18 * 4) = CryptoFailed CryptoError_KeySizeInvalid
|
||||
| otherwise = CryptoPassed . bfMakeKey . w8tow32 . B.unpack $ k
|
||||
| otherwise = CryptoPassed . makeKeySchedule . w8tow32 . B.unpack $ k
|
||||
where
|
||||
w8tow32 :: [Word8] -> [Word32]
|
||||
w8tow32 [] = []
|
||||
@ -95,13 +96,15 @@ coreCrypto (BF p s0 s1 s2 s3) input = doRound input 0
|
||||
d = s3 (fromIntegral $ t .&. 0xff)
|
||||
in fromIntegral (((a + b) `xor` c) + d) `shiftL` 32
|
||||
|
||||
bfMakeKey :: [Word32] -> Context
|
||||
bfMakeKey k = procKey [mixedBox,iSbox0,iSbox1,iSbox2,iSbox3]
|
||||
where mixedBox = V.fromList $ zipWith xor k (map (\i -> iPbox ! i) [0..17])
|
||||
|
||||
procKey :: [Vector Word32] -> Context
|
||||
procKey initialContext =
|
||||
let v = unsafeDoIO (V.unsafeThaw (V.concat initialContext) >>= prepare >>= V.unsafeFreeze)
|
||||
makeKeySchedule :: [Word32] -> Context
|
||||
makeKeySchedule key =
|
||||
let v = unsafeDoIO $ do
|
||||
mv <- V.thaw boxes
|
||||
forM_ (zip key [0..17]) $ \(k, i) ->
|
||||
V.unsafeRead mv i >>= \pVal -> V.unsafeWrite mv i (k `xor` pVal)
|
||||
--mutableArrayWriteXor32 mv i k
|
||||
prepare mv
|
||||
V.unsafeFreeze mv
|
||||
in BF (V.slice 0 18 v !)
|
||||
(V.slice s0 256 v !)
|
||||
(V.slice s1 256 v !)
|
||||
@ -113,7 +116,7 @@ procKey initialContext =
|
||||
s2 = 530
|
||||
s3 = 786
|
||||
|
||||
prepare mctx = loop 0 0 >> return mctx
|
||||
prepare mctx = loop 0 0
|
||||
where loop i input
|
||||
| i == 1042 = return ()
|
||||
| otherwise = do
|
||||
|
||||
Loading…
Reference in New Issue
Block a user