-- | -- Module : Crypto.Cipher.AES -- License : BSD-style -- Maintainer : Vincent Hanquez -- Stability : experimental -- Portability : Good module Crypto.Cipher.AES ( 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 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 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 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 = 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 -> ByteString -> ByteString 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 -> ByteString -> ByteString 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` mRcon it, sbox r2, sbox r3, sbox r0) {-# 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 gm2 #-} gm2 a = V.unsafeIndex gmtab2 $ fromIntegral a {-# INLINE gm3 #-} gm3 a = V.unsafeIndex gmtab3 $ fromIntegral 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 gm14 #-} {-# INLINE gm13 #-} {-# INLINE gm11 #-} {-# INLINE gm9 #-} gm14 a = V.unsafeIndex gmtab14 $ fromIntegral a gm13 a = V.unsafeIndex gmtab13 $ fromIntegral a gm11 a = V.unsafeIndex gmtab11 $ fromIntegral a gm9 a = V.unsafeIndex gmtab9 $ fromIntegral a {-# 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 mRcon #-} mRcon :: Int -> Word8 mRcon i = V.unsafeIndex rcon (i `mod` len) where len = V.length rcon {-# INLINE sbox #-} sbox :: Word8 -> Word8 sbox = V.unsafeIndex tab . fromIntegral where tab = V.fromList [ 0x63, 0x7c, 0x77, 0x7b, 0xf2, 0x6b, 0x6f, 0xc5 , 0x30, 0x01, 0x67, 0x2b, 0xfe, 0xd7, 0xab, 0x76 , 0xca, 0x82, 0xc9, 0x7d, 0xfa, 0x59, 0x47, 0xf0 , 0xad, 0xd4, 0xa2, 0xaf, 0x9c, 0xa4, 0x72, 0xc0 , 0xb7, 0xfd, 0x93, 0x26, 0x36, 0x3f, 0xf7, 0xcc , 0x34, 0xa5, 0xe5, 0xf1, 0x71, 0xd8, 0x31, 0x15 , 0x04, 0xc7, 0x23, 0xc3, 0x18, 0x96, 0x05, 0x9a , 0x07, 0x12, 0x80, 0xe2, 0xeb, 0x27, 0xb2, 0x75 , 0x09, 0x83, 0x2c, 0x1a, 0x1b, 0x6e, 0x5a, 0xa0 , 0x52, 0x3b, 0xd6, 0xb3, 0x29, 0xe3, 0x2f, 0x84 , 0x53, 0xd1, 0x00, 0xed, 0x20, 0xfc, 0xb1, 0x5b , 0x6a, 0xcb, 0xbe, 0x39, 0x4a, 0x4c, 0x58, 0xcf , 0xd0, 0xef, 0xaa, 0xfb, 0x43, 0x4d, 0x33, 0x85 , 0x45, 0xf9, 0x02, 0x7f, 0x50, 0x3c, 0x9f, 0xa8 , 0x51, 0xa3, 0x40, 0x8f, 0x92, 0x9d, 0x38, 0xf5 , 0xbc, 0xb6, 0xda, 0x21, 0x10, 0xff, 0xf3, 0xd2 , 0xcd, 0x0c, 0x13, 0xec, 0x5f, 0x97, 0x44, 0x17 , 0xc4, 0xa7, 0x7e, 0x3d, 0x64, 0x5d, 0x19, 0x73 , 0x60, 0x81, 0x4f, 0xdc, 0x22, 0x2a, 0x90, 0x88 , 0x46, 0xee, 0xb8, 0x14, 0xde, 0x5e, 0x0b, 0xdb , 0xe0, 0x32, 0x3a, 0x0a, 0x49, 0x06, 0x24, 0x5c , 0xc2, 0xd3, 0xac, 0x62, 0x91, 0x95, 0xe4, 0x79 , 0xe7, 0xc8, 0x37, 0x6d, 0x8d, 0xd5, 0x4e, 0xa9 , 0x6c, 0x56, 0xf4, 0xea, 0x65, 0x7a, 0xae, 0x08 , 0xba, 0x78, 0x25, 0x2e, 0x1c, 0xa6, 0xb4, 0xc6 , 0xe8, 0xdd, 0x74, 0x1f, 0x4b, 0xbd, 0x8b, 0x8a , 0x70, 0x3e, 0xb5, 0x66, 0x48, 0x03, 0xf6, 0x0e , 0x61, 0x35, 0x57, 0xb9, 0x86, 0xc1, 0x1d, 0x9e , 0xe1, 0xf8, 0x98, 0x11, 0x69, 0xd9, 0x8e, 0x94 , 0x9b, 0x1e, 0x87, 0xe9, 0xce, 0x55, 0x28, 0xdf , 0x8c, 0xa1, 0x89, 0x0d, 0xbf, 0xe6, 0x42, 0x68 , 0x41, 0x99, 0x2d, 0x0f, 0xb0, 0x54, 0xbb, 0x16 ] sbox1, sbox2, sbox3, sbox4 :: Word8 -> Word32 sbox1 = V.unsafeIndex tab . fromIntegral where tab = V.fromList [ 0x00000063, 0x0000007c, 0x00000077, 0x0000007b , 0x000000f2, 0x0000006b, 0x0000006f, 0x000000c5 , 0x00000030, 0x00000001, 0x00000067, 0x0000002b , 0x000000fe, 0x000000d7, 0x000000ab, 0x00000076 , 0x000000ca, 0x00000082, 0x000000c9, 0x0000007d , 0x000000fa, 0x00000059, 0x00000047, 0x000000f0 , 0x000000ad, 0x000000d4, 0x000000a2, 0x000000af , 0x0000009c, 0x000000a4, 0x00000072, 0x000000c0 , 0x000000b7, 0x000000fd, 0x00000093, 0x00000026 , 0x00000036, 0x0000003f, 0x000000f7, 0x000000cc , 0x00000034, 0x000000a5, 0x000000e5, 0x000000f1 , 0x00000071, 0x000000d8, 0x00000031, 0x00000015 , 0x00000004, 0x000000c7, 0x00000023, 0x000000c3 , 0x00000018, 0x00000096, 0x00000005, 0x0000009a , 0x00000007, 0x00000012, 0x00000080, 0x000000e2 , 0x000000eb, 0x00000027, 0x000000b2, 0x00000075 , 0x00000009, 0x00000083, 0x0000002c, 0x0000001a , 0x0000001b, 0x0000006e, 0x0000005a, 0x000000a0 , 0x00000052, 0x0000003b, 0x000000d6, 0x000000b3 , 0x00000029, 0x000000e3, 0x0000002f, 0x00000084 , 0x00000053, 0x000000d1, 0x00000000, 0x000000ed , 0x00000020, 0x000000fc, 0x000000b1, 0x0000005b , 0x0000006a, 0x000000cb, 0x000000be, 0x00000039 , 0x0000004a, 0x0000004c, 0x00000058, 0x000000cf , 0x000000d0, 0x000000ef, 0x000000aa, 0x000000fb , 0x00000043, 0x0000004d, 0x00000033, 0x00000085 , 0x00000045, 0x000000f9, 0x00000002, 0x0000007f , 0x00000050, 0x0000003c, 0x0000009f, 0x000000a8 , 0x00000051, 0x000000a3, 0x00000040, 0x0000008f , 0x00000092, 0x0000009d, 0x00000038, 0x000000f5 , 0x000000bc, 0x000000b6, 0x000000da, 0x00000021 , 0x00000010, 0x000000ff, 0x000000f3, 0x000000d2 , 0x000000cd, 0x0000000c, 0x00000013, 0x000000ec , 0x0000005f, 0x00000097, 0x00000044, 0x00000017 , 0x000000c4, 0x000000a7, 0x0000007e, 0x0000003d , 0x00000064, 0x0000005d, 0x00000019, 0x00000073 , 0x00000060, 0x00000081, 0x0000004f, 0x000000dc , 0x00000022, 0x0000002a, 0x00000090, 0x00000088 , 0x00000046, 0x000000ee, 0x000000b8, 0x00000014 , 0x000000de, 0x0000005e, 0x0000000b, 0x000000db , 0x000000e0, 0x00000032, 0x0000003a, 0x0000000a , 0x00000049, 0x00000006, 0x00000024, 0x0000005c , 0x000000c2, 0x000000d3, 0x000000ac, 0x00000062 , 0x00000091, 0x00000095, 0x000000e4, 0x00000079 , 0x000000e7, 0x000000c8, 0x00000037, 0x0000006d , 0x0000008d, 0x000000d5, 0x0000004e, 0x000000a9 , 0x0000006c, 0x00000056, 0x000000f4, 0x000000ea , 0x00000065, 0x0000007a, 0x000000ae, 0x00000008 , 0x000000ba, 0x00000078, 0x00000025, 0x0000002e , 0x0000001c, 0x000000a6, 0x000000b4, 0x000000c6 , 0x000000e8, 0x000000dd, 0x00000074, 0x0000001f , 0x0000004b, 0x000000bd, 0x0000008b, 0x0000008a , 0x00000070, 0x0000003e, 0x000000b5, 0x00000066 , 0x00000048, 0x00000003, 0x000000f6, 0x0000000e , 0x00000061, 0x00000035, 0x00000057, 0x000000b9 , 0x00000086, 0x000000c1, 0x0000001d, 0x0000009e , 0x000000e1, 0x000000f8, 0x00000098, 0x00000011 , 0x00000069, 0x000000d9, 0x0000008e, 0x00000094 , 0x0000009b, 0x0000001e, 0x00000087, 0x000000e9 , 0x000000ce, 0x00000055, 0x00000028, 0x000000df , 0x0000008c, 0x000000a1, 0x00000089, 0x0000000d , 0x000000bf, 0x000000e6, 0x00000042, 0x00000068 , 0x00000041, 0x00000099, 0x0000002d, 0x0000000f , 0x000000b0, 0x00000054, 0x000000bb, 0x00000016 ] sbox2 = V.unsafeIndex tab . fromIntegral where tab = V.fromList [ 0x00006300, 0x00007c00, 0x00007700, 0x00007b00 , 0x0000f200, 0x00006b00, 0x00006f00, 0x0000c500 , 0x00003000, 0x00000100, 0x00006700, 0x00002b00 , 0x0000fe00, 0x0000d700, 0x0000ab00, 0x00007600 , 0x0000ca00, 0x00008200, 0x0000c900, 0x00007d00 , 0x0000fa00, 0x00005900, 0x00004700, 0x0000f000 , 0x0000ad00, 0x0000d400, 0x0000a200, 0x0000af00 , 0x00009c00, 0x0000a400, 0x00007200, 0x0000c000 , 0x0000b700, 0x0000fd00, 0x00009300, 0x00002600 , 0x00003600, 0x00003f00, 0x0000f700, 0x0000cc00 , 0x00003400, 0x0000a500, 0x0000e500, 0x0000f100 , 0x00007100, 0x0000d800, 0x00003100, 0x00001500 , 0x00000400, 0x0000c700, 0x00002300, 0x0000c300 , 0x00001800, 0x00009600, 0x00000500, 0x00009a00 , 0x00000700, 0x00001200, 0x00008000, 0x0000e200 , 0x0000eb00, 0x00002700, 0x0000b200, 0x00007500 , 0x00000900, 0x00008300, 0x00002c00, 0x00001a00 , 0x00001b00, 0x00006e00, 0x00005a00, 0x0000a000 , 0x00005200, 0x00003b00, 0x0000d600, 0x0000b300 , 0x00002900, 0x0000e300, 0x00002f00, 0x00008400 , 0x00005300, 0x0000d100, 0x00000000, 0x0000ed00 , 0x00002000, 0x0000fc00, 0x0000b100, 0x00005b00 , 0x00006a00, 0x0000cb00, 0x0000be00, 0x00003900 , 0x00004a00, 0x00004c00, 0x00005800, 0x0000cf00 , 0x0000d000, 0x0000ef00, 0x0000aa00, 0x0000fb00 , 0x00004300, 0x00004d00, 0x00003300, 0x00008500 , 0x00004500, 0x0000f900, 0x00000200, 0x00007f00 , 0x00005000, 0x00003c00, 0x00009f00, 0x0000a800 , 0x00005100, 0x0000a300, 0x00004000, 0x00008f00 , 0x00009200, 0x00009d00, 0x00003800, 0x0000f500 , 0x0000bc00, 0x0000b600, 0x0000da00, 0x00002100 , 0x00001000, 0x0000ff00, 0x0000f300, 0x0000d200 , 0x0000cd00, 0x00000c00, 0x00001300, 0x0000ec00 , 0x00005f00, 0x00009700, 0x00004400, 0x00001700 , 0x0000c400, 0x0000a700, 0x00007e00, 0x00003d00 , 0x00006400, 0x00005d00, 0x00001900, 0x00007300 , 0x00006000, 0x00008100, 0x00004f00, 0x0000dc00 , 0x00002200, 0x00002a00, 0x00009000, 0x00008800 , 0x00004600, 0x0000ee00, 0x0000b800, 0x00001400 , 0x0000de00, 0x00005e00, 0x00000b00, 0x0000db00 , 0x0000e000, 0x00003200, 0x00003a00, 0x00000a00 , 0x00004900, 0x00000600, 0x00002400, 0x00005c00 , 0x0000c200, 0x0000d300, 0x0000ac00, 0x00006200 , 0x00009100, 0x00009500, 0x0000e400, 0x00007900 , 0x0000e700, 0x0000c800, 0x00003700, 0x00006d00 , 0x00008d00, 0x0000d500, 0x00004e00, 0x0000a900 , 0x00006c00, 0x00005600, 0x0000f400, 0x0000ea00 , 0x00006500, 0x00007a00, 0x0000ae00, 0x00000800 , 0x0000ba00, 0x00007800, 0x00002500, 0x00002e00 , 0x00001c00, 0x0000a600, 0x0000b400, 0x0000c600 , 0x0000e800, 0x0000dd00, 0x00007400, 0x00001f00 , 0x00004b00, 0x0000bd00, 0x00008b00, 0x00008a00 , 0x00007000, 0x00003e00, 0x0000b500, 0x00006600 , 0x00004800, 0x00000300, 0x0000f600, 0x00000e00 , 0x00006100, 0x00003500, 0x00005700, 0x0000b900 , 0x00008600, 0x0000c100, 0x00001d00, 0x00009e00 , 0x0000e100, 0x0000f800, 0x00009800, 0x00001100 , 0x00006900, 0x0000d900, 0x00008e00, 0x00009400 , 0x00009b00, 0x00001e00, 0x00008700, 0x0000e900 , 0x0000ce00, 0x00005500, 0x00002800, 0x0000df00 , 0x00008c00, 0x0000a100, 0x00008900, 0x00000d00 , 0x0000bf00, 0x0000e600, 0x00004200, 0x00006800 , 0x00004100, 0x00009900, 0x00002d00, 0x00000f00 , 0x0000b000, 0x00005400, 0x0000bb00, 0x00001600 ] sbox3 = V.unsafeIndex tab . fromIntegral where tab = V.fromList [ 0x00630000, 0x007c0000, 0x00770000, 0x007b0000 , 0x00f20000, 0x006b0000, 0x006f0000, 0x00c50000 , 0x00300000, 0x00010000, 0x00670000, 0x002b0000 , 0x00fe0000, 0x00d70000, 0x00ab0000, 0x00760000 , 0x00ca0000, 0x00820000, 0x00c90000, 0x007d0000 , 0x00fa0000, 0x00590000, 0x00470000, 0x00f00000 , 0x00ad0000, 0x00d40000, 0x00a20000, 0x00af0000 , 0x009c0000, 0x00a40000, 0x00720000, 0x00c00000 , 0x00b70000, 0x00fd0000, 0x00930000, 0x00260000 , 0x00360000, 0x003f0000, 0x00f70000, 0x00cc0000 , 0x00340000, 0x00a50000, 0x00e50000, 0x00f10000 , 0x00710000, 0x00d80000, 0x00310000, 0x00150000 , 0x00040000, 0x00c70000, 0x00230000, 0x00c30000 , 0x00180000, 0x00960000, 0x00050000, 0x009a0000 , 0x00070000, 0x00120000, 0x00800000, 0x00e20000 , 0x00eb0000, 0x00270000, 0x00b20000, 0x00750000 , 0x00090000, 0x00830000, 0x002c0000, 0x001a0000 , 0x001b0000, 0x006e0000, 0x005a0000, 0x00a00000 , 0x00520000, 0x003b0000, 0x00d60000, 0x00b30000 , 0x00290000, 0x00e30000, 0x002f0000, 0x00840000 , 0x00530000, 0x00d10000, 0x00000000, 0x00ed0000 , 0x00200000, 0x00fc0000, 0x00b10000, 0x005b0000 , 0x006a0000, 0x00cb0000, 0x00be0000, 0x00390000 , 0x004a0000, 0x004c0000, 0x00580000, 0x00cf0000 , 0x00d00000, 0x00ef0000, 0x00aa0000, 0x00fb0000 , 0x00430000, 0x004d0000, 0x00330000, 0x00850000 , 0x00450000, 0x00f90000, 0x00020000, 0x007f0000 , 0x00500000, 0x003c0000, 0x009f0000, 0x00a80000 , 0x00510000, 0x00a30000, 0x00400000, 0x008f0000 , 0x00920000, 0x009d0000, 0x00380000, 0x00f50000 , 0x00bc0000, 0x00b60000, 0x00da0000, 0x00210000 , 0x00100000, 0x00ff0000, 0x00f30000, 0x00d20000 , 0x00cd0000, 0x000c0000, 0x00130000, 0x00ec0000 , 0x005f0000, 0x00970000, 0x00440000, 0x00170000 , 0x00c40000, 0x00a70000, 0x007e0000, 0x003d0000 , 0x00640000, 0x005d0000, 0x00190000, 0x00730000 , 0x00600000, 0x00810000, 0x004f0000, 0x00dc0000 , 0x00220000, 0x002a0000, 0x00900000, 0x00880000 , 0x00460000, 0x00ee0000, 0x00b80000, 0x00140000 , 0x00de0000, 0x005e0000, 0x000b0000, 0x00db0000 , 0x00e00000, 0x00320000, 0x003a0000, 0x000a0000 , 0x00490000, 0x00060000, 0x00240000, 0x005c0000 , 0x00c20000, 0x00d30000, 0x00ac0000, 0x00620000 , 0x00910000, 0x00950000, 0x00e40000, 0x00790000 , 0x00e70000, 0x00c80000, 0x00370000, 0x006d0000 , 0x008d0000, 0x00d50000, 0x004e0000, 0x00a90000 , 0x006c0000, 0x00560000, 0x00f40000, 0x00ea0000 , 0x00650000, 0x007a0000, 0x00ae0000, 0x00080000 , 0x00ba0000, 0x00780000, 0x00250000, 0x002e0000 , 0x001c0000, 0x00a60000, 0x00b40000, 0x00c60000 , 0x00e80000, 0x00dd0000, 0x00740000, 0x001f0000 , 0x004b0000, 0x00bd0000, 0x008b0000, 0x008a0000 , 0x00700000, 0x003e0000, 0x00b50000, 0x00660000 , 0x00480000, 0x00030000, 0x00f60000, 0x000e0000 , 0x00610000, 0x00350000, 0x00570000, 0x00b90000 , 0x00860000, 0x00c10000, 0x001d0000, 0x009e0000 , 0x00e10000, 0x00f80000, 0x00980000, 0x00110000 , 0x00690000, 0x00d90000, 0x008e0000, 0x00940000 , 0x009b0000, 0x001e0000, 0x00870000, 0x00e90000 , 0x00ce0000, 0x00550000, 0x00280000, 0x00df0000 , 0x008c0000, 0x00a10000, 0x00890000, 0x000d0000 , 0x00bf0000, 0x00e60000, 0x00420000, 0x00680000 , 0x00410000, 0x00990000, 0x002d0000, 0x000f0000 , 0x00b00000, 0x00540000, 0x00bb0000, 0x00160000 ] sbox4 = V.unsafeIndex tab . fromIntegral where tab = V.fromList [ 0x63000000, 0x7c000000, 0x77000000, 0x7b000000 , 0xf2000000, 0x6b000000, 0x6f000000, 0xc5000000 , 0x30000000, 0x01000000, 0x67000000, 0x2b000000 , 0xfe000000, 0xd7000000, 0xab000000, 0x76000000 , 0xca000000, 0x82000000, 0xc9000000, 0x7d000000 , 0xfa000000, 0x59000000, 0x47000000, 0xf0000000 , 0xad000000, 0xd4000000, 0xa2000000, 0xaf000000 , 0x9c000000, 0xa4000000, 0x72000000, 0xc0000000 , 0xb7000000, 0xfd000000, 0x93000000, 0x26000000 , 0x36000000, 0x3f000000, 0xf7000000, 0xcc000000 , 0x34000000, 0xa5000000, 0xe5000000, 0xf1000000 , 0x71000000, 0xd8000000, 0x31000000, 0x15000000 , 0x04000000, 0xc7000000, 0x23000000, 0xc3000000 , 0x18000000, 0x96000000, 0x05000000, 0x9a000000 , 0x07000000, 0x12000000, 0x80000000, 0xe2000000 , 0xeb000000, 0x27000000, 0xb2000000, 0x75000000 , 0x09000000, 0x83000000, 0x2c000000, 0x1a000000 , 0x1b000000, 0x6e000000, 0x5a000000, 0xa0000000 , 0x52000000, 0x3b000000, 0xd6000000, 0xb3000000 , 0x29000000, 0xe3000000, 0x2f000000, 0x84000000 , 0x53000000, 0xd1000000, 0x00000000, 0xed000000 , 0x20000000, 0xfc000000, 0xb1000000, 0x5b000000 , 0x6a000000, 0xcb000000, 0xbe000000, 0x39000000 , 0x4a000000, 0x4c000000, 0x58000000, 0xcf000000 , 0xd0000000, 0xef000000, 0xaa000000, 0xfb000000 , 0x43000000, 0x4d000000, 0x33000000, 0x85000000 , 0x45000000, 0xf9000000, 0x02000000, 0x7f000000 , 0x50000000, 0x3c000000, 0x9f000000, 0xa8000000 , 0x51000000, 0xa3000000, 0x40000000, 0x8f000000 , 0x92000000, 0x9d000000, 0x38000000, 0xf5000000 , 0xbc000000, 0xb6000000, 0xda000000, 0x21000000 , 0x10000000, 0xff000000, 0xf3000000, 0xd2000000 , 0xcd000000, 0x0c000000, 0x13000000, 0xec000000 , 0x5f000000, 0x97000000, 0x44000000, 0x17000000 , 0xc4000000, 0xa7000000, 0x7e000000, 0x3d000000 , 0x64000000, 0x5d000000, 0x19000000, 0x73000000 , 0x60000000, 0x81000000, 0x4f000000, 0xdc000000 , 0x22000000, 0x2a000000, 0x90000000, 0x88000000 , 0x46000000, 0xee000000, 0xb8000000, 0x14000000 , 0xde000000, 0x5e000000, 0x0b000000, 0xdb000000 , 0xe0000000, 0x32000000, 0x3a000000, 0x0a000000 , 0x49000000, 0x06000000, 0x24000000, 0x5c000000 , 0xc2000000, 0xd3000000, 0xac000000, 0x62000000 , 0x91000000, 0x95000000, 0xe4000000, 0x79000000 , 0xe7000000, 0xc8000000, 0x37000000, 0x6d000000 , 0x8d000000, 0xd5000000, 0x4e000000, 0xa9000000 , 0x6c000000, 0x56000000, 0xf4000000, 0xea000000 , 0x65000000, 0x7a000000, 0xae000000, 0x08000000 , 0xba000000, 0x78000000, 0x25000000, 0x2e000000 , 0x1c000000, 0xa6000000, 0xb4000000, 0xc6000000 , 0xe8000000, 0xdd000000, 0x74000000, 0x1f000000 , 0x4b000000, 0xbd000000, 0x8b000000, 0x8a000000 , 0x70000000, 0x3e000000, 0xb5000000, 0x66000000 , 0x48000000, 0x03000000, 0xf6000000, 0x0e000000 , 0x61000000, 0x35000000, 0x57000000, 0xb9000000 , 0x86000000, 0xc1000000, 0x1d000000, 0x9e000000 , 0xe1000000, 0xf8000000, 0x98000000, 0x11000000 , 0x69000000, 0xd9000000, 0x8e000000, 0x94000000 , 0x9b000000, 0x1e000000, 0x87000000, 0xe9000000 , 0xce000000, 0x55000000, 0x28000000, 0xdf000000 , 0x8c000000, 0xa1000000, 0x89000000, 0x0d000000 , 0xbf000000, 0xe6000000, 0x42000000, 0x68000000 , 0x41000000, 0x99000000, 0x2d000000, 0x0f000000 , 0xb0000000, 0x54000000, 0xbb000000, 0x16000000 ] {-# INLINE rsbox #-} rsbox :: Word8 -> Word8 rsbox = V.unsafeIndex tab . fromIntegral where tab = V.fromList [ 0x52, 0x09, 0x6a, 0xd5, 0x30, 0x36, 0xa5, 0x38 , 0xbf, 0x40, 0xa3, 0x9e, 0x81, 0xf3, 0xd7, 0xfb , 0x7c, 0xe3, 0x39, 0x82, 0x9b, 0x2f, 0xff, 0x87 , 0x34, 0x8e, 0x43, 0x44, 0xc4, 0xde, 0xe9, 0xcb , 0x54, 0x7b, 0x94, 0x32, 0xa6, 0xc2, 0x23, 0x3d , 0xee, 0x4c, 0x95, 0x0b, 0x42, 0xfa, 0xc3, 0x4e , 0x08, 0x2e, 0xa1, 0x66, 0x28, 0xd9, 0x24, 0xb2 , 0x76, 0x5b, 0xa2, 0x49, 0x6d, 0x8b, 0xd1, 0x25 , 0x72, 0xf8, 0xf6, 0x64, 0x86, 0x68, 0x98, 0x16 , 0xd4, 0xa4, 0x5c, 0xcc, 0x5d, 0x65, 0xb6, 0x92 , 0x6c, 0x70, 0x48, 0x50, 0xfd, 0xed, 0xb9, 0xda , 0x5e, 0x15, 0x46, 0x57, 0xa7, 0x8d, 0x9d, 0x84 , 0x90, 0xd8, 0xab, 0x00, 0x8c, 0xbc, 0xd3, 0x0a , 0xf7, 0xe4, 0x58, 0x05, 0xb8, 0xb3, 0x45, 0x06 , 0xd0, 0x2c, 0x1e, 0x8f, 0xca, 0x3f, 0x0f, 0x02 , 0xc1, 0xaf, 0xbd, 0x03, 0x01, 0x13, 0x8a, 0x6b , 0x3a, 0x91, 0x11, 0x41, 0x4f, 0x67, 0xdc, 0xea , 0x97, 0xf2, 0xcf, 0xce, 0xf0, 0xb4, 0xe6, 0x73 , 0x96, 0xac, 0x74, 0x22, 0xe7, 0xad, 0x35, 0x85 , 0xe2, 0xf9, 0x37, 0xe8, 0x1c, 0x75, 0xdf, 0x6e , 0x47, 0xf1, 0x1a, 0x71, 0x1d, 0x29, 0xc5, 0x89 , 0x6f, 0xb7, 0x62, 0x0e, 0xaa, 0x18, 0xbe, 0x1b , 0xfc, 0x56, 0x3e, 0x4b, 0xc6, 0xd2, 0x79, 0x20 , 0x9a, 0xdb, 0xc0, 0xfe, 0x78, 0xcd, 0x5a, 0xf4 , 0x1f, 0xdd, 0xa8, 0x33, 0x88, 0x07, 0xc7, 0x31 , 0xb1, 0x12, 0x10, 0x59, 0x27, 0x80, 0xec, 0x5f , 0x60, 0x51, 0x7f, 0xa9, 0x19, 0xb5, 0x4a, 0x0d , 0x2d, 0xe5, 0x7a, 0x9f, 0x93, 0xc9, 0x9c, 0xef , 0xa0, 0xe0, 0x3b, 0x4d, 0xae, 0x2a, 0xf5, 0xb0 , 0xc8, 0xeb, 0xbb, 0x3c, 0x83, 0x53, 0x99, 0x61 , 0x17, 0x2b, 0x04, 0x7e, 0xba, 0x77, 0xd6, 0x26 , 0xe1, 0x69, 0x14, 0x63, 0x55, 0x21, 0x0c, 0x7d ] rcon :: Vector Word8 rcon = V.fromList [ 0x8d, 0x01, 0x02, 0x04, 0x08, 0x10, 0x20, 0x40 , 0x80, 0x1b, 0x36, 0x6c, 0xd8, 0xab, 0x4d, 0x9a , 0x2f, 0x5e, 0xbc, 0x63, 0xc6, 0x97, 0x35, 0x6a , 0xd4, 0xb3, 0x7d, 0xfa, 0xef, 0xc5, 0x91, 0x39 , 0x72, 0xe4, 0xd3, 0xbd, 0x61, 0xc2, 0x9f, 0x25 , 0x4a, 0x94, 0x33, 0x66, 0xcc, 0x83, 0x1d, 0x3a , 0x74, 0xe8, 0xcb ] gmtab2, gmtab3, gmtab9, gmtab11, gmtab13, gmtab14 :: Vector Word8 gmtab2 = V.fromList [ 0x00, 0x02, 0x04, 0x06, 0x08, 0x0a, 0x0c, 0x0e , 0x10, 0x12, 0x14, 0x16, 0x18, 0x1a, 0x1c, 0x1e , 0x20, 0x22, 0x24, 0x26, 0x28, 0x2a, 0x2c, 0x2e , 0x30, 0x32, 0x34, 0x36, 0x38, 0x3a, 0x3c, 0x3e , 0x40, 0x42, 0x44, 0x46, 0x48, 0x4a, 0x4c, 0x4e , 0x50, 0x52, 0x54, 0x56, 0x58, 0x5a, 0x5c, 0x5e , 0x60, 0x62, 0x64, 0x66, 0x68, 0x6a, 0x6c, 0x6e , 0x70, 0x72, 0x74, 0x76, 0x78, 0x7a, 0x7c, 0x7e , 0x80, 0x82, 0x84, 0x86, 0x88, 0x8a, 0x8c, 0x8e , 0x90, 0x92, 0x94, 0x96, 0x98, 0x9a, 0x9c, 0x9e , 0xa0, 0xa2, 0xa4, 0xa6, 0xa8, 0xaa, 0xac, 0xae , 0xb0, 0xb2, 0xb4, 0xb6, 0xb8, 0xba, 0xbc, 0xbe , 0xc0, 0xc2, 0xc4, 0xc6, 0xc8, 0xca, 0xcc, 0xce , 0xd0, 0xd2, 0xd4, 0xd6, 0xd8, 0xda, 0xdc, 0xde , 0xe0, 0xe2, 0xe4, 0xe6, 0xe8, 0xea, 0xec, 0xee , 0xf0, 0xf2, 0xf4, 0xf6, 0xf8, 0xfa, 0xfc, 0xfe , 0x1b, 0x19, 0x1f, 0x1d, 0x13, 0x11, 0x17, 0x15 , 0x0b, 0x09, 0x0f, 0x0d, 0x03, 0x01, 0x07, 0x05 , 0x3b, 0x39, 0x3f, 0x3d, 0x33, 0x31, 0x37, 0x35 , 0x2b, 0x29, 0x2f, 0x2d, 0x23, 0x21, 0x27, 0x25 , 0x5b, 0x59, 0x5f, 0x5d, 0x53, 0x51, 0x57, 0x55 , 0x4b, 0x49, 0x4f, 0x4d, 0x43, 0x41, 0x47, 0x45 , 0x7b, 0x79, 0x7f, 0x7d, 0x73, 0x71, 0x77, 0x75 , 0x6b, 0x69, 0x6f, 0x6d, 0x63, 0x61, 0x67, 0x65 , 0x9b, 0x99, 0x9f, 0x9d, 0x93, 0x91, 0x97, 0x95 , 0x8b, 0x89, 0x8f, 0x8d, 0x83, 0x81, 0x87, 0x85 , 0xbb, 0xb9, 0xbf, 0xbd, 0xb3, 0xb1, 0xb7, 0xb5 , 0xab, 0xa9, 0xaf, 0xad, 0xa3, 0xa1, 0xa7, 0xa5 , 0xdb, 0xd9, 0xdf, 0xdd, 0xd3, 0xd1, 0xd7, 0xd5 , 0xcb, 0xc9, 0xcf, 0xcd, 0xc3, 0xc1, 0xc7, 0xc5 , 0xfb, 0xf9, 0xff, 0xfd, 0xf3, 0xf1, 0xf7, 0xf5 , 0xeb, 0xe9, 0xef, 0xed, 0xe3, 0xe1, 0xe7, 0xe5 ] gmtab3 = V.fromList [ 0x00, 0x03, 0x06, 0x05, 0x0c, 0x0f, 0x0a, 0x09 , 0x18, 0x1b, 0x1e, 0x1d, 0x14, 0x17, 0x12, 0x11 , 0x30, 0x33, 0x36, 0x35, 0x3c, 0x3f, 0x3a, 0x39 , 0x28, 0x2b, 0x2e, 0x2d, 0x24, 0x27, 0x22, 0x21 , 0x60, 0x63, 0x66, 0x65, 0x6c, 0x6f, 0x6a, 0x69 , 0x78, 0x7b, 0x7e, 0x7d, 0x74, 0x77, 0x72, 0x71 , 0x50, 0x53, 0x56, 0x55, 0x5c, 0x5f, 0x5a, 0x59 , 0x48, 0x4b, 0x4e, 0x4d, 0x44, 0x47, 0x42, 0x41 , 0xc0, 0xc3, 0xc6, 0xc5, 0xcc, 0xcf, 0xca, 0xc9 , 0xd8, 0xdb, 0xde, 0xdd, 0xd4, 0xd7, 0xd2, 0xd1 , 0xf0, 0xf3, 0xf6, 0xf5, 0xfc, 0xff, 0xfa, 0xf9 , 0xe8, 0xeb, 0xee, 0xed, 0xe4, 0xe7, 0xe2, 0xe1 , 0xa0, 0xa3, 0xa6, 0xa5, 0xac, 0xaf, 0xaa, 0xa9 , 0xb8, 0xbb, 0xbe, 0xbd, 0xb4, 0xb7, 0xb2, 0xb1 , 0x90, 0x93, 0x96, 0x95, 0x9c, 0x9f, 0x9a, 0x99 , 0x88, 0x8b, 0x8e, 0x8d, 0x84, 0x87, 0x82, 0x81 , 0x9b, 0x98, 0x9d, 0x9e, 0x97, 0x94, 0x91, 0x92 , 0x83, 0x80, 0x85, 0x86, 0x8f, 0x8c, 0x89, 0x8a , 0xab, 0xa8, 0xad, 0xae, 0xa7, 0xa4, 0xa1, 0xa2 , 0xb3, 0xb0, 0xb5, 0xb6, 0xbf, 0xbc, 0xb9, 0xba , 0xfb, 0xf8, 0xfd, 0xfe, 0xf7, 0xf4, 0xf1, 0xf2 , 0xe3, 0xe0, 0xe5, 0xe6, 0xef, 0xec, 0xe9, 0xea , 0xcb, 0xc8, 0xcd, 0xce, 0xc7, 0xc4, 0xc1, 0xc2 , 0xd3, 0xd0, 0xd5, 0xd6, 0xdf, 0xdc, 0xd9, 0xda , 0x5b, 0x58, 0x5d, 0x5e, 0x57, 0x54, 0x51, 0x52 , 0x43, 0x40, 0x45, 0x46, 0x4f, 0x4c, 0x49, 0x4a , 0x6b, 0x68, 0x6d, 0x6e, 0x67, 0x64, 0x61, 0x62 , 0x73, 0x70, 0x75, 0x76, 0x7f, 0x7c, 0x79, 0x7a , 0x3b, 0x38, 0x3d, 0x3e, 0x37, 0x34, 0x31, 0x32 , 0x23, 0x20, 0x25, 0x26, 0x2f, 0x2c, 0x29, 0x2a , 0x0b, 0x08, 0x0d, 0x0e, 0x07, 0x04, 0x01, 0x02 , 0x13, 0x10, 0x15, 0x16, 0x1f, 0x1c, 0x19, 0x1a ] gmtab9 = V.fromList [ 0x00, 0x09, 0x12, 0x1b, 0x24, 0x2d, 0x36, 0x3f , 0x48, 0x41, 0x5a, 0x53, 0x6c, 0x65, 0x7e, 0x77 , 0x90, 0x99, 0x82, 0x8b, 0xb4, 0xbd, 0xa6, 0xaf , 0xd8, 0xd1, 0xca, 0xc3, 0xfc, 0xf5, 0xee, 0xe7 , 0x3b, 0x32, 0x29, 0x20, 0x1f, 0x16, 0x0d, 0x04 , 0x73, 0x7a, 0x61, 0x68, 0x57, 0x5e, 0x45, 0x4c , 0xab, 0xa2, 0xb9, 0xb0, 0x8f, 0x86, 0x9d, 0x94 , 0xe3, 0xea, 0xf1, 0xf8, 0xc7, 0xce, 0xd5, 0xdc , 0x76, 0x7f, 0x64, 0x6d, 0x52, 0x5b, 0x40, 0x49 , 0x3e, 0x37, 0x2c, 0x25, 0x1a, 0x13, 0x08, 0x01 , 0xe6, 0xef, 0xf4, 0xfd, 0xc2, 0xcb, 0xd0, 0xd9 , 0xae, 0xa7, 0xbc, 0xb5, 0x8a, 0x83, 0x98, 0x91 , 0x4d, 0x44, 0x5f, 0x56, 0x69, 0x60, 0x7b, 0x72 , 0x05, 0x0c, 0x17, 0x1e, 0x21, 0x28, 0x33, 0x3a , 0xdd, 0xd4, 0xcf, 0xc6, 0xf9, 0xf0, 0xeb, 0xe2 , 0x95, 0x9c, 0x87, 0x8e, 0xb1, 0xb8, 0xa3, 0xaa , 0xec, 0xe5, 0xfe, 0xf7, 0xc8, 0xc1, 0xda, 0xd3 , 0xa4, 0xad, 0xb6, 0xbf, 0x80, 0x89, 0x92, 0x9b , 0x7c, 0x75, 0x6e, 0x67, 0x58, 0x51, 0x4a, 0x43 , 0x34, 0x3d, 0x26, 0x2f, 0x10, 0x19, 0x02, 0x0b , 0xd7, 0xde, 0xc5, 0xcc, 0xf3, 0xfa, 0xe1, 0xe8 , 0x9f, 0x96, 0x8d, 0x84, 0xbb, 0xb2, 0xa9, 0xa0 , 0x47, 0x4e, 0x55, 0x5c, 0x63, 0x6a, 0x71, 0x78 , 0x0f, 0x06, 0x1d, 0x14, 0x2b, 0x22, 0x39, 0x30 , 0x9a, 0x93, 0x88, 0x81, 0xbe, 0xb7, 0xac, 0xa5 , 0xd2, 0xdb, 0xc0, 0xc9, 0xf6, 0xff, 0xe4, 0xed , 0x0a, 0x03, 0x18, 0x11, 0x2e, 0x27, 0x3c, 0x35 , 0x42, 0x4b, 0x50, 0x59, 0x66, 0x6f, 0x74, 0x7d , 0xa1, 0xa8, 0xb3, 0xba, 0x85, 0x8c, 0x97, 0x9e , 0xe9, 0xe0, 0xfb, 0xf2, 0xcd, 0xc4, 0xdf, 0xd6 , 0x31, 0x38, 0x23, 0x2a, 0x15, 0x1c, 0x07, 0x0e , 0x79, 0x70, 0x6b, 0x62, 0x5d, 0x54, 0x4f, 0x46 ] gmtab11 = V.fromList [ 0x00, 0x0b, 0x16, 0x1d, 0x2c, 0x27, 0x3a, 0x31 , 0x58, 0x53, 0x4e, 0x45, 0x74, 0x7f, 0x62, 0x69 , 0xb0, 0xbb, 0xa6, 0xad, 0x9c, 0x97, 0x8a, 0x81 , 0xe8, 0xe3, 0xfe, 0xf5, 0xc4, 0xcf, 0xd2, 0xd9 , 0x7b, 0x70, 0x6d, 0x66, 0x57, 0x5c, 0x41, 0x4a , 0x23, 0x28, 0x35, 0x3e, 0x0f, 0x04, 0x19, 0x12 , 0xcb, 0xc0, 0xdd, 0xd6, 0xe7, 0xec, 0xf1, 0xfa , 0x93, 0x98, 0x85, 0x8e, 0xbf, 0xb4, 0xa9, 0xa2 , 0xf6, 0xfd, 0xe0, 0xeb, 0xda, 0xd1, 0xcc, 0xc7 , 0xae, 0xa5, 0xb8, 0xb3, 0x82, 0x89, 0x94, 0x9f , 0x46, 0x4d, 0x50, 0x5b, 0x6a, 0x61, 0x7c, 0x77 , 0x1e, 0x15, 0x08, 0x03, 0x32, 0x39, 0x24, 0x2f , 0x8d, 0x86, 0x9b, 0x90, 0xa1, 0xaa, 0xb7, 0xbc , 0xd5, 0xde, 0xc3, 0xc8, 0xf9, 0xf2, 0xef, 0xe4 , 0x3d, 0x36, 0x2b, 0x20, 0x11, 0x1a, 0x07, 0x0c , 0x65, 0x6e, 0x73, 0x78, 0x49, 0x42, 0x5f, 0x54 , 0xf7, 0xfc, 0xe1, 0xea, 0xdb, 0xd0, 0xcd, 0xc6 , 0xaf, 0xa4, 0xb9, 0xb2, 0x83, 0x88, 0x95, 0x9e , 0x47, 0x4c, 0x51, 0x5a, 0x6b, 0x60, 0x7d, 0x76 , 0x1f, 0x14, 0x09, 0x02, 0x33, 0x38, 0x25, 0x2e , 0x8c, 0x87, 0x9a, 0x91, 0xa0, 0xab, 0xb6, 0xbd , 0xd4, 0xdf, 0xc2, 0xc9, 0xf8, 0xf3, 0xee, 0xe5 , 0x3c, 0x37, 0x2a, 0x21, 0x10, 0x1b, 0x06, 0x0d , 0x64, 0x6f, 0x72, 0x79, 0x48, 0x43, 0x5e, 0x55 , 0x01, 0x0a, 0x17, 0x1c, 0x2d, 0x26, 0x3b, 0x30 , 0x59, 0x52, 0x4f, 0x44, 0x75, 0x7e, 0x63, 0x68 , 0xb1, 0xba, 0xa7, 0xac, 0x9d, 0x96, 0x8b, 0x80 , 0xe9, 0xe2, 0xff, 0xf4, 0xc5, 0xce, 0xd3, 0xd8 , 0x7a, 0x71, 0x6c, 0x67, 0x56, 0x5d, 0x40, 0x4b , 0x22, 0x29, 0x34, 0x3f, 0x0e, 0x05, 0x18, 0x13 , 0xca, 0xc1, 0xdc, 0xd7, 0xe6, 0xed, 0xf0, 0xfb , 0x92, 0x99, 0x84, 0x8f, 0xbe, 0xb5, 0xa8, 0xa3 ] gmtab13 = V.fromList [ 0x00, 0x0d, 0x1a, 0x17, 0x34, 0x39, 0x2e, 0x23 , 0x68, 0x65, 0x72, 0x7f, 0x5c, 0x51, 0x46, 0x4b , 0xd0, 0xdd, 0xca, 0xc7, 0xe4, 0xe9, 0xfe, 0xf3 , 0xb8, 0xb5, 0xa2, 0xaf, 0x8c, 0x81, 0x96, 0x9b , 0xbb, 0xb6, 0xa1, 0xac, 0x8f, 0x82, 0x95, 0x98 , 0xd3, 0xde, 0xc9, 0xc4, 0xe7, 0xea, 0xfd, 0xf0 , 0x6b, 0x66, 0x71, 0x7c, 0x5f, 0x52, 0x45, 0x48 , 0x03, 0x0e, 0x19, 0x14, 0x37, 0x3a, 0x2d, 0x20 , 0x6d, 0x60, 0x77, 0x7a, 0x59, 0x54, 0x43, 0x4e , 0x05, 0x08, 0x1f, 0x12, 0x31, 0x3c, 0x2b, 0x26 , 0xbd, 0xb0, 0xa7, 0xaa, 0x89, 0x84, 0x93, 0x9e , 0xd5, 0xd8, 0xcf, 0xc2, 0xe1, 0xec, 0xfb, 0xf6 , 0xd6, 0xdb, 0xcc, 0xc1, 0xe2, 0xef, 0xf8, 0xf5 , 0xbe, 0xb3, 0xa4, 0xa9, 0x8a, 0x87, 0x90, 0x9d , 0x06, 0x0b, 0x1c, 0x11, 0x32, 0x3f, 0x28, 0x25 , 0x6e, 0x63, 0x74, 0x79, 0x5a, 0x57, 0x40, 0x4d , 0xda, 0xd7, 0xc0, 0xcd, 0xee, 0xe3, 0xf4, 0xf9 , 0xb2, 0xbf, 0xa8, 0xa5, 0x86, 0x8b, 0x9c, 0x91 , 0x0a, 0x07, 0x10, 0x1d, 0x3e, 0x33, 0x24, 0x29 , 0x62, 0x6f, 0x78, 0x75, 0x56, 0x5b, 0x4c, 0x41 , 0x61, 0x6c, 0x7b, 0x76, 0x55, 0x58, 0x4f, 0x42 , 0x09, 0x04, 0x13, 0x1e, 0x3d, 0x30, 0x27, 0x2a , 0xb1, 0xbc, 0xab, 0xa6, 0x85, 0x88, 0x9f, 0x92 , 0xd9, 0xd4, 0xc3, 0xce, 0xed, 0xe0, 0xf7, 0xfa , 0xb7, 0xba, 0xad, 0xa0, 0x83, 0x8e, 0x99, 0x94 , 0xdf, 0xd2, 0xc5, 0xc8, 0xeb, 0xe6, 0xf1, 0xfc , 0x67, 0x6a, 0x7d, 0x70, 0x53, 0x5e, 0x49, 0x44 , 0x0f, 0x02, 0x15, 0x18, 0x3b, 0x36, 0x21, 0x2c , 0x0c, 0x01, 0x16, 0x1b, 0x38, 0x35, 0x22, 0x2f , 0x64, 0x69, 0x7e, 0x73, 0x50, 0x5d, 0x4a, 0x47 , 0xdc, 0xd1, 0xc6, 0xcb, 0xe8, 0xe5, 0xf2, 0xff , 0xb4, 0xb9, 0xae, 0xa3, 0x80, 0x8d, 0x9a, 0x97 ] gmtab14 = V.fromList [ 0x00, 0x0e, 0x1c, 0x12, 0x38, 0x36, 0x24, 0x2a , 0x70, 0x7e, 0x6c, 0x62, 0x48, 0x46, 0x54, 0x5a , 0xe0, 0xee, 0xfc, 0xf2, 0xd8, 0xd6, 0xc4, 0xca , 0x90, 0x9e, 0x8c, 0x82, 0xa8, 0xa6, 0xb4, 0xba , 0xdb, 0xd5, 0xc7, 0xc9, 0xe3, 0xed, 0xff, 0xf1 , 0xab, 0xa5, 0xb7, 0xb9, 0x93, 0x9d, 0x8f, 0x81 , 0x3b, 0x35, 0x27, 0x29, 0x03, 0x0d, 0x1f, 0x11 , 0x4b, 0x45, 0x57, 0x59, 0x73, 0x7d, 0x6f, 0x61 , 0xad, 0xa3, 0xb1, 0xbf, 0x95, 0x9b, 0x89, 0x87 , 0xdd, 0xd3, 0xc1, 0xcf, 0xe5, 0xeb, 0xf9, 0xf7 , 0x4d, 0x43, 0x51, 0x5f, 0x75, 0x7b, 0x69, 0x67 , 0x3d, 0x33, 0x21, 0x2f, 0x05, 0x0b, 0x19, 0x17 , 0x76, 0x78, 0x6a, 0x64, 0x4e, 0x40, 0x52, 0x5c , 0x06, 0x08, 0x1a, 0x14, 0x3e, 0x30, 0x22, 0x2c , 0x96, 0x98, 0x8a, 0x84, 0xae, 0xa0, 0xb2, 0xbc , 0xe6, 0xe8, 0xfa, 0xf4, 0xde, 0xd0, 0xc2, 0xcc , 0x41, 0x4f, 0x5d, 0x53, 0x79, 0x77, 0x65, 0x6b , 0x31, 0x3f, 0x2d, 0x23, 0x09, 0x07, 0x15, 0x1b , 0xa1, 0xaf, 0xbd, 0xb3, 0x99, 0x97, 0x85, 0x8b , 0xd1, 0xdf, 0xcd, 0xc3, 0xe9, 0xe7, 0xf5, 0xfb , 0x9a, 0x94, 0x86, 0x88, 0xa2, 0xac, 0xbe, 0xb0 , 0xea, 0xe4, 0xf6, 0xf8, 0xd2, 0xdc, 0xce, 0xc0 , 0x7a, 0x74, 0x66, 0x68, 0x42, 0x4c, 0x5e, 0x50 , 0x0a, 0x04, 0x16, 0x18, 0x32, 0x3c, 0x2e, 0x20 , 0xec, 0xe2, 0xf0, 0xfe, 0xd4, 0xda, 0xc8, 0xc6 , 0x9c, 0x92, 0x80, 0x8e, 0xa4, 0xaa, 0xb8, 0xb6 , 0x0c, 0x02, 0x10, 0x1e, 0x34, 0x3a, 0x28, 0x26 , 0x7c, 0x72, 0x60, 0x6e, 0x44, 0x4a, 0x58, 0x56 , 0x37, 0x39, 0x2b, 0x25, 0x0f, 0x01, 0x13, 0x1d , 0x47, 0x49, 0x5b, 0x55, 0x7f, 0x71, 0x63, 0x6d , 0xd7, 0xd9, 0xcb, 0xc5, 0xef, 0xe1, 0xf3, 0xfd , 0xa7, 0xa9, 0xbb, 0xb5, 0x9f, 0x91, 0x83, 0x8d ]