{-# LANGUAGE BangPatterns, MagicHash #-} -- | -- Module : Crypto.Cipher.AES.Haskell -- License : BSD-style -- Maintainer : Vincent Hanquez -- Stability : experimental -- Portability : Good module Crypto.Cipher.AES.Haskell ( Key , IV -- * Basic encryption and decryption , encrypt , decrypt -- * CBC encryption and decryption , encryptCBC , decryptCBC -- * key building mechanism , initKey128 , initKey192 , initKey256 -- * Wrappers for "crypto-api" instances , AES128 , AES192 , AES256 ) where import Data.Word import Data.Vector.Unboxed (Vector) import qualified Data.Vector.Unboxed as V import Data.Bits import Data.ByteString (ByteString) import qualified Data.ByteString as B import qualified Data.ByteString.Unsafe as B import qualified Data.ByteString.Internal as B import GHC.Prim (indexWord8OffAddr#, indexWord32OffAddr#, word2Int#, Addr#, remInt#) import GHC.Word import GHC.Types import Foreign.Ptr import Foreign.Storable import Data.Tagged (Tagged(..)) import Crypto.Classes (BlockCipher(..)) import Data.Serialize (Serialize(..), getByteString, putByteString) import Control.Monad (forM_) import Control.Monad.Primitive import Data.Primitive.ByteArray import System.Endian (getSystemEndianness, Endianness(..)) newtype AES128 = A128 { unA128 :: Key } newtype AES192 = A192 { unA192 :: Key } newtype AES256 = A256 { unA256 :: Key } instance BlockCipher AES128 where blockSize = Tagged 128 encryptBlock = encrypt . unA128 decryptBlock = decrypt . unA128 buildKey b = either (const Nothing) (Just . A128) $ initKey128 b keyLength = Tagged 128 instance BlockCipher AES192 where blockSize = Tagged 128 encryptBlock = encrypt . unA192 decryptBlock = decrypt . unA192 buildKey b = either (const Nothing) (Just . A192) $ initKey192 b keyLength = Tagged 192 instance BlockCipher AES256 where blockSize = Tagged 128 encryptBlock = encrypt . unA256 decryptBlock = decrypt . unA256 buildKey b = either (const Nothing) (Just . A256) $ initKey256 b keyLength = Tagged 256 serializeKey :: Key -> ByteString serializeKey (Key v) | V.length v == 176 = B.pack $ map (V.unsafeIndex v) [0..15] | V.length v == 208 = B.pack $ map (V.unsafeIndex v) [0..23] | otherwise = B.pack $ map (V.unsafeIndex v) [0..31] instance Serialize AES128 where put = putByteString . serializeKey . unA128 get = do raw <- getByteString (128 `div` 8) case buildKey raw of Nothing -> fail "Invalid raw key material." Just k -> return k instance Serialize AES192 where put = putByteString . serializeKey . unA192 get = do raw <- getByteString (192 `div` 8) case buildKey raw of Nothing -> fail "Invalid raw key material." Just k -> return k instance Serialize AES256 where put = putByteString . serializeKey . unA256 get = do raw <- getByteString (256 `div` 8) case buildKey raw of Nothing -> fail "Invalid raw key material." Just k -> return k data Key = Key (Vector Word8) deriving (Show,Eq) type IV = B.ByteString type Block = B.ByteString type AESState = MutableByteArray RealWorld {- | encrypt using CBC mode - IV need to be 16 bytes and the data to encrypt a multiple of 16 bytes -} encryptCBC :: Key -> IV -> B.ByteString -> B.ByteString encryptCBC key iv b | B.length iv /= 16 = error "invalid IV length" | B.length b `mod` 16 /= 0 = error "invalid data length" | otherwise = B.concat $ encryptIter iv (makeChunks b) where encryptIter _ [] = [] encryptIter iv' (x:xs) = let r = coreEncrypt key $ B.pack $ B.zipWith xor iv' x in r : encryptIter r xs {- | encrypt using simple EBC mode -} encrypt :: Key -> B.ByteString -> B.ByteString encrypt key b | B.length b `mod` 16 /= 0 = error "invalid data length" | otherwise = B.concat $ doChunks (coreEncrypt key) b {- | decrypt using CBC mode - IV need to be 16 bytes and the data to decrypt a multiple of 16 bytes -} decryptCBC :: Key -> IV -> B.ByteString -> B.ByteString decryptCBC key iv b | B.length iv /= 16 = error "invalid IV length" | B.length b `mod` 16 /= 0 = error "invalid data length" | otherwise = B.concat $ decryptIter iv (makeChunks b) where decryptIter _ [] = [] decryptIter iv' (x:xs) = let r = B.pack $ B.zipWith xor iv' $ coreDecrypt key x in r : decryptIter x xs {- | decrypt using simple EBC mode -} decrypt :: Key -> B.ByteString -> B.ByteString decrypt key b | B.length b `mod` 16 /= 0 = error "invalid data length" | otherwise = B.concat $ doChunks (coreDecrypt key) b doChunks :: (B.ByteString -> B.ByteString) -> B.ByteString -> [B.ByteString] doChunks f b | B.null b = [] | otherwise = let (x, rest) = B.splitAt 16 b in if B.length rest >= 16 then f x : doChunks f rest else [ f x ] makeChunks :: B.ByteString -> [B.ByteString] makeChunks = doChunks id newAESState :: IO AESState newAESState = newAlignedPinnedByteArray 16 16 coreEncrypt :: Key -> Block -> Block coreEncrypt key input = B.unsafeCreate (B.length input) $ \ptr -> do st <- newAESState swapBlock input st aesMain (getNbr key) key st swapBlockInv st ptr coreDecrypt :: Key -> Block -> Block coreDecrypt key input = B.unsafeCreate (B.length input) $ \ptr -> do st <- newAESState swapBlock input st aesMainInv (getNbr key) key st swapBlockInv st ptr getNbr :: Key -> Int getNbr (Key v) | V.length v == 176 = 10 | V.length v == 208 = 12 | otherwise = 14 initKey128, initKey192, initKey256 :: ByteString -> Either String Key initKey128 = initKey 16 initKey192 = initKey 24 initKey256 = initKey 32 initKey :: Int -> ByteString -> Either String Key initKey sz b | B.length b == sz = Right $ coreExpandKey (V.generate sz $ B.unsafeIndex b) | otherwise = Left "wrong key size" aesMain :: Int -> Key -> AESState -> IO () aesMain nbr key blk = do addRoundKey key 0 blk forM_ [1..nbr-1] $ \i -> do shiftRows blk >> mixColumns blk >> addRoundKey key i blk shiftRows blk >> addRoundKey key nbr blk aesMainInv :: Int -> Key -> AESState -> IO () aesMainInv nbr key blk = do addRoundKey key nbr blk forM_ (reverse [1..nbr-1]) $ \i -> do shiftRowsInv blk >> addRoundKey key i blk >> mixColumnsInv blk shiftRowsInv blk >> addRoundKey key 0 blk {-# INLINE swapIndex #-} swapIndex :: Int -> Int swapIndex 0 = 0 swapIndex 1 = 4 swapIndex 2 = 8 swapIndex 3 = 12 swapIndex 4 = 1 swapIndex 5 = 5 swapIndex 6 = 9 swapIndex 7 = 13 swapIndex 8 = 2 swapIndex 9 = 6 swapIndex 10 = 10 swapIndex 11 = 14 swapIndex 12 = 3 swapIndex 13 = 7 swapIndex 14 = 11 swapIndex 15 = 15 swapIndex _ = 0 coreExpandKey :: Vector Word8 -> Key coreExpandKey vkey | V.length vkey == 16 = Key (V.concat (ek0 : ekN16)) | V.length vkey == 24 = Key (V.concat (ek0 : ekN24)) | V.length vkey == 32 = Key (V.concat (ek0 : ekN32)) | otherwise = Key (V.empty) where ek0 = vkey ekN16 = reverse $ snd $ foldl (generateFold generate16) (ek0, []) [1..10] ekN24 = let (lk, acc) = foldl (generateFold generate24) (ek0, []) [1..7] in let nk = generate16 lk 8 in reverse (nk : acc) ekN32 = let (lk, acc) = foldl (generateFold generate32) (ek0, []) [1..6] in let nk = generate16 lk 7 in reverse (nk : acc) generateFold gen (prevk, accK) it = let nk = gen prevk it in (nk, nk : accK) generate16 prevk it = let len = V.length prevk in let v0 = cR0 it (V.unsafeIndex prevk $ len - 4) (V.unsafeIndex prevk $ len - 3) (V.unsafeIndex prevk $ len - 2) (V.unsafeIndex prevk $ len - 1) in let eg0@(e0,e1,e2,e3) = xorVector prevk 0 v0 in let eg1@(e4,e5,e6,e7) = xorVector prevk 4 eg0 in let eg2@(e8,e9,e10,e11) = xorVector prevk 8 eg1 in let (e12,e13,e14,e15) = xorVector prevk 12 eg2 in V.fromList [e0,e1,e2,e3,e4,e5,e6,e7,e8,e9,e10,e11,e12,e13,e14,e15] generate24 prevk it = let len = V.length prevk in let v0 = cR0 it (V.unsafeIndex prevk $ len - 4) (V.unsafeIndex prevk $ len - 3) (V.unsafeIndex prevk $ len - 2) (V.unsafeIndex prevk $ len - 1) in let eg0@(e0,e1,e2,e3) = xorVector prevk 0 v0 in let eg1@(e4,e5,e6,e7) = xorVector prevk 4 eg0 in let eg2@(e8,e9,e10,e11) = xorVector prevk 8 eg1 in let eg3@(e12,e13,e14,e15) = xorVector prevk 12 eg2 in let eg4@(e16,e17,e18,e19) = xorVector prevk 16 eg3 in let (e20,e21,e22,e23) = xorVector prevk 20 eg4 in V.fromList [e0,e1,e2,e3,e4,e5,e6,e7,e8,e9,e10,e11,e12,e13,e14,e15,e16,e17,e18,e19,e20,e21,e22,e23] generate32 prevk it = let len = V.length prevk in let v0 = cR0 it (V.unsafeIndex prevk $ len - 4) (V.unsafeIndex prevk $ len - 3) (V.unsafeIndex prevk $ len - 2) (V.unsafeIndex prevk $ len - 1) in let eg0@(e0,e1,e2,e3) = xorVector prevk 0 v0 in let eg1@(e4,e5,e6,e7) = xorVector prevk 4 eg0 in let eg2@(e8,e9,e10,e11) = xorVector prevk 8 eg1 in let eg3@(e12,e13,e14,e15) = xorVector prevk 12 eg2 in let eg4@(e16,e17,e18,e19) = xorSboxVector prevk 16 eg3 in let eg5@(e20,e21,e22,e23) = xorVector prevk 20 eg4 in let eg6@(e24,e25,e26,e27) = xorVector prevk 24 eg5 in let (e28,e29,e30,e31) = xorVector prevk 28 eg6 in V.fromList [e0,e1,e2,e3,e4,e5,e6,e7,e8,e9,e10,e11,e12,e13,e14,e15,e16 ,e17,e18,e19,e20,e21,e22,e23,e24,e25,e26,e27,e28,e29,e30,e31] xorVector k i (t0,t1,t2,t3) = ( V.unsafeIndex k (i+0) `xor` t0 , V.unsafeIndex k (i+1) `xor` t1 , V.unsafeIndex k (i+2) `xor` t2 , V.unsafeIndex k (i+3) `xor` t3 ) xorSboxVector k i (t0,t1,t2,t3) = ( V.unsafeIndex k (i+0) `xor` sbox t0 , V.unsafeIndex k (i+1) `xor` sbox t1 , V.unsafeIndex k (i+2) `xor` sbox t2 , V.unsafeIndex k (i+3) `xor` sbox t3 ) cR0 it r0 r1 r2 r3 = (sbox r1 `xor` rcon it, sbox r2, sbox r3, sbox r0) rotateR' :: Word32 -> Int -> Word32 rotateR' = case getSystemEndianness of LittleEndian -> rotateR BigEndian -> rotateL {-# INLINE rotateR' #-} rotateL' :: Word32 -> Int -> Word32 rotateL' = case getSystemEndianness of LittleEndian -> rotateL BigEndian -> rotateR {-# INLINE rotateL' #-} {-# INLINE shiftRows #-} shiftRows :: AESState -> IO () shiftRows blk = do r32 blk 0 >>= w32 blk 0 . msbox32 r32 blk 1 >>= \t1 -> w32 blk 1 $ rotateR' (msbox32 t1) 8 r32 blk 2 >>= \t2 -> w32 blk 2 $ rotateR' (msbox32 t2) 16 r32 blk 3 >>= \t3 -> w32 blk 3 $ rotateR' (msbox32 t3) 24 {-# INLINE addRoundKey #-} addRoundKey :: Key -> Int -> AESState -> IO () addRoundKey (Key key) i blk = forM_ [0..15] $ \n -> do r8 blk n >>= \v1 -> w8 blk n $ v1 `xor` V.unsafeIndex key (16 * i + swapIndex n) {-# INLINE mixColumns #-} mixColumns :: AESState -> IO () mixColumns state = pr 0 >> pr 1 >> pr 2 >> pr 3 where {-# INLINE pr #-} pr i = do cpy0 <- r8 state (0 * 4 + i) cpy1 <- r8 state (1 * 4 + i) cpy2 <- r8 state (2 * 4 + i) cpy3 <- r8 state (3 * 4 + i) let state0 = gm2 cpy0 `xor` gm1 cpy3 `xor` gm1 cpy2 `xor` gm3 cpy1 let state4 = gm2 cpy1 `xor` gm1 cpy0 `xor` gm1 cpy3 `xor` gm3 cpy2 let state8 = gm2 cpy2 `xor` gm1 cpy1 `xor` gm1 cpy0 `xor` gm3 cpy3 let state12 = gm2 cpy3 `xor` gm1 cpy2 `xor` gm1 cpy1 `xor` gm3 cpy0 w8 state (0 * 4 + i) state0 w8 state (1 * 4 + i) state4 w8 state (2 * 4 + i) state8 w8 state (3 * 4 + i) state12 {-# INLINE gm1 #-} gm1 a = a {-# INLINE shiftRowsInv #-} shiftRowsInv :: AESState -> IO () shiftRowsInv blk = do r32 blk 0 >>= w32 blk 0 . mrsbox32 r32 blk 1 >>= \t1 -> w32 blk 1 $ mrsbox32 $ rotateL' t1 8 r32 blk 2 >>= \t2 -> w32 blk 2 $ mrsbox32 $ rotateL' t2 16 r32 blk 3 >>= \t3 -> w32 blk 3 $ mrsbox32 $ rotateL' t3 24 {-# INLINE mixColumnsInv #-} mixColumnsInv :: AESState -> IO () mixColumnsInv state = pr 0 >> pr 1 >> pr 2 >> pr 3 where {-# INLINE pr #-} pr i = do cpy0 <- r8 state (0 * 4 + i) cpy1 <- r8 state (1 * 4 + i) cpy2 <- r8 state (2 * 4 + i) cpy3 <- r8 state (3 * 4 + i) let state0 = gm14 cpy0 `xor` gm9 cpy3 `xor` gm13 cpy2 `xor` gm11 cpy1 let state4 = gm14 cpy1 `xor` gm9 cpy0 `xor` gm13 cpy3 `xor` gm11 cpy2 let state8 = gm14 cpy2 `xor` gm9 cpy1 `xor` gm13 cpy0 `xor` gm11 cpy3 let state12 = gm14 cpy3 `xor` gm9 cpy2 `xor` gm13 cpy1 `xor` gm11 cpy0 w8 state (0 * 4 + i) state0 w8 state (1 * 4 + i) state4 w8 state (2 * 4 + i) state8 w8 state (3 * 4 + i) state12 {-# INLINE r8 #-} r8 :: AESState -> Int -> IO Word8 r8 = readByteArray {-# INLINE w8 #-} w8 :: AESState -> Int -> Word8 -> IO () w8 = writeByteArray {-# INLINE r32 #-} r32 :: AESState -> Int -> IO Word32 r32 = readByteArray {-# INLINE w32 #-} w32 :: AESState -> Int -> Word32 -> IO () w32 = writeByteArray msbox32 :: Word32 -> Word32 msbox32 w = sbox4 a .|. sbox3 b .|. sbox2 c .|. sbox1 d where a = fromIntegral (w `shiftR` 24) b = fromIntegral (w `shiftR` 16) c = fromIntegral (w `shiftR` 8) d = fromIntegral w mrsbox32 :: Word32 -> Word32 mrsbox32 w = fromIntegral (rsbox a) `shiftL` 24 .|. fromIntegral (rsbox b) `shiftL` 16 .|. fromIntegral (rsbox c) `shiftL` 8 .|. fromIntegral (rsbox d) where a = fromIntegral (w `shiftR` 24) b = fromIntegral (w `shiftR` 16) c = fromIntegral (w `shiftR` 8) d = fromIntegral w {-# INLINE swapBlock #-} swapBlock :: ByteString -> AESState -> IO () swapBlock b blk = do -- V.generate 16 (\i -> B.unsafeIndex b $ swapIndex i) forM_ [0..15] $ \i -> w8 blk i $ B.unsafeIndex b $ swapIndex i {-# INLINE swapBlockInv #-} swapBlockInv :: AESState -> Ptr Word8 -> IO () swapBlockInv blk ptr = forM_ [0..15] $ \i -> r8 blk (swapIndex i) >>= pokeByteOff ptr i {-# INLINE sbox #-} sbox :: Word8 -> Word8 sbox (W8# w) = W8# (indexWord8OffAddr# table (word2Int# w)) where !table = "\x63\x7c\x77\x7b\xf2\x6b\x6f\xc5\ \\x30\x01\x67\x2b\xfe\xd7\xab\x76\ \\xca\x82\xc9\x7d\xfa\x59\x47\xf0\ \\xad\xd4\xa2\xaf\x9c\xa4\x72\xc0\ \\xb7\xfd\x93\x26\x36\x3f\xf7\xcc\ \\x34\xa5\xe5\xf1\x71\xd8\x31\x15\ \\x04\xc7\x23\xc3\x18\x96\x05\x9a\ \\x07\x12\x80\xe2\xeb\x27\xb2\x75\ \\x09\x83\x2c\x1a\x1b\x6e\x5a\xa0\ \\x52\x3b\xd6\xb3\x29\xe3\x2f\x84\ \\x53\xd1\x00\xed\x20\xfc\xb1\x5b\ \\x6a\xcb\xbe\x39\x4a\x4c\x58\xcf\ \\xd0\xef\xaa\xfb\x43\x4d\x33\x85\ \\x45\xf9\x02\x7f\x50\x3c\x9f\xa8\ \\x51\xa3\x40\x8f\x92\x9d\x38\xf5\ \\xbc\xb6\xda\x21\x10\xff\xf3\xd2\ \\xcd\x0c\x13\xec\x5f\x97\x44\x17\ \\xc4\xa7\x7e\x3d\x64\x5d\x19\x73\ \\x60\x81\x4f\xdc\x22\x2a\x90\x88\ \\x46\xee\xb8\x14\xde\x5e\x0b\xdb\ \\xe0\x32\x3a\x0a\x49\x06\x24\x5c\ \\xc2\xd3\xac\x62\x91\x95\xe4\x79\ \\xe7\xc8\x37\x6d\x8d\xd5\x4e\xa9\ \\x6c\x56\xf4\xea\x65\x7a\xae\x08\ \\xba\x78\x25\x2e\x1c\xa6\xb4\xc6\ \\xe8\xdd\x74\x1f\x4b\xbd\x8b\x8a\ \\x70\x3e\xb5\x66\x48\x03\xf6\x0e\ \\x61\x35\x57\xb9\x86\xc1\x1d\x9e\ \\xe1\xf8\x98\x11\x69\xd9\x8e\x94\ \\x9b\x1e\x87\xe9\xce\x55\x28\xdf\ \\x8c\xa1\x89\x0d\xbf\xe6\x42\x68\ \\x41\x99\x2d\x0f\xb0\x54\xbb\x16"# {-# INLINE sbox1 #-} {-# INLINE sbox2 #-} {-# INLINE sbox3 #-} {-# INLINE sbox4 #-} sbox1, sbox2, sbox3, sbox4 :: Word8 -> Word32 sbox1 (W8# w) = W32# (indexWord32OffAddr# table (word2Int# w)) where !(Table table) = sbox1Tab sbox2 (W8# w) = W32# (indexWord32OffAddr# table (word2Int# w)) where !(Table table) = sbox2Tab sbox3 (W8# w) = W32# (indexWord32OffAddr# table (word2Int# w)) where !(Table table) = sbox3Tab sbox4 (W8# w) = W32# (indexWord32OffAddr# table (word2Int# w)) where !(Table table) = sbox4Tab sbox1Tab, sbox2Tab, sbox3Tab, sbox4Tab :: Table sbox1Tab = if getSystemEndianness == LittleEndian then sbox_x000 else sbox_000x sbox2Tab = if getSystemEndianness == LittleEndian then sbox_0x00 else sbox_00x0 sbox3Tab = if getSystemEndianness == LittleEndian then sbox_00x0 else sbox_0x00 sbox4Tab = if getSystemEndianness == LittleEndian then sbox_000x else sbox_x000 data Table = Table !Addr# sbox_000x, sbox_00x0, sbox_0x00, sbox_x000 :: Table sbox_000x = Table "\x00\x00\x00\x63\x00\x00\x00\x7c\x00\x00\x00\x77\x00\x00\x00\x7b\ \\x00\x00\x00\xf2\x00\x00\x00\x6b\x00\x00\x00\x6f\x00\x00\x00\xc5\ \\x00\x00\x00\x30\x00\x00\x00\x01\x00\x00\x00\x67\x00\x00\x00\x2b\ \\x00\x00\x00\xfe\x00\x00\x00\xd7\x00\x00\x00\xab\x00\x00\x00\x76\ \\x00\x00\x00\xca\x00\x00\x00\x82\x00\x00\x00\xc9\x00\x00\x00\x7d\ \\x00\x00\x00\xfa\x00\x00\x00\x59\x00\x00\x00\x47\x00\x00\x00\xf0\ \\x00\x00\x00\xad\x00\x00\x00\xd4\x00\x00\x00\xa2\x00\x00\x00\xaf\ \\x00\x00\x00\x9c\x00\x00\x00\xa4\x00\x00\x00\x72\x00\x00\x00\xc0\ \\x00\x00\x00\xb7\x00\x00\x00\xfd\x00\x00\x00\x93\x00\x00\x00\x26\ \\x00\x00\x00\x36\x00\x00\x00\x3f\x00\x00\x00\xf7\x00\x00\x00\xcc\ \\x00\x00\x00\x34\x00\x00\x00\xa5\x00\x00\x00\xe5\x00\x00\x00\xf1\ \\x00\x00\x00\x71\x00\x00\x00\xd8\x00\x00\x00\x31\x00\x00\x00\x15\ \\x00\x00\x00\x04\x00\x00\x00\xc7\x00\x00\x00\x23\x00\x00\x00\xc3\ \\x00\x00\x00\x18\x00\x00\x00\x96\x00\x00\x00\x05\x00\x00\x00\x9a\ \\x00\x00\x00\x07\x00\x00\x00\x12\x00\x00\x00\x80\x00\x00\x00\xe2\ \\x00\x00\x00\xeb\x00\x00\x00\x27\x00\x00\x00\xb2\x00\x00\x00\x75\ \\x00\x00\x00\x09\x00\x00\x00\x83\x00\x00\x00\x2c\x00\x00\x00\x1a\ \\x00\x00\x00\x1b\x00\x00\x00\x6e\x00\x00\x00\x5a\x00\x00\x00\xa0\ \\x00\x00\x00\x52\x00\x00\x00\x3b\x00\x00\x00\xd6\x00\x00\x00\xb3\ \\x00\x00\x00\x29\x00\x00\x00\xe3\x00\x00\x00\x2f\x00\x00\x00\x84\ \\x00\x00\x00\x53\x00\x00\x00\xd1\x00\x00\x00\x00\x00\x00\x00\xed\ \\x00\x00\x00\x20\x00\x00\x00\xfc\x00\x00\x00\xb1\x00\x00\x00\x5b\ \\x00\x00\x00\x6a\x00\x00\x00\xcb\x00\x00\x00\xbe\x00\x00\x00\x39\ \\x00\x00\x00\x4a\x00\x00\x00\x4c\x00\x00\x00\x58\x00\x00\x00\xcf\ \\x00\x00\x00\xd0\x00\x00\x00\xef\x00\x00\x00\xaa\x00\x00\x00\xfb\ \\x00\x00\x00\x43\x00\x00\x00\x4d\x00\x00\x00\x33\x00\x00\x00\x85\ \\x00\x00\x00\x45\x00\x00\x00\xf9\x00\x00\x00\x02\x00\x00\x00\x7f\ \\x00\x00\x00\x50\x00\x00\x00\x3c\x00\x00\x00\x9f\x00\x00\x00\xa8\ \\x00\x00\x00\x51\x00\x00\x00\xa3\x00\x00\x00\x40\x00\x00\x00\x8f\ \\x00\x00\x00\x92\x00\x00\x00\x9d\x00\x00\x00\x38\x00\x00\x00\xf5\ \\x00\x00\x00\xbc\x00\x00\x00\xb6\x00\x00\x00\xda\x00\x00\x00\x21\ \\x00\x00\x00\x10\x00\x00\x00\xff\x00\x00\x00\xf3\x00\x00\x00\xd2\ \\x00\x00\x00\xcd\x00\x00\x00\x0c\x00\x00\x00\x13\x00\x00\x00\xec\ \\x00\x00\x00\x5f\x00\x00\x00\x97\x00\x00\x00\x44\x00\x00\x00\x17\ \\x00\x00\x00\xc4\x00\x00\x00\xa7\x00\x00\x00\x7e\x00\x00\x00\x3d\ \\x00\x00\x00\x64\x00\x00\x00\x5d\x00\x00\x00\x19\x00\x00\x00\x73\ \\x00\x00\x00\x60\x00\x00\x00\x81\x00\x00\x00\x4f\x00\x00\x00\xdc\ \\x00\x00\x00\x22\x00\x00\x00\x2a\x00\x00\x00\x90\x00\x00\x00\x88\ \\x00\x00\x00\x46\x00\x00\x00\xee\x00\x00\x00\xb8\x00\x00\x00\x14\ \\x00\x00\x00\xde\x00\x00\x00\x5e\x00\x00\x00\x0b\x00\x00\x00\xdb\ \\x00\x00\x00\xe0\x00\x00\x00\x32\x00\x00\x00\x3a\x00\x00\x00\x0a\ \\x00\x00\x00\x49\x00\x00\x00\x06\x00\x00\x00\x24\x00\x00\x00\x5c\ \\x00\x00\x00\xc2\x00\x00\x00\xd3\x00\x00\x00\xac\x00\x00\x00\x62\ \\x00\x00\x00\x91\x00\x00\x00\x95\x00\x00\x00\xe4\x00\x00\x00\x79\ \\x00\x00\x00\xe7\x00\x00\x00\xc8\x00\x00\x00\x37\x00\x00\x00\x6d\ \\x00\x00\x00\x8d\x00\x00\x00\xd5\x00\x00\x00\x4e\x00\x00\x00\xa9\ \\x00\x00\x00\x6c\x00\x00\x00\x56\x00\x00\x00\xf4\x00\x00\x00\xea\ \\x00\x00\x00\x65\x00\x00\x00\x7a\x00\x00\x00\xae\x00\x00\x00\x08\ \\x00\x00\x00\xba\x00\x00\x00\x78\x00\x00\x00\x25\x00\x00\x00\x2e\ \\x00\x00\x00\x1c\x00\x00\x00\xa6\x00\x00\x00\xb4\x00\x00\x00\xc6\ \\x00\x00\x00\xe8\x00\x00\x00\xdd\x00\x00\x00\x74\x00\x00\x00\x1f\ \\x00\x00\x00\x4b\x00\x00\x00\xbd\x00\x00\x00\x8b\x00\x00\x00\x8a\ \\x00\x00\x00\x70\x00\x00\x00\x3e\x00\x00\x00\xb5\x00\x00\x00\x66\ \\x00\x00\x00\x48\x00\x00\x00\x03\x00\x00\x00\xf6\x00\x00\x00\x0e\ \\x00\x00\x00\x61\x00\x00\x00\x35\x00\x00\x00\x57\x00\x00\x00\xb9\ \\x00\x00\x00\x86\x00\x00\x00\xc1\x00\x00\x00\x1d\x00\x00\x00\x9e\ \\x00\x00\x00\xe1\x00\x00\x00\xf8\x00\x00\x00\x98\x00\x00\x00\x11\ \\x00\x00\x00\x69\x00\x00\x00\xd9\x00\x00\x00\x8e\x00\x00\x00\x94\ \\x00\x00\x00\x9b\x00\x00\x00\x1e\x00\x00\x00\x87\x00\x00\x00\xe9\ \\x00\x00\x00\xce\x00\x00\x00\x55\x00\x00\x00\x28\x00\x00\x00\xdf\ \\x00\x00\x00\x8c\x00\x00\x00\xa1\x00\x00\x00\x89\x00\x00\x00\x0d\ \\x00\x00\x00\xbf\x00\x00\x00\xe6\x00\x00\x00\x42\x00\x00\x00\x68\ \\x00\x00\x00\x41\x00\x00\x00\x99\x00\x00\x00\x2d\x00\x00\x00\x0f\ \\x00\x00\x00\xb0\x00\x00\x00\x54\x00\x00\x00\xbb\x00\x00\x00\x16"# sbox_00x0 = Table "\x00\x00\x63\x00\x00\x00\x7c\x00\x00\x00\x77\x00\x00\x00\x7b\x00\ \\x00\x00\xf2\x00\x00\x00\x6b\x00\x00\x00\x6f\x00\x00\x00\xc5\x00\ \\x00\x00\x30\x00\x00\x00\x01\x00\x00\x00\x67\x00\x00\x00\x2b\x00\ \\x00\x00\xfe\x00\x00\x00\xd7\x00\x00\x00\xab\x00\x00\x00\x76\x00\ \\x00\x00\xca\x00\x00\x00\x82\x00\x00\x00\xc9\x00\x00\x00\x7d\x00\ \\x00\x00\xfa\x00\x00\x00\x59\x00\x00\x00\x47\x00\x00\x00\xf0\x00\ \\x00\x00\xad\x00\x00\x00\xd4\x00\x00\x00\xa2\x00\x00\x00\xaf\x00\ \\x00\x00\x9c\x00\x00\x00\xa4\x00\x00\x00\x72\x00\x00\x00\xc0\x00\ \\x00\x00\xb7\x00\x00\x00\xfd\x00\x00\x00\x93\x00\x00\x00\x26\x00\ \\x00\x00\x36\x00\x00\x00\x3f\x00\x00\x00\xf7\x00\x00\x00\xcc\x00\ \\x00\x00\x34\x00\x00\x00\xa5\x00\x00\x00\xe5\x00\x00\x00\xf1\x00\ \\x00\x00\x71\x00\x00\x00\xd8\x00\x00\x00\x31\x00\x00\x00\x15\x00\ \\x00\x00\x04\x00\x00\x00\xc7\x00\x00\x00\x23\x00\x00\x00\xc3\x00\ \\x00\x00\x18\x00\x00\x00\x96\x00\x00\x00\x05\x00\x00\x00\x9a\x00\ \\x00\x00\x07\x00\x00\x00\x12\x00\x00\x00\x80\x00\x00\x00\xe2\x00\ \\x00\x00\xeb\x00\x00\x00\x27\x00\x00\x00\xb2\x00\x00\x00\x75\x00\ \\x00\x00\x09\x00\x00\x00\x83\x00\x00\x00\x2c\x00\x00\x00\x1a\x00\ \\x00\x00\x1b\x00\x00\x00\x6e\x00\x00\x00\x5a\x00\x00\x00\xa0\x00\ \\x00\x00\x52\x00\x00\x00\x3b\x00\x00\x00\xd6\x00\x00\x00\xb3\x00\ \\x00\x00\x29\x00\x00\x00\xe3\x00\x00\x00\x2f\x00\x00\x00\x84\x00\ \\x00\x00\x53\x00\x00\x00\xd1\x00\x00\x00\x00\x00\x00\x00\xed\x00\ \\x00\x00\x20\x00\x00\x00\xfc\x00\x00\x00\xb1\x00\x00\x00\x5b\x00\ \\x00\x00\x6a\x00\x00\x00\xcb\x00\x00\x00\xbe\x00\x00\x00\x39\x00\ \\x00\x00\x4a\x00\x00\x00\x4c\x00\x00\x00\x58\x00\x00\x00\xcf\x00\ \\x00\x00\xd0\x00\x00\x00\xef\x00\x00\x00\xaa\x00\x00\x00\xfb\x00\ \\x00\x00\x43\x00\x00\x00\x4d\x00\x00\x00\x33\x00\x00\x00\x85\x00\ \\x00\x00\x45\x00\x00\x00\xf9\x00\x00\x00\x02\x00\x00\x00\x7f\x00\ \\x00\x00\x50\x00\x00\x00\x3c\x00\x00\x00\x9f\x00\x00\x00\xa8\x00\ \\x00\x00\x51\x00\x00\x00\xa3\x00\x00\x00\x40\x00\x00\x00\x8f\x00\ \\x00\x00\x92\x00\x00\x00\x9d\x00\x00\x00\x38\x00\x00\x00\xf5\x00\ \\x00\x00\xbc\x00\x00\x00\xb6\x00\x00\x00\xda\x00\x00\x00\x21\x00\ \\x00\x00\x10\x00\x00\x00\xff\x00\x00\x00\xf3\x00\x00\x00\xd2\x00\ \\x00\x00\xcd\x00\x00\x00\x0c\x00\x00\x00\x13\x00\x00\x00\xec\x00\ \\x00\x00\x5f\x00\x00\x00\x97\x00\x00\x00\x44\x00\x00\x00\x17\x00\ \\x00\x00\xc4\x00\x00\x00\xa7\x00\x00\x00\x7e\x00\x00\x00\x3d\x00\ \\x00\x00\x64\x00\x00\x00\x5d\x00\x00\x00\x19\x00\x00\x00\x73\x00\ \\x00\x00\x60\x00\x00\x00\x81\x00\x00\x00\x4f\x00\x00\x00\xdc\x00\ \\x00\x00\x22\x00\x00\x00\x2a\x00\x00\x00\x90\x00\x00\x00\x88\x00\ \\x00\x00\x46\x00\x00\x00\xee\x00\x00\x00\xb8\x00\x00\x00\x14\x00\ \\x00\x00\xde\x00\x00\x00\x5e\x00\x00\x00\x0b\x00\x00\x00\xdb\x00\ \\x00\x00\xe0\x00\x00\x00\x32\x00\x00\x00\x3a\x00\x00\x00\x0a\x00\ \\x00\x00\x49\x00\x00\x00\x06\x00\x00\x00\x24\x00\x00\x00\x5c\x00\ \\x00\x00\xc2\x00\x00\x00\xd3\x00\x00\x00\xac\x00\x00\x00\x62\x00\ \\x00\x00\x91\x00\x00\x00\x95\x00\x00\x00\xe4\x00\x00\x00\x79\x00\ \\x00\x00\xe7\x00\x00\x00\xc8\x00\x00\x00\x37\x00\x00\x00\x6d\x00\ \\x00\x00\x8d\x00\x00\x00\xd5\x00\x00\x00\x4e\x00\x00\x00\xa9\x00\ \\x00\x00\x6c\x00\x00\x00\x56\x00\x00\x00\xf4\x00\x00\x00\xea\x00\ \\x00\x00\x65\x00\x00\x00\x7a\x00\x00\x00\xae\x00\x00\x00\x08\x00\ \\x00\x00\xba\x00\x00\x00\x78\x00\x00\x00\x25\x00\x00\x00\x2e\x00\ \\x00\x00\x1c\x00\x00\x00\xa6\x00\x00\x00\xb4\x00\x00\x00\xc6\x00\ \\x00\x00\xe8\x00\x00\x00\xdd\x00\x00\x00\x74\x00\x00\x00\x1f\x00\ \\x00\x00\x4b\x00\x00\x00\xbd\x00\x00\x00\x8b\x00\x00\x00\x8a\x00\ \\x00\x00\x70\x00\x00\x00\x3e\x00\x00\x00\xb5\x00\x00\x00\x66\x00\ \\x00\x00\x48\x00\x00\x00\x03\x00\x00\x00\xf6\x00\x00\x00\x0e\x00\ \\x00\x00\x61\x00\x00\x00\x35\x00\x00\x00\x57\x00\x00\x00\xb9\x00\ \\x00\x00\x86\x00\x00\x00\xc1\x00\x00\x00\x1d\x00\x00\x00\x9e\x00\ \\x00\x00\xe1\x00\x00\x00\xf8\x00\x00\x00\x98\x00\x00\x00\x11\x00\ \\x00\x00\x69\x00\x00\x00\xd9\x00\x00\x00\x8e\x00\x00\x00\x94\x00\ \\x00\x00\x9b\x00\x00\x00\x1e\x00\x00\x00\x87\x00\x00\x00\xe9\x00\ \\x00\x00\xce\x00\x00\x00\x55\x00\x00\x00\x28\x00\x00\x00\xdf\x00\ \\x00\x00\x8c\x00\x00\x00\xa1\x00\x00\x00\x89\x00\x00\x00\x0d\x00\ \\x00\x00\xbf\x00\x00\x00\xe6\x00\x00\x00\x42\x00\x00\x00\x68\x00\ \\x00\x00\x41\x00\x00\x00\x99\x00\x00\x00\x2d\x00\x00\x00\x0f\x00\ \\x00\x00\xb0\x00\x00\x00\x54\x00\x00\x00\xbb\x00\x00\x00\x16\x00"# sbox_0x00 = Table "\x00\x63\x00\x00\x00\x7c\x00\x00\x00\x77\x00\x00\x00\x7b\x00\x00\ \\x00\xf2\x00\x00\x00\x6b\x00\x00\x00\x6f\x00\x00\x00\xc5\x00\x00\ \\x00\x30\x00\x00\x00\x01\x00\x00\x00\x67\x00\x00\x00\x2b\x00\x00\ \\x00\xfe\x00\x00\x00\xd7\x00\x00\x00\xab\x00\x00\x00\x76\x00\x00\ \\x00\xca\x00\x00\x00\x82\x00\x00\x00\xc9\x00\x00\x00\x7d\x00\x00\ \\x00\xfa\x00\x00\x00\x59\x00\x00\x00\x47\x00\x00\x00\xf0\x00\x00\ \\x00\xad\x00\x00\x00\xd4\x00\x00\x00\xa2\x00\x00\x00\xaf\x00\x00\ \\x00\x9c\x00\x00\x00\xa4\x00\x00\x00\x72\x00\x00\x00\xc0\x00\x00\ \\x00\xb7\x00\x00\x00\xfd\x00\x00\x00\x93\x00\x00\x00\x26\x00\x00\ \\x00\x36\x00\x00\x00\x3f\x00\x00\x00\xf7\x00\x00\x00\xcc\x00\x00\ \\x00\x34\x00\x00\x00\xa5\x00\x00\x00\xe5\x00\x00\x00\xf1\x00\x00\ \\x00\x71\x00\x00\x00\xd8\x00\x00\x00\x31\x00\x00\x00\x15\x00\x00\ \\x00\x04\x00\x00\x00\xc7\x00\x00\x00\x23\x00\x00\x00\xc3\x00\x00\ \\x00\x18\x00\x00\x00\x96\x00\x00\x00\x05\x00\x00\x00\x9a\x00\x00\ \\x00\x07\x00\x00\x00\x12\x00\x00\x00\x80\x00\x00\x00\xe2\x00\x00\ \\x00\xeb\x00\x00\x00\x27\x00\x00\x00\xb2\x00\x00\x00\x75\x00\x00\ \\x00\x09\x00\x00\x00\x83\x00\x00\x00\x2c\x00\x00\x00\x1a\x00\x00\ \\x00\x1b\x00\x00\x00\x6e\x00\x00\x00\x5a\x00\x00\x00\xa0\x00\x00\ \\x00\x52\x00\x00\x00\x3b\x00\x00\x00\xd6\x00\x00\x00\xb3\x00\x00\ \\x00\x29\x00\x00\x00\xe3\x00\x00\x00\x2f\x00\x00\x00\x84\x00\x00\ \\x00\x53\x00\x00\x00\xd1\x00\x00\x00\x00\x00\x00\x00\xed\x00\x00\ \\x00\x20\x00\x00\x00\xfc\x00\x00\x00\xb1\x00\x00\x00\x5b\x00\x00\ \\x00\x6a\x00\x00\x00\xcb\x00\x00\x00\xbe\x00\x00\x00\x39\x00\x00\ \\x00\x4a\x00\x00\x00\x4c\x00\x00\x00\x58\x00\x00\x00\xcf\x00\x00\ \\x00\xd0\x00\x00\x00\xef\x00\x00\x00\xaa\x00\x00\x00\xfb\x00\x00\ \\x00\x43\x00\x00\x00\x4d\x00\x00\x00\x33\x00\x00\x00\x85\x00\x00\ \\x00\x45\x00\x00\x00\xf9\x00\x00\x00\x02\x00\x00\x00\x7f\x00\x00\ \\x00\x50\x00\x00\x00\x3c\x00\x00\x00\x9f\x00\x00\x00\xa8\x00\x00\ \\x00\x51\x00\x00\x00\xa3\x00\x00\x00\x40\x00\x00\x00\x8f\x00\x00\ \\x00\x92\x00\x00\x00\x9d\x00\x00\x00\x38\x00\x00\x00\xf5\x00\x00\ \\x00\xbc\x00\x00\x00\xb6\x00\x00\x00\xda\x00\x00\x00\x21\x00\x00\ \\x00\x10\x00\x00\x00\xff\x00\x00\x00\xf3\x00\x00\x00\xd2\x00\x00\ \\x00\xcd\x00\x00\x00\x0c\x00\x00\x00\x13\x00\x00\x00\xec\x00\x00\ \\x00\x5f\x00\x00\x00\x97\x00\x00\x00\x44\x00\x00\x00\x17\x00\x00\ \\x00\xc4\x00\x00\x00\xa7\x00\x00\x00\x7e\x00\x00\x00\x3d\x00\x00\ \\x00\x64\x00\x00\x00\x5d\x00\x00\x00\x19\x00\x00\x00\x73\x00\x00\ \\x00\x60\x00\x00\x00\x81\x00\x00\x00\x4f\x00\x00\x00\xdc\x00\x00\ \\x00\x22\x00\x00\x00\x2a\x00\x00\x00\x90\x00\x00\x00\x88\x00\x00\ \\x00\x46\x00\x00\x00\xee\x00\x00\x00\xb8\x00\x00\x00\x14\x00\x00\ \\x00\xde\x00\x00\x00\x5e\x00\x00\x00\x0b\x00\x00\x00\xdb\x00\x00\ \\x00\xe0\x00\x00\x00\x32\x00\x00\x00\x3a\x00\x00\x00\x0a\x00\x00\ \\x00\x49\x00\x00\x00\x06\x00\x00\x00\x24\x00\x00\x00\x5c\x00\x00\ \\x00\xc2\x00\x00\x00\xd3\x00\x00\x00\xac\x00\x00\x00\x62\x00\x00\ \\x00\x91\x00\x00\x00\x95\x00\x00\x00\xe4\x00\x00\x00\x79\x00\x00\ \\x00\xe7\x00\x00\x00\xc8\x00\x00\x00\x37\x00\x00\x00\x6d\x00\x00\ \\x00\x8d\x00\x00\x00\xd5\x00\x00\x00\x4e\x00\x00\x00\xa9\x00\x00\ \\x00\x6c\x00\x00\x00\x56\x00\x00\x00\xf4\x00\x00\x00\xea\x00\x00\ \\x00\x65\x00\x00\x00\x7a\x00\x00\x00\xae\x00\x00\x00\x08\x00\x00\ \\x00\xba\x00\x00\x00\x78\x00\x00\x00\x25\x00\x00\x00\x2e\x00\x00\ \\x00\x1c\x00\x00\x00\xa6\x00\x00\x00\xb4\x00\x00\x00\xc6\x00\x00\ \\x00\xe8\x00\x00\x00\xdd\x00\x00\x00\x74\x00\x00\x00\x1f\x00\x00\ \\x00\x4b\x00\x00\x00\xbd\x00\x00\x00\x8b\x00\x00\x00\x8a\x00\x00\ \\x00\x70\x00\x00\x00\x3e\x00\x00\x00\xb5\x00\x00\x00\x66\x00\x00\ \\x00\x48\x00\x00\x00\x03\x00\x00\x00\xf6\x00\x00\x00\x0e\x00\x00\ \\x00\x61\x00\x00\x00\x35\x00\x00\x00\x57\x00\x00\x00\xb9\x00\x00\ \\x00\x86\x00\x00\x00\xc1\x00\x00\x00\x1d\x00\x00\x00\x9e\x00\x00\ \\x00\xe1\x00\x00\x00\xf8\x00\x00\x00\x98\x00\x00\x00\x11\x00\x00\ \\x00\x69\x00\x00\x00\xd9\x00\x00\x00\x8e\x00\x00\x00\x94\x00\x00\ \\x00\x9b\x00\x00\x00\x1e\x00\x00\x00\x87\x00\x00\x00\xe9\x00\x00\ \\x00\xce\x00\x00\x00\x55\x00\x00\x00\x28\x00\x00\x00\xdf\x00\x00\ \\x00\x8c\x00\x00\x00\xa1\x00\x00\x00\x89\x00\x00\x00\x0d\x00\x00\ \\x00\xbf\x00\x00\x00\xe6\x00\x00\x00\x42\x00\x00\x00\x68\x00\x00\ \\x00\x41\x00\x00\x00\x99\x00\x00\x00\x2d\x00\x00\x00\x0f\x00\x00\ \\x00\xb0\x00\x00\x00\x54\x00\x00\x00\xbb\x00\x00\x00\x16\x00\x00"# sbox_x000 = Table "\x63\x00\x00\x00\x7c\x00\x00\x00\x77\x00\x00\x00\x7b\x00\x00\x00\ \\xf2\x00\x00\x00\x6b\x00\x00\x00\x6f\x00\x00\x00\xc5\x00\x00\x00\ \\x30\x00\x00\x00\x01\x00\x00\x00\x67\x00\x00\x00\x2b\x00\x00\x00\ \\xfe\x00\x00\x00\xd7\x00\x00\x00\xab\x00\x00\x00\x76\x00\x00\x00\ \\xca\x00\x00\x00\x82\x00\x00\x00\xc9\x00\x00\x00\x7d\x00\x00\x00\ \\xfa\x00\x00\x00\x59\x00\x00\x00\x47\x00\x00\x00\xf0\x00\x00\x00\ \\xad\x00\x00\x00\xd4\x00\x00\x00\xa2\x00\x00\x00\xaf\x00\x00\x00\ \\x9c\x00\x00\x00\xa4\x00\x00\x00\x72\x00\x00\x00\xc0\x00\x00\x00\ \\xb7\x00\x00\x00\xfd\x00\x00\x00\x93\x00\x00\x00\x26\x00\x00\x00\ \\x36\x00\x00\x00\x3f\x00\x00\x00\xf7\x00\x00\x00\xcc\x00\x00\x00\ \\x34\x00\x00\x00\xa5\x00\x00\x00\xe5\x00\x00\x00\xf1\x00\x00\x00\ \\x71\x00\x00\x00\xd8\x00\x00\x00\x31\x00\x00\x00\x15\x00\x00\x00\ \\x04\x00\x00\x00\xc7\x00\x00\x00\x23\x00\x00\x00\xc3\x00\x00\x00\ \\x18\x00\x00\x00\x96\x00\x00\x00\x05\x00\x00\x00\x9a\x00\x00\x00\ \\x07\x00\x00\x00\x12\x00\x00\x00\x80\x00\x00\x00\xe2\x00\x00\x00\ \\xeb\x00\x00\x00\x27\x00\x00\x00\xb2\x00\x00\x00\x75\x00\x00\x00\ \\x09\x00\x00\x00\x83\x00\x00\x00\x2c\x00\x00\x00\x1a\x00\x00\x00\ \\x1b\x00\x00\x00\x6e\x00\x00\x00\x5a\x00\x00\x00\xa0\x00\x00\x00\ \\x52\x00\x00\x00\x3b\x00\x00\x00\xd6\x00\x00\x00\xb3\x00\x00\x00\ \\x29\x00\x00\x00\xe3\x00\x00\x00\x2f\x00\x00\x00\x84\x00\x00\x00\ \\x53\x00\x00\x00\xd1\x00\x00\x00\x00\x00\x00\x00\xed\x00\x00\x00\ \\x20\x00\x00\x00\xfc\x00\x00\x00\xb1\x00\x00\x00\x5b\x00\x00\x00\ \\x6a\x00\x00\x00\xcb\x00\x00\x00\xbe\x00\x00\x00\x39\x00\x00\x00\ \\x4a\x00\x00\x00\x4c\x00\x00\x00\x58\x00\x00\x00\xcf\x00\x00\x00\ \\xd0\x00\x00\x00\xef\x00\x00\x00\xaa\x00\x00\x00\xfb\x00\x00\x00\ \\x43\x00\x00\x00\x4d\x00\x00\x00\x33\x00\x00\x00\x85\x00\x00\x00\ \\x45\x00\x00\x00\xf9\x00\x00\x00\x02\x00\x00\x00\x7f\x00\x00\x00\ \\x50\x00\x00\x00\x3c\x00\x00\x00\x9f\x00\x00\x00\xa8\x00\x00\x00\ \\x51\x00\x00\x00\xa3\x00\x00\x00\x40\x00\x00\x00\x8f\x00\x00\x00\ \\x92\x00\x00\x00\x9d\x00\x00\x00\x38\x00\x00\x00\xf5\x00\x00\x00\ \\xbc\x00\x00\x00\xb6\x00\x00\x00\xda\x00\x00\x00\x21\x00\x00\x00\ \\x10\x00\x00\x00\xff\x00\x00\x00\xf3\x00\x00\x00\xd2\x00\x00\x00\ \\xcd\x00\x00\x00\x0c\x00\x00\x00\x13\x00\x00\x00\xec\x00\x00\x00\ \\x5f\x00\x00\x00\x97\x00\x00\x00\x44\x00\x00\x00\x17\x00\x00\x00\ \\xc4\x00\x00\x00\xa7\x00\x00\x00\x7e\x00\x00\x00\x3d\x00\x00\x00\ \\x64\x00\x00\x00\x5d\x00\x00\x00\x19\x00\x00\x00\x73\x00\x00\x00\ \\x60\x00\x00\x00\x81\x00\x00\x00\x4f\x00\x00\x00\xdc\x00\x00\x00\ \\x22\x00\x00\x00\x2a\x00\x00\x00\x90\x00\x00\x00\x88\x00\x00\x00\ \\x46\x00\x00\x00\xee\x00\x00\x00\xb8\x00\x00\x00\x14\x00\x00\x00\ \\xde\x00\x00\x00\x5e\x00\x00\x00\x0b\x00\x00\x00\xdb\x00\x00\x00\ \\xe0\x00\x00\x00\x32\x00\x00\x00\x3a\x00\x00\x00\x0a\x00\x00\x00\ \\x49\x00\x00\x00\x06\x00\x00\x00\x24\x00\x00\x00\x5c\x00\x00\x00\ \\xc2\x00\x00\x00\xd3\x00\x00\x00\xac\x00\x00\x00\x62\x00\x00\x00\ \\x91\x00\x00\x00\x95\x00\x00\x00\xe4\x00\x00\x00\x79\x00\x00\x00\ \\xe7\x00\x00\x00\xc8\x00\x00\x00\x37\x00\x00\x00\x6d\x00\x00\x00\ \\x8d\x00\x00\x00\xd5\x00\x00\x00\x4e\x00\x00\x00\xa9\x00\x00\x00\ \\x6c\x00\x00\x00\x56\x00\x00\x00\xf4\x00\x00\x00\xea\x00\x00\x00\ \\x65\x00\x00\x00\x7a\x00\x00\x00\xae\x00\x00\x00\x08\x00\x00\x00\ \\xba\x00\x00\x00\x78\x00\x00\x00\x25\x00\x00\x00\x2e\x00\x00\x00\ \\x1c\x00\x00\x00\xa6\x00\x00\x00\xb4\x00\x00\x00\xc6\x00\x00\x00\ \\xe8\x00\x00\x00\xdd\x00\x00\x00\x74\x00\x00\x00\x1f\x00\x00\x00\ \\x4b\x00\x00\x00\xbd\x00\x00\x00\x8b\x00\x00\x00\x8a\x00\x00\x00\ \\x70\x00\x00\x00\x3e\x00\x00\x00\xb5\x00\x00\x00\x66\x00\x00\x00\ \\x48\x00\x00\x00\x03\x00\x00\x00\xf6\x00\x00\x00\x0e\x00\x00\x00\ \\x61\x00\x00\x00\x35\x00\x00\x00\x57\x00\x00\x00\xb9\x00\x00\x00\ \\x86\x00\x00\x00\xc1\x00\x00\x00\x1d\x00\x00\x00\x9e\x00\x00\x00\ \\xe1\x00\x00\x00\xf8\x00\x00\x00\x98\x00\x00\x00\x11\x00\x00\x00\ \\x69\x00\x00\x00\xd9\x00\x00\x00\x8e\x00\x00\x00\x94\x00\x00\x00\ \\x9b\x00\x00\x00\x1e\x00\x00\x00\x87\x00\x00\x00\xe9\x00\x00\x00\ \\xce\x00\x00\x00\x55\x00\x00\x00\x28\x00\x00\x00\xdf\x00\x00\x00\ \\x8c\x00\x00\x00\xa1\x00\x00\x00\x89\x00\x00\x00\x0d\x00\x00\x00\ \\xbf\x00\x00\x00\xe6\x00\x00\x00\x42\x00\x00\x00\x68\x00\x00\x00\ \\x41\x00\x00\x00\x99\x00\x00\x00\x2d\x00\x00\x00\x0f\x00\x00\x00\ \\xb0\x00\x00\x00\x54\x00\x00\x00\xbb\x00\x00\x00\x16\x00\x00\x00"# {-# INLINE rsbox #-} rsbox :: Word8 -> Word8 rsbox (W8# w) = W8# (indexWord8OffAddr# table (word2Int# w)) where !table = "\x52\x09\x6a\xd5\x30\x36\xa5\x38\ \\xbf\x40\xa3\x9e\x81\xf3\xd7\xfb\ \\x7c\xe3\x39\x82\x9b\x2f\xff\x87\ \\x34\x8e\x43\x44\xc4\xde\xe9\xcb\ \\x54\x7b\x94\x32\xa6\xc2\x23\x3d\ \\xee\x4c\x95\x0b\x42\xfa\xc3\x4e\ \\x08\x2e\xa1\x66\x28\xd9\x24\xb2\ \\x76\x5b\xa2\x49\x6d\x8b\xd1\x25\ \\x72\xf8\xf6\x64\x86\x68\x98\x16\ \\xd4\xa4\x5c\xcc\x5d\x65\xb6\x92\ \\x6c\x70\x48\x50\xfd\xed\xb9\xda\ \\x5e\x15\x46\x57\xa7\x8d\x9d\x84\ \\x90\xd8\xab\x00\x8c\xbc\xd3\x0a\ \\xf7\xe4\x58\x05\xb8\xb3\x45\x06\ \\xd0\x2c\x1e\x8f\xca\x3f\x0f\x02\ \\xc1\xaf\xbd\x03\x01\x13\x8a\x6b\ \\x3a\x91\x11\x41\x4f\x67\xdc\xea\ \\x97\xf2\xcf\xce\xf0\xb4\xe6\x73\ \\x96\xac\x74\x22\xe7\xad\x35\x85\ \\xe2\xf9\x37\xe8\x1c\x75\xdf\x6e\ \\x47\xf1\x1a\x71\x1d\x29\xc5\x89\ \\x6f\xb7\x62\x0e\xaa\x18\xbe\x1b\ \\xfc\x56\x3e\x4b\xc6\xd2\x79\x20\ \\x9a\xdb\xc0\xfe\x78\xcd\x5a\xf4\ \\x1f\xdd\xa8\x33\x88\x07\xc7\x31\ \\xb1\x12\x10\x59\x27\x80\xec\x5f\ \\x60\x51\x7f\xa9\x19\xb5\x4a\x0d\ \\x2d\xe5\x7a\x9f\x93\xc9\x9c\xef\ \\xa0\xe0\x3b\x4d\xae\x2a\xf5\xb0\ \\xc8\xeb\xbb\x3c\x83\x53\x99\x61\ \\x17\x2b\x04\x7e\xba\x77\xd6\x26\ \\xe1\x69\x14\x63\x55\x21\x0c\x7d"# {-# INLINE rcon #-} rcon :: Int -> Word8 rcon (I# i) = W8# (indexWord8OffAddr# table (i `remInt#` 51#)) where !table = "\x8d\x01\x02\x04\x08\x10\x20\x40\ \\x80\x1b\x36\x6c\xd8\xab\x4d\x9a\ \\x2f\x5e\xbc\x63\xc6\x97\x35\x6a\ \\xd4\xb3\x7d\xfa\xef\xc5\x91\x39\ \\x72\xe4\xd3\xbd\x61\xc2\x9f\x25\ \\x4a\x94\x33\x66\xcc\x83\x1d\x3a\ \\x74\xe8\xcb"# {-# INLINE gm2 #-} {-# INLINE gm3 #-} {-# INLINE gm9 #-} {-# INLINE gm11 #-} {-# INLINE gm13 #-} {-# INLINE gm14 #-} gm2, gm3, gm9, gm11, gm13, gm14 :: Word8 -> Word8 gm2 (W8# w) = W8# (indexWord8OffAddr# table (word2Int# w)) where !table = "\x00\x02\x04\x06\x08\x0a\x0c\x0e\ \\x10\x12\x14\x16\x18\x1a\x1c\x1e\ \\x20\x22\x24\x26\x28\x2a\x2c\x2e\ \\x30\x32\x34\x36\x38\x3a\x3c\x3e\ \\x40\x42\x44\x46\x48\x4a\x4c\x4e\ \\x50\x52\x54\x56\x58\x5a\x5c\x5e\ \\x60\x62\x64\x66\x68\x6a\x6c\x6e\ \\x70\x72\x74\x76\x78\x7a\x7c\x7e\ \\x80\x82\x84\x86\x88\x8a\x8c\x8e\ \\x90\x92\x94\x96\x98\x9a\x9c\x9e\ \\xa0\xa2\xa4\xa6\xa8\xaa\xac\xae\ \\xb0\xb2\xb4\xb6\xb8\xba\xbc\xbe\ \\xc0\xc2\xc4\xc6\xc8\xca\xcc\xce\ \\xd0\xd2\xd4\xd6\xd8\xda\xdc\xde\ \\xe0\xe2\xe4\xe6\xe8\xea\xec\xee\ \\xf0\xf2\xf4\xf6\xf8\xfa\xfc\xfe\ \\x1b\x19\x1f\x1d\x13\x11\x17\x15\ \\x0b\x09\x0f\x0d\x03\x01\x07\x05\ \\x3b\x39\x3f\x3d\x33\x31\x37\x35\ \\x2b\x29\x2f\x2d\x23\x21\x27\x25\ \\x5b\x59\x5f\x5d\x53\x51\x57\x55\ \\x4b\x49\x4f\x4d\x43\x41\x47\x45\ \\x7b\x79\x7f\x7d\x73\x71\x77\x75\ \\x6b\x69\x6f\x6d\x63\x61\x67\x65\ \\x9b\x99\x9f\x9d\x93\x91\x97\x95\ \\x8b\x89\x8f\x8d\x83\x81\x87\x85\ \\xbb\xb9\xbf\xbd\xb3\xb1\xb7\xb5\ \\xab\xa9\xaf\xad\xa3\xa1\xa7\xa5\ \\xdb\xd9\xdf\xdd\xd3\xd1\xd7\xd5\ \\xcb\xc9\xcf\xcd\xc3\xc1\xc7\xc5\ \\xfb\xf9\xff\xfd\xf3\xf1\xf7\xf5\ \\xeb\xe9\xef\xed\xe3\xe1\xe7\xe5"# gm3 (W8# w) = W8# (indexWord8OffAddr# table (word2Int# w)) where !table = "\x00\x03\x06\x05\x0c\x0f\x0a\x09\ \\x18\x1b\x1e\x1d\x14\x17\x12\x11\ \\x30\x33\x36\x35\x3c\x3f\x3a\x39\ \\x28\x2b\x2e\x2d\x24\x27\x22\x21\ \\x60\x63\x66\x65\x6c\x6f\x6a\x69\ \\x78\x7b\x7e\x7d\x74\x77\x72\x71\ \\x50\x53\x56\x55\x5c\x5f\x5a\x59\ \\x48\x4b\x4e\x4d\x44\x47\x42\x41\ \\xc0\xc3\xc6\xc5\xcc\xcf\xca\xc9\ \\xd8\xdb\xde\xdd\xd4\xd7\xd2\xd1\ \\xf0\xf3\xf6\xf5\xfc\xff\xfa\xf9\ \\xe8\xeb\xee\xed\xe4\xe7\xe2\xe1\ \\xa0\xa3\xa6\xa5\xac\xaf\xaa\xa9\ \\xb8\xbb\xbe\xbd\xb4\xb7\xb2\xb1\ \\x90\x93\x96\x95\x9c\x9f\x9a\x99\ \\x88\x8b\x8e\x8d\x84\x87\x82\x81\ \\x9b\x98\x9d\x9e\x97\x94\x91\x92\ \\x83\x80\x85\x86\x8f\x8c\x89\x8a\ \\xab\xa8\xad\xae\xa7\xa4\xa1\xa2\ \\xb3\xb0\xb5\xb6\xbf\xbc\xb9\xba\ \\xfb\xf8\xfd\xfe\xf7\xf4\xf1\xf2\ \\xe3\xe0\xe5\xe6\xef\xec\xe9\xea\ \\xcb\xc8\xcd\xce\xc7\xc4\xc1\xc2\ \\xd3\xd0\xd5\xd6\xdf\xdc\xd9\xda\ \\x5b\x58\x5d\x5e\x57\x54\x51\x52\ \\x43\x40\x45\x46\x4f\x4c\x49\x4a\ \\x6b\x68\x6d\x6e\x67\x64\x61\x62\ \\x73\x70\x75\x76\x7f\x7c\x79\x7a\ \\x3b\x38\x3d\x3e\x37\x34\x31\x32\ \\x23\x20\x25\x26\x2f\x2c\x29\x2a\ \\x0b\x08\x0d\x0e\x07\x04\x01\x02\ \\x13\x10\x15\x16\x1f\x1c\x19\x1a"# gm9 (W8# w) = W8# (indexWord8OffAddr# table (word2Int# w)) where !table = "\x00\x09\x12\x1b\x24\x2d\x36\x3f\ \\x48\x41\x5a\x53\x6c\x65\x7e\x77\ \\x90\x99\x82\x8b\xb4\xbd\xa6\xaf\ \\xd8\xd1\xca\xc3\xfc\xf5\xee\xe7\ \\x3b\x32\x29\x20\x1f\x16\x0d\x04\ \\x73\x7a\x61\x68\x57\x5e\x45\x4c\ \\xab\xa2\xb9\xb0\x8f\x86\x9d\x94\ \\xe3\xea\xf1\xf8\xc7\xce\xd5\xdc\ \\x76\x7f\x64\x6d\x52\x5b\x40\x49\ \\x3e\x37\x2c\x25\x1a\x13\x08\x01\ \\xe6\xef\xf4\xfd\xc2\xcb\xd0\xd9\ \\xae\xa7\xbc\xb5\x8a\x83\x98\x91\ \\x4d\x44\x5f\x56\x69\x60\x7b\x72\ \\x05\x0c\x17\x1e\x21\x28\x33\x3a\ \\xdd\xd4\xcf\xc6\xf9\xf0\xeb\xe2\ \\x95\x9c\x87\x8e\xb1\xb8\xa3\xaa\ \\xec\xe5\xfe\xf7\xc8\xc1\xda\xd3\ \\xa4\xad\xb6\xbf\x80\x89\x92\x9b\ \\x7c\x75\x6e\x67\x58\x51\x4a\x43\ \\x34\x3d\x26\x2f\x10\x19\x02\x0b\ \\xd7\xde\xc5\xcc\xf3\xfa\xe1\xe8\ \\x9f\x96\x8d\x84\xbb\xb2\xa9\xa0\ \\x47\x4e\x55\x5c\x63\x6a\x71\x78\ \\x0f\x06\x1d\x14\x2b\x22\x39\x30\ \\x9a\x93\x88\x81\xbe\xb7\xac\xa5\ \\xd2\xdb\xc0\xc9\xf6\xff\xe4\xed\ \\x0a\x03\x18\x11\x2e\x27\x3c\x35\ \\x42\x4b\x50\x59\x66\x6f\x74\x7d\ \\xa1\xa8\xb3\xba\x85\x8c\x97\x9e\ \\xe9\xe0\xfb\xf2\xcd\xc4\xdf\xd6\ \\x31\x38\x23\x2a\x15\x1c\x07\x0e\ \\x79\x70\x6b\x62\x5d\x54\x4f\x46"# gm11 (W8# w) = W8# (indexWord8OffAddr# table (word2Int# w)) where !table = "\x00\x0b\x16\x1d\x2c\x27\x3a\x31\ \\x58\x53\x4e\x45\x74\x7f\x62\x69\ \\xb0\xbb\xa6\xad\x9c\x97\x8a\x81\ \\xe8\xe3\xfe\xf5\xc4\xcf\xd2\xd9\ \\x7b\x70\x6d\x66\x57\x5c\x41\x4a\ \\x23\x28\x35\x3e\x0f\x04\x19\x12\ \\xcb\xc0\xdd\xd6\xe7\xec\xf1\xfa\ \\x93\x98\x85\x8e\xbf\xb4\xa9\xa2\ \\xf6\xfd\xe0\xeb\xda\xd1\xcc\xc7\ \\xae\xa5\xb8\xb3\x82\x89\x94\x9f\ \\x46\x4d\x50\x5b\x6a\x61\x7c\x77\ \\x1e\x15\x08\x03\x32\x39\x24\x2f\ \\x8d\x86\x9b\x90\xa1\xaa\xb7\xbc\ \\xd5\xde\xc3\xc8\xf9\xf2\xef\xe4\ \\x3d\x36\x2b\x20\x11\x1a\x07\x0c\ \\x65\x6e\x73\x78\x49\x42\x5f\x54\ \\xf7\xfc\xe1\xea\xdb\xd0\xcd\xc6\ \\xaf\xa4\xb9\xb2\x83\x88\x95\x9e\ \\x47\x4c\x51\x5a\x6b\x60\x7d\x76\ \\x1f\x14\x09\x02\x33\x38\x25\x2e\ \\x8c\x87\x9a\x91\xa0\xab\xb6\xbd\ \\xd4\xdf\xc2\xc9\xf8\xf3\xee\xe5\ \\x3c\x37\x2a\x21\x10\x1b\x06\x0d\ \\x64\x6f\x72\x79\x48\x43\x5e\x55\ \\x01\x0a\x17\x1c\x2d\x26\x3b\x30\ \\x59\x52\x4f\x44\x75\x7e\x63\x68\ \\xb1\xba\xa7\xac\x9d\x96\x8b\x80\ \\xe9\xe2\xff\xf4\xc5\xce\xd3\xd8\ \\x7a\x71\x6c\x67\x56\x5d\x40\x4b\ \\x22\x29\x34\x3f\x0e\x05\x18\x13\ \\xca\xc1\xdc\xd7\xe6\xed\xf0\xfb\ \\x92\x99\x84\x8f\xbe\xb5\xa8\xa3"# gm13 (W8# w) = W8# (indexWord8OffAddr# table (word2Int# w)) where !table = "\x00\x0d\x1a\x17\x34\x39\x2e\x23\ \\x68\x65\x72\x7f\x5c\x51\x46\x4b\ \\xd0\xdd\xca\xc7\xe4\xe9\xfe\xf3\ \\xb8\xb5\xa2\xaf\x8c\x81\x96\x9b\ \\xbb\xb6\xa1\xac\x8f\x82\x95\x98\ \\xd3\xde\xc9\xc4\xe7\xea\xfd\xf0\ \\x6b\x66\x71\x7c\x5f\x52\x45\x48\ \\x03\x0e\x19\x14\x37\x3a\x2d\x20\ \\x6d\x60\x77\x7a\x59\x54\x43\x4e\ \\x05\x08\x1f\x12\x31\x3c\x2b\x26\ \\xbd\xb0\xa7\xaa\x89\x84\x93\x9e\ \\xd5\xd8\xcf\xc2\xe1\xec\xfb\xf6\ \\xd6\xdb\xcc\xc1\xe2\xef\xf8\xf5\ \\xbe\xb3\xa4\xa9\x8a\x87\x90\x9d\ \\x06\x0b\x1c\x11\x32\x3f\x28\x25\ \\x6e\x63\x74\x79\x5a\x57\x40\x4d\ \\xda\xd7\xc0\xcd\xee\xe3\xf4\xf9\ \\xb2\xbf\xa8\xa5\x86\x8b\x9c\x91\ \\x0a\x07\x10\x1d\x3e\x33\x24\x29\ \\x62\x6f\x78\x75\x56\x5b\x4c\x41\ \\x61\x6c\x7b\x76\x55\x58\x4f\x42\ \\x09\x04\x13\x1e\x3d\x30\x27\x2a\ \\xb1\xbc\xab\xa6\x85\x88\x9f\x92\ \\xd9\xd4\xc3\xce\xed\xe0\xf7\xfa\ \\xb7\xba\xad\xa0\x83\x8e\x99\x94\ \\xdf\xd2\xc5\xc8\xeb\xe6\xf1\xfc\ \\x67\x6a\x7d\x70\x53\x5e\x49\x44\ \\x0f\x02\x15\x18\x3b\x36\x21\x2c\ \\x0c\x01\x16\x1b\x38\x35\x22\x2f\ \\x64\x69\x7e\x73\x50\x5d\x4a\x47\ \\xdc\xd1\xc6\xcb\xe8\xe5\xf2\xff\ \\xb4\xb9\xae\xa3\x80\x8d\x9a\x97"# gm14 (W8# w) = W8# (indexWord8OffAddr# table (word2Int# w)) where !table = "\x00\x0e\x1c\x12\x38\x36\x24\x2a\ \\x70\x7e\x6c\x62\x48\x46\x54\x5a\ \\xe0\xee\xfc\xf2\xd8\xd6\xc4\xca\ \\x90\x9e\x8c\x82\xa8\xa6\xb4\xba\ \\xdb\xd5\xc7\xc9\xe3\xed\xff\xf1\ \\xab\xa5\xb7\xb9\x93\x9d\x8f\x81\ \\x3b\x35\x27\x29\x03\x0d\x1f\x11\ \\x4b\x45\x57\x59\x73\x7d\x6f\x61\ \\xad\xa3\xb1\xbf\x95\x9b\x89\x87\ \\xdd\xd3\xc1\xcf\xe5\xeb\xf9\xf7\ \\x4d\x43\x51\x5f\x75\x7b\x69\x67\ \\x3d\x33\x21\x2f\x05\x0b\x19\x17\ \\x76\x78\x6a\x64\x4e\x40\x52\x5c\ \\x06\x08\x1a\x14\x3e\x30\x22\x2c\ \\x96\x98\x8a\x84\xae\xa0\xb2\xbc\ \\xe6\xe8\xfa\xf4\xde\xd0\xc2\xcc\ \\x41\x4f\x5d\x53\x79\x77\x65\x6b\ \\x31\x3f\x2d\x23\x09\x07\x15\x1b\ \\xa1\xaf\xbd\xb3\x99\x97\x85\x8b\ \\xd1\xdf\xcd\xc3\xe9\xe7\xf5\xfb\ \\x9a\x94\x86\x88\xa2\xac\xbe\xb0\ \\xea\xe4\xf6\xf8\xd2\xdc\xce\xc0\ \\x7a\x74\x66\x68\x42\x4c\x5e\x50\ \\x0a\x04\x16\x18\x32\x3c\x2e\x20\ \\xec\xe2\xf0\xfe\xd4\xda\xc8\xc6\ \\x9c\x92\x80\x8e\xa4\xaa\xb8\xb6\ \\x0c\x02\x10\x1e\x34\x3a\x28\x26\ \\x7c\x72\x60\x6e\x44\x4a\x58\x56\ \\x37\x39\x2b\x25\x0f\x01\x13\x1d\ \\x47\x49\x5b\x55\x7f\x71\x63\x6d\ \\xd7\xd9\xcb\xc5\xef\xe1\xf3\xfd\ \\xa7\xa9\xbb\xb5\x9f\x91\x83\x8d"#