summaryrefslogtreecommitdiffstats
path: root/src/modules/rijndael
diff options
context:
space:
mode:
Diffstat (limited to 'src/modules/rijndael')
-rw-r--r--src/modules/rijndael/Makefile.am23
-rw-r--r--src/modules/rijndael/ablowfish.cpp632
-rw-r--r--src/modules/rijndael/ablowfish.h141
-rw-r--r--src/modules/rijndael/caps/Makefile.am9
-rw-r--r--src/modules/rijndael/caps/rijndael1
-rw-r--r--src/modules/rijndael/libkvirijndael.cpp853
-rw-r--r--src/modules/rijndael/libkvirijndael.h169
-rw-r--r--src/modules/rijndael/rijndael.cpp1626
-rw-r--r--src/modules/rijndael/rijndael.h153
9 files changed, 3607 insertions, 0 deletions
diff --git a/src/modules/rijndael/Makefile.am b/src/modules/rijndael/Makefile.am
new file mode 100644
index 00000000..69b2fe01
--- /dev/null
+++ b/src/modules/rijndael/Makefile.am
@@ -0,0 +1,23 @@
+###############################################################################
+# KVirc IRC client Makefile - 10.03.2000 Szymon Stefanek <stefanek@tin.it>
+###############################################################################
+
+SUBDIRS = caps
+
+AM_CPPFLAGS = -I$(SS_TOPSRCDIR)/src/kvilib/include/ -I$(SS_TOPSRCDIR)/src/kvirc/include/ \
+$(SS_INCDIRS) $(SS_CPPFLAGS) -DGLOBAL_KVIRC_DIR=\"$(globalkvircdir)\"
+
+pluglib_LTLIBRARIES = libkvirijndael.la
+
+libkvirijndael_la_LDFLAGS = -module -avoid-version $(SS_LDFLAGS) $(SS_LIBDIRS)
+
+libkvirijndael_la_SOURCES = libkvirijndael.cpp rijndael.cpp ablowfish.cpp
+libkvirijndael_la_LIBADD = $(SS_LIBLINK) ../../kvilib/build/libkvilib.la
+
+noinst_HEADERS= libkvirijndael.h rijndael.h ablowfish.h
+
+
+%.moc: %.h
+ $(SS_QT_MOC) $< -o $@
+
+libkvirijndael.cpp: libkvirijndael.moc
diff --git a/src/modules/rijndael/ablowfish.cpp b/src/modules/rijndael/ablowfish.cpp
new file mode 100644
index 00000000..c56ff36a
--- /dev/null
+++ b/src/modules/rijndael/ablowfish.cpp
@@ -0,0 +1,632 @@
+//
+// File : ablowfish.cpp
+// Creation date : Wed Jan 13 2005 02:04:10 CEST by Szymon Stefanek
+//
+// This file is part of the KVirc irc client distribution
+// Copyright (C) 2005 Szymon Stefanek (pragma at kvirc dot net)
+//
+// This program is FREE software. You can redistribute it and/or
+// modify it under the terms of the GNU General Public License
+// as published by the Free Software Foundation; either version 2
+// of the License, or (at your opinion) any later version.
+//
+// This program is distributed in the HOPE that it will be USEFUL,
+// but WITHOUT ANY WARRANTY; without even the implied warranty of
+// MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
+// See the GNU General Public License for more details.
+//
+// You should have received a copy of the GNU General Public License
+// along with this program. If not, write to the Free Software Foundation,
+// Inc. ,51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
+//
+
+#include "ablowfish.h"
+#include "kvi_memmove.h"
+
+#ifdef COMPILE_CRYPT_SUPPORT
+
+
+//Initialization with a fixed string which consists of the hexadecimal digits of PI (less the initial 3)
+//P-array, 18 32-bit subkeys
+const unsigned int BlowFish::scm_auiInitP[18] = {
+ 0x243f6a88, 0x85a308d3, 0x13198a2e, 0x03707344,
+ 0xa4093822, 0x299f31d0, 0x082efa98, 0xec4e6c89,
+ 0x452821e6, 0x38d01377, 0xbe5466cf, 0x34e90c6c,
+ 0xc0ac29b7, 0xc97c50dd, 0x3f84d5b5, 0xb5470917,
+ 0x9216d5d9, 0x8979fb1b
+};
+
+//Four 32-bit S-boxes with 256 entries each
+const unsigned int BlowFish::scm_auiInitS[4][256] = {
+ //0
+ {0xd1310ba6, 0x98dfb5ac, 0x2ffd72db, 0xd01adfb7,
+ 0xb8e1afed, 0x6a267e96, 0xba7c9045, 0xf12c7f99,
+ 0x24a19947, 0xb3916cf7, 0x0801f2e2, 0x858efc16,
+ 0x636920d8, 0x71574e69, 0xa458fea3, 0xf4933d7e,
+ 0x0d95748f, 0x728eb658, 0x718bcd58, 0x82154aee,
+ 0x7b54a41d, 0xc25a59b5, 0x9c30d539, 0x2af26013,
+ 0xc5d1b023, 0x286085f0, 0xca417918, 0xb8db38ef,
+ 0x8e79dcb0, 0x603a180e, 0x6c9e0e8b, 0xb01e8a3e,
+ 0xd71577c1, 0xbd314b27, 0x78af2fda, 0x55605c60,
+ 0xe65525f3, 0xaa55ab94, 0x57489862, 0x63e81440,
+ 0x55ca396a, 0x2aab10b6, 0xb4cc5c34, 0x1141e8ce,
+ 0xa15486af, 0x7c72e993, 0xb3ee1411, 0x636fbc2a,
+ 0x2ba9c55d, 0x741831f6, 0xce5c3e16, 0x9b87931e,
+ 0xafd6ba33, 0x6c24cf5c, 0x7a325381, 0x28958677,
+ 0x3b8f4898, 0x6b4bb9af, 0xc4bfe81b, 0x66282193,
+ 0x61d809cc, 0xfb21a991, 0x487cac60, 0x5dec8032,
+ 0xef845d5d, 0xe98575b1, 0xdc262302, 0xeb651b88,
+ 0x23893e81, 0xd396acc5, 0x0f6d6ff3, 0x83f44239,
+ 0x2e0b4482, 0xa4842004, 0x69c8f04a, 0x9e1f9b5e,
+ 0x21c66842, 0xf6e96c9a, 0x670c9c61, 0xabd388f0,
+ 0x6a51a0d2, 0xd8542f68, 0x960fa728, 0xab5133a3,
+ 0x6eef0b6c, 0x137a3be4, 0xba3bf050, 0x7efb2a98,
+ 0xa1f1651d, 0x39af0176, 0x66ca593e, 0x82430e88,
+ 0x8cee8619, 0x456f9fb4, 0x7d84a5c3, 0x3b8b5ebe,
+ 0xe06f75d8, 0x85c12073, 0x401a449f, 0x56c16aa6,
+ 0x4ed3aa62, 0x363f7706, 0x1bfedf72, 0x429b023d,
+ 0x37d0d724, 0xd00a1248, 0xdb0fead3, 0x49f1c09b,
+ 0x075372c9, 0x80991b7b, 0x25d479d8, 0xf6e8def7,
+ 0xe3fe501a, 0xb6794c3b, 0x976ce0bd, 0x04c006ba,
+ 0xc1a94fb6, 0x409f60c4, 0x5e5c9ec2, 0x196a2463,
+ 0x68fb6faf, 0x3e6c53b5, 0x1339b2eb, 0x3b52ec6f,
+ 0x6dfc511f, 0x9b30952c, 0xcc814544, 0xaf5ebd09,
+ 0xbee3d004, 0xde334afd, 0x660f2807, 0x192e4bb3,
+ 0xc0cba857, 0x45c8740f, 0xd20b5f39, 0xb9d3fbdb,
+ 0x5579c0bd, 0x1a60320a, 0xd6a100c6, 0x402c7279,
+ 0x679f25fe, 0xfb1fa3cc, 0x8ea5e9f8, 0xdb3222f8,
+ 0x3c7516df, 0xfd616b15, 0x2f501ec8, 0xad0552ab,
+ 0x323db5fa, 0xfd238760, 0x53317b48, 0x3e00df82,
+ 0x9e5c57bb, 0xca6f8ca0, 0x1a87562e, 0xdf1769db,
+ 0xd542a8f6, 0x287effc3, 0xac6732c6, 0x8c4f5573,
+ 0x695b27b0, 0xbbca58c8, 0xe1ffa35d, 0xb8f011a0,
+ 0x10fa3d98, 0xfd2183b8, 0x4afcb56c, 0x2dd1d35b,
+ 0x9a53e479, 0xb6f84565, 0xd28e49bc, 0x4bfb9790,
+ 0xe1ddf2da, 0xa4cb7e33, 0x62fb1341, 0xcee4c6e8,
+ 0xef20cada, 0x36774c01, 0xd07e9efe, 0x2bf11fb4,
+ 0x95dbda4d, 0xae909198, 0xeaad8e71, 0x6b93d5a0,
+ 0xd08ed1d0, 0xafc725e0, 0x8e3c5b2f, 0x8e7594b7,
+ 0x8ff6e2fb, 0xf2122b64, 0x8888b812, 0x900df01c,
+ 0x4fad5ea0, 0x688fc31c, 0xd1cff191, 0xb3a8c1ad,
+ 0x2f2f2218, 0xbe0e1777, 0xea752dfe, 0x8b021fa1,
+ 0xe5a0cc0f, 0xb56f74e8, 0x18acf3d6, 0xce89e299,
+ 0xb4a84fe0, 0xfd13e0b7, 0x7cc43b81, 0xd2ada8d9,
+ 0x165fa266, 0x80957705, 0x93cc7314, 0x211a1477,
+ 0xe6ad2065, 0x77b5fa86, 0xc75442f5, 0xfb9d35cf,
+ 0xebcdaf0c, 0x7b3e89a0, 0xd6411bd3, 0xae1e7e49,
+ 0x00250e2d, 0x2071b35e, 0x226800bb, 0x57b8e0af,
+ 0x2464369b, 0xf009b91e, 0x5563911d, 0x59dfa6aa,
+ 0x78c14389, 0xd95a537f, 0x207d5ba2, 0x02e5b9c5,
+ 0x83260376, 0x6295cfa9, 0x11c81968, 0x4e734a41,
+ 0xb3472dca, 0x7b14a94a, 0x1b510052, 0x9a532915,
+ 0xd60f573f, 0xbc9bc6e4, 0x2b60a476, 0x81e67400,
+ 0x08ba6fb5, 0x571be91f, 0xf296ec6b, 0x2a0dd915,
+ 0xb6636521, 0xe7b9f9b6, 0xff34052e, 0xc5855664,
+ 0x53b02d5d, 0xa99f8fa1, 0x08ba4799, 0x6e85076a},
+
+ //1
+ {0x4b7a70e9, 0xb5b32944, 0xdb75092e, 0xc4192623,
+ 0xad6ea6b0, 0x49a7df7d, 0x9cee60b8, 0x8fedb266,
+ 0xecaa8c71, 0x699a17ff, 0x5664526c, 0xc2b19ee1,
+ 0x193602a5, 0x75094c29, 0xa0591340, 0xe4183a3e,
+ 0x3f54989a, 0x5b429d65, 0x6b8fe4d6, 0x99f73fd6,
+ 0xa1d29c07, 0xefe830f5, 0x4d2d38e6, 0xf0255dc1,
+ 0x4cdd2086, 0x8470eb26, 0x6382e9c6, 0x021ecc5e,
+ 0x09686b3f, 0x3ebaefc9, 0x3c971814, 0x6b6a70a1,
+ 0x687f3584, 0x52a0e286, 0xb79c5305, 0xaa500737,
+ 0x3e07841c, 0x7fdeae5c, 0x8e7d44ec, 0x5716f2b8,
+ 0xb03ada37, 0xf0500c0d, 0xf01c1f04, 0x0200b3ff,
+ 0xae0cf51a, 0x3cb574b2, 0x25837a58, 0xdc0921bd,
+ 0xd19113f9, 0x7ca92ff6, 0x94324773, 0x22f54701,
+ 0x3ae5e581, 0x37c2dadc, 0xc8b57634, 0x9af3dda7,
+ 0xa9446146, 0x0fd0030e, 0xecc8c73e, 0xa4751e41,
+ 0xe238cd99, 0x3bea0e2f, 0x3280bba1, 0x183eb331,
+ 0x4e548b38, 0x4f6db908, 0x6f420d03, 0xf60a04bf,
+ 0x2cb81290, 0x24977c79, 0x5679b072, 0xbcaf89af,
+ 0xde9a771f, 0xd9930810, 0xb38bae12, 0xdccf3f2e,
+ 0x5512721f, 0x2e6b7124, 0x501adde6, 0x9f84cd87,
+ 0x7a584718, 0x7408da17, 0xbc9f9abc, 0xe94b7d8c,
+ 0xec7aec3a, 0xdb851dfa, 0x63094366, 0xc464c3d2,
+ 0xef1c1847, 0x3215d908, 0xdd433b37, 0x24c2ba16,
+ 0x12a14d43, 0x2a65c451, 0x50940002, 0x133ae4dd,
+ 0x71dff89e, 0x10314e55, 0x81ac77d6, 0x5f11199b,
+ 0x043556f1, 0xd7a3c76b, 0x3c11183b, 0x5924a509,
+ 0xf28fe6ed, 0x97f1fbfa, 0x9ebabf2c, 0x1e153c6e,
+ 0x86e34570, 0xeae96fb1, 0x860e5e0a, 0x5a3e2ab3,
+ 0x771fe71c, 0x4e3d06fa, 0x2965dcb9, 0x99e71d0f,
+ 0x803e89d6, 0x5266c825, 0x2e4cc978, 0x9c10b36a,
+ 0xc6150eba, 0x94e2ea78, 0xa5fc3c53, 0x1e0a2df4,
+ 0xf2f74ea7, 0x361d2b3d, 0x1939260f, 0x19c27960,
+ 0x5223a708, 0xf71312b6, 0xebadfe6e, 0xeac31f66,
+ 0xe3bc4595, 0xa67bc883, 0xb17f37d1, 0x018cff28,
+ 0xc332ddef, 0xbe6c5aa5, 0x65582185, 0x68ab9802,
+ 0xeecea50f, 0xdb2f953b, 0x2aef7dad, 0x5b6e2f84,
+ 0x1521b628, 0x29076170, 0xecdd4775, 0x619f1510,
+ 0x13cca830, 0xeb61bd96, 0x0334fe1e, 0xaa0363cf,
+ 0xb5735c90, 0x4c70a239, 0xd59e9e0b, 0xcbaade14,
+ 0xeecc86bc, 0x60622ca7, 0x9cab5cab, 0xb2f3846e,
+ 0x648b1eaf, 0x19bdf0ca, 0xa02369b9, 0x655abb50,
+ 0x40685a32, 0x3c2ab4b3, 0x319ee9d5, 0xc021b8f7,
+ 0x9b540b19, 0x875fa099, 0x95f7997e, 0x623d7da8,
+ 0xf837889a, 0x97e32d77, 0x11ed935f, 0x16681281,
+ 0x0e358829, 0xc7e61fd6, 0x96dedfa1, 0x7858ba99,
+ 0x57f584a5, 0x1b227263, 0x9b83c3ff, 0x1ac24696,
+ 0xcdb30aeb, 0x532e3054, 0x8fd948e4, 0x6dbc3128,
+ 0x58ebf2ef, 0x34c6ffea, 0xfe28ed61, 0xee7c3c73,
+ 0x5d4a14d9, 0xe864b7e3, 0x42105d14, 0x203e13e0,
+ 0x45eee2b6, 0xa3aaabea, 0xdb6c4f15, 0xfacb4fd0,
+ 0xc742f442, 0xef6abbb5, 0x654f3b1d, 0x41cd2105,
+ 0xd81e799e, 0x86854dc7, 0xe44b476a, 0x3d816250,
+ 0xcf62a1f2, 0x5b8d2646, 0xfc8883a0, 0xc1c7b6a3,
+ 0x7f1524c3, 0x69cb7492, 0x47848a0b, 0x5692b285,
+ 0x095bbf00, 0xad19489d, 0x1462b174, 0x23820e00,
+ 0x58428d2a, 0x0c55f5ea, 0x1dadf43e, 0x233f7061,
+ 0x3372f092, 0x8d937e41, 0xd65fecf1, 0x6c223bdb,
+ 0x7cde3759, 0xcbee7460, 0x4085f2a7, 0xce77326e,
+ 0xa6078084, 0x19f8509e, 0xe8efd855, 0x61d99735,
+ 0xa969a7aa, 0xc50c06c2, 0x5a04abfc, 0x800bcadc,
+ 0x9e447a2e, 0xc3453484, 0xfdd56705, 0x0e1e9ec9,
+ 0xdb73dbd3, 0x105588cd, 0x675fda79, 0xe3674340,
+ 0xc5c43465, 0x713e38d8, 0x3d28f89e, 0xf16dff20,
+ 0x153e21e7, 0x8fb03d4a, 0xe6e39f2b, 0xdb83adf7},
+
+ //2
+ {0xe93d5a68, 0x948140f7, 0xf64c261c, 0x94692934,
+ 0x411520f7, 0x7602d4f7, 0xbcf46b2e, 0xd4a20068,
+ 0xd4082471, 0x3320f46a, 0x43b7d4b7, 0x500061af,
+ 0x1e39f62e, 0x97244546, 0x14214f74, 0xbf8b8840,
+ 0x4d95fc1d, 0x96b591af, 0x70f4ddd3, 0x66a02f45,
+ 0xbfbc09ec, 0x03bd9785, 0x7fac6dd0, 0x31cb8504,
+ 0x96eb27b3, 0x55fd3941, 0xda2547e6, 0xabca0a9a,
+ 0x28507825, 0x530429f4, 0x0a2c86da, 0xe9b66dfb,
+ 0x68dc1462, 0xd7486900, 0x680ec0a4, 0x27a18dee,
+ 0x4f3ffea2, 0xe887ad8c, 0xb58ce006, 0x7af4d6b6,
+ 0xaace1e7c, 0xd3375fec, 0xce78a399, 0x406b2a42,
+ 0x20fe9e35, 0xd9f385b9, 0xee39d7ab, 0x3b124e8b,
+ 0x1dc9faf7, 0x4b6d1856, 0x26a36631, 0xeae397b2,
+ 0x3a6efa74, 0xdd5b4332, 0x6841e7f7, 0xca7820fb,
+ 0xfb0af54e, 0xd8feb397, 0x454056ac, 0xba489527,
+ 0x55533a3a, 0x20838d87, 0xfe6ba9b7, 0xd096954b,
+ 0x55a867bc, 0xa1159a58, 0xcca92963, 0x99e1db33,
+ 0xa62a4a56, 0x3f3125f9, 0x5ef47e1c, 0x9029317c,
+ 0xfdf8e802, 0x04272f70, 0x80bb155c, 0x05282ce3,
+ 0x95c11548, 0xe4c66d22, 0x48c1133f, 0xc70f86dc,
+ 0x07f9c9ee, 0x41041f0f, 0x404779a4, 0x5d886e17,
+ 0x325f51eb, 0xd59bc0d1, 0xf2bcc18f, 0x41113564,
+ 0x257b7834, 0x602a9c60, 0xdff8e8a3, 0x1f636c1b,
+ 0x0e12b4c2, 0x02e1329e, 0xaf664fd1, 0xcad18115,
+ 0x6b2395e0, 0x333e92e1, 0x3b240b62, 0xeebeb922,
+ 0x85b2a20e, 0xe6ba0d99, 0xde720c8c, 0x2da2f728,
+ 0xd0127845, 0x95b794fd, 0x647d0862, 0xe7ccf5f0,
+ 0x5449a36f, 0x877d48fa, 0xc39dfd27, 0xf33e8d1e,
+ 0x0a476341, 0x992eff74, 0x3a6f6eab, 0xf4f8fd37,
+ 0xa812dc60, 0xa1ebddf8, 0x991be14c, 0xdb6e6b0d,
+ 0xc67b5510, 0x6d672c37, 0x2765d43b, 0xdcd0e804,
+ 0xf1290dc7, 0xcc00ffa3, 0xb5390f92, 0x690fed0b,
+ 0x667b9ffb, 0xcedb7d9c, 0xa091cf0b, 0xd9155ea3,
+ 0xbb132f88, 0x515bad24, 0x7b9479bf, 0x763bd6eb,
+ 0x37392eb3, 0xcc115979, 0x8026e297, 0xf42e312d,
+ 0x6842ada7, 0xc66a2b3b, 0x12754ccc, 0x782ef11c,
+ 0x6a124237, 0xb79251e7, 0x06a1bbe6, 0x4bfb6350,
+ 0x1a6b1018, 0x11caedfa, 0x3d25bdd8, 0xe2e1c3c9,
+ 0x44421659, 0x0a121386, 0xd90cec6e, 0xd5abea2a,
+ 0x64af674e, 0xda86a85f, 0xbebfe988, 0x64e4c3fe,
+ 0x9dbc8057, 0xf0f7c086, 0x60787bf8, 0x6003604d,
+ 0xd1fd8346, 0xf6381fb0, 0x7745ae04, 0xd736fccc,
+ 0x83426b33, 0xf01eab71, 0xb0804187, 0x3c005e5f,
+ 0x77a057be, 0xbde8ae24, 0x55464299, 0xbf582e61,
+ 0x4e58f48f, 0xf2ddfda2, 0xf474ef38, 0x8789bdc2,
+ 0x5366f9c3, 0xc8b38e74, 0xb475f255, 0x46fcd9b9,
+ 0x7aeb2661, 0x8b1ddf84, 0x846a0e79, 0x915f95e2,
+ 0x466e598e, 0x20b45770, 0x8cd55591, 0xc902de4c,
+ 0xb90bace1, 0xbb8205d0, 0x11a86248, 0x7574a99e,
+ 0xb77f19b6, 0xe0a9dc09, 0x662d09a1, 0xc4324633,
+ 0xe85a1f02, 0x09f0be8c, 0x4a99a025, 0x1d6efe10,
+ 0x1ab93d1d, 0x0ba5a4df, 0xa186f20f, 0x2868f169,
+ 0xdcb7da83, 0x573906fe, 0xa1e2ce9b, 0x4fcd7f52,
+ 0x50115e01, 0xa70683fa, 0xa002b5c4, 0x0de6d027,
+ 0x9af88c27, 0x773f8641, 0xc3604c06, 0x61a806b5,
+ 0xf0177a28, 0xc0f586e0, 0x006058aa, 0x30dc7d62,
+ 0x11e69ed7, 0x2338ea63, 0x53c2dd94, 0xc2c21634,
+ 0xbbcbee56, 0x90bcb6de, 0xebfc7da1, 0xce591d76,
+ 0x6f05e409, 0x4b7c0188, 0x39720a3d, 0x7c927c24,
+ 0x86e3725f, 0x724d9db9, 0x1ac15bb4, 0xd39eb8fc,
+ 0xed545578, 0x08fca5b5, 0xd83d7cd3, 0x4dad0fc4,
+ 0x1e50ef5e, 0xb161e6f8, 0xa28514d9, 0x6c51133c,
+ 0x6fd5c7e7, 0x56e14ec4, 0x362abfce, 0xddc6c837,
+ 0xd79a3234, 0x92638212, 0x670efa8e, 0x406000e0},
+
+ //3
+ {0x3a39ce37, 0xd3faf5cf, 0xabc27737, 0x5ac52d1b,
+ 0x5cb0679e, 0x4fa33742, 0xd3822740, 0x99bc9bbe,
+ 0xd5118e9d, 0xbf0f7315, 0xd62d1c7e, 0xc700c47b,
+ 0xb78c1b6b, 0x21a19045, 0xb26eb1be, 0x6a366eb4,
+ 0x5748ab2f, 0xbc946e79, 0xc6a376d2, 0x6549c2c8,
+ 0x530ff8ee, 0x468dde7d, 0xd5730a1d, 0x4cd04dc6,
+ 0x2939bbdb, 0xa9ba4650, 0xac9526e8, 0xbe5ee304,
+ 0xa1fad5f0, 0x6a2d519a, 0x63ef8ce2, 0x9a86ee22,
+ 0xc089c2b8, 0x43242ef6, 0xa51e03aa, 0x9cf2d0a4,
+ 0x83c061ba, 0x9be96a4d, 0x8fe51550, 0xba645bd6,
+ 0x2826a2f9, 0xa73a3ae1, 0x4ba99586, 0xef5562e9,
+ 0xc72fefd3, 0xf752f7da, 0x3f046f69, 0x77fa0a59,
+ 0x80e4a915, 0x87b08601, 0x9b09e6ad, 0x3b3ee593,
+ 0xe990fd5a, 0x9e34d797, 0x2cf0b7d9, 0x022b8b51,
+ 0x96d5ac3a, 0x017da67d, 0xd1cf3ed6, 0x7c7d2d28,
+ 0x1f9f25cf, 0xadf2b89b, 0x5ad6b472, 0x5a88f54c,
+ 0xe029ac71, 0xe019a5e6, 0x47b0acfd, 0xed93fa9b,
+ 0xe8d3c48d, 0x283b57cc, 0xf8d56629, 0x79132e28,
+ 0x785f0191, 0xed756055, 0xf7960e44, 0xe3d35e8c,
+ 0x15056dd4, 0x88f46dba, 0x03a16125, 0x0564f0bd,
+ 0xc3eb9e15, 0x3c9057a2, 0x97271aec, 0xa93a072a,
+ 0x1b3f6d9b, 0x1e6321f5, 0xf59c66fb, 0x26dcf319,
+ 0x7533d928, 0xb155fdf5, 0x03563482, 0x8aba3cbb,
+ 0x28517711, 0xc20ad9f8, 0xabcc5167, 0xccad925f,
+ 0x4de81751, 0x3830dc8e, 0x379d5862, 0x9320f991,
+ 0xea7a90c2, 0xfb3e7bce, 0x5121ce64, 0x774fbe32,
+ 0xa8b6e37e, 0xc3293d46, 0x48de5369, 0x6413e680,
+ 0xa2ae0810, 0xdd6db224, 0x69852dfd, 0x09072166,
+ 0xb39a460a, 0x6445c0dd, 0x586cdecf, 0x1c20c8ae,
+ 0x5bbef7dd, 0x1b588d40, 0xccd2017f, 0x6bb4e3bb,
+ 0xdda26a7e, 0x3a59ff45, 0x3e350a44, 0xbcb4cdd5,
+ 0x72eacea8, 0xfa6484bb, 0x8d6612ae, 0xbf3c6f47,
+ 0xd29be463, 0x542f5d9e, 0xaec2771b, 0xf64e6370,
+ 0x740e0d8d, 0xe75b1357, 0xf8721671, 0xaf537d5d,
+ 0x4040cb08, 0x4eb4e2cc, 0x34d2466a, 0x0115af84,
+ 0xe1b00428, 0x95983a1d, 0x06b89fb4, 0xce6ea048,
+ 0x6f3f3b82, 0x3520ab82, 0x011a1d4b, 0x277227f8,
+ 0x611560b1, 0xe7933fdc, 0xbb3a792b, 0x344525bd,
+ 0xa08839e1, 0x51ce794b, 0x2f32c9b7, 0xa01fbac9,
+ 0xe01cc87e, 0xbcc7d1f6, 0xcf0111c3, 0xa1e8aac7,
+ 0x1a908749, 0xd44fbd9a, 0xd0dadecb, 0xd50ada38,
+ 0x0339c32a, 0xc6913667, 0x8df9317c, 0xe0b12b4f,
+ 0xf79e59b7, 0x43f5bb3a, 0xf2d519ff, 0x27d9459c,
+ 0xbf97222c, 0x15e6fc2a, 0x0f91fc71, 0x9b941525,
+ 0xfae59361, 0xceb69ceb, 0xc2a86459, 0x12baa8d1,
+ 0xb6c1075e, 0xe3056a0c, 0x10d25065, 0xcb03a442,
+ 0xe0ec6e0e, 0x1698db3b, 0x4c98a0be, 0x3278e964,
+ 0x9f1f9532, 0xe0d392df, 0xd3a0342b, 0x8971f21e,
+ 0x1b0a7441, 0x4ba3348c, 0xc5be7120, 0xc37632d8,
+ 0xdf359f8d, 0x9b992f2e, 0xe60b6f47, 0x0fe3f11d,
+ 0xe54cda54, 0x1edad891, 0xce6279cf, 0xcd3e7e6f,
+ 0x1618b166, 0xfd2c1d05, 0x848fd2c5, 0xf6fb2299,
+ 0xf523f357, 0xa6327623, 0x93a83531, 0x56cccd02,
+ 0xacf08162, 0x5a75ebb5, 0x6e163697, 0x88d273cc,
+ 0xde966292, 0x81b949d0, 0x4c50901b, 0x71c65614,
+ 0xe6c6c7bd, 0x327a140a, 0x45e1d006, 0xc3f27b9a,
+ 0xc9aa53fd, 0x62a80f00, 0xbb25bfe2, 0x35bdd2f6,
+ 0x71126905, 0xb2040222, 0xb6cbcf7c, 0xcd769c2b,
+ 0x53113ec0, 0x1640e3d3, 0x38abbd60, 0x2547adf0,
+ 0xba38209c, 0xf746ce76, 0x77afa1c5, 0x20756060,
+ 0x85cbfe4e, 0x8ae88dd8, 0x7aaaf9b0, 0x4cf9aa7e,
+ 0x1948c25c, 0x02fb8a8c, 0x01c36ae4, 0xd6ebe1f9,
+ 0x90d4f869, 0xa65cdea0, 0x3f09252d, 0xc208e69f,
+ 0xb74e6132, 0xce77e25b, 0x578fdfe3, 0x3ac372e6}
+};
+
+//Constructor - Initialize the P and S boxes for a given Key
+BlowFish::BlowFish(unsigned char* ucKey, unsigned int keysize, const SBlock& roChain) : m_oChain0(roChain), m_oChain(roChain)
+{
+ if(keysize<1)
+ // throw exception("Incorrect key length");
+ return;
+
+
+ //Check the Key - the key length should be between 1 and 56 bytes
+ if(keysize>56)
+ keysize = 56;
+ unsigned char aucLocalKey[56];
+ unsigned int i, j;
+ kvi_fastmove(aucLocalKey, ucKey, keysize);
+ //Reflexive Initialization of the Blowfish.
+ //Generating the Subkeys from the Key flood P and S boxes with PI
+ kvi_fastmove(m_auiP, scm_auiInitP, sizeof(m_auiP));
+ kvi_fastmove(m_auiS, scm_auiInitS, sizeof(m_auiS));
+ //Load P boxes with key bytes
+ const unsigned char* p = aucLocalKey;
+ unsigned int x=0;
+ //Repeatedly cycle through the key bits until the entire P array has been XORed with key bits
+ int iCount = 0;
+ for(i=0; i<18; i++)
+ {
+ x=0;
+ for(int n=4; n--; )
+ {
+ x <<= 8;
+ x |= *(p++);
+ iCount++;
+ if(iCount == ((int)keysize))
+ {
+ //All bytes used, so recycle bytes
+ iCount = 0;
+ p = aucLocalKey;
+ }
+ }
+ m_auiP[i] ^= x;
+ }
+ //Reflect P and S boxes through the evolving Blowfish
+ SBlock block(0UL,0UL); //all-zero block
+ for(i=0; i<18; )
+ Encrypt(block), m_auiP[i++] = block.m_uil, m_auiP[i++] = block.m_uir;
+ for(j=0; j<4; j++)
+ for(int k=0; k<256; )
+ Encrypt(block), m_auiS[j][k++] = block.m_uil, m_auiS[j][k++] = block.m_uir;
+}
+
+//Sixteen Round Encipher of Block
+void BlowFish::Encrypt(SBlock& block)
+{
+ unsigned int uiLeft = block.m_uil;
+ unsigned int uiRight = block.m_uir;
+ uiLeft ^= m_auiP[0];
+ uiRight ^= F(uiLeft)^m_auiP[1]; uiLeft ^= F(uiRight)^m_auiP[2];
+ uiRight ^= F(uiLeft)^m_auiP[3]; uiLeft ^= F(uiRight)^m_auiP[4];
+ uiRight ^= F(uiLeft)^m_auiP[5]; uiLeft ^= F(uiRight)^m_auiP[6];
+ uiRight ^= F(uiLeft)^m_auiP[7]; uiLeft ^= F(uiRight)^m_auiP[8];
+ uiRight ^= F(uiLeft)^m_auiP[9]; uiLeft ^= F(uiRight)^m_auiP[10];
+ uiRight ^= F(uiLeft)^m_auiP[11]; uiLeft ^= F(uiRight)^m_auiP[12];
+ uiRight ^= F(uiLeft)^m_auiP[13]; uiLeft ^= F(uiRight)^m_auiP[14];
+ uiRight ^= F(uiLeft)^m_auiP[15]; uiLeft ^= F(uiRight)^m_auiP[16];
+ uiRight ^= m_auiP[17];
+ block.m_uil = uiRight;
+ block.m_uir = uiLeft;
+}
+
+//Sixteen Round Decipher of SBlock
+void BlowFish::Decrypt(SBlock& block)
+{
+ unsigned int uiLeft = block.m_uil;
+ unsigned int uiRight = block.m_uir;
+ uiLeft ^= m_auiP[17];
+ uiRight ^= F(uiLeft)^m_auiP[16]; uiLeft ^= F(uiRight)^m_auiP[15];
+ uiRight ^= F(uiLeft)^m_auiP[14]; uiLeft ^= F(uiRight)^m_auiP[13];
+ uiRight ^= F(uiLeft)^m_auiP[12]; uiLeft ^= F(uiRight)^m_auiP[11];
+ uiRight ^= F(uiLeft)^m_auiP[10]; uiLeft ^= F(uiRight)^m_auiP[9];
+ uiRight ^= F(uiLeft)^m_auiP[8]; uiLeft ^= F(uiRight)^m_auiP[7];
+ uiRight ^= F(uiLeft)^m_auiP[6]; uiLeft ^= F(uiRight)^m_auiP[5];
+ uiRight ^= F(uiLeft)^m_auiP[4]; uiLeft ^= F(uiRight)^m_auiP[3];
+ uiRight ^= F(uiLeft)^m_auiP[2]; uiLeft ^= F(uiRight)^m_auiP[1];
+ uiRight ^= m_auiP[0];
+ block.m_uil = uiRight;
+ block.m_uir = uiLeft;
+}
+
+//Semi-Portable Byte Shuffling
+inline void BytesToBlock(unsigned char const* p, SBlock& b)
+{
+ unsigned int y;
+ //Left
+ b.m_uil = 0;
+ y = *p++;
+ y <<= 24;
+ b.m_uil |= y;
+ y = *p++;
+ y <<= 16;
+ b.m_uil |= y;
+ y = *p++;
+ y <<= 8;
+ b.m_uil |= y;
+ y = *p++;
+ b.m_uil |= y;
+ //Right
+ b.m_uir = 0;
+ y = *p++;
+ y <<= 24;
+ b.m_uir |= y;
+ y = *p++;
+ y <<= 16;
+ b.m_uir |= y;
+ y = *p++;
+ y <<= 8;
+ b.m_uir |= y;
+ y = *p++;
+ b.m_uir |= y;
+}
+
+inline void BlockToBytes(SBlock const& b, unsigned char* p)
+{
+ unsigned int y;
+ //Right
+ y = b.m_uir;
+ *--p = Byte(y);
+ y = b.m_uir >> 8;
+ *--p = Byte(y);
+ y = b.m_uir >> 16;
+ *--p = Byte(y);
+ y = b.m_uir >> 24;
+ *--p = Byte(y);
+ //Left
+ y = b.m_uil;
+ *--p = Byte(y);
+ y = b.m_uil >> 8;
+ *--p = Byte(y);
+ y = b.m_uil >> 16;
+ *--p = Byte(y);
+ y = b.m_uil >> 24;
+ *--p = Byte(y);
+}
+
+//Encrypt Buffer in Place
+//Returns false if n is multiple of 8
+void BlowFish::Encrypt(unsigned char* buf, unsigned int n, int iMode)
+{
+ //Check the buffer's length - should be > 0 and multiple of 8
+ if((n==0)||(n%8!=0))
+ //throw exception("Incorrect buffer length");
+ return;
+
+ SBlock work;
+ if(iMode == CBC) //CBC mode, using the Chain
+ {
+ SBlock chain(m_oChain);
+ for(; n >= 8; n -= 8)
+ {
+ BytesToBlock(buf, work);
+ work ^= chain;
+ Encrypt(work);
+ chain = work;
+ BlockToBytes(work, buf+=8);
+ }
+ }
+ else if(iMode == CFB) //CFB mode, using the Chain
+ {
+ SBlock chain(m_oChain);
+ for(; n >= 8; n -= 8)
+ {
+ Encrypt(chain);
+ BytesToBlock(buf, work);
+ work ^= chain;
+ chain = work;
+ BlockToBytes(work, buf+=8);
+ }
+ }
+ else //ECB mode, not using the Chain
+ {
+ for(; n >= 8; n -= 8)
+ {
+ BytesToBlock(buf, work);
+ Encrypt(work);
+ BlockToBytes(work, buf+=8);
+ }
+ }
+}
+
+//Decrypt Buffer in Place
+//Returns false if n is multiple of 8
+void BlowFish::Decrypt(unsigned char* buf, unsigned int n, int iMode)
+{
+ //Check the buffer's length - should be > 0 and multiple of 8
+ if((n==0)||(n%8!=0))
+ //throw exception("Incorrect buffer length");
+ return;
+
+ SBlock work;
+ if(iMode == CBC) //CBC mode, using the Chain
+ {
+ SBlock crypt, chain(m_oChain);
+ for(; n >= 8; n -= 8)
+ {
+ BytesToBlock(buf, work);
+ crypt = work;
+ Decrypt(work);
+ work ^= chain;
+ chain = crypt;
+ BlockToBytes(work, buf+=8);
+ }
+ }
+ else if(iMode == CFB) //CFB mode, using the Chain, not using Decrypt()
+ {
+ SBlock crypt, chain(m_oChain);
+ for(; n >= 8; n -= 8)
+ {
+ BytesToBlock(buf, work);
+ Encrypt(chain);
+ crypt = work;
+ work ^= chain;
+ chain = crypt;
+ BlockToBytes(work, buf+=8);
+ }
+ }
+ else //ECB mode, not using the Chain
+ {
+ for(; n >= 8; n -= 8)
+ {
+ BytesToBlock(buf, work);
+ Decrypt(work);
+ BlockToBytes(work, buf+=8);
+ }
+ }
+}
+
+//Encrypt from Input Buffer to Output Buffer
+//Returns false if n is multiple of 8
+void BlowFish::Encrypt(const unsigned char* in, unsigned char* out, unsigned int n, int iMode)
+{
+ //Check the buffer's length - should be > 0 and multiple of 8
+ if((n==0)||(n%8!=0))
+ //throw exception("Incorrect buffer length");
+ return;
+
+ SBlock work;
+ if(iMode == CBC) //CBC mode, using the Chain
+ {
+ SBlock chain(m_oChain);
+ for(; n >= 8; n -= 8, in += 8)
+ {
+ BytesToBlock(in, work);
+ work ^= chain;
+ Encrypt(work);
+ chain = work;
+ BlockToBytes(work, out+=8);
+ }
+ }
+ else if(iMode == CFB) //CFB mode, using the Chain
+ {
+ SBlock chain(m_oChain);
+ for(; n >= 8; n -= 8, in += 8)
+ {
+ Encrypt(chain);
+ BytesToBlock(in, work);
+ work ^= chain;
+ chain = work;
+ BlockToBytes(work, out+=8);
+ }
+ }
+ else //ECB mode, not using the Chain
+ {
+ for(; n >= 8; n -= 8, in += 8)
+ {
+ BytesToBlock(in, work);
+ Encrypt(work);
+ BlockToBytes(work, out+=8);
+ }
+ }
+}
+
+//Decrypt from Input Buffer to Output Buffer
+//Returns false if n is multiple of 8
+void BlowFish::Decrypt(const unsigned char* in, unsigned char* out, unsigned int n, int iMode)
+{
+ //Check the buffer's length - should be > 0 and multiple of 8
+ if((n==0)||(n%8!=0))
+ //throw exception("Incorrect buffer length");
+ return;
+
+ SBlock work;
+ if(iMode == CBC) //CBC mode, using the Chain
+ {
+ SBlock crypt, chain(m_oChain);
+ for(; n >= 8; n -= 8, in += 8)
+ {
+ BytesToBlock(in, work);
+ crypt = work;
+ Decrypt(work);
+ work ^= chain;
+ chain = crypt;
+ BlockToBytes(work, out+=8);
+ }
+ }
+ else if(iMode == CFB) //CFB mode, using the Chain, not using Decrypt()
+ {
+ SBlock crypt, chain(m_oChain);
+ for(; n >= 8; n -= 8, in += 8)
+ {
+ BytesToBlock(in, work);
+ Encrypt(chain);
+ crypt = work;
+ work ^= chain;
+ chain = crypt;
+ BlockToBytes(work, out+=8);
+ }
+ }
+ else //ECB mode, not using the Chain
+ {
+ for(; n >= 8; n -= 8, in += 8)
+ {
+ BytesToBlock(in, work);
+ Decrypt(work);
+ BlockToBytes(work, out+=8);
+ }
+ }
+}
+
+#endif //COMPILE_CRYPT_SUPPORT
diff --git a/src/modules/rijndael/ablowfish.h b/src/modules/rijndael/ablowfish.h
new file mode 100644
index 00000000..862477dc
--- /dev/null
+++ b/src/modules/rijndael/ablowfish.h
@@ -0,0 +1,141 @@
+#ifndef _BLOWFISH_H_
+#define _BLOWFISH_H_
+//=============================================================================
+//
+// File : ablowfish.h
+// Creation date : Wed Jan 13 2005 02:04:10 CEST by Szymon Stefanek
+//
+// This file is part of the KVirc irc client distribution
+// Copyright (C) 2005 Szymon Stefanek (pragma at kvirc dot net)
+//
+// This program is FREE software. You can redistribute it and/or
+// modify it under the terms of the GNU General Public License
+// as published by the Free Software Foundation; either version 2
+// of the License, or (at your opinion) any later version.
+//
+// This program is distributed in the HOPE that it will be USEFUL,
+// but WITHOUT ANY WARRANTY; without even the implied warranty of
+// MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
+// See the GNU General Public License for more details.
+//
+// You should have received a copy of the GNU General Public License
+// along with this program. If not, write to the Free Software Foundation,
+// Inc. ,51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
+//
+//=============================================================================
+
+//
+// This code is adapted from the MircCryption engine suite by Dark Raichu
+// Original comments follow.
+//
+
+//---------------------------------------------------------------------------
+// The implementation of blowfish for CBC mode is from
+// http://www.thecodeproject.com/cpp/blowfish.asp by George Anescu
+// I removed exception handling, so it is callers responsibility to insure
+// that strings are length multiples of 8 bytes
+// -mouser 1/08/05
+//---------------------------------------------------------------------------
+
+
+//
+// BLOWFISH ENCRYPTION ALGORITHM
+//
+// Implementation of Bruce Schneier's BLOWFISH algorithm from "Applied
+// Cryptography", Second Edition.
+//
+// Encryption and Decryption of Byte Strings using the Blowfish Encryption Algorithm.
+// Blowfish is a block cipher that encrypts data in 8-byte blocks. The algorithm consists
+// of two parts: a key-expansion part and a data-ancryption part. Key expansion converts a
+// variable key of at least 1 and at most 56 bytes into several subkey arrays totaling
+// 4168 bytes. Blowfish has 16 rounds. Each round consists of a key-dependent permutation,
+// and a key and data-dependent substitution. All operations are XORs and additions on 32-bit words.
+// The only additional operations are four indexed array data lookups per round.
+// Blowfish uses a large number of subkeys. These keys must be precomputed before any data
+// encryption or decryption. The P-array consists of 18 32-bit subkeys: P0, P1,...,P17.
+// There are also four 32-bit S-boxes with 256 entries each: S0,0, S0,1,...,S0,255;
+// S1,0, S1,1,...,S1,255; S2,0, S2,1,...,S2,255; S3,0, S3,1,...,S3,255;
+//
+// The Electronic Code Book (ECB), Cipher Block Chaining (CBC) and Cipher Feedback modes
+// are used:
+//
+// In ECB mode if the same block is encrypted twice with the same key, the resulting
+// ciphertext blocks are the same.
+//
+// In CBC Mode a ciphertext block is obtained by first xoring the
+// plaintext block with the previous ciphertext block, and encrypting the resulting value.
+//
+// In CFB mode a ciphertext block is obtained by encrypting the previous ciphertext block
+// and xoring the resulting value with the plaintext
+//
+// The previous ciphertext block is usually stored in an Initialization Vector (IV).
+// An Initialization Vector of zero is commonly used for the first block, though other
+// arrangements are also in use.
+//
+
+#include "kvi_settings.h"
+
+#ifdef COMPILE_CRYPT_SUPPORT
+
+
+//Block Structure
+struct SBlock
+{
+ //Constructors
+ SBlock(unsigned int l=0, unsigned int r=0) : m_uil(l), m_uir(r) {}
+ //Copy Constructor
+ SBlock(const SBlock& roBlock) : m_uil(roBlock.m_uil), m_uir(roBlock.m_uir) {}
+ SBlock& operator^=(SBlock& b) { m_uil ^= b.m_uil; m_uir ^= b.m_uir; return *this; }
+ unsigned int m_uil, m_uir;
+};
+
+class BlowFish
+{
+public:
+ enum { ECB=0, CBC=1, CFB=2 };
+
+ //Constructor - Initialize the P and S boxes for a given Key
+ BlowFish(unsigned char* ucKey, unsigned int n, const SBlock& roChain = SBlock(0UL,0UL));
+
+ //Resetting the chaining block
+ void ResetChain() { m_oChain = m_oChain0; }
+
+ // Encrypt/Decrypt Buffer in Place
+ void Encrypt(unsigned char* buf, unsigned int n, int iMode=ECB);
+ void Decrypt(unsigned char* buf, unsigned int n, int iMode=ECB);
+
+ // Encrypt/Decrypt from Input Buffer to Output Buffer
+ void Encrypt(const unsigned char* in, unsigned char* out, unsigned int n, int iMode=ECB);
+ void Decrypt(const unsigned char* in, unsigned char* out, unsigned int n, int iMode=ECB);
+
+//Private Functions
+private:
+ unsigned int F(unsigned int ui);
+ void Encrypt(SBlock&);
+ void Decrypt(SBlock&);
+
+private:
+ //The Initialization Vector, by default {0, 0}
+ SBlock m_oChain0;
+ SBlock m_oChain;
+ unsigned int m_auiP[18];
+ unsigned int m_auiS[4][256];
+ static const unsigned int scm_auiInitP[18];
+ static const unsigned int scm_auiInitS[4][256];
+};
+
+//Extract low order byte
+inline unsigned char Byte(unsigned int ui)
+{
+ return (unsigned char)(ui & 0xff);
+}
+
+//Function F
+inline unsigned int BlowFish::F(unsigned int ui)
+{
+ return ((m_auiS[0][Byte(ui>>24)] + m_auiS[1][Byte(ui>>16)]) ^ m_auiS[2][Byte(ui>>8)]) + m_auiS[3][Byte(ui)];
+}
+
+#endif //COMPILE_CRYPT_SUPPORT
+
+#endif //!_BLOWFISH_H_
diff --git a/src/modules/rijndael/caps/Makefile.am b/src/modules/rijndael/caps/Makefile.am
new file mode 100644
index 00000000..663f77a8
--- /dev/null
+++ b/src/modules/rijndael/caps/Makefile.am
@@ -0,0 +1,9 @@
+###############################################################################
+# KVirc IRC client Makefile - 10.03.2000 Szymon Stefanek <stefanek@tin.it>
+###############################################################################
+
+tmpdir = $(pluglibdir)/caps/crypt/
+
+tmp_DATA= rijndael
+
+EXTRA_DIST = $(tmp_DATA)
diff --git a/src/modules/rijndael/caps/rijndael b/src/modules/rijndael/caps/rijndael
new file mode 100644
index 00000000..9788f702
--- /dev/null
+++ b/src/modules/rijndael/caps/rijndael
@@ -0,0 +1 @@
+timestamp
diff --git a/src/modules/rijndael/libkvirijndael.cpp b/src/modules/rijndael/libkvirijndael.cpp
new file mode 100644
index 00000000..0a678437
--- /dev/null
+++ b/src/modules/rijndael/libkvirijndael.cpp
@@ -0,0 +1,853 @@
+//
+// File : libkvirijndael.cpp
+// Creation date : Sat Now 4 2000 15:33:12 CEST by Szymon Stefanek
+//
+// This file is part of the KVirc irc client distribution
+// Copyright (C) 1999-2000 Till Bush (buti@geocities.com)
+//
+// This program is FREE software. You can redistribute it and/or
+// modify it under the terms of the GNU General Public License
+// as published by the Free Software Foundation; either version 2
+// of the License, or (at your opinion) any later version.
+//
+// This program is distributed in the HOPE that it will be USEFUL,
+// but WITHOUT ANY WARRANTY; without even the implied warranty of
+// MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
+// See the GNU General Public License for more details.
+//
+// You should have received a copy of the GNU General Public License
+// along with this program. If not, write to the Free Software Foundation,
+// Inc. ,51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
+//
+
+#include "libkvirijndael.h"
+
+#include "rijndael.h"
+
+#include "kvi_module.h"
+#include "kvi_debug.h"
+#include "kvi_locale.h"
+
+#include "kvi_mirccntrl.h"
+#include "kvi_time.h"
+
+//#warning "Other engines: mircStrip koi2win colorizer lamerizer etc.."
+
+/*
+ @doc: rijndael
+ @type:
+ module
+ @short:
+ The Rijndael cryptographic engines
+ @title:
+ The rijndael module
+ @body:
+ The rijndael module exports six [doc:crypt_engines]cryptographic engines[/doc] based
+ on the Advanced Encryptiong Standard algorithm called Rijndael. Rijndael was
+ originally written by Joan Daemen and Vincent Rijmen. The original Rijndael
+ description is available at http://www.esat.kuleuven.ac.be/~rijmen/rijndael/.[br]
+ It is a private key block cipher that has been designed to replace
+ the widely used DES, and it should provide at leas a decent security agains
+ common attacks. Theoretically the best attack that one can perform on this cipher
+ is the "brute force" attack that requires a really massive parallel computation:
+ actually out of the possibilities of a common "hacker".[br]
+ My implementation allows the usage of 128, 192 and 256 bit keys
+ on 128 bit data blocks. The encrypted binary data buffer is then converted
+ into an ascii-string by using the base64 conversion or hex-digit-string rappresentation.
+ The six engines are the six possible combinations of the key lengths and ascii-string
+ conversions.
+*/
+
+
+
+#ifdef COMPILE_CRYPT_SUPPORT
+
+ #include "kvi_memmove.h"
+ #include "kvi_malloc.h"
+
+ #include "kvi_pointerlist.h"
+
+ static KviPointerList<KviCryptEngine> * g_pEngineList = 0;
+
+
+
+
+ KviRijndaelEngine::KviRijndaelEngine()
+ : KviCryptEngine()
+ {
+ g_pEngineList->append(this);
+ m_pEncryptCipher = 0;
+ m_pDecryptCipher = 0;
+ }
+
+ KviRijndaelEngine::~KviRijndaelEngine()
+ {
+ g_pEngineList->removeRef(this);
+ if(m_pEncryptCipher)delete m_pEncryptCipher;
+ if(m_pDecryptCipher)delete m_pDecryptCipher;
+ }
+
+ bool KviRijndaelEngine::init(const char *encKey,int encKeyLen,const char *decKey,int decKeyLen)
+ {
+ if(m_pEncryptCipher)
+ {
+ delete m_pEncryptCipher;
+ m_pEncryptCipher = 0;
+ }
+ if(m_pDecryptCipher)
+ {
+ delete m_pDecryptCipher;
+ m_pDecryptCipher = 0;
+ }
+
+ if(encKey && (encKeyLen > 0))
+ {
+ if(!(decKey && (decKeyLen > 0)))
+ {
+ decKey = encKey;
+ decKeyLen = encKeyLen;
+ } // else all
+ } else {
+ // no encrypt key specified...
+ if(decKey && decKeyLen)
+ {
+ encKey = decKey;
+ encKeyLen = decKeyLen;
+ } else {
+ // both keys missing
+ setLastError(__tr("Missing both encrypt and decrypt key: at least one is needed"));
+ return false;
+ }
+ }
+
+ int defLen = getKeyLen();
+
+ char * encryptKey = (char *)kvi_malloc(defLen);
+ char * decryptKey = (char *)kvi_malloc(defLen);
+
+ if(encKeyLen > defLen)encKeyLen = defLen;
+ kvi_memmove(encryptKey,encKey,encKeyLen);
+ if(encKeyLen < defLen)kvi_memset(encryptKey + encKeyLen,'0',defLen - encKeyLen);
+
+ if(decKeyLen > defLen)decKeyLen = defLen;
+ kvi_memmove(decryptKey,decKey,decKeyLen);
+ if(decKeyLen < defLen)kvi_memset(decryptKey + decKeyLen,'0',defLen - decKeyLen);
+
+ m_pEncryptCipher = new Rijndael();
+ int retVal = m_pEncryptCipher->init(Rijndael::CBC,Rijndael::Encrypt,(unsigned char *)encryptKey,getKeyLenId());
+ kvi_free(encryptKey);
+ if(retVal != RIJNDAEL_SUCCESS)
+ {
+ kvi_free(decryptKey);
+ delete m_pEncryptCipher;
+ m_pEncryptCipher = 0;
+ setLastErrorFromRijndaelErrorCode(retVal);
+ return false;
+ }
+
+ m_pDecryptCipher = new Rijndael();
+ retVal = m_pDecryptCipher->init(Rijndael::CBC,Rijndael::Decrypt,(unsigned char *)decryptKey,getKeyLenId());
+ kvi_free(decryptKey);
+ if(retVal != RIJNDAEL_SUCCESS)
+ {
+ delete m_pEncryptCipher;
+ m_pEncryptCipher = 0;
+ delete m_pDecryptCipher;
+ m_pDecryptCipher = 0;
+ setLastErrorFromRijndaelErrorCode(retVal);
+ return false;
+ }
+
+ return true;
+ }
+
+ void KviRijndaelEngine::setLastErrorFromRijndaelErrorCode(int errCode)
+ {
+ switch(errCode)
+ {
+ case RIJNDAEL_SUCCESS: setLastError(__tr("Error 0: Success ?")); break;
+ case RIJNDAEL_UNSUPPORTED_MODE: setLastError(__tr("Unsupported crypt mode")); break;
+ case RIJNDAEL_UNSUPPORTED_DIRECTION: setLastError(__tr("Unsupported direction")); break;
+ case RIJNDAEL_UNSUPPORTED_KEY_LENGTH: setLastError(__tr("Unsupported key length")); break;
+ case RIJNDAEL_BAD_KEY: setLastError(__tr("Bad key data")); break;
+ case RIJNDAEL_NOT_INITIALIZED: setLastError(__tr("Engine not initialized")); break;
+ case RIJNDAEL_BAD_DIRECTION: setLastError(__tr("Invalid direction for this engine")); break;
+ case RIJNDAEL_CORRUPTED_DATA: setLastError(__tr("Corrupted message data or invalid decrypt key")); break;
+ default: setLastError(__tr("Unknown error")); break;
+ }
+ }
+
+ KviCryptEngine::EncryptResult KviRijndaelEngine::encrypt(const char * plainText,KviStr &outBuffer)
+ {
+ if(!m_pEncryptCipher)
+ {
+ setLastError(__tr("Ops...encrypt cipher not initialized"));
+ return KviCryptEngine::EncryptError;
+ }
+ int len = (int)kvi_strLen(plainText);
+ char * buf = (char *)kvi_malloc(len + 16);
+
+ int retVal = m_pEncryptCipher->padEncrypt((const unsigned char *)plainText,len,(unsigned char *)buf);
+ if(retVal < 0)
+ {
+ kvi_free(buf);
+ setLastErrorFromRijndaelErrorCode(retVal);
+ return KviCryptEngine::EncryptError;
+ }
+
+ if(!binaryToAscii(buf,retVal,outBuffer))
+ {
+ kvi_free(buf);
+ return KviCryptEngine::EncryptError;
+ }
+ kvi_free(buf);
+
+ if(outBuffer.len() > maxEncryptLen())
+ {
+ if(maxEncryptLen() > 0)
+ {
+ setLastError(__tr("Data buffer too long"));
+ return KviCryptEngine::EncryptError;
+ }
+ }
+ outBuffer.prepend(KVI_TEXT_CRYPTESCAPE);
+ return KviCryptEngine::Encrypted;
+ }
+
+ KviCryptEngine::DecryptResult KviRijndaelEngine::decrypt(const char * inBuffer,KviStr &plainText)
+ {
+ if(!m_pDecryptCipher)
+ {
+ setLastError(__tr("Ops...decrypt cipher not initialized"));
+ return KviCryptEngine::DecryptError;
+ }
+
+ if(*inBuffer != KVI_TEXT_CRYPTESCAPE)
+ {
+ plainText = inBuffer;
+ return KviCryptEngine::DecryptOkWasPlainText;
+ }
+
+ inBuffer++;
+
+ if(!*inBuffer)
+ {
+ plainText = inBuffer;
+ return KviCryptEngine::DecryptOkWasPlainText; // empty buffer
+ }
+
+ int len;
+ char * binary;
+
+ if(!asciiToBinary(inBuffer,&len,&binary))return KviCryptEngine::DecryptError;
+
+ char * buf = (char *)kvi_malloc(len + 1);
+
+ int retVal = m_pDecryptCipher->padDecrypt((const unsigned char *)binary,len,(unsigned char *)buf);
+ kvi_free(binary);
+
+ if(retVal < 0)
+ {
+ kvi_free(buf);
+ setLastErrorFromRijndaelErrorCode(retVal);
+ return KviCryptEngine::DecryptError;
+ }
+
+ buf[retVal] = '\0';
+
+ plainText = buf;
+
+ kvi_free(buf);
+ return KviCryptEngine::DecryptOkWasEncrypted;
+ }
+
+ bool KviRijndaelHexEngine::binaryToAscii(const char * inBuffer,int len,KviStr &outBuffer)
+ {
+ outBuffer.bufferToHex(inBuffer,len);
+ return true;
+ }
+
+ bool KviRijndaelHexEngine::asciiToBinary(const char * inBuffer,int * len,char ** outBuffer)
+ {
+ KviStr hex(inBuffer);
+ char * tmpBuf;
+ *len = hex.hexToBuffer(&tmpBuf,false);
+ if(*len < 0)
+ {
+ setLastError(__tr("The message is not a hexadecimal string: this is not my stuff"));
+ return false;
+ } else {
+ if(len > 0)
+ {
+ *outBuffer = (char *)kvi_malloc(*len);
+ kvi_memmove(*outBuffer,tmpBuf,*len);
+ KviStr::freeBuffer(tmpBuf);
+ }
+ }
+ return true;
+ }
+
+ bool KviRijndaelBase64Engine::binaryToAscii(const char * inBuffer,int len,KviStr &outBuffer)
+ {
+ outBuffer.bufferToBase64(inBuffer,len);
+ return true;
+ }
+
+ bool KviRijndaelBase64Engine::asciiToBinary(const char * inBuffer,int * len,char ** outBuffer)
+ {
+ KviStr base64(inBuffer);
+ char * tmpBuf;
+ *len = base64.base64ToBuffer(&tmpBuf,false);
+ if(*len < 0)
+ {
+ setLastError(__tr("The message is not a base64 string: this is not my stuff"));
+ return false;
+ } else {
+ if(len > 0)
+ {
+ *outBuffer = (char *)kvi_malloc(*len);
+ kvi_memmove(*outBuffer,tmpBuf,*len);
+ KviStr::freeBuffer(tmpBuf);
+ }
+ }
+ return true;
+ }
+
+ static KviCryptEngine * allocRijndael128HexEngine()
+ {
+ return new KviRijndael128HexEngine();
+ }
+
+ static KviCryptEngine * allocRijndael192HexEngine()
+ {
+ return new KviRijndael192HexEngine();
+ }
+
+ static KviCryptEngine * allocRijndael256HexEngine()
+ {
+ return new KviRijndael256HexEngine();
+ }
+
+ static KviCryptEngine * allocRijndael128Base64Engine()
+ {
+ return new KviRijndael128Base64Engine();
+ }
+
+ static KviCryptEngine * allocRijndael192Base64Engine()
+ {
+ return new KviRijndael192Base64Engine();
+ }
+
+ static KviCryptEngine * allocRijndael256Base64Engine()
+ {
+ return new KviRijndael256Base64Engine();
+ }
+
+ static void deallocRijndaelCryptEngine(KviCryptEngine * e)
+ {
+ delete e;
+ }
+
+
+
+
+
+ // Mircryption stuff
+
+ #include "ablowfish.h"
+
+ KviMircryptionEngine::KviMircryptionEngine()
+ : KviCryptEngine()
+ {
+ g_pEngineList->append(this);
+ }
+
+ KviMircryptionEngine::~KviMircryptionEngine()
+ {
+ g_pEngineList->removeRef(this);
+ }
+
+ bool KviMircryptionEngine::init(const char * encKey,int encKeyLen,const char * decKey,int decKeyLen)
+ {
+ if(encKey && (encKeyLen > 0))
+ {
+ if(!(decKey && (decKeyLen > 0)))
+ {
+ decKey = encKey;
+ decKeyLen = encKeyLen;
+ } // else all
+ } else {
+ // no encrypt key specified...
+ if(decKey && decKeyLen)
+ {
+ encKey = decKey;
+ encKeyLen = decKeyLen;
+ } else {
+ // both keys missing
+ setLastError(__tr("Missing both encrypt and decrypt key: at least one is needed"));
+ return false;
+ }
+ }
+ m_szEncryptKey = KviStr(encKey,encKeyLen);
+ m_szDecryptKey = KviStr(decKey,decKeyLen);
+ if(kvi_strEqualCIN("cbc:",m_szEncryptKey.ptr(),4) && (m_szEncryptKey.len() > 4))
+ m_szEncryptKey.cutLeft(4);
+ else
+ m_bEncryptCBC = false;
+ if(kvi_strEqualCIN("cbc:",m_szDecryptKey.ptr(),4) && (m_szDecryptKey.len() > 4))
+ m_szDecryptKey.cutLeft(4);
+ else
+ m_bDecryptCBC = false;
+ return true;
+ }
+
+ KviCryptEngine::EncryptResult KviMircryptionEngine::encrypt(const char * plainText,KviStr &outBuffer)
+ {
+ KviStr szPlain = plainText;
+ outBuffer = "";
+ if(m_bEncryptCBC)
+ {
+ if(!doEncryptCBC(szPlain,outBuffer))return KviCryptEngine::EncryptError;
+ } else {
+ if(!doEncryptECB(szPlain,outBuffer))return KviCryptEngine::EncryptError;
+ }
+ outBuffer.prepend("+OK ");
+
+ if(outBuffer.len() > maxEncryptLen())
+ {
+ if(maxEncryptLen() > 0)
+ {
+ setLastError(__tr("Data buffer too long"));
+ return KviCryptEngine::EncryptError;
+ }
+ }
+
+ //outBuffer = MCPS2_STARTTAG;
+ //outBuffer += MCPS2_ENDTAG;
+ return KviCryptEngine::Encrypted;
+ }
+
+ KviCryptEngine::DecryptResult KviMircryptionEngine::decrypt(const char * inBuffer,KviStr &plainText)
+ {
+ plainText = "";
+ KviStr szIn = inBuffer;
+ // various old versions
+ if(kvi_strEqualCSN(inBuffer,"mcps ",5))
+ szIn.cutLeft(5);
+ else if(kvi_strEqualCSN(inBuffer,"+OK ",4))
+ szIn.cutLeft(4);
+ else {
+ plainText = szIn;
+ return KviCryptEngine::DecryptOkWasPlainText;
+ }
+
+ if(m_bDecryptCBC)return doDecryptCBC(szIn,plainText) ? KviCryptEngine::DecryptOkWasEncrypted : KviCryptEngine::DecryptError;
+ return doDecryptECB(szIn,plainText) ? KviCryptEngine::DecryptOkWasEncrypted : KviCryptEngine::DecryptError;
+
+ /*
+ int len1 = kvi_strLen(MCPS2_STARTTAG);
+ int len2 = kvi_strLen(MCPS2_ENDTAG);
+ while(szIn.len() > 0)
+ {
+ int idx = szIn.findFirstIdx(MCPS2_STARTTAG);
+ if(idx == -1)
+ {
+ // no more encrypted stuff
+ plainText += szIn;
+ return true;
+ }
+ if(idx > 0) // a non encrypted block
+ plainText += szIn.left(idx);
+ szIn.cutLeft(idx + len1);
+
+ idx = szIn.findFirstIdx(MCPS2_ENDTAG);
+ if(idx != -1)
+ {
+ KviStr toDecrypt = szIn.left(idx);
+ if(!doDecrypt(toDecrypt,plainText))return false;
+ }
+ szIn.cutLeft(idx + len2);
+ }
+ */
+ }
+
+ static unsigned char fake_base64[]="./0123456789abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ";
+
+ unsigned int fake_base64dec(unsigned char c)
+ {
+ static char base64unmap[255];
+ static bool didinit=false;
+ int i;
+
+ if(!didinit)
+ {
+ // initialize base64unmap
+ for (i=0;i<255;++i)base64unmap[i]=0;
+ for (i=0;i<64;++i)base64unmap[fake_base64[i]]=i;
+ didinit=true;
+ }
+
+ return base64unmap[c];
+ }
+
+ static void byteswap_buffer(unsigned char * p,int len)
+ {
+ while(len > 0)
+ {
+ unsigned char aux = p[0];
+ p[0] = p[3];
+ p[3] = aux;
+ aux = p[1];
+ p[1] = p[2];
+ p[2] = aux;
+ p += 4;
+ len -= 4;
+ }
+ }
+
+ bool KviMircryptionEngine::doEncryptECB(KviStr &plain,KviStr &encoded)
+ {
+ // make sure it is a multiple of 8 bytes (eventually pad with zeroes)
+ if(plain.len() % 8)
+ {
+ int oldL = plain.len();
+ plain.setLength(plain.len() + (8 - (plain.len() % 8)));
+ char * padB = plain.ptr() + oldL;
+ char * padE = plain.ptr() + plain.len();
+ while(padB < padE)*padB++ = 0;
+ }
+
+ //byteswap_buffer((unsigned char *)plain.ptr(),plain.len());
+
+ unsigned char * out =(unsigned char *)kvi_malloc(plain.len()); // we use this to avoid endiannes problems
+
+ BlowFish bf((unsigned char *)m_szEncryptKey.ptr(),m_szEncryptKey.len());
+ bf.ResetChain();
+ bf.Encrypt((unsigned char *)plain.ptr(),out,plain.len(),BlowFish::ECB);
+
+ // FIXME: this is probably needed only on LittleEndian machines!
+ byteswap_buffer((unsigned char *)out,plain.len());
+
+ // da uglybase64 encoding
+ unsigned char * outb = out;
+ unsigned char * oute = out + plain.len();
+
+ int ll = (plain.len() * 3) / 2;
+ encoded.setLength(ll);
+
+ unsigned char * p = (unsigned char *)encoded.ptr();
+ while(outb < oute)
+ {
+ Q_UINT32 * dd1 = (Q_UINT32 *)outb;
+ outb += 4;
+ Q_UINT32 * dd2 = (Q_UINT32 *)outb;
+ outb += 4;
+ *p++ = fake_base64[*dd2 & 0x3f]; *dd2 >>= 6;
+ *p++ = fake_base64[*dd2 & 0x3f]; *dd2 >>= 6;
+ *p++ = fake_base64[*dd2 & 0x3f]; *dd2 >>= 6;
+ *p++ = fake_base64[*dd2 & 0x3f]; *dd2 >>= 6;
+ *p++ = fake_base64[*dd2 & 0x3f]; *dd2 >>= 6;
+ *p++ = fake_base64[*dd2 & 0x3f];
+
+ *p++ = fake_base64[*dd1 & 0x3f]; *dd1 >>= 6;
+ *p++ = fake_base64[*dd1 & 0x3f]; *dd1 >>= 6;
+ *p++ = fake_base64[*dd1 & 0x3f]; *dd1 >>= 6;
+ *p++ = fake_base64[*dd1 & 0x3f]; *dd1 >>= 6;
+ *p++ = fake_base64[*dd1 & 0x3f]; *dd1 >>= 6;
+ *p++ = fake_base64[*dd1 & 0x3f];
+ }
+
+ kvi_free(out);
+ return true;
+ }
+
+ bool KviMircryptionEngine::doDecryptECB(KviStr &encoded,KviStr &plain)
+ {
+ // encoded is in this strange base64...
+ // make sure its length is multiple of 12 (eventually pad with zeroes)
+ if(encoded.len() % 12)
+ {
+ int oldL = encoded.len();
+ encoded.setLength(encoded.len() + (12 - (encoded.len() % 12)));
+ char * padB = encoded.ptr() + oldL;
+ char * padE = encoded.ptr() + encoded.len();
+ while(padB < padE)*padB++ = 0;
+ }
+
+ // a fake base64 decoding algo, use a different character set
+ // and stuff 6 bytes at a time into a 32 bit long...
+ int ll = (encoded.len() * 2) / 3;
+
+ unsigned char * buf = (unsigned char *)kvi_malloc(ll);
+ unsigned char * p = (unsigned char *)encoded.ptr();
+ unsigned char * e = p + encoded.len();
+ int i;
+ unsigned char * bufp = buf;
+ while(p < e)
+ {
+ Q_UINT32 * dw1 = (Q_UINT32 *)bufp;
+ bufp += 4;
+ Q_UINT32 * dw2 = (Q_UINT32 *)bufp;
+ bufp += 4;
+ *dw2 = 0;
+ for(i=0;i < 6;i++)*dw2 |= (fake_base64dec(*p++)) << (i * 6);
+ *dw1 = 0;
+ for(i=0;i < 6;i++)*dw1 |= (fake_base64dec(*p++)) << (i * 6);
+ }
+
+ // FIXME: this is probably needed only on LittleEndian machines!
+ byteswap_buffer((unsigned char *)buf,ll);
+
+ plain.setLength(ll);
+ BlowFish bf((unsigned char *)m_szDecryptKey.ptr(),m_szDecryptKey.len());
+ bf.ResetChain();
+ bf.Decrypt(buf,(unsigned char *)plain.ptr(),ll,BlowFish::ECB);
+
+ //byteswap_buffer((unsigned char *)plain.ptr(),ll);
+
+ kvi_free(buf);
+
+ return true;
+ }
+
+ bool KviMircryptionEngine::doEncryptCBC(KviStr &plain,KviStr &encoded)
+ {
+ // make sure it is a multiple of 8 bytes (eventually pad with zeroes)
+ if(plain.len() % 8)
+ {
+ int oldL = plain.len();
+ plain.setLength(plain.len() + (8 - (plain.len() % 8)));
+ char * padB = plain.ptr() + oldL;
+ char * padE = plain.ptr() + plain.len();
+ while(padB < padE)*padB++ = 0;
+ }
+
+ int ll = plain.len() + 8;
+ unsigned char * in = (unsigned char *)kvi_malloc(ll);
+
+ // choose an IV
+ static bool bDidInit = false;
+
+ int t = (int)kvi_unixTime();
+
+ if(!bDidInit)
+ {
+ srand(t);
+ bDidInit = true;
+ }
+
+ for(int i=0;i<8;i++)in[i] = (unsigned char)(rand() % 256);
+
+ kvi_fastmove(in+8,plain.ptr(),plain.len());
+
+ // encrypt
+ unsigned char * out = (unsigned char *)kvi_malloc(ll);
+ BlowFish bf((unsigned char *)m_szEncryptKey.ptr(),m_szEncryptKey.len());
+ bf.ResetChain();
+ bf.Encrypt(in,out,ll,BlowFish::CBC);
+ kvi_free(in);
+
+ encoded.bufferToBase64((const char *)out,ll);
+ kvi_free(out);
+
+ encoded.prepend('*'); // prepend the signature
+
+ return true;
+ }
+
+ bool KviMircryptionEngine::doDecryptCBC(KviStr &encoded,KviStr &plain)
+ {
+ if(*(encoded.ptr()) != '*')
+ {
+ debug("WARNING: Specified a CBC key but the incoming message doesn't seem to be a CBC one");
+ return doDecryptECB(encoded,plain);
+ }
+ encoded.cutLeft(1);
+
+ char * tmpBuf;
+ int len = encoded.base64ToBuffer(&tmpBuf,false);
+ if(len < 0)
+ {
+ setLastError(__tr("The message is not a base64 string: this is not my stuff"));
+ return false;
+ }
+ if((len < 8) || (len % 8))
+ {
+ setLastError(__tr("The message doesn't seem to be encoded with CBC Mircryption"));
+ if(len > 0)KviStr::freeBuffer(tmpBuf);
+ return false;
+ }
+
+ plain.setLength(len);
+ BlowFish bf((unsigned char *)m_szDecryptKey.ptr(),m_szDecryptKey.len());
+ bf.ResetChain();
+ bf.Decrypt((unsigned char *)tmpBuf,(unsigned char *)plain.ptr(),len,BlowFish::CBC);
+
+ // kill the first 8 bytes (random IV)
+ plain.cutLeft(8);
+
+ KviStr::freeBuffer(tmpBuf);
+
+ return true;
+ }
+
+
+ static KviCryptEngine * allocMircryptionEngine()
+ {
+ return new KviMircryptionEngine();
+ }
+
+#endif
+
+
+// =======================================
+// module routines
+// =======================================
+static bool rijndael_module_init(KviModule * m)
+{
+#ifdef COMPILE_CRYPT_SUPPORT
+ g_pEngineList = new KviPointerList<KviCryptEngine>;
+ g_pEngineList->setAutoDelete(false);
+
+ KviStr format = __tr("Cryptographic engine based on the\n" \
+ "Advanced Encryption Standard (AES)\n" \
+ "algorithm called Rijndael.\n" \
+ "The text is first encrypted with rijndael\n" \
+ "and then converted to %s notation.\n" \
+ "The keys used are %d bit long and will be padded\n" \
+ "with zeros if you provide shorter ones.\n" \
+ "If only one key is provided, this engine\n" \
+ "will use it for both encrypting and decrypting.\n" \
+ "See the rijndael module documentation\n" \
+ "for more info on the algorithm used.\n");
+
+ // FIXME: Maybe convert this repeated code to a function eh ?
+
+ KviCryptEngineDescription * d = new KviCryptEngineDescription;
+ d->szName = "Rijndael128Hex";
+ d->szAuthor = "Szymon Stefanek";
+ d->szDescription.sprintf(format.ptr(),__tr("hexadecimal"),128);
+ d->iFlags = KVI_CRYPTENGINE_CAN_ENCRYPT | KVI_CRYPTENGINE_CAN_DECRYPT |
+ KVI_CRYPTENGINE_WANT_ENCRYPT_KEY | KVI_CRYPTENGINE_WANT_DECRYPT_KEY;
+ d->allocFunc = allocRijndael128HexEngine;
+ d->deallocFunc = deallocRijndaelCryptEngine;
+ m->registerCryptEngine(d);
+
+ d = new KviCryptEngineDescription;
+ d->szName = "Rijndael192Hex";
+ d->szAuthor = "Szymon Stefanek";
+ d->szDescription.sprintf(format.ptr(),__tr("hexadecimal"),192);
+ d->iFlags = KVI_CRYPTENGINE_CAN_ENCRYPT | KVI_CRYPTENGINE_CAN_DECRYPT |
+ KVI_CRYPTENGINE_WANT_ENCRYPT_KEY | KVI_CRYPTENGINE_WANT_DECRYPT_KEY;
+ d->allocFunc = allocRijndael192HexEngine;
+ d->deallocFunc = deallocRijndaelCryptEngine;
+ m->registerCryptEngine(d);
+
+ d = new KviCryptEngineDescription;
+ d->szName = "Rijndael256Hex";
+ d->szAuthor = "Szymon Stefanek";
+ d->szDescription.sprintf(format.ptr(),__tr("hexadecimal"),256);
+ d->iFlags = KVI_CRYPTENGINE_CAN_ENCRYPT | KVI_CRYPTENGINE_CAN_DECRYPT |
+ KVI_CRYPTENGINE_WANT_ENCRYPT_KEY | KVI_CRYPTENGINE_WANT_DECRYPT_KEY;
+ d->allocFunc = allocRijndael256HexEngine;
+ d->deallocFunc = deallocRijndaelCryptEngine;
+ m->registerCryptEngine(d);
+
+ d = new KviCryptEngineDescription;
+ d->szName = "Rijndael128Base64";
+ d->szAuthor = "Szymon Stefanek";
+ d->szDescription.sprintf(format.ptr(),__tr("base64"),128);
+ d->iFlags = KVI_CRYPTENGINE_CAN_ENCRYPT | KVI_CRYPTENGINE_CAN_DECRYPT |
+ KVI_CRYPTENGINE_WANT_ENCRYPT_KEY | KVI_CRYPTENGINE_WANT_DECRYPT_KEY;
+ d->allocFunc = allocRijndael128Base64Engine;
+ d->deallocFunc = deallocRijndaelCryptEngine;
+ m->registerCryptEngine(d);
+
+ d = new KviCryptEngineDescription;
+ d->szName = "Rijndael192Base64";
+ d->szAuthor = "Szymon Stefanek";
+ d->szDescription.sprintf(format.ptr(),__tr("base64"),192);
+ d->iFlags = KVI_CRYPTENGINE_CAN_ENCRYPT | KVI_CRYPTENGINE_CAN_DECRYPT |
+ KVI_CRYPTENGINE_WANT_ENCRYPT_KEY | KVI_CRYPTENGINE_WANT_DECRYPT_KEY;
+ d->allocFunc = allocRijndael192Base64Engine;
+ d->deallocFunc = deallocRijndaelCryptEngine;
+ m->registerCryptEngine(d);
+
+ d = new KviCryptEngineDescription;
+ d->szName = "Rijndael256Base64";
+ d->szAuthor = "Szymon Stefanek";
+ d->szDescription.sprintf(format.ptr(),__tr("base64"),256);
+ d->iFlags = KVI_CRYPTENGINE_CAN_ENCRYPT | KVI_CRYPTENGINE_CAN_DECRYPT |
+ KVI_CRYPTENGINE_WANT_ENCRYPT_KEY | KVI_CRYPTENGINE_WANT_DECRYPT_KEY;
+ d->allocFunc = allocRijndael256Base64Engine;
+ d->deallocFunc = deallocRijndaelCryptEngine;
+ m->registerCryptEngine(d);
+
+
+ d = new KviCryptEngineDescription;
+ d->szName = "Mircryption";
+ d->szAuthor = "Szymon Stefanek";
+ d->szDescription = __tr("Popular cryptographic engine based on the\n" \
+ "old Blowfish encryption algorithm.\n" \
+ "The text is first encrypted with Blowfish \n" \
+ "and then converted to base64 notation.\n" \
+ "The keys used have variable length and\n" \
+ "are specified as character strings.\n" \
+ "You can specify keys long up to 56 bytes (448 bits).\n" \
+ "If only one key is provided, this engine\n" \
+ "will use it for both encrypting and decrypting.\n" \
+ "This engine works in ECB mode by default:\n" \
+ "if you want to use CBC mode you must prefix\n" \
+ "your key(s) with \"cbc:\".\n");
+ d->iFlags = KVI_CRYPTENGINE_CAN_ENCRYPT | KVI_CRYPTENGINE_CAN_DECRYPT |
+ KVI_CRYPTENGINE_WANT_ENCRYPT_KEY | KVI_CRYPTENGINE_WANT_DECRYPT_KEY;
+ d->allocFunc = allocMircryptionEngine;
+ d->deallocFunc = deallocRijndaelCryptEngine;
+ m->registerCryptEngine(d);
+
+
+ return true;
+#else
+ return false;
+#endif
+}
+
+static bool rijndael_module_cleanup(KviModule *m)
+{
+#ifdef COMPILE_CRYPT_SUPPORT
+ while(g_pEngineList->first())delete g_pEngineList->first();
+ delete g_pEngineList;
+ g_pEngineList = 0;
+ m->unregisterCryptEngines();
+ return true;
+#else
+ return false;
+#endif
+}
+
+static bool rijndael_module_can_unload(KviModule *)
+{
+#ifdef COMPILE_CRYPT_SUPPORT
+ return g_pEngineList->isEmpty();
+#else
+ return true;
+#endif
+}
+
+// =======================================
+// plugin definition structure
+// =======================================
+KVIRC_MODULE(
+ "Rijndael crypt engine",
+ "1.0.0",
+ "Szymon Stefanek <pragma at kvirc dot net>" ,
+ "Exports the rijndael crypt engine",
+ rijndael_module_init ,
+ rijndael_module_can_unload,
+ 0,
+ rijndael_module_cleanup
+)
+
+#ifdef COMPILE_CRYPT_SUPPORT
+ #include "libkvirijndael.moc"
+#endif
diff --git a/src/modules/rijndael/libkvirijndael.h b/src/modules/rijndael/libkvirijndael.h
new file mode 100644
index 00000000..900ff252
--- /dev/null
+++ b/src/modules/rijndael/libkvirijndael.h
@@ -0,0 +1,169 @@
+#ifndef _LIBKVIRIJNDAEL_H_
+#define _LIBKVIRIJNDAEL_H_
+//
+// File : libkvirijndael.h
+// Creation date : Sat Now 4 2000 15:41:41 CEST by Szymon Stefanek
+//
+// This file is part of the KVirc irc client distribution
+// Copyright (C) 1999-2000 Till Bush (buti@geocities.com)
+//
+// This program is FREE software. You can redistribute it and/or
+// modify it under the terms of the GNU General Public License
+// as published by the Free Software Foundation; either version 2
+// of the License, or (at your opinion) any later version.
+//
+// This program is distributed in the HOPE that it will be USEFUL,
+// but WITHOUT ANY WARRANTY; without even the implied warranty of
+// MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
+// See the GNU General Public License for more details.
+//
+// You should have received a copy of the GNU General Public License
+// along with this program. If not, write to the Free Software Foundation,
+// Inc. ,51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
+//
+
+#include "kvi_settings.h"
+
+#ifdef COMPILE_CRYPT_SUPPORT
+
+ #include "kvi_crypt.h"
+ #include "rijndael.h"
+
+ class KviRijndaelEngine : public KviCryptEngine
+ {
+ Q_OBJECT
+ public:
+ KviRijndaelEngine();
+ virtual ~KviRijndaelEngine();
+ private:
+ Rijndael * m_pEncryptCipher;
+ Rijndael * m_pDecryptCipher;
+ public:
+ virtual bool init(const char *encKey,int encKeyLen,const char *decKey,int decKeyLen);
+ virtual KviCryptEngine::EncryptResult encrypt(const char * plainText,KviStr &outBuffer);
+ virtual KviCryptEngine::DecryptResult decrypt(const char * inBuffer,KviStr &plainText);
+ protected:
+ virtual bool binaryToAscii(const char * inBuffer,int len,KviStr &outBuffer){ return false; };
+ virtual bool asciiToBinary(const char * inBuffer,int * len,char ** outBuffer){ return false; };
+ virtual int getKeyLen(){ return 32; };
+ virtual Rijndael::KeyLength getKeyLenId(){ return Rijndael::Key32Bytes; };
+ private:
+ void setLastErrorFromRijndaelErrorCode(int errCode);
+ };
+
+ class KviRijndaelHexEngine : public KviRijndaelEngine
+ {
+ Q_OBJECT
+ public:
+ KviRijndaelHexEngine() : KviRijndaelEngine() {};
+ virtual ~KviRijndaelHexEngine(){};
+ protected:
+ virtual bool binaryToAscii(const char * inBuffer,int len,KviStr &outBuffer);
+ virtual bool asciiToBinary(const char * inBuffer,int * len,char ** outBuffer);
+ };
+
+ class KviRijndael128HexEngine : public KviRijndaelHexEngine
+ {
+ Q_OBJECT
+ public:
+ KviRijndael128HexEngine() : KviRijndaelHexEngine() {};
+ virtual ~KviRijndael128HexEngine(){};
+ protected:
+ virtual int getKenLen(){ return 16; };
+ virtual Rijndael::KeyLength getKeyLenId(){ return Rijndael::Key16Bytes; };
+ };
+
+ class KviRijndael192HexEngine : public KviRijndaelHexEngine
+ {
+ Q_OBJECT
+ public:
+ KviRijndael192HexEngine() : KviRijndaelHexEngine() {};
+ virtual ~KviRijndael192HexEngine(){};
+ protected:
+ virtual int getKenLen(){ return 24; };
+ virtual Rijndael::KeyLength getKeyLenId(){ return Rijndael::Key24Bytes; };
+ };
+
+ class KviRijndael256HexEngine : public KviRijndaelHexEngine
+ {
+ Q_OBJECT
+ public:
+ KviRijndael256HexEngine() : KviRijndaelHexEngine() {};
+ virtual ~KviRijndael256HexEngine(){};
+ protected:
+ virtual int getKenLen(){ return 32; };
+ };
+
+ class KviRijndaelBase64Engine : public KviRijndaelEngine
+ {
+ Q_OBJECT
+ public:
+ KviRijndaelBase64Engine() : KviRijndaelEngine() {};
+ virtual ~KviRijndaelBase64Engine(){};
+ protected:
+ virtual bool binaryToAscii(const char * inBuffer,int len,KviStr &outBuffer);
+ virtual bool asciiToBinary(const char * inBuffer,int * len,char ** outBuffer);
+ };
+
+ class KviRijndael128Base64Engine : public KviRijndaelBase64Engine
+ {
+ Q_OBJECT
+ public:
+ KviRijndael128Base64Engine() : KviRijndaelBase64Engine() {};
+ virtual ~KviRijndael128Base64Engine(){};
+ protected:
+ virtual int getKenLen(){ return 16; };
+ virtual Rijndael::KeyLength getKeyLenId(){ return Rijndael::Key16Bytes; };
+ };
+
+ class KviRijndael192Base64Engine : public KviRijndaelBase64Engine
+ {
+ Q_OBJECT
+ public:
+ KviRijndael192Base64Engine() : KviRijndaelBase64Engine() {};
+ virtual ~KviRijndael192Base64Engine(){};
+ protected:
+ virtual int getKenLen(){ return 24; };
+ virtual Rijndael::KeyLength getKeyLenId(){ return Rijndael::Key24Bytes; };
+ };
+
+ class KviRijndael256Base64Engine : public KviRijndaelBase64Engine
+ {
+ Q_OBJECT
+ public:
+ KviRijndael256Base64Engine() : KviRijndaelBase64Engine() {};
+ virtual ~KviRijndael256Base64Engine(){};
+ protected:
+ virtual int getKenLen(){ return 32; };
+ };
+
+ // Mircyption stuff
+ #define MCPS2_STARTTAG "\xABm\xAB"
+ #define MCPS2_ENDTAG "\xBBm\xBB"
+
+ class KviMircryptionEngine : public KviCryptEngine
+ {
+ Q_OBJECT
+ public:
+ KviMircryptionEngine();
+ ~KviMircryptionEngine();
+ protected:
+ KviStr m_szEncryptKey;
+ bool m_bEncryptCBC;
+ KviStr m_szDecryptKey;
+ bool m_bDecryptCBC;
+ public:
+ virtual bool isCryptographicEngine(){ return false; }; // we need to return false since it doesn't use the Qt::CTRL+P escape
+ virtual bool init(const char *encKey,int encKeyLen,const char *decKey,int decKeyLen);
+ virtual KviCryptEngine::EncryptResult encrypt(const char * plainText,KviStr &outBuffer);
+ virtual KviCryptEngine::DecryptResult decrypt(const char * inBuffer,KviStr &plainText);
+ protected:
+ bool doDecryptECB(KviStr &encoded,KviStr &plain);
+ bool doDecryptCBC(KviStr &encoded,KviStr &plain);
+ bool doEncryptECB(KviStr &plain,KviStr &encoded);
+ bool doEncryptCBC(KviStr &plain,KviStr &encoded);
+ };
+
+#endif // COMPILE_CRYPT_SUPPORT
+
+#endif // _LIBKVIRIJNDAEL_H_
diff --git a/src/modules/rijndael/rijndael.cpp b/src/modules/rijndael/rijndael.cpp
new file mode 100644
index 00000000..8adbf926
--- /dev/null
+++ b/src/modules/rijndael/rijndael.cpp
@@ -0,0 +1,1626 @@
+//
+// File : rijndael.cpp
+// Creation date : Sun Nov 5 2000 03:22:10 CEST by Szymon Stefanek
+//
+// This file is part of the KVirc irc client distribution
+// Copyright (C) 1999-2000 Szymon Stefanek (pragma at kvirc dot net)
+//
+// This program is FREE software. You can redistribute it and/or
+// modify it under the terms of the GNU General Public License
+// as published by the Free Software Foundation; either version 2
+// of the License, or (at your opinion) any later version.
+//
+// This program is distributed in the HOPE that it will be USEFUL,
+// but WITHOUT ANY WARRANTY; without even the implied warranty of
+// MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
+// See the GNU General Public License for more details.
+//
+// You should have received a copy of the GNU General Public License
+// along with this program. If not, write to the Free Software Foundation,
+// Inc. ,51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
+//
+
+//
+// Another implementation of the Rijndael cipher.
+// This is intended to be an easily usable library file.
+// Based on the Vincent Rijmen and K.U.Leuven implementation 2.4.
+//
+
+//
+// Original Copyright notice:
+//
+// rijndael-alg-fst.c v2.4 April '2000
+// rijndael-alg-fst.h
+// rijndael-api-fst.c
+// rijndael-api-fst.h
+//
+// Optimised ANSI C code
+//
+// authors: v1.0: Antoon Bosselaers
+// v2.0: Vincent Rijmen, K.U.Leuven
+// v2.3: Paulo Barreto
+// v2.4: Vincent Rijmen, K.U.Leuven
+//
+// This code is placed in the public domain.
+//
+
+//
+// This implementation works on 128 , 192 , 256 bit keys
+// and on 128 bit blocks
+//
+
+#include "kvi_settings.h"
+
+#ifdef COMPILE_CRYPT_SUPPORT
+
+#define _RIJNDAEL_CPP_
+
+#include "rijndael.h"
+
+#include "kvi_memmove.h"
+
+//#include <stdio.h>
+//#include <stdlib.h>
+
+static UINT8 S[256]=
+{
+ 99, 124, 119, 123, 242, 107, 111, 197, 48, 1, 103, 43, 254, 215, 171, 118,
+ 202, 130, 201, 125, 250, 89, 71, 240, 173, 212, 162, 175, 156, 164, 114, 192,
+ 183, 253, 147, 38, 54, 63, 247, 204, 52, 165, 229, 241, 113, 216, 49, 21,
+ 4, 199, 35, 195, 24, 150, 5, 154, 7, 18, 128, 226, 235, 39, 178, 117,
+ 9, 131, 44, 26, 27, 110, 90, 160, 82, 59, 214, 179, 41, 227, 47, 132,
+ 83, 209, 0, 237, 32, 252, 177, 91, 106, 203, 190, 57, 74, 76, 88, 207,
+ 208, 239, 170, 251, 67, 77, 51, 133, 69, 249, 2, 127, 80, 60, 159, 168,
+ 81, 163, 64, 143, 146, 157, 56, 245, 188, 182, 218, 33, 16, 255, 243, 210,
+ 205, 12, 19, 236, 95, 151, 68, 23, 196, 167, 126, 61, 100, 93, 25, 115,
+ 96, 129, 79, 220, 34, 42, 144, 136, 70, 238, 184, 20, 222, 94, 11, 219,
+ 224, 50, 58, 10, 73, 6, 36, 92, 194, 211, 172, 98, 145, 149, 228, 121,
+ 231, 200, 55, 109, 141, 213, 78, 169, 108, 86, 244, 234, 101, 122, 174, 8,
+ 186, 120, 37, 46, 28, 166, 180, 198, 232, 221, 116, 31, 75, 189, 139, 138,
+ 112, 62, 181, 102, 72, 3, 246, 14, 97, 53, 87, 185, 134, 193, 29, 158,
+ 225, 248, 152, 17, 105, 217, 142, 148, 155, 30, 135, 233, 206, 85, 40, 223,
+ 140, 161, 137, 13, 191, 230, 66, 104, 65, 153, 45, 15, 176, 84, 187, 22
+};
+
+
+static UINT8 T1[256][4]=
+{
+ 0xc6,0x63,0x63,0xa5, 0xf8,0x7c,0x7c,0x84, 0xee,0x77,0x77,0x99, 0xf6,0x7b,0x7b,0x8d,
+ 0xff,0xf2,0xf2,0x0d, 0xd6,0x6b,0x6b,0xbd, 0xde,0x6f,0x6f,0xb1, 0x91,0xc5,0xc5,0x54,
+ 0x60,0x30,0x30,0x50, 0x02,0x01,0x01,0x03, 0xce,0x67,0x67,0xa9, 0x56,0x2b,0x2b,0x7d,
+ 0xe7,0xfe,0xfe,0x19, 0xb5,0xd7,0xd7,0x62, 0x4d,0xab,0xab,0xe6, 0xec,0x76,0x76,0x9a,
+ 0x8f,0xca,0xca,0x45, 0x1f,0x82,0x82,0x9d, 0x89,0xc9,0xc9,0x40, 0xfa,0x7d,0x7d,0x87,
+ 0xef,0xfa,0xfa,0x15, 0xb2,0x59,0x59,0xeb, 0x8e,0x47,0x47,0xc9, 0xfb,0xf0,0xf0,0x0b,
+ 0x41,0xad,0xad,0xec, 0xb3,0xd4,0xd4,0x67, 0x5f,0xa2,0xa2,0xfd, 0x45,0xaf,0xaf,0xea,
+ 0x23,0x9c,0x9c,0xbf, 0x53,0xa4,0xa4,0xf7, 0xe4,0x72,0x72,0x96, 0x9b,0xc0,0xc0,0x5b,
+ 0x75,0xb7,0xb7,0xc2, 0xe1,0xfd,0xfd,0x1c, 0x3d,0x93,0x93,0xae, 0x4c,0x26,0x26,0x6a,
+ 0x6c,0x36,0x36,0x5a, 0x7e,0x3f,0x3f,0x41, 0xf5,0xf7,0xf7,0x02, 0x83,0xcc,0xcc,0x4f,
+ 0x68,0x34,0x34,0x5c, 0x51,0xa5,0xa5,0xf4, 0xd1,0xe5,0xe5,0x34, 0xf9,0xf1,0xf1,0x08,
+ 0xe2,0x71,0x71,0x93, 0xab,0xd8,0xd8,0x73, 0x62,0x31,0x31,0x53, 0x2a,0x15,0x15,0x3f,
+ 0x08,0x04,0x04,0x0c, 0x95,0xc7,0xc7,0x52, 0x46,0x23,0x23,0x65, 0x9d,0xc3,0xc3,0x5e,
+ 0x30,0x18,0x18,0x28, 0x37,0x96,0x96,0xa1, 0x0a,0x05,0x05,0x0f, 0x2f,0x9a,0x9a,0xb5,
+ 0x0e,0x07,0x07,0x09, 0x24,0x12,0x12,0x36, 0x1b,0x80,0x80,0x9b, 0xdf,0xe2,0xe2,0x3d,
+ 0xcd,0xeb,0xeb,0x26, 0x4e,0x27,0x27,0x69, 0x7f,0xb2,0xb2,0xcd, 0xea,0x75,0x75,0x9f,
+ 0x12,0x09,0x09,0x1b, 0x1d,0x83,0x83,0x9e, 0x58,0x2c,0x2c,0x74, 0x34,0x1a,0x1a,0x2e,
+ 0x36,0x1b,0x1b,0x2d, 0xdc,0x6e,0x6e,0xb2, 0xb4,0x5a,0x5a,0xee, 0x5b,0xa0,0xa0,0xfb,
+ 0xa4,0x52,0x52,0xf6, 0x76,0x3b,0x3b,0x4d, 0xb7,0xd6,0xd6,0x61, 0x7d,0xb3,0xb3,0xce,
+ 0x52,0x29,0x29,0x7b, 0xdd,0xe3,0xe3,0x3e, 0x5e,0x2f,0x2f,0x71, 0x13,0x84,0x84,0x97,
+ 0xa6,0x53,0x53,0xf5, 0xb9,0xd1,0xd1,0x68, 0x00,0x00,0x00,0x00, 0xc1,0xed,0xed,0x2c,
+ 0x40,0x20,0x20,0x60, 0xe3,0xfc,0xfc,0x1f, 0x79,0xb1,0xb1,0xc8, 0xb6,0x5b,0x5b,0xed,
+ 0xd4,0x6a,0x6a,0xbe, 0x8d,0xcb,0xcb,0x46, 0x67,0xbe,0xbe,0xd9, 0x72,0x39,0x39,0x4b,
+ 0x94,0x4a,0x4a,0xde, 0x98,0x4c,0x4c,0xd4, 0xb0,0x58,0x58,0xe8, 0x85,0xcf,0xcf,0x4a,
+ 0xbb,0xd0,0xd0,0x6b, 0xc5,0xef,0xef,0x2a, 0x4f,0xaa,0xaa,0xe5, 0xed,0xfb,0xfb,0x16,
+ 0x86,0x43,0x43,0xc5, 0x9a,0x4d,0x4d,0xd7, 0x66,0x33,0x33,0x55, 0x11,0x85,0x85,0x94,
+ 0x8a,0x45,0x45,0xcf, 0xe9,0xf9,0xf9,0x10, 0x04,0x02,0x02,0x06, 0xfe,0x7f,0x7f,0x81,
+ 0xa0,0x50,0x50,0xf0, 0x78,0x3c,0x3c,0x44, 0x25,0x9f,0x9f,0xba, 0x4b,0xa8,0xa8,0xe3,
+ 0xa2,0x51,0x51,0xf3, 0x5d,0xa3,0xa3,0xfe, 0x80,0x40,0x40,0xc0, 0x05,0x8f,0x8f,0x8a,
+ 0x3f,0x92,0x92,0xad, 0x21,0x9d,0x9d,0xbc, 0x70,0x38,0x38,0x48, 0xf1,0xf5,0xf5,0x04,
+ 0x63,0xbc,0xbc,0xdf, 0x77,0xb6,0xb6,0xc1, 0xaf,0xda,0xda,0x75, 0x42,0x21,0x21,0x63,
+ 0x20,0x10,0x10,0x30, 0xe5,0xff,0xff,0x1a, 0xfd,0xf3,0xf3,0x0e, 0xbf,0xd2,0xd2,0x6d,
+ 0x81,0xcd,0xcd,0x4c, 0x18,0x0c,0x0c,0x14, 0x26,0x13,0x13,0x35, 0xc3,0xec,0xec,0x2f,
+ 0xbe,0x5f,0x5f,0xe1, 0x35,0x97,0x97,0xa2, 0x88,0x44,0x44,0xcc, 0x2e,0x17,0x17,0x39,
+ 0x93,0xc4,0xc4,0x57, 0x55,0xa7,0xa7,0xf2, 0xfc,0x7e,0x7e,0x82, 0x7a,0x3d,0x3d,0x47,
+ 0xc8,0x64,0x64,0xac, 0xba,0x5d,0x5d,0xe7, 0x32,0x19,0x19,0x2b, 0xe6,0x73,0x73,0x95,
+ 0xc0,0x60,0x60,0xa0, 0x19,0x81,0x81,0x98, 0x9e,0x4f,0x4f,0xd1, 0xa3,0xdc,0xdc,0x7f,
+ 0x44,0x22,0x22,0x66, 0x54,0x2a,0x2a,0x7e, 0x3b,0x90,0x90,0xab, 0x0b,0x88,0x88,0x83,
+ 0x8c,0x46,0x46,0xca, 0xc7,0xee,0xee,0x29, 0x6b,0xb8,0xb8,0xd3, 0x28,0x14,0x14,0x3c,
+ 0xa7,0xde,0xde,0x79, 0xbc,0x5e,0x5e,0xe2, 0x16,0x0b,0x0b,0x1d, 0xad,0xdb,0xdb,0x76,
+ 0xdb,0xe0,0xe0,0x3b, 0x64,0x32,0x32,0x56, 0x74,0x3a,0x3a,0x4e, 0x14,0x0a,0x0a,0x1e,
+ 0x92,0x49,0x49,0xdb, 0x0c,0x06,0x06,0x0a, 0x48,0x24,0x24,0x6c, 0xb8,0x5c,0x5c,0xe4,
+ 0x9f,0xc2,0xc2,0x5d, 0xbd,0xd3,0xd3,0x6e, 0x43,0xac,0xac,0xef, 0xc4,0x62,0x62,0xa6,
+ 0x39,0x91,0x91,0xa8, 0x31,0x95,0x95,0xa4, 0xd3,0xe4,0xe4,0x37, 0xf2,0x79,0x79,0x8b,
+ 0xd5,0xe7,0xe7,0x32, 0x8b,0xc8,0xc8,0x43, 0x6e,0x37,0x37,0x59, 0xda,0x6d,0x6d,0xb7,
+ 0x01,0x8d,0x8d,0x8c, 0xb1,0xd5,0xd5,0x64, 0x9c,0x4e,0x4e,0xd2, 0x49,0xa9,0xa9,0xe0,
+ 0xd8,0x6c,0x6c,0xb4, 0xac,0x56,0x56,0xfa, 0xf3,0xf4,0xf4,0x07, 0xcf,0xea,0xea,0x25,
+ 0xca,0x65,0x65,0xaf, 0xf4,0x7a,0x7a,0x8e, 0x47,0xae,0xae,0xe9, 0x10,0x08,0x08,0x18,
+ 0x6f,0xba,0xba,0xd5, 0xf0,0x78,0x78,0x88, 0x4a,0x25,0x25,0x6f, 0x5c,0x2e,0x2e,0x72,
+ 0x38,0x1c,0x1c,0x24, 0x57,0xa6,0xa6,0xf1, 0x73,0xb4,0xb4,0xc7, 0x97,0xc6,0xc6,0x51,
+ 0xcb,0xe8,0xe8,0x23, 0xa1,0xdd,0xdd,0x7c, 0xe8,0x74,0x74,0x9c, 0x3e,0x1f,0x1f,0x21,
+ 0x96,0x4b,0x4b,0xdd, 0x61,0xbd,0xbd,0xdc, 0x0d,0x8b,0x8b,0x86, 0x0f,0x8a,0x8a,0x85,
+ 0xe0,0x70,0x70,0x90, 0x7c,0x3e,0x3e,0x42, 0x71,0xb5,0xb5,0xc4, 0xcc,0x66,0x66,0xaa,
+ 0x90,0x48,0x48,0xd8, 0x06,0x03,0x03,0x05, 0xf7,0xf6,0xf6,0x01, 0x1c,0x0e,0x0e,0x12,
+ 0xc2,0x61,0x61,0xa3, 0x6a,0x35,0x35,0x5f, 0xae,0x57,0x57,0xf9, 0x69,0xb9,0xb9,0xd0,
+ 0x17,0x86,0x86,0x91, 0x99,0xc1,0xc1,0x58, 0x3a,0x1d,0x1d,0x27, 0x27,0x9e,0x9e,0xb9,
+ 0xd9,0xe1,0xe1,0x38, 0xeb,0xf8,0xf8,0x13, 0x2b,0x98,0x98,0xb3, 0x22,0x11,0x11,0x33,
+ 0xd2,0x69,0x69,0xbb, 0xa9,0xd9,0xd9,0x70, 0x07,0x8e,0x8e,0x89, 0x33,0x94,0x94,0xa7,
+ 0x2d,0x9b,0x9b,0xb6, 0x3c,0x1e,0x1e,0x22, 0x15,0x87,0x87,0x92, 0xc9,0xe9,0xe9,0x20,
+ 0x87,0xce,0xce,0x49, 0xaa,0x55,0x55,0xff, 0x50,0x28,0x28,0x78, 0xa5,0xdf,0xdf,0x7a,
+ 0x03,0x8c,0x8c,0x8f, 0x59,0xa1,0xa1,0xf8, 0x09,0x89,0x89,0x80, 0x1a,0x0d,0x0d,0x17,
+ 0x65,0xbf,0xbf,0xda, 0xd7,0xe6,0xe6,0x31, 0x84,0x42,0x42,0xc6, 0xd0,0x68,0x68,0xb8,
+ 0x82,0x41,0x41,0xc3, 0x29,0x99,0x99,0xb0, 0x5a,0x2d,0x2d,0x77, 0x1e,0x0f,0x0f,0x11,
+ 0x7b,0xb0,0xb0,0xcb, 0xa8,0x54,0x54,0xfc, 0x6d,0xbb,0xbb,0xd6, 0x2c,0x16,0x16,0x3a
+};
+
+static UINT8 T2[256][4]=
+{
+ 0xa5,0xc6,0x63,0x63, 0x84,0xf8,0x7c,0x7c, 0x99,0xee,0x77,0x77, 0x8d,0xf6,0x7b,0x7b,
+ 0x0d,0xff,0xf2,0xf2, 0xbd,0xd6,0x6b,0x6b, 0xb1,0xde,0x6f,0x6f, 0x54,0x91,0xc5,0xc5,
+ 0x50,0x60,0x30,0x30, 0x03,0x02,0x01,0x01, 0xa9,0xce,0x67,0x67, 0x7d,0x56,0x2b,0x2b,
+ 0x19,0xe7,0xfe,0xfe, 0x62,0xb5,0xd7,0xd7, 0xe6,0x4d,0xab,0xab, 0x9a,0xec,0x76,0x76,
+ 0x45,0x8f,0xca,0xca, 0x9d,0x1f,0x82,0x82, 0x40,0x89,0xc9,0xc9, 0x87,0xfa,0x7d,0x7d,
+ 0x15,0xef,0xfa,0xfa, 0xeb,0xb2,0x59,0x59, 0xc9,0x8e,0x47,0x47, 0x0b,0xfb,0xf0,0xf0,
+ 0xec,0x41,0xad,0xad, 0x67,0xb3,0xd4,0xd4, 0xfd,0x5f,0xa2,0xa2, 0xea,0x45,0xaf,0xaf,
+ 0xbf,0x23,0x9c,0x9c, 0xf7,0x53,0xa4,0xa4, 0x96,0xe4,0x72,0x72, 0x5b,0x9b,0xc0,0xc0,
+ 0xc2,0x75,0xb7,0xb7, 0x1c,0xe1,0xfd,0xfd, 0xae,0x3d,0x93,0x93, 0x6a,0x4c,0x26,0x26,
+ 0x5a,0x6c,0x36,0x36, 0x41,0x7e,0x3f,0x3f, 0x02,0xf5,0xf7,0xf7, 0x4f,0x83,0xcc,0xcc,
+ 0x5c,0x68,0x34,0x34, 0xf4,0x51,0xa5,0xa5, 0x34,0xd1,0xe5,0xe5, 0x08,0xf9,0xf1,0xf1,
+ 0x93,0xe2,0x71,0x71, 0x73,0xab,0xd8,0xd8, 0x53,0x62,0x31,0x31, 0x3f,0x2a,0x15,0x15,
+ 0x0c,0x08,0x04,0x04, 0x52,0x95,0xc7,0xc7, 0x65,0x46,0x23,0x23, 0x5e,0x9d,0xc3,0xc3,
+ 0x28,0x30,0x18,0x18, 0xa1,0x37,0x96,0x96, 0x0f,0x0a,0x05,0x05, 0xb5,0x2f,0x9a,0x9a,
+ 0x09,0x0e,0x07,0x07, 0x36,0x24,0x12,0x12, 0x9b,0x1b,0x80,0x80, 0x3d,0xdf,0xe2,0xe2,
+ 0x26,0xcd,0xeb,0xeb, 0x69,0x4e,0x27,0x27, 0xcd,0x7f,0xb2,0xb2, 0x9f,0xea,0x75,0x75,
+ 0x1b,0x12,0x09,0x09, 0x9e,0x1d,0x83,0x83, 0x74,0x58,0x2c,0x2c, 0x2e,0x34,0x1a,0x1a,
+ 0x2d,0x36,0x1b,0x1b, 0xb2,0xdc,0x6e,0x6e, 0xee,0xb4,0x5a,0x5a, 0xfb,0x5b,0xa0,0xa0,
+ 0xf6,0xa4,0x52,0x52, 0x4d,0x76,0x3b,0x3b, 0x61,0xb7,0xd6,0xd6, 0xce,0x7d,0xb3,0xb3,
+ 0x7b,0x52,0x29,0x29, 0x3e,0xdd,0xe3,0xe3, 0x71,0x5e,0x2f,0x2f, 0x97,0x13,0x84,0x84,
+ 0xf5,0xa6,0x53,0x53, 0x68,0xb9,0xd1,0xd1, 0x00,0x00,0x00,0x00, 0x2c,0xc1,0xed,0xed,
+ 0x60,0x40,0x20,0x20, 0x1f,0xe3,0xfc,0xfc, 0xc8,0x79,0xb1,0xb1, 0xed,0xb6,0x5b,0x5b,
+ 0xbe,0xd4,0x6a,0x6a, 0x46,0x8d,0xcb,0xcb, 0xd9,0x67,0xbe,0xbe, 0x4b,0x72,0x39,0x39,
+ 0xde,0x94,0x4a,0x4a, 0xd4,0x98,0x4c,0x4c, 0xe8,0xb0,0x58,0x58, 0x4a,0x85,0xcf,0xcf,
+ 0x6b,0xbb,0xd0,0xd0, 0x2a,0xc5,0xef,0xef, 0xe5,0x4f,0xaa,0xaa, 0x16,0xed,0xfb,0xfb,
+ 0xc5,0x86,0x43,0x43, 0xd7,0x9a,0x4d,0x4d, 0x55,0x66,0x33,0x33, 0x94,0x11,0x85,0x85,
+ 0xcf,0x8a,0x45,0x45, 0x10,0xe9,0xf9,0xf9, 0x06,0x04,0x02,0x02, 0x81,0xfe,0x7f,0x7f,
+ 0xf0,0xa0,0x50,0x50, 0x44,0x78,0x3c,0x3c, 0xba,0x25,0x9f,0x9f, 0xe3,0x4b,0xa8,0xa8,
+ 0xf3,0xa2,0x51,0x51, 0xfe,0x5d,0xa3,0xa3, 0xc0,0x80,0x40,0x40, 0x8a,0x05,0x8f,0x8f,
+ 0xad,0x3f,0x92,0x92, 0xbc,0x21,0x9d,0x9d, 0x48,0x70,0x38,0x38, 0x04,0xf1,0xf5,0xf5,
+ 0xdf,0x63,0xbc,0xbc, 0xc1,0x77,0xb6,0xb6, 0x75,0xaf,0xda,0xda, 0x63,0x42,0x21,0x21,
+ 0x30,0x20,0x10,0x10, 0x1a,0xe5,0xff,0xff, 0x0e,0xfd,0xf3,0xf3, 0x6d,0xbf,0xd2,0xd2,
+ 0x4c,0x81,0xcd,0xcd, 0x14,0x18,0x0c,0x0c, 0x35,0x26,0x13,0x13, 0x2f,0xc3,0xec,0xec,
+ 0xe1,0xbe,0x5f,0x5f, 0xa2,0x35,0x97,0x97, 0xcc,0x88,0x44,0x44, 0x39,0x2e,0x17,0x17,
+ 0x57,0x93,0xc4,0xc4, 0xf2,0x55,0xa7,0xa7, 0x82,0xfc,0x7e,0x7e, 0x47,0x7a,0x3d,0x3d,
+ 0xac,0xc8,0x64,0x64, 0xe7,0xba,0x5d,0x5d, 0x2b,0x32,0x19,0x19, 0x95,0xe6,0x73,0x73,
+ 0xa0,0xc0,0x60,0x60, 0x98,0x19,0x81,0x81, 0xd1,0x9e,0x4f,0x4f, 0x7f,0xa3,0xdc,0xdc,
+ 0x66,0x44,0x22,0x22, 0x7e,0x54,0x2a,0x2a, 0xab,0x3b,0x90,0x90, 0x83,0x0b,0x88,0x88,
+ 0xca,0x8c,0x46,0x46, 0x29,0xc7,0xee,0xee, 0xd3,0x6b,0xb8,0xb8, 0x3c,0x28,0x14,0x14,
+ 0x79,0xa7,0xde,0xde, 0xe2,0xbc,0x5e,0x5e, 0x1d,0x16,0x0b,0x0b, 0x76,0xad,0xdb,0xdb,
+ 0x3b,0xdb,0xe0,0xe0, 0x56,0x64,0x32,0x32, 0x4e,0x74,0x3a,0x3a, 0x1e,0x14,0x0a,0x0a,
+ 0xdb,0x92,0x49,0x49, 0x0a,0x0c,0x06,0x06, 0x6c,0x48,0x24,0x24, 0xe4,0xb8,0x5c,0x5c,
+ 0x5d,0x9f,0xc2,0xc2, 0x6e,0xbd,0xd3,0xd3, 0xef,0x43,0xac,0xac, 0xa6,0xc4,0x62,0x62,
+ 0xa8,0x39,0x91,0x91, 0xa4,0x31,0x95,0x95, 0x37,0xd3,0xe4,0xe4, 0x8b,0xf2,0x79,0x79,
+ 0x32,0xd5,0xe7,0xe7, 0x43,0x8b,0xc8,0xc8, 0x59,0x6e,0x37,0x37, 0xb7,0xda,0x6d,0x6d,
+ 0x8c,0x01,0x8d,0x8d, 0x64,0xb1,0xd5,0xd5, 0xd2,0x9c,0x4e,0x4e, 0xe0,0x49,0xa9,0xa9,
+ 0xb4,0xd8,0x6c,0x6c, 0xfa,0xac,0x56,0x56, 0x07,0xf3,0xf4,0xf4, 0x25,0xcf,0xea,0xea,
+ 0xaf,0xca,0x65,0x65, 0x8e,0xf4,0x7a,0x7a, 0xe9,0x47,0xae,0xae, 0x18,0x10,0x08,0x08,
+ 0xd5,0x6f,0xba,0xba, 0x88,0xf0,0x78,0x78, 0x6f,0x4a,0x25,0x25, 0x72,0x5c,0x2e,0x2e,
+ 0x24,0x38,0x1c,0x1c, 0xf1,0x57,0xa6,0xa6, 0xc7,0x73,0xb4,0xb4, 0x51,0x97,0xc6,0xc6,
+ 0x23,0xcb,0xe8,0xe8, 0x7c,0xa1,0xdd,0xdd, 0x9c,0xe8,0x74,0x74, 0x21,0x3e,0x1f,0x1f,
+ 0xdd,0x96,0x4b,0x4b, 0xdc,0x61,0xbd,0xbd, 0x86,0x0d,0x8b,0x8b, 0x85,0x0f,0x8a,0x8a,
+ 0x90,0xe0,0x70,0x70, 0x42,0x7c,0x3e,0x3e, 0xc4,0x71,0xb5,0xb5, 0xaa,0xcc,0x66,0x66,
+ 0xd8,0x90,0x48,0x48, 0x05,0x06,0x03,0x03, 0x01,0xf7,0xf6,0xf6, 0x12,0x1c,0x0e,0x0e,
+ 0xa3,0xc2,0x61,0x61, 0x5f,0x6a,0x35,0x35, 0xf9,0xae,0x57,0x57, 0xd0,0x69,0xb9,0xb9,
+ 0x91,0x17,0x86,0x86, 0x58,0x99,0xc1,0xc1, 0x27,0x3a,0x1d,0x1d, 0xb9,0x27,0x9e,0x9e,
+ 0x38,0xd9,0xe1,0xe1, 0x13,0xeb,0xf8,0xf8, 0xb3,0x2b,0x98,0x98, 0x33,0x22,0x11,0x11,
+ 0xbb,0xd2,0x69,0x69, 0x70,0xa9,0xd9,0xd9, 0x89,0x07,0x8e,0x8e, 0xa7,0x33,0x94,0x94,
+ 0xb6,0x2d,0x9b,0x9b, 0x22,0x3c,0x1e,0x1e, 0x92,0x15,0x87,0x87, 0x20,0xc9,0xe9,0xe9,
+ 0x49,0x87,0xce,0xce, 0xff,0xaa,0x55,0x55, 0x78,0x50,0x28,0x28, 0x7a,0xa5,0xdf,0xdf,
+ 0x8f,0x03,0x8c,0x8c, 0xf8,0x59,0xa1,0xa1, 0x80,0x09,0x89,0x89, 0x17,0x1a,0x0d,0x0d,
+ 0xda,0x65,0xbf,0xbf, 0x31,0xd7,0xe6,0xe6, 0xc6,0x84,0x42,0x42, 0xb8,0xd0,0x68,0x68,
+ 0xc3,0x82,0x41,0x41, 0xb0,0x29,0x99,0x99, 0x77,0x5a,0x2d,0x2d, 0x11,0x1e,0x0f,0x0f,
+ 0xcb,0x7b,0xb0,0xb0, 0xfc,0xa8,0x54,0x54, 0xd6,0x6d,0xbb,0xbb, 0x3a,0x2c,0x16,0x16
+};
+
+static UINT8 T3[256][4]=
+{
+ 0x63,0xa5,0xc6,0x63, 0x7c,0x84,0xf8,0x7c, 0x77,0x99,0xee,0x77, 0x7b,0x8d,0xf6,0x7b,
+ 0xf2,0x0d,0xff,0xf2, 0x6b,0xbd,0xd6,0x6b, 0x6f,0xb1,0xde,0x6f, 0xc5,0x54,0x91,0xc5,
+ 0x30,0x50,0x60,0x30, 0x01,0x03,0x02,0x01, 0x67,0xa9,0xce,0x67, 0x2b,0x7d,0x56,0x2b,
+ 0xfe,0x19,0xe7,0xfe, 0xd7,0x62,0xb5,0xd7, 0xab,0xe6,0x4d,0xab, 0x76,0x9a,0xec,0x76,
+ 0xca,0x45,0x8f,0xca, 0x82,0x9d,0x1f,0x82, 0xc9,0x40,0x89,0xc9, 0x7d,0x87,0xfa,0x7d,
+ 0xfa,0x15,0xef,0xfa, 0x59,0xeb,0xb2,0x59, 0x47,0xc9,0x8e,0x47, 0xf0,0x0b,0xfb,0xf0,
+ 0xad,0xec,0x41,0xad, 0xd4,0x67,0xb3,0xd4, 0xa2,0xfd,0x5f,0xa2, 0xaf,0xea,0x45,0xaf,
+ 0x9c,0xbf,0x23,0x9c, 0xa4,0xf7,0x53,0xa4, 0x72,0x96,0xe4,0x72, 0xc0,0x5b,0x9b,0xc0,
+ 0xb7,0xc2,0x75,0xb7, 0xfd,0x1c,0xe1,0xfd, 0x93,0xae,0x3d,0x93, 0x26,0x6a,0x4c,0x26,
+ 0x36,0x5a,0x6c,0x36, 0x3f,0x41,0x7e,0x3f, 0xf7,0x02,0xf5,0xf7, 0xcc,0x4f,0x83,0xcc,
+ 0x34,0x5c,0x68,0x34, 0xa5,0xf4,0x51,0xa5, 0xe5,0x34,0xd1,0xe5, 0xf1,0x08,0xf9,0xf1,
+ 0x71,0x93,0xe2,0x71, 0xd8,0x73,0xab,0xd8, 0x31,0x53,0x62,0x31, 0x15,0x3f,0x2a,0x15,
+ 0x04,0x0c,0x08,0x04, 0xc7,0x52,0x95,0xc7, 0x23,0x65,0x46,0x23, 0xc3,0x5e,0x9d,0xc3,
+ 0x18,0x28,0x30,0x18, 0x96,0xa1,0x37,0x96, 0x05,0x0f,0x0a,0x05, 0x9a,0xb5,0x2f,0x9a,
+ 0x07,0x09,0x0e,0x07, 0x12,0x36,0x24,0x12, 0x80,0x9b,0x1b,0x80, 0xe2,0x3d,0xdf,0xe2,
+ 0xeb,0x26,0xcd,0xeb, 0x27,0x69,0x4e,0x27, 0xb2,0xcd,0x7f,0xb2, 0x75,0x9f,0xea,0x75,
+ 0x09,0x1b,0x12,0x09, 0x83,0x9e,0x1d,0x83, 0x2c,0x74,0x58,0x2c, 0x1a,0x2e,0x34,0x1a,
+ 0x1b,0x2d,0x36,0x1b, 0x6e,0xb2,0xdc,0x6e, 0x5a,0xee,0xb4,0x5a, 0xa0,0xfb,0x5b,0xa0,
+ 0x52,0xf6,0xa4,0x52, 0x3b,0x4d,0x76,0x3b, 0xd6,0x61,0xb7,0xd6, 0xb3,0xce,0x7d,0xb3,
+ 0x29,0x7b,0x52,0x29, 0xe3,0x3e,0xdd,0xe3, 0x2f,0x71,0x5e,0x2f, 0x84,0x97,0x13,0x84,
+ 0x53,0xf5,0xa6,0x53, 0xd1,0x68,0xb9,0xd1, 0x00,0x00,0x00,0x00, 0xed,0x2c,0xc1,0xed,
+ 0x20,0x60,0x40,0x20, 0xfc,0x1f,0xe3,0xfc, 0xb1,0xc8,0x79,0xb1, 0x5b,0xed,0xb6,0x5b,
+ 0x6a,0xbe,0xd4,0x6a, 0xcb,0x46,0x8d,0xcb, 0xbe,0xd9,0x67,0xbe, 0x39,0x4b,0x72,0x39,
+ 0x4a,0xde,0x94,0x4a, 0x4c,0xd4,0x98,0x4c, 0x58,0xe8,0xb0,0x58, 0xcf,0x4a,0x85,0xcf,
+ 0xd0,0x6b,0xbb,0xd0, 0xef,0x2a,0xc5,0xef, 0xaa,0xe5,0x4f,0xaa, 0xfb,0x16,0xed,0xfb,
+ 0x43,0xc5,0x86,0x43, 0x4d,0xd7,0x9a,0x4d, 0x33,0x55,0x66,0x33, 0x85,0x94,0x11,0x85,
+ 0x45,0xcf,0x8a,0x45, 0xf9,0x10,0xe9,0xf9, 0x02,0x06,0x04,0x02, 0x7f,0x81,0xfe,0x7f,
+ 0x50,0xf0,0xa0,0x50, 0x3c,0x44,0x78,0x3c, 0x9f,0xba,0x25,0x9f, 0xa8,0xe3,0x4b,0xa8,
+ 0x51,0xf3,0xa2,0x51, 0xa3,0xfe,0x5d,0xa3, 0x40,0xc0,0x80,0x40, 0x8f,0x8a,0x05,0x8f,
+ 0x92,0xad,0x3f,0x92, 0x9d,0xbc,0x21,0x9d, 0x38,0x48,0x70,0x38, 0xf5,0x04,0xf1,0xf5,
+ 0xbc,0xdf,0x63,0xbc, 0xb6,0xc1,0x77,0xb6, 0xda,0x75,0xaf,0xda, 0x21,0x63,0x42,0x21,
+ 0x10,0x30,0x20,0x10, 0xff,0x1a,0xe5,0xff, 0xf3,0x0e,0xfd,0xf3, 0xd2,0x6d,0xbf,0xd2,
+ 0xcd,0x4c,0x81,0xcd, 0x0c,0x14,0x18,0x0c, 0x13,0x35,0x26,0x13, 0xec,0x2f,0xc3,0xec,
+ 0x5f,0xe1,0xbe,0x5f, 0x97,0xa2,0x35,0x97, 0x44,0xcc,0x88,0x44, 0x17,0x39,0x2e,0x17,
+ 0xc4,0x57,0x93,0xc4, 0xa7,0xf2,0x55,0xa7, 0x7e,0x82,0xfc,0x7e, 0x3d,0x47,0x7a,0x3d,
+ 0x64,0xac,0xc8,0x64, 0x5d,0xe7,0xba,0x5d, 0x19,0x2b,0x32,0x19, 0x73,0x95,0xe6,0x73,
+ 0x60,0xa0,0xc0,0x60, 0x81,0x98,0x19,0x81, 0x4f,0xd1,0x9e,0x4f, 0xdc,0x7f,0xa3,0xdc,
+ 0x22,0x66,0x44,0x22, 0x2a,0x7e,0x54,0x2a, 0x90,0xab,0x3b,0x90, 0x88,0x83,0x0b,0x88,
+ 0x46,0xca,0x8c,0x46, 0xee,0x29,0xc7,0xee, 0xb8,0xd3,0x6b,0xb8, 0x14,0x3c,0x28,0x14,
+ 0xde,0x79,0xa7,0xde, 0x5e,0xe2,0xbc,0x5e, 0x0b,0x1d,0x16,0x0b, 0xdb,0x76,0xad,0xdb,
+ 0xe0,0x3b,0xdb,0xe0, 0x32,0x56,0x64,0x32, 0x3a,0x4e,0x74,0x3a, 0x0a,0x1e,0x14,0x0a,
+ 0x49,0xdb,0x92,0x49, 0x06,0x0a,0x0c,0x06, 0x24,0x6c,0x48,0x24, 0x5c,0xe4,0xb8,0x5c,
+ 0xc2,0x5d,0x9f,0xc2, 0xd3,0x6e,0xbd,0xd3, 0xac,0xef,0x43,0xac, 0x62,0xa6,0xc4,0x62,
+ 0x91,0xa8,0x39,0x91, 0x95,0xa4,0x31,0x95, 0xe4,0x37,0xd3,0xe4, 0x79,0x8b,0xf2,0x79,
+ 0xe7,0x32,0xd5,0xe7, 0xc8,0x43,0x8b,0xc8, 0x37,0x59,0x6e,0x37, 0x6d,0xb7,0xda,0x6d,
+ 0x8d,0x8c,0x01,0x8d, 0xd5,0x64,0xb1,0xd5, 0x4e,0xd2,0x9c,0x4e, 0xa9,0xe0,0x49,0xa9,
+ 0x6c,0xb4,0xd8,0x6c, 0x56,0xfa,0xac,0x56, 0xf4,0x07,0xf3,0xf4, 0xea,0x25,0xcf,0xea,
+ 0x65,0xaf,0xca,0x65, 0x7a,0x8e,0xf4,0x7a, 0xae,0xe9,0x47,0xae, 0x08,0x18,0x10,0x08,
+ 0xba,0xd5,0x6f,0xba, 0x78,0x88,0xf0,0x78, 0x25,0x6f,0x4a,0x25, 0x2e,0x72,0x5c,0x2e,
+ 0x1c,0x24,0x38,0x1c, 0xa6,0xf1,0x57,0xa6, 0xb4,0xc7,0x73,0xb4, 0xc6,0x51,0x97,0xc6,
+ 0xe8,0x23,0xcb,0xe8, 0xdd,0x7c,0xa1,0xdd, 0x74,0x9c,0xe8,0x74, 0x1f,0x21,0x3e,0x1f,
+ 0x4b,0xdd,0x96,0x4b, 0xbd,0xdc,0x61,0xbd, 0x8b,0x86,0x0d,0x8b, 0x8a,0x85,0x0f,0x8a,
+ 0x70,0x90,0xe0,0x70, 0x3e,0x42,0x7c,0x3e, 0xb5,0xc4,0x71,0xb5, 0x66,0xaa,0xcc,0x66,
+ 0x48,0xd8,0x90,0x48, 0x03,0x05,0x06,0x03, 0xf6,0x01,0xf7,0xf6, 0x0e,0x12,0x1c,0x0e,
+ 0x61,0xa3,0xc2,0x61, 0x35,0x5f,0x6a,0x35, 0x57,0xf9,0xae,0x57, 0xb9,0xd0,0x69,0xb9,
+ 0x86,0x91,0x17,0x86, 0xc1,0x58,0x99,0xc1, 0x1d,0x27,0x3a,0x1d, 0x9e,0xb9,0x27,0x9e,
+ 0xe1,0x38,0xd9,0xe1, 0xf8,0x13,0xeb,0xf8, 0x98,0xb3,0x2b,0x98, 0x11,0x33,0x22,0x11,
+ 0x69,0xbb,0xd2,0x69, 0xd9,0x70,0xa9,0xd9, 0x8e,0x89,0x07,0x8e, 0x94,0xa7,0x33,0x94,
+ 0x9b,0xb6,0x2d,0x9b, 0x1e,0x22,0x3c,0x1e, 0x87,0x92,0x15,0x87, 0xe9,0x20,0xc9,0xe9,
+ 0xce,0x49,0x87,0xce, 0x55,0xff,0xaa,0x55, 0x28,0x78,0x50,0x28, 0xdf,0x7a,0xa5,0xdf,
+ 0x8c,0x8f,0x03,0x8c, 0xa1,0xf8,0x59,0xa1, 0x89,0x80,0x09,0x89, 0x0d,0x17,0x1a,0x0d,
+ 0xbf,0xda,0x65,0xbf, 0xe6,0x31,0xd7,0xe6, 0x42,0xc6,0x84,0x42, 0x68,0xb8,0xd0,0x68,
+ 0x41,0xc3,0x82,0x41, 0x99,0xb0,0x29,0x99, 0x2d,0x77,0x5a,0x2d, 0x0f,0x11,0x1e,0x0f,
+ 0xb0,0xcb,0x7b,0xb0, 0x54,0xfc,0xa8,0x54, 0xbb,0xd6,0x6d,0xbb, 0x16,0x3a,0x2c,0x16
+};
+
+static UINT8 T4[256][4]=
+{
+ 0x63,0x63,0xa5,0xc6, 0x7c,0x7c,0x84,0xf8, 0x77,0x77,0x99,0xee, 0x7b,0x7b,0x8d,0xf6,
+ 0xf2,0xf2,0x0d,0xff, 0x6b,0x6b,0xbd,0xd6, 0x6f,0x6f,0xb1,0xde, 0xc5,0xc5,0x54,0x91,
+ 0x30,0x30,0x50,0x60, 0x01,0x01,0x03,0x02, 0x67,0x67,0xa9,0xce, 0x2b,0x2b,0x7d,0x56,
+ 0xfe,0xfe,0x19,0xe7, 0xd7,0xd7,0x62,0xb5, 0xab,0xab,0xe6,0x4d, 0x76,0x76,0x9a,0xec,
+ 0xca,0xca,0x45,0x8f, 0x82,0x82,0x9d,0x1f, 0xc9,0xc9,0x40,0x89, 0x7d,0x7d,0x87,0xfa,
+ 0xfa,0xfa,0x15,0xef, 0x59,0x59,0xeb,0xb2, 0x47,0x47,0xc9,0x8e, 0xf0,0xf0,0x0b,0xfb,
+ 0xad,0xad,0xec,0x41, 0xd4,0xd4,0x67,0xb3, 0xa2,0xa2,0xfd,0x5f, 0xaf,0xaf,0xea,0x45,
+ 0x9c,0x9c,0xbf,0x23, 0xa4,0xa4,0xf7,0x53, 0x72,0x72,0x96,0xe4, 0xc0,0xc0,0x5b,0x9b,
+ 0xb7,0xb7,0xc2,0x75, 0xfd,0xfd,0x1c,0xe1, 0x93,0x93,0xae,0x3d, 0x26,0x26,0x6a,0x4c,
+ 0x36,0x36,0x5a,0x6c, 0x3f,0x3f,0x41,0x7e, 0xf7,0xf7,0x02,0xf5, 0xcc,0xcc,0x4f,0x83,
+ 0x34,0x34,0x5c,0x68, 0xa5,0xa5,0xf4,0x51, 0xe5,0xe5,0x34,0xd1, 0xf1,0xf1,0x08,0xf9,
+ 0x71,0x71,0x93,0xe2, 0xd8,0xd8,0x73,0xab, 0x31,0x31,0x53,0x62, 0x15,0x15,0x3f,0x2a,
+ 0x04,0x04,0x0c,0x08, 0xc7,0xc7,0x52,0x95, 0x23,0x23,0x65,0x46, 0xc3,0xc3,0x5e,0x9d,
+ 0x18,0x18,0x28,0x30, 0x96,0x96,0xa1,0x37, 0x05,0x05,0x0f,0x0a, 0x9a,0x9a,0xb5,0x2f,
+ 0x07,0x07,0x09,0x0e, 0x12,0x12,0x36,0x24, 0x80,0x80,0x9b,0x1b, 0xe2,0xe2,0x3d,0xdf,
+ 0xeb,0xeb,0x26,0xcd, 0x27,0x27,0x69,0x4e, 0xb2,0xb2,0xcd,0x7f, 0x75,0x75,0x9f,0xea,
+ 0x09,0x09,0x1b,0x12, 0x83,0x83,0x9e,0x1d, 0x2c,0x2c,0x74,0x58, 0x1a,0x1a,0x2e,0x34,
+ 0x1b,0x1b,0x2d,0x36, 0x6e,0x6e,0xb2,0xdc, 0x5a,0x5a,0xee,0xb4, 0xa0,0xa0,0xfb,0x5b,
+ 0x52,0x52,0xf6,0xa4, 0x3b,0x3b,0x4d,0x76, 0xd6,0xd6,0x61,0xb7, 0xb3,0xb3,0xce,0x7d,
+ 0x29,0x29,0x7b,0x52, 0xe3,0xe3,0x3e,0xdd, 0x2f,0x2f,0x71,0x5e, 0x84,0x84,0x97,0x13,
+ 0x53,0x53,0xf5,0xa6, 0xd1,0xd1,0x68,0xb9, 0x00,0x00,0x00,0x00, 0xed,0xed,0x2c,0xc1,
+ 0x20,0x20,0x60,0x40, 0xfc,0xfc,0x1f,0xe3, 0xb1,0xb1,0xc8,0x79, 0x5b,0x5b,0xed,0xb6,
+ 0x6a,0x6a,0xbe,0xd4, 0xcb,0xcb,0x46,0x8d, 0xbe,0xbe,0xd9,0x67, 0x39,0x39,0x4b,0x72,
+ 0x4a,0x4a,0xde,0x94, 0x4c,0x4c,0xd4,0x98, 0x58,0x58,0xe8,0xb0, 0xcf,0xcf,0x4a,0x85,
+ 0xd0,0xd0,0x6b,0xbb, 0xef,0xef,0x2a,0xc5, 0xaa,0xaa,0xe5,0x4f, 0xfb,0xfb,0x16,0xed,
+ 0x43,0x43,0xc5,0x86, 0x4d,0x4d,0xd7,0x9a, 0x33,0x33,0x55,0x66, 0x85,0x85,0x94,0x11,
+ 0x45,0x45,0xcf,0x8a, 0xf9,0xf9,0x10,0xe9, 0x02,0x02,0x06,0x04, 0x7f,0x7f,0x81,0xfe,
+ 0x50,0x50,0xf0,0xa0, 0x3c,0x3c,0x44,0x78, 0x9f,0x9f,0xba,0x25, 0xa8,0xa8,0xe3,0x4b,
+ 0x51,0x51,0xf3,0xa2, 0xa3,0xa3,0xfe,0x5d, 0x40,0x40,0xc0,0x80, 0x8f,0x8f,0x8a,0x05,
+ 0x92,0x92,0xad,0x3f, 0x9d,0x9d,0xbc,0x21, 0x38,0x38,0x48,0x70, 0xf5,0xf5,0x04,0xf1,
+ 0xbc,0xbc,0xdf,0x63, 0xb6,0xb6,0xc1,0x77, 0xda,0xda,0x75,0xaf, 0x21,0x21,0x63,0x42,
+ 0x10,0x10,0x30,0x20, 0xff,0xff,0x1a,0xe5, 0xf3,0xf3,0x0e,0xfd, 0xd2,0xd2,0x6d,0xbf,
+ 0xcd,0xcd,0x4c,0x81, 0x0c,0x0c,0x14,0x18, 0x13,0x13,0x35,0x26, 0xec,0xec,0x2f,0xc3,
+ 0x5f,0x5f,0xe1,0xbe, 0x97,0x97,0xa2,0x35, 0x44,0x44,0xcc,0x88, 0x17,0x17,0x39,0x2e,
+ 0xc4,0xc4,0x57,0x93, 0xa7,0xa7,0xf2,0x55, 0x7e,0x7e,0x82,0xfc, 0x3d,0x3d,0x47,0x7a,
+ 0x64,0x64,0xac,0xc8, 0x5d,0x5d,0xe7,0xba, 0x19,0x19,0x2b,0x32, 0x73,0x73,0x95,0xe6,
+ 0x60,0x60,0xa0,0xc0, 0x81,0x81,0x98,0x19, 0x4f,0x4f,0xd1,0x9e, 0xdc,0xdc,0x7f,0xa3,
+ 0x22,0x22,0x66,0x44, 0x2a,0x2a,0x7e,0x54, 0x90,0x90,0xab,0x3b, 0x88,0x88,0x83,0x0b,
+ 0x46,0x46,0xca,0x8c, 0xee,0xee,0x29,0xc7, 0xb8,0xb8,0xd3,0x6b, 0x14,0x14,0x3c,0x28,
+ 0xde,0xde,0x79,0xa7, 0x5e,0x5e,0xe2,0xbc, 0x0b,0x0b,0x1d,0x16, 0xdb,0xdb,0x76,0xad,
+ 0xe0,0xe0,0x3b,0xdb, 0x32,0x32,0x56,0x64, 0x3a,0x3a,0x4e,0x74, 0x0a,0x0a,0x1e,0x14,
+ 0x49,0x49,0xdb,0x92, 0x06,0x06,0x0a,0x0c, 0x24,0x24,0x6c,0x48, 0x5c,0x5c,0xe4,0xb8,
+ 0xc2,0xc2,0x5d,0x9f, 0xd3,0xd3,0x6e,0xbd, 0xac,0xac,0xef,0x43, 0x62,0x62,0xa6,0xc4,
+ 0x91,0x91,0xa8,0x39, 0x95,0x95,0xa4,0x31, 0xe4,0xe4,0x37,0xd3, 0x79,0x79,0x8b,0xf2,
+ 0xe7,0xe7,0x32,0xd5, 0xc8,0xc8,0x43,0x8b, 0x37,0x37,0x59,0x6e, 0x6d,0x6d,0xb7,0xda,
+ 0x8d,0x8d,0x8c,0x01, 0xd5,0xd5,0x64,0xb1, 0x4e,0x4e,0xd2,0x9c, 0xa9,0xa9,0xe0,0x49,
+ 0x6c,0x6c,0xb4,0xd8, 0x56,0x56,0xfa,0xac, 0xf4,0xf4,0x07,0xf3, 0xea,0xea,0x25,0xcf,
+ 0x65,0x65,0xaf,0xca, 0x7a,0x7a,0x8e,0xf4, 0xae,0xae,0xe9,0x47, 0x08,0x08,0x18,0x10,
+ 0xba,0xba,0xd5,0x6f, 0x78,0x78,0x88,0xf0, 0x25,0x25,0x6f,0x4a, 0x2e,0x2e,0x72,0x5c,
+ 0x1c,0x1c,0x24,0x38, 0xa6,0xa6,0xf1,0x57, 0xb4,0xb4,0xc7,0x73, 0xc6,0xc6,0x51,0x97,
+ 0xe8,0xe8,0x23,0xcb, 0xdd,0xdd,0x7c,0xa1, 0x74,0x74,0x9c,0xe8, 0x1f,0x1f,0x21,0x3e,
+ 0x4b,0x4b,0xdd,0x96, 0xbd,0xbd,0xdc,0x61, 0x8b,0x8b,0x86,0x0d, 0x8a,0x8a,0x85,0x0f,
+ 0x70,0x70,0x90,0xe0, 0x3e,0x3e,0x42,0x7c, 0xb5,0xb5,0xc4,0x71, 0x66,0x66,0xaa,0xcc,
+ 0x48,0x48,0xd8,0x90, 0x03,0x03,0x05,0x06, 0xf6,0xf6,0x01,0xf7, 0x0e,0x0e,0x12,0x1c,
+ 0x61,0x61,0xa3,0xc2, 0x35,0x35,0x5f,0x6a, 0x57,0x57,0xf9,0xae, 0xb9,0xb9,0xd0,0x69,
+ 0x86,0x86,0x91,0x17, 0xc1,0xc1,0x58,0x99, 0x1d,0x1d,0x27,0x3a, 0x9e,0x9e,0xb9,0x27,
+ 0xe1,0xe1,0x38,0xd9, 0xf8,0xf8,0x13,0xeb, 0x98,0x98,0xb3,0x2b, 0x11,0x11,0x33,0x22,
+ 0x69,0x69,0xbb,0xd2, 0xd9,0xd9,0x70,0xa9, 0x8e,0x8e,0x89,0x07, 0x94,0x94,0xa7,0x33,
+ 0x9b,0x9b,0xb6,0x2d, 0x1e,0x1e,0x22,0x3c, 0x87,0x87,0x92,0x15, 0xe9,0xe9,0x20,0xc9,
+ 0xce,0xce,0x49,0x87, 0x55,0x55,0xff,0xaa, 0x28,0x28,0x78,0x50, 0xdf,0xdf,0x7a,0xa5,
+ 0x8c,0x8c,0x8f,0x03, 0xa1,0xa1,0xf8,0x59, 0x89,0x89,0x80,0x09, 0x0d,0x0d,0x17,0x1a,
+ 0xbf,0xbf,0xda,0x65, 0xe6,0xe6,0x31,0xd7, 0x42,0x42,0xc6,0x84, 0x68,0x68,0xb8,0xd0,
+ 0x41,0x41,0xc3,0x82, 0x99,0x99,0xb0,0x29, 0x2d,0x2d,0x77,0x5a, 0x0f,0x0f,0x11,0x1e,
+ 0xb0,0xb0,0xcb,0x7b, 0x54,0x54,0xfc,0xa8, 0xbb,0xbb,0xd6,0x6d, 0x16,0x16,0x3a,0x2c
+};
+
+static UINT8 T5[256][4]=
+{
+ 0x51,0xf4,0xa7,0x50, 0x7e,0x41,0x65,0x53, 0x1a,0x17,0xa4,0xc3, 0x3a,0x27,0x5e,0x96,
+ 0x3b,0xab,0x6b,0xcb, 0x1f,0x9d,0x45,0xf1, 0xac,0xfa,0x58,0xab, 0x4b,0xe3,0x03,0x93,
+ 0x20,0x30,0xfa,0x55, 0xad,0x76,0x6d,0xf6, 0x88,0xcc,0x76,0x91, 0xf5,0x02,0x4c,0x25,
+ 0x4f,0xe5,0xd7,0xfc, 0xc5,0x2a,0xcb,0xd7, 0x26,0x35,0x44,0x80, 0xb5,0x62,0xa3,0x8f,
+ 0xde,0xb1,0x5a,0x49, 0x25,0xba,0x1b,0x67, 0x45,0xea,0x0e,0x98, 0x5d,0xfe,0xc0,0xe1,
+ 0xc3,0x2f,0x75,0x02, 0x81,0x4c,0xf0,0x12, 0x8d,0x46,0x97,0xa3, 0x6b,0xd3,0xf9,0xc6,
+ 0x03,0x8f,0x5f,0xe7, 0x15,0x92,0x9c,0x95, 0xbf,0x6d,0x7a,0xeb, 0x95,0x52,0x59,0xda,
+ 0xd4,0xbe,0x83,0x2d, 0x58,0x74,0x21,0xd3, 0x49,0xe0,0x69,0x29, 0x8e,0xc9,0xc8,0x44,
+ 0x75,0xc2,0x89,0x6a, 0xf4,0x8e,0x79,0x78, 0x99,0x58,0x3e,0x6b, 0x27,0xb9,0x71,0xdd,
+ 0xbe,0xe1,0x4f,0xb6, 0xf0,0x88,0xad,0x17, 0xc9,0x20,0xac,0x66, 0x7d,0xce,0x3a,0xb4,
+ 0x63,0xdf,0x4a,0x18, 0xe5,0x1a,0x31,0x82, 0x97,0x51,0x33,0x60, 0x62,0x53,0x7f,0x45,
+ 0xb1,0x64,0x77,0xe0, 0xbb,0x6b,0xae,0x84, 0xfe,0x81,0xa0,0x1c, 0xf9,0x08,0x2b,0x94,
+ 0x70,0x48,0x68,0x58, 0x8f,0x45,0xfd,0x19, 0x94,0xde,0x6c,0x87, 0x52,0x7b,0xf8,0xb7,
+ 0xab,0x73,0xd3,0x23, 0x72,0x4b,0x02,0xe2, 0xe3,0x1f,0x8f,0x57, 0x66,0x55,0xab,0x2a,
+ 0xb2,0xeb,0x28,0x07, 0x2f,0xb5,0xc2,0x03, 0x86,0xc5,0x7b,0x9a, 0xd3,0x37,0x08,0xa5,
+ 0x30,0x28,0x87,0xf2, 0x23,0xbf,0xa5,0xb2, 0x02,0x03,0x6a,0xba, 0xed,0x16,0x82,0x5c,
+ 0x8a,0xcf,0x1c,0x2b, 0xa7,0x79,0xb4,0x92, 0xf3,0x07,0xf2,0xf0, 0x4e,0x69,0xe2,0xa1,
+ 0x65,0xda,0xf4,0xcd, 0x06,0x05,0xbe,0xd5, 0xd1,0x34,0x62,0x1f, 0xc4,0xa6,0xfe,0x8a,
+ 0x34,0x2e,0x53,0x9d, 0xa2,0xf3,0x55,0xa0, 0x05,0x8a,0xe1,0x32, 0xa4,0xf6,0xeb,0x75,
+ 0x0b,0x83,0xec,0x39, 0x40,0x60,0xef,0xaa, 0x5e,0x71,0x9f,0x06, 0xbd,0x6e,0x10,0x51,
+ 0x3e,0x21,0x8a,0xf9, 0x96,0xdd,0x06,0x3d, 0xdd,0x3e,0x05,0xae, 0x4d,0xe6,0xbd,0x46,
+ 0x91,0x54,0x8d,0xb5, 0x71,0xc4,0x5d,0x05, 0x04,0x06,0xd4,0x6f, 0x60,0x50,0x15,0xff,
+ 0x19,0x98,0xfb,0x24, 0xd6,0xbd,0xe9,0x97, 0x89,0x40,0x43,0xcc, 0x67,0xd9,0x9e,0x77,
+ 0xb0,0xe8,0x42,0xbd, 0x07,0x89,0x8b,0x88, 0xe7,0x19,0x5b,0x38, 0x79,0xc8,0xee,0xdb,
+ 0xa1,0x7c,0x0a,0x47, 0x7c,0x42,0x0f,0xe9, 0xf8,0x84,0x1e,0xc9, 0x00,0x00,0x00,0x00,
+ 0x09,0x80,0x86,0x83, 0x32,0x2b,0xed,0x48, 0x1e,0x11,0x70,0xac, 0x6c,0x5a,0x72,0x4e,
+ 0xfd,0x0e,0xff,0xfb, 0x0f,0x85,0x38,0x56, 0x3d,0xae,0xd5,0x1e, 0x36,0x2d,0x39,0x27,
+ 0x0a,0x0f,0xd9,0x64, 0x68,0x5c,0xa6,0x21, 0x9b,0x5b,0x54,0xd1, 0x24,0x36,0x2e,0x3a,
+ 0x0c,0x0a,0x67,0xb1, 0x93,0x57,0xe7,0x0f, 0xb4,0xee,0x96,0xd2, 0x1b,0x9b,0x91,0x9e,
+ 0x80,0xc0,0xc5,0x4f, 0x61,0xdc,0x20,0xa2, 0x5a,0x77,0x4b,0x69, 0x1c,0x12,0x1a,0x16,
+ 0xe2,0x93,0xba,0x0a, 0xc0,0xa0,0x2a,0xe5, 0x3c,0x22,0xe0,0x43, 0x12,0x1b,0x17,0x1d,
+ 0x0e,0x09,0x0d,0x0b, 0xf2,0x8b,0xc7,0xad, 0x2d,0xb6,0xa8,0xb9, 0x14,0x1e,0xa9,0xc8,
+ 0x57,0xf1,0x19,0x85, 0xaf,0x75,0x07,0x4c, 0xee,0x99,0xdd,0xbb, 0xa3,0x7f,0x60,0xfd,
+ 0xf7,0x01,0x26,0x9f, 0x5c,0x72,0xf5,0xbc, 0x44,0x66,0x3b,0xc5, 0x5b,0xfb,0x7e,0x34,
+ 0x8b,0x43,0x29,0x76, 0xcb,0x23,0xc6,0xdc, 0xb6,0xed,0xfc,0x68, 0xb8,0xe4,0xf1,0x63,
+ 0xd7,0x31,0xdc,0xca, 0x42,0x63,0x85,0x10, 0x13,0x97,0x22,0x40, 0x84,0xc6,0x11,0x20,
+ 0x85,0x4a,0x24,0x7d, 0xd2,0xbb,0x3d,0xf8, 0xae,0xf9,0x32,0x11, 0xc7,0x29,0xa1,0x6d,
+ 0x1d,0x9e,0x2f,0x4b, 0xdc,0xb2,0x30,0xf3, 0x0d,0x86,0x52,0xec, 0x77,0xc1,0xe3,0xd0,
+ 0x2b,0xb3,0x16,0x6c, 0xa9,0x70,0xb9,0x99, 0x11,0x94,0x48,0xfa, 0x47,0xe9,0x64,0x22,
+ 0xa8,0xfc,0x8c,0xc4, 0xa0,0xf0,0x3f,0x1a, 0x56,0x7d,0x2c,0xd8, 0x22,0x33,0x90,0xef,
+ 0x87,0x49,0x4e,0xc7, 0xd9,0x38,0xd1,0xc1, 0x8c,0xca,0xa2,0xfe, 0x98,0xd4,0x0b,0x36,
+ 0xa6,0xf5,0x81,0xcf, 0xa5,0x7a,0xde,0x28, 0xda,0xb7,0x8e,0x26, 0x3f,0xad,0xbf,0xa4,
+ 0x2c,0x3a,0x9d,0xe4, 0x50,0x78,0x92,0x0d, 0x6a,0x5f,0xcc,0x9b, 0x54,0x7e,0x46,0x62,
+ 0xf6,0x8d,0x13,0xc2, 0x90,0xd8,0xb8,0xe8, 0x2e,0x39,0xf7,0x5e, 0x82,0xc3,0xaf,0xf5,
+ 0x9f,0x5d,0x80,0xbe, 0x69,0xd0,0x93,0x7c, 0x6f,0xd5,0x2d,0xa9, 0xcf,0x25,0x12,0xb3,
+ 0xc8,0xac,0x99,0x3b, 0x10,0x18,0x7d,0xa7, 0xe8,0x9c,0x63,0x6e, 0xdb,0x3b,0xbb,0x7b,
+ 0xcd,0x26,0x78,0x09, 0x6e,0x59,0x18,0xf4, 0xec,0x9a,0xb7,0x01, 0x83,0x4f,0x9a,0xa8,
+ 0xe6,0x95,0x6e,0x65, 0xaa,0xff,0xe6,0x7e, 0x21,0xbc,0xcf,0x08, 0xef,0x15,0xe8,0xe6,
+ 0xba,0xe7,0x9b,0xd9, 0x4a,0x6f,0x36,0xce, 0xea,0x9f,0x09,0xd4, 0x29,0xb0,0x7c,0xd6,
+ 0x31,0xa4,0xb2,0xaf, 0x2a,0x3f,0x23,0x31, 0xc6,0xa5,0x94,0x30, 0x35,0xa2,0x66,0xc0,
+ 0x74,0x4e,0xbc,0x37, 0xfc,0x82,0xca,0xa6, 0xe0,0x90,0xd0,0xb0, 0x33,0xa7,0xd8,0x15,
+ 0xf1,0x04,0x98,0x4a, 0x41,0xec,0xda,0xf7, 0x7f,0xcd,0x50,0x0e, 0x17,0x91,0xf6,0x2f,
+ 0x76,0x4d,0xd6,0x8d, 0x43,0xef,0xb0,0x4d, 0xcc,0xaa,0x4d,0x54, 0xe4,0x96,0x04,0xdf,
+ 0x9e,0xd1,0xb5,0xe3, 0x4c,0x6a,0x88,0x1b, 0xc1,0x2c,0x1f,0xb8, 0x46,0x65,0x51,0x7f,
+ 0x9d,0x5e,0xea,0x04, 0x01,0x8c,0x35,0x5d, 0xfa,0x87,0x74,0x73, 0xfb,0x0b,0x41,0x2e,
+ 0xb3,0x67,0x1d,0x5a, 0x92,0xdb,0xd2,0x52, 0xe9,0x10,0x56,0x33, 0x6d,0xd6,0x47,0x13,
+ 0x9a,0xd7,0x61,0x8c, 0x37,0xa1,0x0c,0x7a, 0x59,0xf8,0x14,0x8e, 0xeb,0x13,0x3c,0x89,
+ 0xce,0xa9,0x27,0xee, 0xb7,0x61,0xc9,0x35, 0xe1,0x1c,0xe5,0xed, 0x7a,0x47,0xb1,0x3c,
+ 0x9c,0xd2,0xdf,0x59, 0x55,0xf2,0x73,0x3f, 0x18,0x14,0xce,0x79, 0x73,0xc7,0x37,0xbf,
+ 0x53,0xf7,0xcd,0xea, 0x5f,0xfd,0xaa,0x5b, 0xdf,0x3d,0x6f,0x14, 0x78,0x44,0xdb,0x86,
+ 0xca,0xaf,0xf3,0x81, 0xb9,0x68,0xc4,0x3e, 0x38,0x24,0x34,0x2c, 0xc2,0xa3,0x40,0x5f,
+ 0x16,0x1d,0xc3,0x72, 0xbc,0xe2,0x25,0x0c, 0x28,0x3c,0x49,0x8b, 0xff,0x0d,0x95,0x41,
+ 0x39,0xa8,0x01,0x71, 0x08,0x0c,0xb3,0xde, 0xd8,0xb4,0xe4,0x9c, 0x64,0x56,0xc1,0x90,
+ 0x7b,0xcb,0x84,0x61, 0xd5,0x32,0xb6,0x70, 0x48,0x6c,0x5c,0x74, 0xd0,0xb8,0x57,0x42
+};
+
+static UINT8 T6[256][4]=
+{
+ 0x50,0x51,0xf4,0xa7, 0x53,0x7e,0x41,0x65, 0xc3,0x1a,0x17,0xa4, 0x96,0x3a,0x27,0x5e,
+ 0xcb,0x3b,0xab,0x6b, 0xf1,0x1f,0x9d,0x45, 0xab,0xac,0xfa,0x58, 0x93,0x4b,0xe3,0x03,
+ 0x55,0x20,0x30,0xfa, 0xf6,0xad,0x76,0x6d, 0x91,0x88,0xcc,0x76, 0x25,0xf5,0x02,0x4c,
+ 0xfc,0x4f,0xe5,0xd7, 0xd7,0xc5,0x2a,0xcb, 0x80,0x26,0x35,0x44, 0x8f,0xb5,0x62,0xa3,
+ 0x49,0xde,0xb1,0x5a, 0x67,0x25,0xba,0x1b, 0x98,0x45,0xea,0x0e, 0xe1,0x5d,0xfe,0xc0,
+ 0x02,0xc3,0x2f,0x75, 0x12,0x81,0x4c,0xf0, 0xa3,0x8d,0x46,0x97, 0xc6,0x6b,0xd3,0xf9,
+ 0xe7,0x03,0x8f,0x5f, 0x95,0x15,0x92,0x9c, 0xeb,0xbf,0x6d,0x7a, 0xda,0x95,0x52,0x59,
+ 0x2d,0xd4,0xbe,0x83, 0xd3,0x58,0x74,0x21, 0x29,0x49,0xe0,0x69, 0x44,0x8e,0xc9,0xc8,
+ 0x6a,0x75,0xc2,0x89, 0x78,0xf4,0x8e,0x79, 0x6b,0x99,0x58,0x3e, 0xdd,0x27,0xb9,0x71,
+ 0xb6,0xbe,0xe1,0x4f, 0x17,0xf0,0x88,0xad, 0x66,0xc9,0x20,0xac, 0xb4,0x7d,0xce,0x3a,
+ 0x18,0x63,0xdf,0x4a, 0x82,0xe5,0x1a,0x31, 0x60,0x97,0x51,0x33, 0x45,0x62,0x53,0x7f,
+ 0xe0,0xb1,0x64,0x77, 0x84,0xbb,0x6b,0xae, 0x1c,0xfe,0x81,0xa0, 0x94,0xf9,0x08,0x2b,
+ 0x58,0x70,0x48,0x68, 0x19,0x8f,0x45,0xfd, 0x87,0x94,0xde,0x6c, 0xb7,0x52,0x7b,0xf8,
+ 0x23,0xab,0x73,0xd3, 0xe2,0x72,0x4b,0x02, 0x57,0xe3,0x1f,0x8f, 0x2a,0x66,0x55,0xab,
+ 0x07,0xb2,0xeb,0x28, 0x03,0x2f,0xb5,0xc2, 0x9a,0x86,0xc5,0x7b, 0xa5,0xd3,0x37,0x08,
+ 0xf2,0x30,0x28,0x87, 0xb2,0x23,0xbf,0xa5, 0xba,0x02,0x03,0x6a, 0x5c,0xed,0x16,0x82,
+ 0x2b,0x8a,0xcf,0x1c, 0x92,0xa7,0x79,0xb4, 0xf0,0xf3,0x07,0xf2, 0xa1,0x4e,0x69,0xe2,
+ 0xcd,0x65,0xda,0xf4, 0xd5,0x06,0x05,0xbe, 0x1f,0xd1,0x34,0x62, 0x8a,0xc4,0xa6,0xfe,
+ 0x9d,0x34,0x2e,0x53, 0xa0,0xa2,0xf3,0x55, 0x32,0x05,0x8a,0xe1, 0x75,0xa4,0xf6,0xeb,
+ 0x39,0x0b,0x83,0xec, 0xaa,0x40,0x60,0xef, 0x06,0x5e,0x71,0x9f, 0x51,0xbd,0x6e,0x10,
+ 0xf9,0x3e,0x21,0x8a, 0x3d,0x96,0xdd,0x06, 0xae,0xdd,0x3e,0x05, 0x46,0x4d,0xe6,0xbd,
+ 0xb5,0x91,0x54,0x8d, 0x05,0x71,0xc4,0x5d, 0x6f,0x04,0x06,0xd4, 0xff,0x60,0x50,0x15,
+ 0x24,0x19,0x98,0xfb, 0x97,0xd6,0xbd,0xe9, 0xcc,0x89,0x40,0x43, 0x77,0x67,0xd9,0x9e,
+ 0xbd,0xb0,0xe8,0x42, 0x88,0x07,0x89,0x8b, 0x38,0xe7,0x19,0x5b, 0xdb,0x79,0xc8,0xee,
+ 0x47,0xa1,0x7c,0x0a, 0xe9,0x7c,0x42,0x0f, 0xc9,0xf8,0x84,0x1e, 0x00,0x00,0x00,0x00,
+ 0x83,0x09,0x80,0x86, 0x48,0x32,0x2b,0xed, 0xac,0x1e,0x11,0x70, 0x4e,0x6c,0x5a,0x72,
+ 0xfb,0xfd,0x0e,0xff, 0x56,0x0f,0x85,0x38, 0x1e,0x3d,0xae,0xd5, 0x27,0x36,0x2d,0x39,
+ 0x64,0x0a,0x0f,0xd9, 0x21,0x68,0x5c,0xa6, 0xd1,0x9b,0x5b,0x54, 0x3a,0x24,0x36,0x2e,
+ 0xb1,0x0c,0x0a,0x67, 0x0f,0x93,0x57,0xe7, 0xd2,0xb4,0xee,0x96, 0x9e,0x1b,0x9b,0x91,
+ 0x4f,0x80,0xc0,0xc5, 0xa2,0x61,0xdc,0x20, 0x69,0x5a,0x77,0x4b, 0x16,0x1c,0x12,0x1a,
+ 0x0a,0xe2,0x93,0xba, 0xe5,0xc0,0xa0,0x2a, 0x43,0x3c,0x22,0xe0, 0x1d,0x12,0x1b,0x17,
+ 0x0b,0x0e,0x09,0x0d, 0xad,0xf2,0x8b,0xc7, 0xb9,0x2d,0xb6,0xa8, 0xc8,0x14,0x1e,0xa9,
+ 0x85,0x57,0xf1,0x19, 0x4c,0xaf,0x75,0x07, 0xbb,0xee,0x99,0xdd, 0xfd,0xa3,0x7f,0x60,
+ 0x9f,0xf7,0x01,0x26, 0xbc,0x5c,0x72,0xf5, 0xc5,0x44,0x66,0x3b, 0x34,0x5b,0xfb,0x7e,
+ 0x76,0x8b,0x43,0x29, 0xdc,0xcb,0x23,0xc6, 0x68,0xb6,0xed,0xfc, 0x63,0xb8,0xe4,0xf1,
+ 0xca,0xd7,0x31,0xdc, 0x10,0x42,0x63,0x85, 0x40,0x13,0x97,0x22, 0x20,0x84,0xc6,0x11,
+ 0x7d,0x85,0x4a,0x24, 0xf8,0xd2,0xbb,0x3d, 0x11,0xae,0xf9,0x32, 0x6d,0xc7,0x29,0xa1,
+ 0x4b,0x1d,0x9e,0x2f, 0xf3,0xdc,0xb2,0x30, 0xec,0x0d,0x86,0x52, 0xd0,0x77,0xc1,0xe3,
+ 0x6c,0x2b,0xb3,0x16, 0x99,0xa9,0x70,0xb9, 0xfa,0x11,0x94,0x48, 0x22,0x47,0xe9,0x64,
+ 0xc4,0xa8,0xfc,0x8c, 0x1a,0xa0,0xf0,0x3f, 0xd8,0x56,0x7d,0x2c, 0xef,0x22,0x33,0x90,
+ 0xc7,0x87,0x49,0x4e, 0xc1,0xd9,0x38,0xd1, 0xfe,0x8c,0xca,0xa2, 0x36,0x98,0xd4,0x0b,
+ 0xcf,0xa6,0xf5,0x81, 0x28,0xa5,0x7a,0xde, 0x26,0xda,0xb7,0x8e, 0xa4,0x3f,0xad,0xbf,
+ 0xe4,0x2c,0x3a,0x9d, 0x0d,0x50,0x78,0x92, 0x9b,0x6a,0x5f,0xcc, 0x62,0x54,0x7e,0x46,
+ 0xc2,0xf6,0x8d,0x13, 0xe8,0x90,0xd8,0xb8, 0x5e,0x2e,0x39,0xf7, 0xf5,0x82,0xc3,0xaf,
+ 0xbe,0x9f,0x5d,0x80, 0x7c,0x69,0xd0,0x93, 0xa9,0x6f,0xd5,0x2d, 0xb3,0xcf,0x25,0x12,
+ 0x3b,0xc8,0xac,0x99, 0xa7,0x10,0x18,0x7d, 0x6e,0xe8,0x9c,0x63, 0x7b,0xdb,0x3b,0xbb,
+ 0x09,0xcd,0x26,0x78, 0xf4,0x6e,0x59,0x18, 0x01,0xec,0x9a,0xb7, 0xa8,0x83,0x4f,0x9a,
+ 0x65,0xe6,0x95,0x6e, 0x7e,0xaa,0xff,0xe6, 0x08,0x21,0xbc,0xcf, 0xe6,0xef,0x15,0xe8,
+ 0xd9,0xba,0xe7,0x9b, 0xce,0x4a,0x6f,0x36, 0xd4,0xea,0x9f,0x09, 0xd6,0x29,0xb0,0x7c,
+ 0xaf,0x31,0xa4,0xb2, 0x31,0x2a,0x3f,0x23, 0x30,0xc6,0xa5,0x94, 0xc0,0x35,0xa2,0x66,
+ 0x37,0x74,0x4e,0xbc, 0xa6,0xfc,0x82,0xca, 0xb0,0xe0,0x90,0xd0, 0x15,0x33,0xa7,0xd8,
+ 0x4a,0xf1,0x04,0x98, 0xf7,0x41,0xec,0xda, 0x0e,0x7f,0xcd,0x50, 0x2f,0x17,0x91,0xf6,
+ 0x8d,0x76,0x4d,0xd6, 0x4d,0x43,0xef,0xb0, 0x54,0xcc,0xaa,0x4d, 0xdf,0xe4,0x96,0x04,
+ 0xe3,0x9e,0xd1,0xb5, 0x1b,0x4c,0x6a,0x88, 0xb8,0xc1,0x2c,0x1f, 0x7f,0x46,0x65,0x51,
+ 0x04,0x9d,0x5e,0xea, 0x5d,0x01,0x8c,0x35, 0x73,0xfa,0x87,0x74, 0x2e,0xfb,0x0b,0x41,
+ 0x5a,0xb3,0x67,0x1d, 0x52,0x92,0xdb,0xd2, 0x33,0xe9,0x10,0x56, 0x13,0x6d,0xd6,0x47,
+ 0x8c,0x9a,0xd7,0x61, 0x7a,0x37,0xa1,0x0c, 0x8e,0x59,0xf8,0x14, 0x89,0xeb,0x13,0x3c,
+ 0xee,0xce,0xa9,0x27, 0x35,0xb7,0x61,0xc9, 0xed,0xe1,0x1c,0xe5, 0x3c,0x7a,0x47,0xb1,
+ 0x59,0x9c,0xd2,0xdf, 0x3f,0x55,0xf2,0x73, 0x79,0x18,0x14,0xce, 0xbf,0x73,0xc7,0x37,
+ 0xea,0x53,0xf7,0xcd, 0x5b,0x5f,0xfd,0xaa, 0x14,0xdf,0x3d,0x6f, 0x86,0x78,0x44,0xdb,
+ 0x81,0xca,0xaf,0xf3, 0x3e,0xb9,0x68,0xc4, 0x2c,0x38,0x24,0x34, 0x5f,0xc2,0xa3,0x40,
+ 0x72,0x16,0x1d,0xc3, 0x0c,0xbc,0xe2,0x25, 0x8b,0x28,0x3c,0x49, 0x41,0xff,0x0d,0x95,
+ 0x71,0x39,0xa8,0x01, 0xde,0x08,0x0c,0xb3, 0x9c,0xd8,0xb4,0xe4, 0x90,0x64,0x56,0xc1,
+ 0x61,0x7b,0xcb,0x84, 0x70,0xd5,0x32,0xb6, 0x74,0x48,0x6c,0x5c, 0x42,0xd0,0xb8,0x57
+};
+
+static UINT8 T7[256][4]=
+{
+ 0xa7,0x50,0x51,0xf4, 0x65,0x53,0x7e,0x41, 0xa4,0xc3,0x1a,0x17, 0x5e,0x96,0x3a,0x27,
+ 0x6b,0xcb,0x3b,0xab, 0x45,0xf1,0x1f,0x9d, 0x58,0xab,0xac,0xfa, 0x03,0x93,0x4b,0xe3,
+ 0xfa,0x55,0x20,0x30, 0x6d,0xf6,0xad,0x76, 0x76,0x91,0x88,0xcc, 0x4c,0x25,0xf5,0x02,
+ 0xd7,0xfc,0x4f,0xe5, 0xcb,0xd7,0xc5,0x2a, 0x44,0x80,0x26,0x35, 0xa3,0x8f,0xb5,0x62,
+ 0x5a,0x49,0xde,0xb1, 0x1b,0x67,0x25,0xba, 0x0e,0x98,0x45,0xea, 0xc0,0xe1,0x5d,0xfe,
+ 0x75,0x02,0xc3,0x2f, 0xf0,0x12,0x81,0x4c, 0x97,0xa3,0x8d,0x46, 0xf9,0xc6,0x6b,0xd3,
+ 0x5f,0xe7,0x03,0x8f, 0x9c,0x95,0x15,0x92, 0x7a,0xeb,0xbf,0x6d, 0x59,0xda,0x95,0x52,
+ 0x83,0x2d,0xd4,0xbe, 0x21,0xd3,0x58,0x74, 0x69,0x29,0x49,0xe0, 0xc8,0x44,0x8e,0xc9,
+ 0x89,0x6a,0x75,0xc2, 0x79,0x78,0xf4,0x8e, 0x3e,0x6b,0x99,0x58, 0x71,0xdd,0x27,0xb9,
+ 0x4f,0xb6,0xbe,0xe1, 0xad,0x17,0xf0,0x88, 0xac,0x66,0xc9,0x20, 0x3a,0xb4,0x7d,0xce,
+ 0x4a,0x18,0x63,0xdf, 0x31,0x82,0xe5,0x1a, 0x33,0x60,0x97,0x51, 0x7f,0x45,0x62,0x53,
+ 0x77,0xe0,0xb1,0x64, 0xae,0x84,0xbb,0x6b, 0xa0,0x1c,0xfe,0x81, 0x2b,0x94,0xf9,0x08,
+ 0x68,0x58,0x70,0x48, 0xfd,0x19,0x8f,0x45, 0x6c,0x87,0x94,0xde, 0xf8,0xb7,0x52,0x7b,
+ 0xd3,0x23,0xab,0x73, 0x02,0xe2,0x72,0x4b, 0x8f,0x57,0xe3,0x1f, 0xab,0x2a,0x66,0x55,
+ 0x28,0x07,0xb2,0xeb, 0xc2,0x03,0x2f,0xb5, 0x7b,0x9a,0x86,0xc5, 0x08,0xa5,0xd3,0x37,
+ 0x87,0xf2,0x30,0x28, 0xa5,0xb2,0x23,0xbf, 0x6a,0xba,0x02,0x03, 0x82,0x5c,0xed,0x16,
+ 0x1c,0x2b,0x8a,0xcf, 0xb4,0x92,0xa7,0x79, 0xf2,0xf0,0xf3,0x07, 0xe2,0xa1,0x4e,0x69,
+ 0xf4,0xcd,0x65,0xda, 0xbe,0xd5,0x06,0x05, 0x62,0x1f,0xd1,0x34, 0xfe,0x8a,0xc4,0xa6,
+ 0x53,0x9d,0x34,0x2e, 0x55,0xa0,0xa2,0xf3, 0xe1,0x32,0x05,0x8a, 0xeb,0x75,0xa4,0xf6,
+ 0xec,0x39,0x0b,0x83, 0xef,0xaa,0x40,0x60, 0x9f,0x06,0x5e,0x71, 0x10,0x51,0xbd,0x6e,
+ 0x8a,0xf9,0x3e,0x21, 0x06,0x3d,0x96,0xdd, 0x05,0xae,0xdd,0x3e, 0xbd,0x46,0x4d,0xe6,
+ 0x8d,0xb5,0x91,0x54, 0x5d,0x05,0x71,0xc4, 0xd4,0x6f,0x04,0x06, 0x15,0xff,0x60,0x50,
+ 0xfb,0x24,0x19,0x98, 0xe9,0x97,0xd6,0xbd, 0x43,0xcc,0x89,0x40, 0x9e,0x77,0x67,0xd9,
+ 0x42,0xbd,0xb0,0xe8, 0x8b,0x88,0x07,0x89, 0x5b,0x38,0xe7,0x19, 0xee,0xdb,0x79,0xc8,
+ 0x0a,0x47,0xa1,0x7c, 0x0f,0xe9,0x7c,0x42, 0x1e,0xc9,0xf8,0x84, 0x00,0x00,0x00,0x00,
+ 0x86,0x83,0x09,0x80, 0xed,0x48,0x32,0x2b, 0x70,0xac,0x1e,0x11, 0x72,0x4e,0x6c,0x5a,
+ 0xff,0xfb,0xfd,0x0e, 0x38,0x56,0x0f,0x85, 0xd5,0x1e,0x3d,0xae, 0x39,0x27,0x36,0x2d,
+ 0xd9,0x64,0x0a,0x0f, 0xa6,0x21,0x68,0x5c, 0x54,0xd1,0x9b,0x5b, 0x2e,0x3a,0x24,0x36,
+ 0x67,0xb1,0x0c,0x0a, 0xe7,0x0f,0x93,0x57, 0x96,0xd2,0xb4,0xee, 0x91,0x9e,0x1b,0x9b,
+ 0xc5,0x4f,0x80,0xc0, 0x20,0xa2,0x61,0xdc, 0x4b,0x69,0x5a,0x77, 0x1a,0x16,0x1c,0x12,
+ 0xba,0x0a,0xe2,0x93, 0x2a,0xe5,0xc0,0xa0, 0xe0,0x43,0x3c,0x22, 0x17,0x1d,0x12,0x1b,
+ 0x0d,0x0b,0x0e,0x09, 0xc7,0xad,0xf2,0x8b, 0xa8,0xb9,0x2d,0xb6, 0xa9,0xc8,0x14,0x1e,
+ 0x19,0x85,0x57,0xf1, 0x07,0x4c,0xaf,0x75, 0xdd,0xbb,0xee,0x99, 0x60,0xfd,0xa3,0x7f,
+ 0x26,0x9f,0xf7,0x01, 0xf5,0xbc,0x5c,0x72, 0x3b,0xc5,0x44,0x66, 0x7e,0x34,0x5b,0xfb,
+ 0x29,0x76,0x8b,0x43, 0xc6,0xdc,0xcb,0x23, 0xfc,0x68,0xb6,0xed, 0xf1,0x63,0xb8,0xe4,
+ 0xdc,0xca,0xd7,0x31, 0x85,0x10,0x42,0x63, 0x22,0x40,0x13,0x97, 0x11,0x20,0x84,0xc6,
+ 0x24,0x7d,0x85,0x4a, 0x3d,0xf8,0xd2,0xbb, 0x32,0x11,0xae,0xf9, 0xa1,0x6d,0xc7,0x29,
+ 0x2f,0x4b,0x1d,0x9e, 0x30,0xf3,0xdc,0xb2, 0x52,0xec,0x0d,0x86, 0xe3,0xd0,0x77,0xc1,
+ 0x16,0x6c,0x2b,0xb3, 0xb9,0x99,0xa9,0x70, 0x48,0xfa,0x11,0x94, 0x64,0x22,0x47,0xe9,
+ 0x8c,0xc4,0xa8,0xfc, 0x3f,0x1a,0xa0,0xf0, 0x2c,0xd8,0x56,0x7d, 0x90,0xef,0x22,0x33,
+ 0x4e,0xc7,0x87,0x49, 0xd1,0xc1,0xd9,0x38, 0xa2,0xfe,0x8c,0xca, 0x0b,0x36,0x98,0xd4,
+ 0x81,0xcf,0xa6,0xf5, 0xde,0x28,0xa5,0x7a, 0x8e,0x26,0xda,0xb7, 0xbf,0xa4,0x3f,0xad,
+ 0x9d,0xe4,0x2c,0x3a, 0x92,0x0d,0x50,0x78, 0xcc,0x9b,0x6a,0x5f, 0x46,0x62,0x54,0x7e,
+ 0x13,0xc2,0xf6,0x8d, 0xb8,0xe8,0x90,0xd8, 0xf7,0x5e,0x2e,0x39, 0xaf,0xf5,0x82,0xc3,
+ 0x80,0xbe,0x9f,0x5d, 0x93,0x7c,0x69,0xd0, 0x2d,0xa9,0x6f,0xd5, 0x12,0xb3,0xcf,0x25,
+ 0x99,0x3b,0xc8,0xac, 0x7d,0xa7,0x10,0x18, 0x63,0x6e,0xe8,0x9c, 0xbb,0x7b,0xdb,0x3b,
+ 0x78,0x09,0xcd,0x26, 0x18,0xf4,0x6e,0x59, 0xb7,0x01,0xec,0x9a, 0x9a,0xa8,0x83,0x4f,
+ 0x6e,0x65,0xe6,0x95, 0xe6,0x7e,0xaa,0xff, 0xcf,0x08,0x21,0xbc, 0xe8,0xe6,0xef,0x15,
+ 0x9b,0xd9,0xba,0xe7, 0x36,0xce,0x4a,0x6f, 0x09,0xd4,0xea,0x9f, 0x7c,0xd6,0x29,0xb0,
+ 0xb2,0xaf,0x31,0xa4, 0x23,0x31,0x2a,0x3f, 0x94,0x30,0xc6,0xa5, 0x66,0xc0,0x35,0xa2,
+ 0xbc,0x37,0x74,0x4e, 0xca,0xa6,0xfc,0x82, 0xd0,0xb0,0xe0,0x90, 0xd8,0x15,0x33,0xa7,
+ 0x98,0x4a,0xf1,0x04, 0xda,0xf7,0x41,0xec, 0x50,0x0e,0x7f,0xcd, 0xf6,0x2f,0x17,0x91,
+ 0xd6,0x8d,0x76,0x4d, 0xb0,0x4d,0x43,0xef, 0x4d,0x54,0xcc,0xaa, 0x04,0xdf,0xe4,0x96,
+ 0xb5,0xe3,0x9e,0xd1, 0x88,0x1b,0x4c,0x6a, 0x1f,0xb8,0xc1,0x2c, 0x51,0x7f,0x46,0x65,
+ 0xea,0x04,0x9d,0x5e, 0x35,0x5d,0x01,0x8c, 0x74,0x73,0xfa,0x87, 0x41,0x2e,0xfb,0x0b,
+ 0x1d,0x5a,0xb3,0x67, 0xd2,0x52,0x92,0xdb, 0x56,0x33,0xe9,0x10, 0x47,0x13,0x6d,0xd6,
+ 0x61,0x8c,0x9a,0xd7, 0x0c,0x7a,0x37,0xa1, 0x14,0x8e,0x59,0xf8, 0x3c,0x89,0xeb,0x13,
+ 0x27,0xee,0xce,0xa9, 0xc9,0x35,0xb7,0x61, 0xe5,0xed,0xe1,0x1c, 0xb1,0x3c,0x7a,0x47,
+ 0xdf,0x59,0x9c,0xd2, 0x73,0x3f,0x55,0xf2, 0xce,0x79,0x18,0x14, 0x37,0xbf,0x73,0xc7,
+ 0xcd,0xea,0x53,0xf7, 0xaa,0x5b,0x5f,0xfd, 0x6f,0x14,0xdf,0x3d, 0xdb,0x86,0x78,0x44,
+ 0xf3,0x81,0xca,0xaf, 0xc4,0x3e,0xb9,0x68, 0x34,0x2c,0x38,0x24, 0x40,0x5f,0xc2,0xa3,
+ 0xc3,0x72,0x16,0x1d, 0x25,0x0c,0xbc,0xe2, 0x49,0x8b,0x28,0x3c, 0x95,0x41,0xff,0x0d,
+ 0x01,0x71,0x39,0xa8, 0xb3,0xde,0x08,0x0c, 0xe4,0x9c,0xd8,0xb4, 0xc1,0x90,0x64,0x56,
+ 0x84,0x61,0x7b,0xcb, 0xb6,0x70,0xd5,0x32, 0x5c,0x74,0x48,0x6c, 0x57,0x42,0xd0,0xb8
+};
+
+static UINT8 T8[256][4]=
+{
+ 0xf4,0xa7,0x50,0x51, 0x41,0x65,0x53,0x7e, 0x17,0xa4,0xc3,0x1a, 0x27,0x5e,0x96,0x3a,
+ 0xab,0x6b,0xcb,0x3b, 0x9d,0x45,0xf1,0x1f, 0xfa,0x58,0xab,0xac, 0xe3,0x03,0x93,0x4b,
+ 0x30,0xfa,0x55,0x20, 0x76,0x6d,0xf6,0xad, 0xcc,0x76,0x91,0x88, 0x02,0x4c,0x25,0xf5,
+ 0xe5,0xd7,0xfc,0x4f, 0x2a,0xcb,0xd7,0xc5, 0x35,0x44,0x80,0x26, 0x62,0xa3,0x8f,0xb5,
+ 0xb1,0x5a,0x49,0xde, 0xba,0x1b,0x67,0x25, 0xea,0x0e,0x98,0x45, 0xfe,0xc0,0xe1,0x5d,
+ 0x2f,0x75,0x02,0xc3, 0x4c,0xf0,0x12,0x81, 0x46,0x97,0xa3,0x8d, 0xd3,0xf9,0xc6,0x6b,
+ 0x8f,0x5f,0xe7,0x03, 0x92,0x9c,0x95,0x15, 0x6d,0x7a,0xeb,0xbf, 0x52,0x59,0xda,0x95,
+ 0xbe,0x83,0x2d,0xd4, 0x74,0x21,0xd3,0x58, 0xe0,0x69,0x29,0x49, 0xc9,0xc8,0x44,0x8e,
+ 0xc2,0x89,0x6a,0x75, 0x8e,0x79,0x78,0xf4, 0x58,0x3e,0x6b,0x99, 0xb9,0x71,0xdd,0x27,
+ 0xe1,0x4f,0xb6,0xbe, 0x88,0xad,0x17,0xf0, 0x20,0xac,0x66,0xc9, 0xce,0x3a,0xb4,0x7d,
+ 0xdf,0x4a,0x18,0x63, 0x1a,0x31,0x82,0xe5, 0x51,0x33,0x60,0x97, 0x53,0x7f,0x45,0x62,
+ 0x64,0x77,0xe0,0xb1, 0x6b,0xae,0x84,0xbb, 0x81,0xa0,0x1c,0xfe, 0x08,0x2b,0x94,0xf9,
+ 0x48,0x68,0x58,0x70, 0x45,0xfd,0x19,0x8f, 0xde,0x6c,0x87,0x94, 0x7b,0xf8,0xb7,0x52,
+ 0x73,0xd3,0x23,0xab, 0x4b,0x02,0xe2,0x72, 0x1f,0x8f,0x57,0xe3, 0x55,0xab,0x2a,0x66,
+ 0xeb,0x28,0x07,0xb2, 0xb5,0xc2,0x03,0x2f, 0xc5,0x7b,0x9a,0x86, 0x37,0x08,0xa5,0xd3,
+ 0x28,0x87,0xf2,0x30, 0xbf,0xa5,0xb2,0x23, 0x03,0x6a,0xba,0x02, 0x16,0x82,0x5c,0xed,
+ 0xcf,0x1c,0x2b,0x8a, 0x79,0xb4,0x92,0xa7, 0x07,0xf2,0xf0,0xf3, 0x69,0xe2,0xa1,0x4e,
+ 0xda,0xf4,0xcd,0x65, 0x05,0xbe,0xd5,0x06, 0x34,0x62,0x1f,0xd1, 0xa6,0xfe,0x8a,0xc4,
+ 0x2e,0x53,0x9d,0x34, 0xf3,0x55,0xa0,0xa2, 0x8a,0xe1,0x32,0x05, 0xf6,0xeb,0x75,0xa4,
+ 0x83,0xec,0x39,0x0b, 0x60,0xef,0xaa,0x40, 0x71,0x9f,0x06,0x5e, 0x6e,0x10,0x51,0xbd,
+ 0x21,0x8a,0xf9,0x3e, 0xdd,0x06,0x3d,0x96, 0x3e,0x05,0xae,0xdd, 0xe6,0xbd,0x46,0x4d,
+ 0x54,0x8d,0xb5,0x91, 0xc4,0x5d,0x05,0x71, 0x06,0xd4,0x6f,0x04, 0x50,0x15,0xff,0x60,
+ 0x98,0xfb,0x24,0x19, 0xbd,0xe9,0x97,0xd6, 0x40,0x43,0xcc,0x89, 0xd9,0x9e,0x77,0x67,
+ 0xe8,0x42,0xbd,0xb0, 0x89,0x8b,0x88,0x07, 0x19,0x5b,0x38,0xe7, 0xc8,0xee,0xdb,0x79,
+ 0x7c,0x0a,0x47,0xa1, 0x42,0x0f,0xe9,0x7c, 0x84,0x1e,0xc9,0xf8, 0x00,0x00,0x00,0x00,
+ 0x80,0x86,0x83,0x09, 0x2b,0xed,0x48,0x32, 0x11,0x70,0xac,0x1e, 0x5a,0x72,0x4e,0x6c,
+ 0x0e,0xff,0xfb,0xfd, 0x85,0x38,0x56,0x0f, 0xae,0xd5,0x1e,0x3d, 0x2d,0x39,0x27,0x36,
+ 0x0f,0xd9,0x64,0x0a, 0x5c,0xa6,0x21,0x68, 0x5b,0x54,0xd1,0x9b, 0x36,0x2e,0x3a,0x24,
+ 0x0a,0x67,0xb1,0x0c, 0x57,0xe7,0x0f,0x93, 0xee,0x96,0xd2,0xb4, 0x9b,0x91,0x9e,0x1b,
+ 0xc0,0xc5,0x4f,0x80, 0xdc,0x20,0xa2,0x61, 0x77,0x4b,0x69,0x5a, 0x12,0x1a,0x16,0x1c,
+ 0x93,0xba,0x0a,0xe2, 0xa0,0x2a,0xe5,0xc0, 0x22,0xe0,0x43,0x3c, 0x1b,0x17,0x1d,0x12,
+ 0x09,0x0d,0x0b,0x0e, 0x8b,0xc7,0xad,0xf2, 0xb6,0xa8,0xb9,0x2d, 0x1e,0xa9,0xc8,0x14,
+ 0xf1,0x19,0x85,0x57, 0x75,0x07,0x4c,0xaf, 0x99,0xdd,0xbb,0xee, 0x7f,0x60,0xfd,0xa3,
+ 0x01,0x26,0x9f,0xf7, 0x72,0xf5,0xbc,0x5c, 0x66,0x3b,0xc5,0x44, 0xfb,0x7e,0x34,0x5b,
+ 0x43,0x29,0x76,0x8b, 0x23,0xc6,0xdc,0xcb, 0xed,0xfc,0x68,0xb6, 0xe4,0xf1,0x63,0xb8,
+ 0x31,0xdc,0xca,0xd7, 0x63,0x85,0x10,0x42, 0x97,0x22,0x40,0x13, 0xc6,0x11,0x20,0x84,
+ 0x4a,0x24,0x7d,0x85, 0xbb,0x3d,0xf8,0xd2, 0xf9,0x32,0x11,0xae, 0x29,0xa1,0x6d,0xc7,
+ 0x9e,0x2f,0x4b,0x1d, 0xb2,0x30,0xf3,0xdc, 0x86,0x52,0xec,0x0d, 0xc1,0xe3,0xd0,0x77,
+ 0xb3,0x16,0x6c,0x2b, 0x70,0xb9,0x99,0xa9, 0x94,0x48,0xfa,0x11, 0xe9,0x64,0x22,0x47,
+ 0xfc,0x8c,0xc4,0xa8, 0xf0,0x3f,0x1a,0xa0, 0x7d,0x2c,0xd8,0x56, 0x33,0x90,0xef,0x22,
+ 0x49,0x4e,0xc7,0x87, 0x38,0xd1,0xc1,0xd9, 0xca,0xa2,0xfe,0x8c, 0xd4,0x0b,0x36,0x98,
+ 0xf5,0x81,0xcf,0xa6, 0x7a,0xde,0x28,0xa5, 0xb7,0x8e,0x26,0xda, 0xad,0xbf,0xa4,0x3f,
+ 0x3a,0x9d,0xe4,0x2c, 0x78,0x92,0x0d,0x50, 0x5f,0xcc,0x9b,0x6a, 0x7e,0x46,0x62,0x54,
+ 0x8d,0x13,0xc2,0xf6, 0xd8,0xb8,0xe8,0x90, 0x39,0xf7,0x5e,0x2e, 0xc3,0xaf,0xf5,0x82,
+ 0x5d,0x80,0xbe,0x9f, 0xd0,0x93,0x7c,0x69, 0xd5,0x2d,0xa9,0x6f, 0x25,0x12,0xb3,0xcf,
+ 0xac,0x99,0x3b,0xc8, 0x18,0x7d,0xa7,0x10, 0x9c,0x63,0x6e,0xe8, 0x3b,0xbb,0x7b,0xdb,
+ 0x26,0x78,0x09,0xcd, 0x59,0x18,0xf4,0x6e, 0x9a,0xb7,0x01,0xec, 0x4f,0x9a,0xa8,0x83,
+ 0x95,0x6e,0x65,0xe6, 0xff,0xe6,0x7e,0xaa, 0xbc,0xcf,0x08,0x21, 0x15,0xe8,0xe6,0xef,
+ 0xe7,0x9b,0xd9,0xba, 0x6f,0x36,0xce,0x4a, 0x9f,0x09,0xd4,0xea, 0xb0,0x7c,0xd6,0x29,
+ 0xa4,0xb2,0xaf,0x31, 0x3f,0x23,0x31,0x2a, 0xa5,0x94,0x30,0xc6, 0xa2,0x66,0xc0,0x35,
+ 0x4e,0xbc,0x37,0x74, 0x82,0xca,0xa6,0xfc, 0x90,0xd0,0xb0,0xe0, 0xa7,0xd8,0x15,0x33,
+ 0x04,0x98,0x4a,0xf1, 0xec,0xda,0xf7,0x41, 0xcd,0x50,0x0e,0x7f, 0x91,0xf6,0x2f,0x17,
+ 0x4d,0xd6,0x8d,0x76, 0xef,0xb0,0x4d,0x43, 0xaa,0x4d,0x54,0xcc, 0x96,0x04,0xdf,0xe4,
+ 0xd1,0xb5,0xe3,0x9e, 0x6a,0x88,0x1b,0x4c, 0x2c,0x1f,0xb8,0xc1, 0x65,0x51,0x7f,0x46,
+ 0x5e,0xea,0x04,0x9d, 0x8c,0x35,0x5d,0x01, 0x87,0x74,0x73,0xfa, 0x0b,0x41,0x2e,0xfb,
+ 0x67,0x1d,0x5a,0xb3, 0xdb,0xd2,0x52,0x92, 0x10,0x56,0x33,0xe9, 0xd6,0x47,0x13,0x6d,
+ 0xd7,0x61,0x8c,0x9a, 0xa1,0x0c,0x7a,0x37, 0xf8,0x14,0x8e,0x59, 0x13,0x3c,0x89,0xeb,
+ 0xa9,0x27,0xee,0xce, 0x61,0xc9,0x35,0xb7, 0x1c,0xe5,0xed,0xe1, 0x47,0xb1,0x3c,0x7a,
+ 0xd2,0xdf,0x59,0x9c, 0xf2,0x73,0x3f,0x55, 0x14,0xce,0x79,0x18, 0xc7,0x37,0xbf,0x73,
+ 0xf7,0xcd,0xea,0x53, 0xfd,0xaa,0x5b,0x5f, 0x3d,0x6f,0x14,0xdf, 0x44,0xdb,0x86,0x78,
+ 0xaf,0xf3,0x81,0xca, 0x68,0xc4,0x3e,0xb9, 0x24,0x34,0x2c,0x38, 0xa3,0x40,0x5f,0xc2,
+ 0x1d,0xc3,0x72,0x16, 0xe2,0x25,0x0c,0xbc, 0x3c,0x49,0x8b,0x28, 0x0d,0x95,0x41,0xff,
+ 0xa8,0x01,0x71,0x39, 0x0c,0xb3,0xde,0x08, 0xb4,0xe4,0x9c,0xd8, 0x56,0xc1,0x90,0x64,
+ 0xcb,0x84,0x61,0x7b, 0x32,0xb6,0x70,0xd5, 0x6c,0x5c,0x74,0x48, 0xb8,0x57,0x42,0xd0
+};
+
+static UINT8 S5[256]=
+{
+ 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
+};
+
+static UINT8 U1[256][4]=
+{
+ 0x00,0x00,0x00,0x00, 0x0e,0x09,0x0d,0x0b, 0x1c,0x12,0x1a,0x16, 0x12,0x1b,0x17,0x1d,
+ 0x38,0x24,0x34,0x2c, 0x36,0x2d,0x39,0x27, 0x24,0x36,0x2e,0x3a, 0x2a,0x3f,0x23,0x31,
+ 0x70,0x48,0x68,0x58, 0x7e,0x41,0x65,0x53, 0x6c,0x5a,0x72,0x4e, 0x62,0x53,0x7f,0x45,
+ 0x48,0x6c,0x5c,0x74, 0x46,0x65,0x51,0x7f, 0x54,0x7e,0x46,0x62, 0x5a,0x77,0x4b,0x69,
+ 0xe0,0x90,0xd0,0xb0, 0xee,0x99,0xdd,0xbb, 0xfc,0x82,0xca,0xa6, 0xf2,0x8b,0xc7,0xad,
+ 0xd8,0xb4,0xe4,0x9c, 0xd6,0xbd,0xe9,0x97, 0xc4,0xa6,0xfe,0x8a, 0xca,0xaf,0xf3,0x81,
+ 0x90,0xd8,0xb8,0xe8, 0x9e,0xd1,0xb5,0xe3, 0x8c,0xca,0xa2,0xfe, 0x82,0xc3,0xaf,0xf5,
+ 0xa8,0xfc,0x8c,0xc4, 0xa6,0xf5,0x81,0xcf, 0xb4,0xee,0x96,0xd2, 0xba,0xe7,0x9b,0xd9,
+ 0xdb,0x3b,0xbb,0x7b, 0xd5,0x32,0xb6,0x70, 0xc7,0x29,0xa1,0x6d, 0xc9,0x20,0xac,0x66,
+ 0xe3,0x1f,0x8f,0x57, 0xed,0x16,0x82,0x5c, 0xff,0x0d,0x95,0x41, 0xf1,0x04,0x98,0x4a,
+ 0xab,0x73,0xd3,0x23, 0xa5,0x7a,0xde,0x28, 0xb7,0x61,0xc9,0x35, 0xb9,0x68,0xc4,0x3e,
+ 0x93,0x57,0xe7,0x0f, 0x9d,0x5e,0xea,0x04, 0x8f,0x45,0xfd,0x19, 0x81,0x4c,0xf0,0x12,
+ 0x3b,0xab,0x6b,0xcb, 0x35,0xa2,0x66,0xc0, 0x27,0xb9,0x71,0xdd, 0x29,0xb0,0x7c,0xd6,
+ 0x03,0x8f,0x5f,0xe7, 0x0d,0x86,0x52,0xec, 0x1f,0x9d,0x45,0xf1, 0x11,0x94,0x48,0xfa,
+ 0x4b,0xe3,0x03,0x93, 0x45,0xea,0x0e,0x98, 0x57,0xf1,0x19,0x85, 0x59,0xf8,0x14,0x8e,
+ 0x73,0xc7,0x37,0xbf, 0x7d,0xce,0x3a,0xb4, 0x6f,0xd5,0x2d,0xa9, 0x61,0xdc,0x20,0xa2,
+ 0xad,0x76,0x6d,0xf6, 0xa3,0x7f,0x60,0xfd, 0xb1,0x64,0x77,0xe0, 0xbf,0x6d,0x7a,0xeb,
+ 0x95,0x52,0x59,0xda, 0x9b,0x5b,0x54,0xd1, 0x89,0x40,0x43,0xcc, 0x87,0x49,0x4e,0xc7,
+ 0xdd,0x3e,0x05,0xae, 0xd3,0x37,0x08,0xa5, 0xc1,0x2c,0x1f,0xb8, 0xcf,0x25,0x12,0xb3,
+ 0xe5,0x1a,0x31,0x82, 0xeb,0x13,0x3c,0x89, 0xf9,0x08,0x2b,0x94, 0xf7,0x01,0x26,0x9f,
+ 0x4d,0xe6,0xbd,0x46, 0x43,0xef,0xb0,0x4d, 0x51,0xf4,0xa7,0x50, 0x5f,0xfd,0xaa,0x5b,
+ 0x75,0xc2,0x89,0x6a, 0x7b,0xcb,0x84,0x61, 0x69,0xd0,0x93,0x7c, 0x67,0xd9,0x9e,0x77,
+ 0x3d,0xae,0xd5,0x1e, 0x33,0xa7,0xd8,0x15, 0x21,0xbc,0xcf,0x08, 0x2f,0xb5,0xc2,0x03,
+ 0x05,0x8a,0xe1,0x32, 0x0b,0x83,0xec,0x39, 0x19,0x98,0xfb,0x24, 0x17,0x91,0xf6,0x2f,
+ 0x76,0x4d,0xd6,0x8d, 0x78,0x44,0xdb,0x86, 0x6a,0x5f,0xcc,0x9b, 0x64,0x56,0xc1,0x90,
+ 0x4e,0x69,0xe2,0xa1, 0x40,0x60,0xef,0xaa, 0x52,0x7b,0xf8,0xb7, 0x5c,0x72,0xf5,0xbc,
+ 0x06,0x05,0xbe,0xd5, 0x08,0x0c,0xb3,0xde, 0x1a,0x17,0xa4,0xc3, 0x14,0x1e,0xa9,0xc8,
+ 0x3e,0x21,0x8a,0xf9, 0x30,0x28,0x87,0xf2, 0x22,0x33,0x90,0xef, 0x2c,0x3a,0x9d,0xe4,
+ 0x96,0xdd,0x06,0x3d, 0x98,0xd4,0x0b,0x36, 0x8a,0xcf,0x1c,0x2b, 0x84,0xc6,0x11,0x20,
+ 0xae,0xf9,0x32,0x11, 0xa0,0xf0,0x3f,0x1a, 0xb2,0xeb,0x28,0x07, 0xbc,0xe2,0x25,0x0c,
+ 0xe6,0x95,0x6e,0x65, 0xe8,0x9c,0x63,0x6e, 0xfa,0x87,0x74,0x73, 0xf4,0x8e,0x79,0x78,
+ 0xde,0xb1,0x5a,0x49, 0xd0,0xb8,0x57,0x42, 0xc2,0xa3,0x40,0x5f, 0xcc,0xaa,0x4d,0x54,
+ 0x41,0xec,0xda,0xf7, 0x4f,0xe5,0xd7,0xfc, 0x5d,0xfe,0xc0,0xe1, 0x53,0xf7,0xcd,0xea,
+ 0x79,0xc8,0xee,0xdb, 0x77,0xc1,0xe3,0xd0, 0x65,0xda,0xf4,0xcd, 0x6b,0xd3,0xf9,0xc6,
+ 0x31,0xa4,0xb2,0xaf, 0x3f,0xad,0xbf,0xa4, 0x2d,0xb6,0xa8,0xb9, 0x23,0xbf,0xa5,0xb2,
+ 0x09,0x80,0x86,0x83, 0x07,0x89,0x8b,0x88, 0x15,0x92,0x9c,0x95, 0x1b,0x9b,0x91,0x9e,
+ 0xa1,0x7c,0x0a,0x47, 0xaf,0x75,0x07,0x4c, 0xbd,0x6e,0x10,0x51, 0xb3,0x67,0x1d,0x5a,
+ 0x99,0x58,0x3e,0x6b, 0x97,0x51,0x33,0x60, 0x85,0x4a,0x24,0x7d, 0x8b,0x43,0x29,0x76,
+ 0xd1,0x34,0x62,0x1f, 0xdf,0x3d,0x6f,0x14, 0xcd,0x26,0x78,0x09, 0xc3,0x2f,0x75,0x02,
+ 0xe9,0x10,0x56,0x33, 0xe7,0x19,0x5b,0x38, 0xf5,0x02,0x4c,0x25, 0xfb,0x0b,0x41,0x2e,
+ 0x9a,0xd7,0x61,0x8c, 0x94,0xde,0x6c,0x87, 0x86,0xc5,0x7b,0x9a, 0x88,0xcc,0x76,0x91,
+ 0xa2,0xf3,0x55,0xa0, 0xac,0xfa,0x58,0xab, 0xbe,0xe1,0x4f,0xb6, 0xb0,0xe8,0x42,0xbd,
+ 0xea,0x9f,0x09,0xd4, 0xe4,0x96,0x04,0xdf, 0xf6,0x8d,0x13,0xc2, 0xf8,0x84,0x1e,0xc9,
+ 0xd2,0xbb,0x3d,0xf8, 0xdc,0xb2,0x30,0xf3, 0xce,0xa9,0x27,0xee, 0xc0,0xa0,0x2a,0xe5,
+ 0x7a,0x47,0xb1,0x3c, 0x74,0x4e,0xbc,0x37, 0x66,0x55,0xab,0x2a, 0x68,0x5c,0xa6,0x21,
+ 0x42,0x63,0x85,0x10, 0x4c,0x6a,0x88,0x1b, 0x5e,0x71,0x9f,0x06, 0x50,0x78,0x92,0x0d,
+ 0x0a,0x0f,0xd9,0x64, 0x04,0x06,0xd4,0x6f, 0x16,0x1d,0xc3,0x72, 0x18,0x14,0xce,0x79,
+ 0x32,0x2b,0xed,0x48, 0x3c,0x22,0xe0,0x43, 0x2e,0x39,0xf7,0x5e, 0x20,0x30,0xfa,0x55,
+ 0xec,0x9a,0xb7,0x01, 0xe2,0x93,0xba,0x0a, 0xf0,0x88,0xad,0x17, 0xfe,0x81,0xa0,0x1c,
+ 0xd4,0xbe,0x83,0x2d, 0xda,0xb7,0x8e,0x26, 0xc8,0xac,0x99,0x3b, 0xc6,0xa5,0x94,0x30,
+ 0x9c,0xd2,0xdf,0x59, 0x92,0xdb,0xd2,0x52, 0x80,0xc0,0xc5,0x4f, 0x8e,0xc9,0xc8,0x44,
+ 0xa4,0xf6,0xeb,0x75, 0xaa,0xff,0xe6,0x7e, 0xb8,0xe4,0xf1,0x63, 0xb6,0xed,0xfc,0x68,
+ 0x0c,0x0a,0x67,0xb1, 0x02,0x03,0x6a,0xba, 0x10,0x18,0x7d,0xa7, 0x1e,0x11,0x70,0xac,
+ 0x34,0x2e,0x53,0x9d, 0x3a,0x27,0x5e,0x96, 0x28,0x3c,0x49,0x8b, 0x26,0x35,0x44,0x80,
+ 0x7c,0x42,0x0f,0xe9, 0x72,0x4b,0x02,0xe2, 0x60,0x50,0x15,0xff, 0x6e,0x59,0x18,0xf4,
+ 0x44,0x66,0x3b,0xc5, 0x4a,0x6f,0x36,0xce, 0x58,0x74,0x21,0xd3, 0x56,0x7d,0x2c,0xd8,
+ 0x37,0xa1,0x0c,0x7a, 0x39,0xa8,0x01,0x71, 0x2b,0xb3,0x16,0x6c, 0x25,0xba,0x1b,0x67,
+ 0x0f,0x85,0x38,0x56, 0x01,0x8c,0x35,0x5d, 0x13,0x97,0x22,0x40, 0x1d,0x9e,0x2f,0x4b,
+ 0x47,0xe9,0x64,0x22, 0x49,0xe0,0x69,0x29, 0x5b,0xfb,0x7e,0x34, 0x55,0xf2,0x73,0x3f,
+ 0x7f,0xcd,0x50,0x0e, 0x71,0xc4,0x5d,0x05, 0x63,0xdf,0x4a,0x18, 0x6d,0xd6,0x47,0x13,
+ 0xd7,0x31,0xdc,0xca, 0xd9,0x38,0xd1,0xc1, 0xcb,0x23,0xc6,0xdc, 0xc5,0x2a,0xcb,0xd7,
+ 0xef,0x15,0xe8,0xe6, 0xe1,0x1c,0xe5,0xed, 0xf3,0x07,0xf2,0xf0, 0xfd,0x0e,0xff,0xfb,
+ 0xa7,0x79,0xb4,0x92, 0xa9,0x70,0xb9,0x99, 0xbb,0x6b,0xae,0x84, 0xb5,0x62,0xa3,0x8f,
+ 0x9f,0x5d,0x80,0xbe, 0x91,0x54,0x8d,0xb5, 0x83,0x4f,0x9a,0xa8, 0x8d,0x46,0x97,0xa3
+};
+
+static UINT8 U2[256][4]=
+{
+ 0x00,0x00,0x00,0x00, 0x0b,0x0e,0x09,0x0d, 0x16,0x1c,0x12,0x1a, 0x1d,0x12,0x1b,0x17,
+ 0x2c,0x38,0x24,0x34, 0x27,0x36,0x2d,0x39, 0x3a,0x24,0x36,0x2e, 0x31,0x2a,0x3f,0x23,
+ 0x58,0x70,0x48,0x68, 0x53,0x7e,0x41,0x65, 0x4e,0x6c,0x5a,0x72, 0x45,0x62,0x53,0x7f,
+ 0x74,0x48,0x6c,0x5c, 0x7f,0x46,0x65,0x51, 0x62,0x54,0x7e,0x46, 0x69,0x5a,0x77,0x4b,
+ 0xb0,0xe0,0x90,0xd0, 0xbb,0xee,0x99,0xdd, 0xa6,0xfc,0x82,0xca, 0xad,0xf2,0x8b,0xc7,
+ 0x9c,0xd8,0xb4,0xe4, 0x97,0xd6,0xbd,0xe9, 0x8a,0xc4,0xa6,0xfe, 0x81,0xca,0xaf,0xf3,
+ 0xe8,0x90,0xd8,0xb8, 0xe3,0x9e,0xd1,0xb5, 0xfe,0x8c,0xca,0xa2, 0xf5,0x82,0xc3,0xaf,
+ 0xc4,0xa8,0xfc,0x8c, 0xcf,0xa6,0xf5,0x81, 0xd2,0xb4,0xee,0x96, 0xd9,0xba,0xe7,0x9b,
+ 0x7b,0xdb,0x3b,0xbb, 0x70,0xd5,0x32,0xb6, 0x6d,0xc7,0x29,0xa1, 0x66,0xc9,0x20,0xac,
+ 0x57,0xe3,0x1f,0x8f, 0x5c,0xed,0x16,0x82, 0x41,0xff,0x0d,0x95, 0x4a,0xf1,0x04,0x98,
+ 0x23,0xab,0x73,0xd3, 0x28,0xa5,0x7a,0xde, 0x35,0xb7,0x61,0xc9, 0x3e,0xb9,0x68,0xc4,
+ 0x0f,0x93,0x57,0xe7, 0x04,0x9d,0x5e,0xea, 0x19,0x8f,0x45,0xfd, 0x12,0x81,0x4c,0xf0,
+ 0xcb,0x3b,0xab,0x6b, 0xc0,0x35,0xa2,0x66, 0xdd,0x27,0xb9,0x71, 0xd6,0x29,0xb0,0x7c,
+ 0xe7,0x03,0x8f,0x5f, 0xec,0x0d,0x86,0x52, 0xf1,0x1f,0x9d,0x45, 0xfa,0x11,0x94,0x48,
+ 0x93,0x4b,0xe3,0x03, 0x98,0x45,0xea,0x0e, 0x85,0x57,0xf1,0x19, 0x8e,0x59,0xf8,0x14,
+ 0xbf,0x73,0xc7,0x37, 0xb4,0x7d,0xce,0x3a, 0xa9,0x6f,0xd5,0x2d, 0xa2,0x61,0xdc,0x20,
+ 0xf6,0xad,0x76,0x6d, 0xfd,0xa3,0x7f,0x60, 0xe0,0xb1,0x64,0x77, 0xeb,0xbf,0x6d,0x7a,
+ 0xda,0x95,0x52,0x59, 0xd1,0x9b,0x5b,0x54, 0xcc,0x89,0x40,0x43, 0xc7,0x87,0x49,0x4e,
+ 0xae,0xdd,0x3e,0x05, 0xa5,0xd3,0x37,0x08, 0xb8,0xc1,0x2c,0x1f, 0xb3,0xcf,0x25,0x12,
+ 0x82,0xe5,0x1a,0x31, 0x89,0xeb,0x13,0x3c, 0x94,0xf9,0x08,0x2b, 0x9f,0xf7,0x01,0x26,
+ 0x46,0x4d,0xe6,0xbd, 0x4d,0x43,0xef,0xb0, 0x50,0x51,0xf4,0xa7, 0x5b,0x5f,0xfd,0xaa,
+ 0x6a,0x75,0xc2,0x89, 0x61,0x7b,0xcb,0x84, 0x7c,0x69,0xd0,0x93, 0x77,0x67,0xd9,0x9e,
+ 0x1e,0x3d,0xae,0xd5, 0x15,0x33,0xa7,0xd8, 0x08,0x21,0xbc,0xcf, 0x03,0x2f,0xb5,0xc2,
+ 0x32,0x05,0x8a,0xe1, 0x39,0x0b,0x83,0xec, 0x24,0x19,0x98,0xfb, 0x2f,0x17,0x91,0xf6,
+ 0x8d,0x76,0x4d,0xd6, 0x86,0x78,0x44,0xdb, 0x9b,0x6a,0x5f,0xcc, 0x90,0x64,0x56,0xc1,
+ 0xa1,0x4e,0x69,0xe2, 0xaa,0x40,0x60,0xef, 0xb7,0x52,0x7b,0xf8, 0xbc,0x5c,0x72,0xf5,
+ 0xd5,0x06,0x05,0xbe, 0xde,0x08,0x0c,0xb3, 0xc3,0x1a,0x17,0xa4, 0xc8,0x14,0x1e,0xa9,
+ 0xf9,0x3e,0x21,0x8a, 0xf2,0x30,0x28,0x87, 0xef,0x22,0x33,0x90, 0xe4,0x2c,0x3a,0x9d,
+ 0x3d,0x96,0xdd,0x06, 0x36,0x98,0xd4,0x0b, 0x2b,0x8a,0xcf,0x1c, 0x20,0x84,0xc6,0x11,
+ 0x11,0xae,0xf9,0x32, 0x1a,0xa0,0xf0,0x3f, 0x07,0xb2,0xeb,0x28, 0x0c,0xbc,0xe2,0x25,
+ 0x65,0xe6,0x95,0x6e, 0x6e,0xe8,0x9c,0x63, 0x73,0xfa,0x87,0x74, 0x78,0xf4,0x8e,0x79,
+ 0x49,0xde,0xb1,0x5a, 0x42,0xd0,0xb8,0x57, 0x5f,0xc2,0xa3,0x40, 0x54,0xcc,0xaa,0x4d,
+ 0xf7,0x41,0xec,0xda, 0xfc,0x4f,0xe5,0xd7, 0xe1,0x5d,0xfe,0xc0, 0xea,0x53,0xf7,0xcd,
+ 0xdb,0x79,0xc8,0xee, 0xd0,0x77,0xc1,0xe3, 0xcd,0x65,0xda,0xf4, 0xc6,0x6b,0xd3,0xf9,
+ 0xaf,0x31,0xa4,0xb2, 0xa4,0x3f,0xad,0xbf, 0xb9,0x2d,0xb6,0xa8, 0xb2,0x23,0xbf,0xa5,
+ 0x83,0x09,0x80,0x86, 0x88,0x07,0x89,0x8b, 0x95,0x15,0x92,0x9c, 0x9e,0x1b,0x9b,0x91,
+ 0x47,0xa1,0x7c,0x0a, 0x4c,0xaf,0x75,0x07, 0x51,0xbd,0x6e,0x10, 0x5a,0xb3,0x67,0x1d,
+ 0x6b,0x99,0x58,0x3e, 0x60,0x97,0x51,0x33, 0x7d,0x85,0x4a,0x24, 0x76,0x8b,0x43,0x29,
+ 0x1f,0xd1,0x34,0x62, 0x14,0xdf,0x3d,0x6f, 0x09,0xcd,0x26,0x78, 0x02,0xc3,0x2f,0x75,
+ 0x33,0xe9,0x10,0x56, 0x38,0xe7,0x19,0x5b, 0x25,0xf5,0x02,0x4c, 0x2e,0xfb,0x0b,0x41,
+ 0x8c,0x9a,0xd7,0x61, 0x87,0x94,0xde,0x6c, 0x9a,0x86,0xc5,0x7b, 0x91,0x88,0xcc,0x76,
+ 0xa0,0xa2,0xf3,0x55, 0xab,0xac,0xfa,0x58, 0xb6,0xbe,0xe1,0x4f, 0xbd,0xb0,0xe8,0x42,
+ 0xd4,0xea,0x9f,0x09, 0xdf,0xe4,0x96,0x04, 0xc2,0xf6,0x8d,0x13, 0xc9,0xf8,0x84,0x1e,
+ 0xf8,0xd2,0xbb,0x3d, 0xf3,0xdc,0xb2,0x30, 0xee,0xce,0xa9,0x27, 0xe5,0xc0,0xa0,0x2a,
+ 0x3c,0x7a,0x47,0xb1, 0x37,0x74,0x4e,0xbc, 0x2a,0x66,0x55,0xab, 0x21,0x68,0x5c,0xa6,
+ 0x10,0x42,0x63,0x85, 0x1b,0x4c,0x6a,0x88, 0x06,0x5e,0x71,0x9f, 0x0d,0x50,0x78,0x92,
+ 0x64,0x0a,0x0f,0xd9, 0x6f,0x04,0x06,0xd4, 0x72,0x16,0x1d,0xc3, 0x79,0x18,0x14,0xce,
+ 0x48,0x32,0x2b,0xed, 0x43,0x3c,0x22,0xe0, 0x5e,0x2e,0x39,0xf7, 0x55,0x20,0x30,0xfa,
+ 0x01,0xec,0x9a,0xb7, 0x0a,0xe2,0x93,0xba, 0x17,0xf0,0x88,0xad, 0x1c,0xfe,0x81,0xa0,
+ 0x2d,0xd4,0xbe,0x83, 0x26,0xda,0xb7,0x8e, 0x3b,0xc8,0xac,0x99, 0x30,0xc6,0xa5,0x94,
+ 0x59,0x9c,0xd2,0xdf, 0x52,0x92,0xdb,0xd2, 0x4f,0x80,0xc0,0xc5, 0x44,0x8e,0xc9,0xc8,
+ 0x75,0xa4,0xf6,0xeb, 0x7e,0xaa,0xff,0xe6, 0x63,0xb8,0xe4,0xf1, 0x68,0xb6,0xed,0xfc,
+ 0xb1,0x0c,0x0a,0x67, 0xba,0x02,0x03,0x6a, 0xa7,0x10,0x18,0x7d, 0xac,0x1e,0x11,0x70,
+ 0x9d,0x34,0x2e,0x53, 0x96,0x3a,0x27,0x5e, 0x8b,0x28,0x3c,0x49, 0x80,0x26,0x35,0x44,
+ 0xe9,0x7c,0x42,0x0f, 0xe2,0x72,0x4b,0x02, 0xff,0x60,0x50,0x15, 0xf4,0x6e,0x59,0x18,
+ 0xc5,0x44,0x66,0x3b, 0xce,0x4a,0x6f,0x36, 0xd3,0x58,0x74,0x21, 0xd8,0x56,0x7d,0x2c,
+ 0x7a,0x37,0xa1,0x0c, 0x71,0x39,0xa8,0x01, 0x6c,0x2b,0xb3,0x16, 0x67,0x25,0xba,0x1b,
+ 0x56,0x0f,0x85,0x38, 0x5d,0x01,0x8c,0x35, 0x40,0x13,0x97,0x22, 0x4b,0x1d,0x9e,0x2f,
+ 0x22,0x47,0xe9,0x64, 0x29,0x49,0xe0,0x69, 0x34,0x5b,0xfb,0x7e, 0x3f,0x55,0xf2,0x73,
+ 0x0e,0x7f,0xcd,0x50, 0x05,0x71,0xc4,0x5d, 0x18,0x63,0xdf,0x4a, 0x13,0x6d,0xd6,0x47,
+ 0xca,0xd7,0x31,0xdc, 0xc1,0xd9,0x38,0xd1, 0xdc,0xcb,0x23,0xc6, 0xd7,0xc5,0x2a,0xcb,
+ 0xe6,0xef,0x15,0xe8, 0xed,0xe1,0x1c,0xe5, 0xf0,0xf3,0x07,0xf2, 0xfb,0xfd,0x0e,0xff,
+ 0x92,0xa7,0x79,0xb4, 0x99,0xa9,0x70,0xb9, 0x84,0xbb,0x6b,0xae, 0x8f,0xb5,0x62,0xa3,
+ 0xbe,0x9f,0x5d,0x80, 0xb5,0x91,0x54,0x8d, 0xa8,0x83,0x4f,0x9a, 0xa3,0x8d,0x46,0x97
+};
+
+static UINT8 U3[256][4]=
+{
+ 0x00,0x00,0x00,0x00, 0x0d,0x0b,0x0e,0x09, 0x1a,0x16,0x1c,0x12, 0x17,0x1d,0x12,0x1b,
+ 0x34,0x2c,0x38,0x24, 0x39,0x27,0x36,0x2d, 0x2e,0x3a,0x24,0x36, 0x23,0x31,0x2a,0x3f,
+ 0x68,0x58,0x70,0x48, 0x65,0x53,0x7e,0x41, 0x72,0x4e,0x6c,0x5a, 0x7f,0x45,0x62,0x53,
+ 0x5c,0x74,0x48,0x6c, 0x51,0x7f,0x46,0x65, 0x46,0x62,0x54,0x7e, 0x4b,0x69,0x5a,0x77,
+ 0xd0,0xb0,0xe0,0x90, 0xdd,0xbb,0xee,0x99, 0xca,0xa6,0xfc,0x82, 0xc7,0xad,0xf2,0x8b,
+ 0xe4,0x9c,0xd8,0xb4, 0xe9,0x97,0xd6,0xbd, 0xfe,0x8a,0xc4,0xa6, 0xf3,0x81,0xca,0xaf,
+ 0xb8,0xe8,0x90,0xd8, 0xb5,0xe3,0x9e,0xd1, 0xa2,0xfe,0x8c,0xca, 0xaf,0xf5,0x82,0xc3,
+ 0x8c,0xc4,0xa8,0xfc, 0x81,0xcf,0xa6,0xf5, 0x96,0xd2,0xb4,0xee, 0x9b,0xd9,0xba,0xe7,
+ 0xbb,0x7b,0xdb,0x3b, 0xb6,0x70,0xd5,0x32, 0xa1,0x6d,0xc7,0x29, 0xac,0x66,0xc9,0x20,
+ 0x8f,0x57,0xe3,0x1f, 0x82,0x5c,0xed,0x16, 0x95,0x41,0xff,0x0d, 0x98,0x4a,0xf1,0x04,
+ 0xd3,0x23,0xab,0x73, 0xde,0x28,0xa5,0x7a, 0xc9,0x35,0xb7,0x61, 0xc4,0x3e,0xb9,0x68,
+ 0xe7,0x0f,0x93,0x57, 0xea,0x04,0x9d,0x5e, 0xfd,0x19,0x8f,0x45, 0xf0,0x12,0x81,0x4c,
+ 0x6b,0xcb,0x3b,0xab, 0x66,0xc0,0x35,0xa2, 0x71,0xdd,0x27,0xb9, 0x7c,0xd6,0x29,0xb0,
+ 0x5f,0xe7,0x03,0x8f, 0x52,0xec,0x0d,0x86, 0x45,0xf1,0x1f,0x9d, 0x48,0xfa,0x11,0x94,
+ 0x03,0x93,0x4b,0xe3, 0x0e,0x98,0x45,0xea, 0x19,0x85,0x57,0xf1, 0x14,0x8e,0x59,0xf8,
+ 0x37,0xbf,0x73,0xc7, 0x3a,0xb4,0x7d,0xce, 0x2d,0xa9,0x6f,0xd5, 0x20,0xa2,0x61,0xdc,
+ 0x6d,0xf6,0xad,0x76, 0x60,0xfd,0xa3,0x7f, 0x77,0xe0,0xb1,0x64, 0x7a,0xeb,0xbf,0x6d,
+ 0x59,0xda,0x95,0x52, 0x54,0xd1,0x9b,0x5b, 0x43,0xcc,0x89,0x40, 0x4e,0xc7,0x87,0x49,
+ 0x05,0xae,0xdd,0x3e, 0x08,0xa5,0xd3,0x37, 0x1f,0xb8,0xc1,0x2c, 0x12,0xb3,0xcf,0x25,
+ 0x31,0x82,0xe5,0x1a, 0x3c,0x89,0xeb,0x13, 0x2b,0x94,0xf9,0x08, 0x26,0x9f,0xf7,0x01,
+ 0xbd,0x46,0x4d,0xe6, 0xb0,0x4d,0x43,0xef, 0xa7,0x50,0x51,0xf4, 0xaa,0x5b,0x5f,0xfd,
+ 0x89,0x6a,0x75,0xc2, 0x84,0x61,0x7b,0xcb, 0x93,0x7c,0x69,0xd0, 0x9e,0x77,0x67,0xd9,
+ 0xd5,0x1e,0x3d,0xae, 0xd8,0x15,0x33,0xa7, 0xcf,0x08,0x21,0xbc, 0xc2,0x03,0x2f,0xb5,
+ 0xe1,0x32,0x05,0x8a, 0xec,0x39,0x0b,0x83, 0xfb,0x24,0x19,0x98, 0xf6,0x2f,0x17,0x91,
+ 0xd6,0x8d,0x76,0x4d, 0xdb,0x86,0x78,0x44, 0xcc,0x9b,0x6a,0x5f, 0xc1,0x90,0x64,0x56,
+ 0xe2,0xa1,0x4e,0x69, 0xef,0xaa,0x40,0x60, 0xf8,0xb7,0x52,0x7b, 0xf5,0xbc,0x5c,0x72,
+ 0xbe,0xd5,0x06,0x05, 0xb3,0xde,0x08,0x0c, 0xa4,0xc3,0x1a,0x17, 0xa9,0xc8,0x14,0x1e,
+ 0x8a,0xf9,0x3e,0x21, 0x87,0xf2,0x30,0x28, 0x90,0xef,0x22,0x33, 0x9d,0xe4,0x2c,0x3a,
+ 0x06,0x3d,0x96,0xdd, 0x0b,0x36,0x98,0xd4, 0x1c,0x2b,0x8a,0xcf, 0x11,0x20,0x84,0xc6,
+ 0x32,0x11,0xae,0xf9, 0x3f,0x1a,0xa0,0xf0, 0x28,0x07,0xb2,0xeb, 0x25,0x0c,0xbc,0xe2,
+ 0x6e,0x65,0xe6,0x95, 0x63,0x6e,0xe8,0x9c, 0x74,0x73,0xfa,0x87, 0x79,0x78,0xf4,0x8e,
+ 0x5a,0x49,0xde,0xb1, 0x57,0x42,0xd0,0xb8, 0x40,0x5f,0xc2,0xa3, 0x4d,0x54,0xcc,0xaa,
+ 0xda,0xf7,0x41,0xec, 0xd7,0xfc,0x4f,0xe5, 0xc0,0xe1,0x5d,0xfe, 0xcd,0xea,0x53,0xf7,
+ 0xee,0xdb,0x79,0xc8, 0xe3,0xd0,0x77,0xc1, 0xf4,0xcd,0x65,0xda, 0xf9,0xc6,0x6b,0xd3,
+ 0xb2,0xaf,0x31,0xa4, 0xbf,0xa4,0x3f,0xad, 0xa8,0xb9,0x2d,0xb6, 0xa5,0xb2,0x23,0xbf,
+ 0x86,0x83,0x09,0x80, 0x8b,0x88,0x07,0x89, 0x9c,0x95,0x15,0x92, 0x91,0x9e,0x1b,0x9b,
+ 0x0a,0x47,0xa1,0x7c, 0x07,0x4c,0xaf,0x75, 0x10,0x51,0xbd,0x6e, 0x1d,0x5a,0xb3,0x67,
+ 0x3e,0x6b,0x99,0x58, 0x33,0x60,0x97,0x51, 0x24,0x7d,0x85,0x4a, 0x29,0x76,0x8b,0x43,
+ 0x62,0x1f,0xd1,0x34, 0x6f,0x14,0xdf,0x3d, 0x78,0x09,0xcd,0x26, 0x75,0x02,0xc3,0x2f,
+ 0x56,0x33,0xe9,0x10, 0x5b,0x38,0xe7,0x19, 0x4c,0x25,0xf5,0x02, 0x41,0x2e,0xfb,0x0b,
+ 0x61,0x8c,0x9a,0xd7, 0x6c,0x87,0x94,0xde, 0x7b,0x9a,0x86,0xc5, 0x76,0x91,0x88,0xcc,
+ 0x55,0xa0,0xa2,0xf3, 0x58,0xab,0xac,0xfa, 0x4f,0xb6,0xbe,0xe1, 0x42,0xbd,0xb0,0xe8,
+ 0x09,0xd4,0xea,0x9f, 0x04,0xdf,0xe4,0x96, 0x13,0xc2,0xf6,0x8d, 0x1e,0xc9,0xf8,0x84,
+ 0x3d,0xf8,0xd2,0xbb, 0x30,0xf3,0xdc,0xb2, 0x27,0xee,0xce,0xa9, 0x2a,0xe5,0xc0,0xa0,
+ 0xb1,0x3c,0x7a,0x47, 0xbc,0x37,0x74,0x4e, 0xab,0x2a,0x66,0x55, 0xa6,0x21,0x68,0x5c,
+ 0x85,0x10,0x42,0x63, 0x88,0x1b,0x4c,0x6a, 0x9f,0x06,0x5e,0x71, 0x92,0x0d,0x50,0x78,
+ 0xd9,0x64,0x0a,0x0f, 0xd4,0x6f,0x04,0x06, 0xc3,0x72,0x16,0x1d, 0xce,0x79,0x18,0x14,
+ 0xed,0x48,0x32,0x2b, 0xe0,0x43,0x3c,0x22, 0xf7,0x5e,0x2e,0x39, 0xfa,0x55,0x20,0x30,
+ 0xb7,0x01,0xec,0x9a, 0xba,0x0a,0xe2,0x93, 0xad,0x17,0xf0,0x88, 0xa0,0x1c,0xfe,0x81,
+ 0x83,0x2d,0xd4,0xbe, 0x8e,0x26,0xda,0xb7, 0x99,0x3b,0xc8,0xac, 0x94,0x30,0xc6,0xa5,
+ 0xdf,0x59,0x9c,0xd2, 0xd2,0x52,0x92,0xdb, 0xc5,0x4f,0x80,0xc0, 0xc8,0x44,0x8e,0xc9,
+ 0xeb,0x75,0xa4,0xf6, 0xe6,0x7e,0xaa,0xff, 0xf1,0x63,0xb8,0xe4, 0xfc,0x68,0xb6,0xed,
+ 0x67,0xb1,0x0c,0x0a, 0x6a,0xba,0x02,0x03, 0x7d,0xa7,0x10,0x18, 0x70,0xac,0x1e,0x11,
+ 0x53,0x9d,0x34,0x2e, 0x5e,0x96,0x3a,0x27, 0x49,0x8b,0x28,0x3c, 0x44,0x80,0x26,0x35,
+ 0x0f,0xe9,0x7c,0x42, 0x02,0xe2,0x72,0x4b, 0x15,0xff,0x60,0x50, 0x18,0xf4,0x6e,0x59,
+ 0x3b,0xc5,0x44,0x66, 0x36,0xce,0x4a,0x6f, 0x21,0xd3,0x58,0x74, 0x2c,0xd8,0x56,0x7d,
+ 0x0c,0x7a,0x37,0xa1, 0x01,0x71,0x39,0xa8, 0x16,0x6c,0x2b,0xb3, 0x1b,0x67,0x25,0xba,
+ 0x38,0x56,0x0f,0x85, 0x35,0x5d,0x01,0x8c, 0x22,0x40,0x13,0x97, 0x2f,0x4b,0x1d,0x9e,
+ 0x64,0x22,0x47,0xe9, 0x69,0x29,0x49,0xe0, 0x7e,0x34,0x5b,0xfb, 0x73,0x3f,0x55,0xf2,
+ 0x50,0x0e,0x7f,0xcd, 0x5d,0x05,0x71,0xc4, 0x4a,0x18,0x63,0xdf, 0x47,0x13,0x6d,0xd6,
+ 0xdc,0xca,0xd7,0x31, 0xd1,0xc1,0xd9,0x38, 0xc6,0xdc,0xcb,0x23, 0xcb,0xd7,0xc5,0x2a,
+ 0xe8,0xe6,0xef,0x15, 0xe5,0xed,0xe1,0x1c, 0xf2,0xf0,0xf3,0x07, 0xff,0xfb,0xfd,0x0e,
+ 0xb4,0x92,0xa7,0x79, 0xb9,0x99,0xa9,0x70, 0xae,0x84,0xbb,0x6b, 0xa3,0x8f,0xb5,0x62,
+ 0x80,0xbe,0x9f,0x5d, 0x8d,0xb5,0x91,0x54, 0x9a,0xa8,0x83,0x4f, 0x97,0xa3,0x8d,0x46
+};
+
+static UINT8 U4[256][4]=
+{
+ 0x00,0x00,0x00,0x00, 0x09,0x0d,0x0b,0x0e, 0x12,0x1a,0x16,0x1c, 0x1b,0x17,0x1d,0x12,
+ 0x24,0x34,0x2c,0x38, 0x2d,0x39,0x27,0x36, 0x36,0x2e,0x3a,0x24, 0x3f,0x23,0x31,0x2a,
+ 0x48,0x68,0x58,0x70, 0x41,0x65,0x53,0x7e, 0x5a,0x72,0x4e,0x6c, 0x53,0x7f,0x45,0x62,
+ 0x6c,0x5c,0x74,0x48, 0x65,0x51,0x7f,0x46, 0x7e,0x46,0x62,0x54, 0x77,0x4b,0x69,0x5a,
+ 0x90,0xd0,0xb0,0xe0, 0x99,0xdd,0xbb,0xee, 0x82,0xca,0xa6,0xfc, 0x8b,0xc7,0xad,0xf2,
+ 0xb4,0xe4,0x9c,0xd8, 0xbd,0xe9,0x97,0xd6, 0xa6,0xfe,0x8a,0xc4, 0xaf,0xf3,0x81,0xca,
+ 0xd8,0xb8,0xe8,0x90, 0xd1,0xb5,0xe3,0x9e, 0xca,0xa2,0xfe,0x8c, 0xc3,0xaf,0xf5,0x82,
+ 0xfc,0x8c,0xc4,0xa8, 0xf5,0x81,0xcf,0xa6, 0xee,0x96,0xd2,0xb4, 0xe7,0x9b,0xd9,0xba,
+ 0x3b,0xbb,0x7b,0xdb, 0x32,0xb6,0x70,0xd5, 0x29,0xa1,0x6d,0xc7, 0x20,0xac,0x66,0xc9,
+ 0x1f,0x8f,0x57,0xe3, 0x16,0x82,0x5c,0xed, 0x0d,0x95,0x41,0xff, 0x04,0x98,0x4a,0xf1,
+ 0x73,0xd3,0x23,0xab, 0x7a,0xde,0x28,0xa5, 0x61,0xc9,0x35,0xb7, 0x68,0xc4,0x3e,0xb9,
+ 0x57,0xe7,0x0f,0x93, 0x5e,0xea,0x04,0x9d, 0x45,0xfd,0x19,0x8f, 0x4c,0xf0,0x12,0x81,
+ 0xab,0x6b,0xcb,0x3b, 0xa2,0x66,0xc0,0x35, 0xb9,0x71,0xdd,0x27, 0xb0,0x7c,0xd6,0x29,
+ 0x8f,0x5f,0xe7,0x03, 0x86,0x52,0xec,0x0d, 0x9d,0x45,0xf1,0x1f, 0x94,0x48,0xfa,0x11,
+ 0xe3,0x03,0x93,0x4b, 0xea,0x0e,0x98,0x45, 0xf1,0x19,0x85,0x57, 0xf8,0x14,0x8e,0x59,
+ 0xc7,0x37,0xbf,0x73, 0xce,0x3a,0xb4,0x7d, 0xd5,0x2d,0xa9,0x6f, 0xdc,0x20,0xa2,0x61,
+ 0x76,0x6d,0xf6,0xad, 0x7f,0x60,0xfd,0xa3, 0x64,0x77,0xe0,0xb1, 0x6d,0x7a,0xeb,0xbf,
+ 0x52,0x59,0xda,0x95, 0x5b,0x54,0xd1,0x9b, 0x40,0x43,0xcc,0x89, 0x49,0x4e,0xc7,0x87,
+ 0x3e,0x05,0xae,0xdd, 0x37,0x08,0xa5,0xd3, 0x2c,0x1f,0xb8,0xc1, 0x25,0x12,0xb3,0xcf,
+ 0x1a,0x31,0x82,0xe5, 0x13,0x3c,0x89,0xeb, 0x08,0x2b,0x94,0xf9, 0x01,0x26,0x9f,0xf7,
+ 0xe6,0xbd,0x46,0x4d, 0xef,0xb0,0x4d,0x43, 0xf4,0xa7,0x50,0x51, 0xfd,0xaa,0x5b,0x5f,
+ 0xc2,0x89,0x6a,0x75, 0xcb,0x84,0x61,0x7b, 0xd0,0x93,0x7c,0x69, 0xd9,0x9e,0x77,0x67,
+ 0xae,0xd5,0x1e,0x3d, 0xa7,0xd8,0x15,0x33, 0xbc,0xcf,0x08,0x21, 0xb5,0xc2,0x03,0x2f,
+ 0x8a,0xe1,0x32,0x05, 0x83,0xec,0x39,0x0b, 0x98,0xfb,0x24,0x19, 0x91,0xf6,0x2f,0x17,
+ 0x4d,0xd6,0x8d,0x76, 0x44,0xdb,0x86,0x78, 0x5f,0xcc,0x9b,0x6a, 0x56,0xc1,0x90,0x64,
+ 0x69,0xe2,0xa1,0x4e, 0x60,0xef,0xaa,0x40, 0x7b,0xf8,0xb7,0x52, 0x72,0xf5,0xbc,0x5c,
+ 0x05,0xbe,0xd5,0x06, 0x0c,0xb3,0xde,0x08, 0x17,0xa4,0xc3,0x1a, 0x1e,0xa9,0xc8,0x14,
+ 0x21,0x8a,0xf9,0x3e, 0x28,0x87,0xf2,0x30, 0x33,0x90,0xef,0x22, 0x3a,0x9d,0xe4,0x2c,
+ 0xdd,0x06,0x3d,0x96, 0xd4,0x0b,0x36,0x98, 0xcf,0x1c,0x2b,0x8a, 0xc6,0x11,0x20,0x84,
+ 0xf9,0x32,0x11,0xae, 0xf0,0x3f,0x1a,0xa0, 0xeb,0x28,0x07,0xb2, 0xe2,0x25,0x0c,0xbc,
+ 0x95,0x6e,0x65,0xe6, 0x9c,0x63,0x6e,0xe8, 0x87,0x74,0x73,0xfa, 0x8e,0x79,0x78,0xf4,
+ 0xb1,0x5a,0x49,0xde, 0xb8,0x57,0x42,0xd0, 0xa3,0x40,0x5f,0xc2, 0xaa,0x4d,0x54,0xcc,
+ 0xec,0xda,0xf7,0x41, 0xe5,0xd7,0xfc,0x4f, 0xfe,0xc0,0xe1,0x5d, 0xf7,0xcd,0xea,0x53,
+ 0xc8,0xee,0xdb,0x79, 0xc1,0xe3,0xd0,0x77, 0xda,0xf4,0xcd,0x65, 0xd3,0xf9,0xc6,0x6b,
+ 0xa4,0xb2,0xaf,0x31, 0xad,0xbf,0xa4,0x3f, 0xb6,0xa8,0xb9,0x2d, 0xbf,0xa5,0xb2,0x23,
+ 0x80,0x86,0x83,0x09, 0x89,0x8b,0x88,0x07, 0x92,0x9c,0x95,0x15, 0x9b,0x91,0x9e,0x1b,
+ 0x7c,0x0a,0x47,0xa1, 0x75,0x07,0x4c,0xaf, 0x6e,0x10,0x51,0xbd, 0x67,0x1d,0x5a,0xb3,
+ 0x58,0x3e,0x6b,0x99, 0x51,0x33,0x60,0x97, 0x4a,0x24,0x7d,0x85, 0x43,0x29,0x76,0x8b,
+ 0x34,0x62,0x1f,0xd1, 0x3d,0x6f,0x14,0xdf, 0x26,0x78,0x09,0xcd, 0x2f,0x75,0x02,0xc3,
+ 0x10,0x56,0x33,0xe9, 0x19,0x5b,0x38,0xe7, 0x02,0x4c,0x25,0xf5, 0x0b,0x41,0x2e,0xfb,
+ 0xd7,0x61,0x8c,0x9a, 0xde,0x6c,0x87,0x94, 0xc5,0x7b,0x9a,0x86, 0xcc,0x76,0x91,0x88,
+ 0xf3,0x55,0xa0,0xa2, 0xfa,0x58,0xab,0xac, 0xe1,0x4f,0xb6,0xbe, 0xe8,0x42,0xbd,0xb0,
+ 0x9f,0x09,0xd4,0xea, 0x96,0x04,0xdf,0xe4, 0x8d,0x13,0xc2,0xf6, 0x84,0x1e,0xc9,0xf8,
+ 0xbb,0x3d,0xf8,0xd2, 0xb2,0x30,0xf3,0xdc, 0xa9,0x27,0xee,0xce, 0xa0,0x2a,0xe5,0xc0,
+ 0x47,0xb1,0x3c,0x7a, 0x4e,0xbc,0x37,0x74, 0x55,0xab,0x2a,0x66, 0x5c,0xa6,0x21,0x68,
+ 0x63,0x85,0x10,0x42, 0x6a,0x88,0x1b,0x4c, 0x71,0x9f,0x06,0x5e, 0x78,0x92,0x0d,0x50,
+ 0x0f,0xd9,0x64,0x0a, 0x06,0xd4,0x6f,0x04, 0x1d,0xc3,0x72,0x16, 0x14,0xce,0x79,0x18,
+ 0x2b,0xed,0x48,0x32, 0x22,0xe0,0x43,0x3c, 0x39,0xf7,0x5e,0x2e, 0x30,0xfa,0x55,0x20,
+ 0x9a,0xb7,0x01,0xec, 0x93,0xba,0x0a,0xe2, 0x88,0xad,0x17,0xf0, 0x81,0xa0,0x1c,0xfe,
+ 0xbe,0x83,0x2d,0xd4, 0xb7,0x8e,0x26,0xda, 0xac,0x99,0x3b,0xc8, 0xa5,0x94,0x30,0xc6,
+ 0xd2,0xdf,0x59,0x9c, 0xdb,0xd2,0x52,0x92, 0xc0,0xc5,0x4f,0x80, 0xc9,0xc8,0x44,0x8e,
+ 0xf6,0xeb,0x75,0xa4, 0xff,0xe6,0x7e,0xaa, 0xe4,0xf1,0x63,0xb8, 0xed,0xfc,0x68,0xb6,
+ 0x0a,0x67,0xb1,0x0c, 0x03,0x6a,0xba,0x02, 0x18,0x7d,0xa7,0x10, 0x11,0x70,0xac,0x1e,
+ 0x2e,0x53,0x9d,0x34, 0x27,0x5e,0x96,0x3a, 0x3c,0x49,0x8b,0x28, 0x35,0x44,0x80,0x26,
+ 0x42,0x0f,0xe9,0x7c, 0x4b,0x02,0xe2,0x72, 0x50,0x15,0xff,0x60, 0x59,0x18,0xf4,0x6e,
+ 0x66,0x3b,0xc5,0x44, 0x6f,0x36,0xce,0x4a, 0x74,0x21,0xd3,0x58, 0x7d,0x2c,0xd8,0x56,
+ 0xa1,0x0c,0x7a,0x37, 0xa8,0x01,0x71,0x39, 0xb3,0x16,0x6c,0x2b, 0xba,0x1b,0x67,0x25,
+ 0x85,0x38,0x56,0x0f, 0x8c,0x35,0x5d,0x01, 0x97,0x22,0x40,0x13, 0x9e,0x2f,0x4b,0x1d,
+ 0xe9,0x64,0x22,0x47, 0xe0,0x69,0x29,0x49, 0xfb,0x7e,0x34,0x5b, 0xf2,0x73,0x3f,0x55,
+ 0xcd,0x50,0x0e,0x7f, 0xc4,0x5d,0x05,0x71, 0xdf,0x4a,0x18,0x63, 0xd6,0x47,0x13,0x6d,
+ 0x31,0xdc,0xca,0xd7, 0x38,0xd1,0xc1,0xd9, 0x23,0xc6,0xdc,0xcb, 0x2a,0xcb,0xd7,0xc5,
+ 0x15,0xe8,0xe6,0xef, 0x1c,0xe5,0xed,0xe1, 0x07,0xf2,0xf0,0xf3, 0x0e,0xff,0xfb,0xfd,
+ 0x79,0xb4,0x92,0xa7, 0x70,0xb9,0x99,0xa9, 0x6b,0xae,0x84,0xbb, 0x62,0xa3,0x8f,0xb5,
+ 0x5d,0x80,0xbe,0x9f, 0x54,0x8d,0xb5,0x91, 0x4f,0x9a,0xa8,0x83, 0x46,0x97,0xa3,0x8d
+};
+
+static UINT32 rcon[30]=
+{
+ 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
+};
+
+
+
+//////////////////////////////////////////////////////////////////////////////////////////////////////////////////
+// API
+//////////////////////////////////////////////////////////////////////////////////////////////////////////////////
+
+Rijndael::Rijndael()
+{
+ m_state = Invalid;
+}
+
+Rijndael::~Rijndael()
+{
+ // nothing here
+}
+
+int Rijndael::init(Mode mode,Direction dir,const UINT8 * key,KeyLength keyLen,UINT8 * initVector)
+{
+ // Not initialized yet
+ m_state = Invalid;
+
+ // Check the mode
+ if((mode != CBC) && (mode != ECB) && (mode != CFB1))return RIJNDAEL_UNSUPPORTED_MODE;
+ m_mode = mode;
+
+ // And the direction
+ if((dir != Encrypt) && (dir != Decrypt))return RIJNDAEL_UNSUPPORTED_DIRECTION;
+ m_direction = dir;
+
+ // Allow to set an init vector
+ if(initVector)
+ {
+ // specified init vector
+ for(int i = 0;i < MAX_IV_SIZE;i++)
+ {
+ m_initVector[i] = initVector[i];
+ }
+ } else {
+ // zero init vector
+ for(int i = 0;i < MAX_IV_SIZE;i++)
+ {
+ m_initVector[i] = 0;
+ }
+ }
+
+ UINT32 uKeyLenInBytes;
+
+ // And check the key length
+ switch(keyLen)
+ {
+ case Key16Bytes:
+ uKeyLenInBytes = 16;
+ m_uRounds = 10;
+ break;
+ case Key24Bytes:
+ uKeyLenInBytes = 24;
+ m_uRounds = 12;
+ break;
+ case Key32Bytes:
+ uKeyLenInBytes = 32;
+ m_uRounds = 14;
+ break;
+ default:
+ return RIJNDAEL_UNSUPPORTED_KEY_LENGTH;
+ break;
+ }
+ // The number of rounds is calculated as
+ // m_uRounds = (m_uKeyLenInBits / 32) + 6;
+
+ if(!key)return RIJNDAEL_BAD_KEY;
+
+ UINT8 keyMatrix[_MAX_KEY_COLUMNS][4];
+
+ for(UINT32 i = 0;i < uKeyLenInBytes;i++)keyMatrix[i >> 2][i & 3] = key[i];
+
+ keySched(keyMatrix);
+
+ if(m_direction == Decrypt)keyEncToDec();
+
+ m_state = Valid;
+
+ return RIJNDAEL_SUCCESS;
+}
+
+int Rijndael::blockEncrypt(const UINT8 *input,int inputLen,UINT8 *outBuffer)
+{
+ int i, k, numBlocks;
+ UINT8 block[16], iv[4][4];
+
+ if(m_state != Valid)return RIJNDAEL_NOT_INITIALIZED;
+ if(m_direction != Encrypt)return RIJNDAEL_BAD_DIRECTION;
+
+ if(input == 0 || inputLen <= 0)return 0;
+
+ numBlocks = inputLen/128;
+
+ switch(m_mode){
+ case ECB:
+ for(i = numBlocks;i > 0;i--)
+ {
+ encrypt(input,outBuffer);
+ input += 16;
+ outBuffer += 16;
+ }
+ break;
+ case CBC:
+ ((UINT32*)block)[0] = ((UINT32*)m_initVector)[0] ^ ((UINT32*)input)[0];
+ ((UINT32*)block)[1] = ((UINT32*)m_initVector)[1] ^ ((UINT32*)input)[1];
+ ((UINT32*)block)[2] = ((UINT32*)m_initVector)[2] ^ ((UINT32*)input)[2];
+ ((UINT32*)block)[3] = ((UINT32*)m_initVector)[3] ^ ((UINT32*)input)[3];
+ encrypt(block,outBuffer);
+ input += 16;
+ for(i = numBlocks - 1;i > 0;i--)
+ {
+ ((UINT32*)block)[0] = ((UINT32*)outBuffer)[0] ^ ((UINT32*)input)[0];
+ ((UINT32*)block)[1] = ((UINT32*)outBuffer)[1] ^ ((UINT32*)input)[1];
+ ((UINT32*)block)[2] = ((UINT32*)outBuffer)[2] ^ ((UINT32*)input)[2];
+ ((UINT32*)block)[3] = ((UINT32*)outBuffer)[3] ^ ((UINT32*)input)[3];
+ outBuffer += 16;
+ encrypt(block,outBuffer);
+ input += 16;
+ }
+ break;
+ case CFB1:
+#if STRICT_ALIGN
+ kvi_memmove(iv,m_initVector,16);
+#else /* !STRICT_ALIGN */
+ *((UINT32*)iv[0]) = *((UINT32*)(m_initVector ));
+ *((UINT32*)iv[1]) = *((UINT32*)(m_initVector + 4));
+ *((UINT32*)iv[2]) = *((UINT32*)(m_initVector + 8));
+ *((UINT32*)iv[3]) = *((UINT32*)(m_initVector +12));
+#endif /* ?STRICT_ALIGN */
+ for(i = numBlocks; i > 0; i--)
+ {
+ for(k = 0; k < 128; k++)
+ {
+ *((UINT32*) block ) = *((UINT32*)iv[0]);
+ *((UINT32*)(block+ 4)) = *((UINT32*)iv[1]);
+ *((UINT32*)(block+ 8)) = *((UINT32*)iv[2]);
+ *((UINT32*)(block+12)) = *((UINT32*)iv[3]);
+ encrypt(block,block);
+ outBuffer[k/8] ^= (block[0] & 0x80) >> (k & 7);
+ iv[0][0] = (iv[0][0] << 1) | (iv[0][1] >> 7);
+ iv[0][1] = (iv[0][1] << 1) | (iv[0][2] >> 7);
+ iv[0][2] = (iv[0][2] << 1) | (iv[0][3] >> 7);
+ iv[0][3] = (iv[0][3] << 1) | (iv[1][0] >> 7);
+ iv[1][0] = (iv[1][0] << 1) | (iv[1][1] >> 7);
+ iv[1][1] = (iv[1][1] << 1) | (iv[1][2] >> 7);
+ iv[1][2] = (iv[1][2] << 1) | (iv[1][3] >> 7);
+ iv[1][3] = (iv[1][3] << 1) | (iv[2][0] >> 7);
+ iv[2][0] = (iv[2][0] << 1) | (iv[2][1] >> 7);
+ iv[2][1] = (iv[2][1] << 1) | (iv[2][2] >> 7);
+ iv[2][2] = (iv[2][2] << 1) | (iv[2][3] >> 7);
+ iv[2][3] = (iv[2][3] << 1) | (iv[3][0] >> 7);
+ iv[3][0] = (iv[3][0] << 1) | (iv[3][1] >> 7);
+ iv[3][1] = (iv[3][1] << 1) | (iv[3][2] >> 7);
+ iv[3][2] = (iv[3][2] << 1) | (iv[3][3] >> 7);
+ iv[3][3] = (iv[3][3] << 1) | (outBuffer[k/8] >> (7-(k&7))) & 1;
+ }
+ }
+ break;
+ default:
+ return -1;
+ break;
+ }
+
+ return 128 * numBlocks;
+}
+
+int Rijndael::padEncrypt(const UINT8 *input, int inputOctets, UINT8 *outBuffer)
+{
+ int i, numBlocks, padLen;
+ UINT8 block[16], *iv;
+
+ if(m_state != Valid)return RIJNDAEL_NOT_INITIALIZED;
+ if(m_direction != Encrypt)return RIJNDAEL_NOT_INITIALIZED;
+
+ if(input == 0 || inputOctets <= 0)return 0;
+
+ numBlocks = inputOctets/16;
+
+ switch(m_mode)
+ {
+ case ECB:
+ for(i = numBlocks; i > 0; i--)
+ {
+ encrypt(input, outBuffer);
+ input += 16;
+ outBuffer += 16;
+ }
+ padLen = 16 - (inputOctets - 16*numBlocks);
+// assert(padLen > 0 && padLen <= 16);
+ kvi_memmove(block, input, 16 - padLen);
+ kvi_memset(block + 16 - padLen, padLen, padLen);
+ encrypt(block,outBuffer);
+ break;
+ case CBC:
+ iv = m_initVector;
+ for(i = numBlocks; i > 0; i--)
+ {
+ ((UINT32*)block)[0] = ((UINT32*)input)[0] ^ ((UINT32*)iv)[0];
+ ((UINT32*)block)[1] = ((UINT32*)input)[1] ^ ((UINT32*)iv)[1];
+ ((UINT32*)block)[2] = ((UINT32*)input)[2] ^ ((UINT32*)iv)[2];
+ ((UINT32*)block)[3] = ((UINT32*)input)[3] ^ ((UINT32*)iv)[3];
+ encrypt(block, outBuffer);
+ iv = outBuffer;
+ input += 16;
+ outBuffer += 16;
+ }
+ padLen = 16 - (inputOctets - 16*numBlocks);
+// assert(padLen > 0 && padLen <= 16); // DO SOMETHING HERE ?
+ for (i = 0; i < 16 - padLen; i++) {
+ block[i] = input[i] ^ iv[i];
+ }
+ for (i = 16 - padLen; i < 16; i++) {
+ block[i] = (UINT8)padLen ^ iv[i];
+ }
+ encrypt(block,outBuffer);
+ break;
+ default:
+ return -1;
+ break;
+ }
+
+ return 16*(numBlocks + 1);
+}
+
+int Rijndael::blockDecrypt(const UINT8 *input, int inputLen, UINT8 *outBuffer)
+{
+ int i, k, numBlocks;
+ UINT8 block[16], iv[4][4];
+
+ if(m_state != Valid)return RIJNDAEL_NOT_INITIALIZED;
+ if((m_mode != CFB1) && (m_direction == Encrypt))return RIJNDAEL_BAD_DIRECTION;
+
+ if (input == 0 || inputLen <= 0)return 0;
+
+ numBlocks = inputLen/128;
+
+ switch(m_mode)
+ {
+ case ECB:
+ for (i = numBlocks; i > 0; i--)
+ {
+ decrypt(input,outBuffer);
+ input += 16;
+ outBuffer += 16;
+ }
+ break;
+ case CBC:
+#if STRICT_ALIGN
+ kvi_memmove(iv,m_initVector,16);
+#else
+ *((UINT32*)iv[0]) = *((UINT32*)(m_initVector ));
+ *((UINT32*)iv[1]) = *((UINT32*)(m_initVector+ 4));
+ *((UINT32*)iv[2]) = *((UINT32*)(m_initVector+ 8));
+ *((UINT32*)iv[3]) = *((UINT32*)(m_initVector+12));
+#endif
+ for (i = numBlocks; i > 0; i--)
+ {
+ decrypt(input, block);
+ ((UINT32*)block)[0] ^= *((UINT32*)iv[0]);
+ ((UINT32*)block)[1] ^= *((UINT32*)iv[1]);
+ ((UINT32*)block)[2] ^= *((UINT32*)iv[2]);
+ ((UINT32*)block)[3] ^= *((UINT32*)iv[3]);
+#if STRICT_ALIGN
+ kvi_memmove(iv, input, 16);
+ kvi_memmove(outBuf, block, 16);
+#else
+ *((UINT32*)iv[0]) = ((UINT32*)input)[0]; ((UINT32*)outBuffer)[0] = ((UINT32*)block)[0];
+ *((UINT32*)iv[1]) = ((UINT32*)input)[1]; ((UINT32*)outBuffer)[1] = ((UINT32*)block)[1];
+ *((UINT32*)iv[2]) = ((UINT32*)input)[2]; ((UINT32*)outBuffer)[2] = ((UINT32*)block)[2];
+ *((UINT32*)iv[3]) = ((UINT32*)input)[3]; ((UINT32*)outBuffer)[3] = ((UINT32*)block)[3];
+#endif
+ input += 16;
+ outBuffer += 16;
+ }
+ break;
+ case CFB1:
+#if STRICT_ALIGN
+ kvi_memmove(iv, m_initVector, 16);
+#else
+ *((UINT32*)iv[0]) = *((UINT32*)(m_initVector));
+ *((UINT32*)iv[1]) = *((UINT32*)(m_initVector+ 4));
+ *((UINT32*)iv[2]) = *((UINT32*)(m_initVector+ 8));
+ *((UINT32*)iv[3]) = *((UINT32*)(m_initVector+12));
+#endif
+ for(i = numBlocks; i > 0; i--)
+ {
+ for(k = 0; k < 128; k++)
+ {
+ *((UINT32*) block ) = *((UINT32*)iv[0]);
+ *((UINT32*)(block+ 4)) = *((UINT32*)iv[1]);
+ *((UINT32*)(block+ 8)) = *((UINT32*)iv[2]);
+ *((UINT32*)(block+12)) = *((UINT32*)iv[3]);
+ encrypt(block, block);
+ iv[0][0] = (iv[0][0] << 1) | (iv[0][1] >> 7);
+ iv[0][1] = (iv[0][1] << 1) | (iv[0][2] >> 7);
+ iv[0][2] = (iv[0][2] << 1) | (iv[0][3] >> 7);
+ iv[0][3] = (iv[0][3] << 1) | (iv[1][0] >> 7);
+ iv[1][0] = (iv[1][0] << 1) | (iv[1][1] >> 7);
+ iv[1][1] = (iv[1][1] << 1) | (iv[1][2] >> 7);
+ iv[1][2] = (iv[1][2] << 1) | (iv[1][3] >> 7);
+ iv[1][3] = (iv[1][3] << 1) | (iv[2][0] >> 7);
+ iv[2][0] = (iv[2][0] << 1) | (iv[2][1] >> 7);
+ iv[2][1] = (iv[2][1] << 1) | (iv[2][2] >> 7);
+ iv[2][2] = (iv[2][2] << 1) | (iv[2][3] >> 7);
+ iv[2][3] = (iv[2][3] << 1) | (iv[3][0] >> 7);
+ iv[3][0] = (iv[3][0] << 1) | (iv[3][1] >> 7);
+ iv[3][1] = (iv[3][1] << 1) | (iv[3][2] >> 7);
+ iv[3][2] = (iv[3][2] << 1) | (iv[3][3] >> 7);
+ iv[3][3] = (iv[3][3] << 1) | (input[k/8] >> (7-(k&7))) & 1;
+ outBuffer[k/8] ^= (block[0] & 0x80) >> (k & 7);
+ }
+ }
+ break;
+ default:
+ return -1;
+ break;
+ }
+
+ return 128*numBlocks;
+}
+
+int Rijndael::padDecrypt(const UINT8 *input, int inputOctets, UINT8 *outBuffer)
+{
+ int i, numBlocks, padLen;
+ UINT8 block[16];
+ UINT32 iv[4];
+
+ if(m_state != Valid)return RIJNDAEL_NOT_INITIALIZED;
+ if(m_direction != Decrypt)return RIJNDAEL_BAD_DIRECTION;
+
+ if(input == 0 || inputOctets <= 0)return 0;
+
+ if((inputOctets % 16) != 0)return RIJNDAEL_CORRUPTED_DATA;
+
+ numBlocks = inputOctets/16;
+
+ switch(m_mode){
+ case ECB:
+ for (i = numBlocks - 1; i > 0; i--)
+ {
+ decrypt(input, outBuffer);
+ input += 16;
+ outBuffer += 16;
+ }
+
+ decrypt(input, block);
+ padLen = block[15];
+ if (padLen >= 16)return RIJNDAEL_CORRUPTED_DATA;
+ for(i = 16 - padLen; i < 16; i++)
+ {
+ if(block[i] != padLen)return RIJNDAEL_CORRUPTED_DATA;
+ }
+ kvi_memmove(outBuffer, block, 16 - padLen);
+ break;
+ case CBC:
+ kvi_memmove(iv, m_initVector, 16);
+ /* all blocks but last */
+ for (i = numBlocks - 1; i > 0; i--)
+ {
+ decrypt(input, block);
+ ((UINT32*)block)[0] ^= iv[0];
+ ((UINT32*)block)[1] ^= iv[1];
+ ((UINT32*)block)[2] ^= iv[2];
+ ((UINT32*)block)[3] ^= iv[3];
+ kvi_memmove(iv, input, 16);
+ kvi_memmove(outBuffer, block, 16);
+ input += 16;
+ outBuffer += 16;
+ }
+ /* last block */
+ decrypt(input, block);
+ ((UINT32*)block)[0] ^= iv[0];
+ ((UINT32*)block)[1] ^= iv[1];
+ ((UINT32*)block)[2] ^= iv[2];
+ ((UINT32*)block)[3] ^= iv[3];
+ padLen = block[15];
+ if(padLen <= 0 || padLen > 16)return RIJNDAEL_CORRUPTED_DATA;
+ for(i = 16 - padLen; i < 16; i++)
+ {
+ if(block[i] != padLen)return RIJNDAEL_CORRUPTED_DATA;
+ }
+ kvi_memmove(outBuffer, block, 16 - padLen);
+ break;
+
+ default:
+ return -1;
+ break;
+ }
+
+ return 16*numBlocks - padLen;
+}
+
+//////////////////////////////////////////////////////////////////////////////////////////////////////////////////
+// ALGORITHM
+//////////////////////////////////////////////////////////////////////////////////////////////////////////////////
+
+
+void Rijndael::keySched(UINT8 key[_MAX_KEY_COLUMNS][4])
+{
+ int j,rconpointer = 0;
+
+ // Calculate the necessary round keys
+ // The number of calculations depends on keyBits and blockBits
+ int uKeyColumns = m_uRounds - 6;
+
+ UINT8 tempKey[_MAX_KEY_COLUMNS][4];
+
+ // Copy the input key to the temporary key matrix
+
+ for(j = 0;j < uKeyColumns;j++)
+ {
+ *((UINT32*)(tempKey[j])) = *((UINT32*)(key[j]));
+ }
+
+ unsigned int r = 0;
+ int t = 0;
+
+ // copy values into round key array
+ for(j = 0;(j < uKeyColumns) && (r <= m_uRounds); )
+ {
+ for(;(j < uKeyColumns) && (t < 4); j++, t++)
+ {
+ *((UINT32*)m_expandedKey[r][t]) = *((UINT32*)tempKey[j]);
+ }
+
+
+ if(t == 4)
+ {
+ r++;
+ t = 0;
+ }
+ }
+
+ while(r <= m_uRounds)
+ {
+ tempKey[0][0] ^= S[tempKey[uKeyColumns-1][1]];
+ tempKey[0][1] ^= S[tempKey[uKeyColumns-1][2]];
+ tempKey[0][2] ^= S[tempKey[uKeyColumns-1][3]];
+ tempKey[0][3] ^= S[tempKey[uKeyColumns-1][0]];
+ tempKey[0][0] ^= rcon[rconpointer++];
+
+ if (uKeyColumns != 8)
+ {
+ for(j = 1; j < uKeyColumns; j++)
+ {
+ *((UINT32*)tempKey[j]) ^= *((UINT32*)tempKey[j-1]);
+ }
+ } else {
+ for(j = 1; j < uKeyColumns/2; j++)
+ {
+ *((UINT32*)tempKey[j]) ^= *((UINT32*)tempKey[j-1]);
+ }
+ tempKey[uKeyColumns/2][0] ^= S[tempKey[uKeyColumns/2 - 1][0]];
+ tempKey[uKeyColumns/2][1] ^= S[tempKey[uKeyColumns/2 - 1][1]];
+ tempKey[uKeyColumns/2][2] ^= S[tempKey[uKeyColumns/2 - 1][2]];
+ tempKey[uKeyColumns/2][3] ^= S[tempKey[uKeyColumns/2 - 1][3]];
+ for(j = uKeyColumns/2 + 1; j < uKeyColumns; j++)
+ {
+ *((UINT32*)tempKey[j]) ^= *((UINT32*)tempKey[j-1]);
+ }
+ }
+ for(j = 0; (j < uKeyColumns) && (r <= m_uRounds); )
+ {
+ for(; (j < uKeyColumns) && (t < 4); j++, t++)
+ {
+ *((UINT32*)m_expandedKey[r][t]) = *((UINT32*)tempKey[j]);
+ }
+ if(t == 4)
+ {
+ r++;
+ t = 0;
+ }
+ }
+ }
+}
+
+void Rijndael::keyEncToDec()
+{
+ UINT8 *w;
+
+ for(unsigned int r = 1; r < m_uRounds; r++)
+ {
+ w = m_expandedKey[r][0];
+ *((UINT32*)w) = *((UINT32*)U1[w[0]]) ^ *((UINT32*)U2[w[1]]) ^ *((UINT32*)U3[w[2]]) ^ *((UINT32*)U4[w[3]]);
+ w = m_expandedKey[r][1];
+ *((UINT32*)w) = *((UINT32*)U1[w[0]]) ^ *((UINT32*)U2[w[1]]) ^ *((UINT32*)U3[w[2]]) ^ *((UINT32*)U4[w[3]]);
+ w = m_expandedKey[r][2];
+ *((UINT32*)w) = *((UINT32*)U1[w[0]]) ^ *((UINT32*)U2[w[1]]) ^ *((UINT32*)U3[w[2]]) ^ *((UINT32*)U4[w[3]]);
+ w = m_expandedKey[r][3];
+ *((UINT32*)w) = *((UINT32*)U1[w[0]]) ^ *((UINT32*)U2[w[1]]) ^ *((UINT32*)U3[w[2]]) ^ *((UINT32*)U4[w[3]]);
+ }
+}
+
+void Rijndael::encrypt(const UINT8 a[16], UINT8 b[16])
+{
+ unsigned int r;
+ UINT8 temp[4][4];
+
+ *((UINT32*)temp[0]) = *((UINT32*)(a )) ^ *((UINT32*)m_expandedKey[0][0]);
+ *((UINT32*)temp[1]) = *((UINT32*)(a+ 4)) ^ *((UINT32*)m_expandedKey[0][1]);
+ *((UINT32*)temp[2]) = *((UINT32*)(a+ 8)) ^ *((UINT32*)m_expandedKey[0][2]);
+ *((UINT32*)temp[3]) = *((UINT32*)(a+12)) ^ *((UINT32*)m_expandedKey[0][3]);
+ *((UINT32*)(b )) = *((UINT32*)T1[temp[0][0]])
+ ^ *((UINT32*)T2[temp[1][1]])
+ ^ *((UINT32*)T3[temp[2][2]])
+ ^ *((UINT32*)T4[temp[3][3]]);
+ *((UINT32*)(b + 4)) = *((UINT32*)T1[temp[1][0]])
+ ^ *((UINT32*)T2[temp[2][1]])
+ ^ *((UINT32*)T3[temp[3][2]])
+ ^ *((UINT32*)T4[temp[0][3]]);
+ *((UINT32*)(b + 8)) = *((UINT32*)T1[temp[2][0]])
+ ^ *((UINT32*)T2[temp[3][1]])
+ ^ *((UINT32*)T3[temp[0][2]])
+ ^ *((UINT32*)T4[temp[1][3]]);
+ *((UINT32*)(b +12)) = *((UINT32*)T1[temp[3][0]])
+ ^ *((UINT32*)T2[temp[0][1]])
+ ^ *((UINT32*)T3[temp[1][2]])
+ ^ *((UINT32*)T4[temp[2][3]]);
+ for(r = 1; r < m_uRounds-1; r++)
+ {
+ *((UINT32*)temp[0]) = *((UINT32*)(b )) ^ *((UINT32*)m_expandedKey[r][0]);
+ *((UINT32*)temp[1]) = *((UINT32*)(b+ 4)) ^ *((UINT32*)m_expandedKey[r][1]);
+ *((UINT32*)temp[2]) = *((UINT32*)(b+ 8)) ^ *((UINT32*)m_expandedKey[r][2]);
+ *((UINT32*)temp[3]) = *((UINT32*)(b+12)) ^ *((UINT32*)m_expandedKey[r][3]);
+
+ *((UINT32*)(b )) = *((UINT32*)T1[temp[0][0]])
+ ^ *((UINT32*)T2[temp[1][1]])
+ ^ *((UINT32*)T3[temp[2][2]])
+ ^ *((UINT32*)T4[temp[3][3]]);
+ *((UINT32*)(b + 4)) = *((UINT32*)T1[temp[1][0]])
+ ^ *((UINT32*)T2[temp[2][1]])
+ ^ *((UINT32*)T3[temp[3][2]])
+ ^ *((UINT32*)T4[temp[0][3]]);
+ *((UINT32*)(b + 8)) = *((UINT32*)T1[temp[2][0]])
+ ^ *((UINT32*)T2[temp[3][1]])
+ ^ *((UINT32*)T3[temp[0][2]])
+ ^ *((UINT32*)T4[temp[1][3]]);
+ *((UINT32*)(b +12)) = *((UINT32*)T1[temp[3][0]])
+ ^ *((UINT32*)T2[temp[0][1]])
+ ^ *((UINT32*)T3[temp[1][2]])
+ ^ *((UINT32*)T4[temp[2][3]]);
+ }
+ *((UINT32*)temp[0]) = *((UINT32*)(b )) ^ *((UINT32*)m_expandedKey[m_uRounds-1][0]);
+ *((UINT32*)temp[1]) = *((UINT32*)(b+ 4)) ^ *((UINT32*)m_expandedKey[m_uRounds-1][1]);
+ *((UINT32*)temp[2]) = *((UINT32*)(b+ 8)) ^ *((UINT32*)m_expandedKey[m_uRounds-1][2]);
+ *((UINT32*)temp[3]) = *((UINT32*)(b+12)) ^ *((UINT32*)m_expandedKey[m_uRounds-1][3]);
+ b[ 0] = T1[temp[0][0]][1];
+ b[ 1] = T1[temp[1][1]][1];
+ b[ 2] = T1[temp[2][2]][1];
+ b[ 3] = T1[temp[3][3]][1];
+ b[ 4] = T1[temp[1][0]][1];
+ b[ 5] = T1[temp[2][1]][1];
+ b[ 6] = T1[temp[3][2]][1];
+ b[ 7] = T1[temp[0][3]][1];
+ b[ 8] = T1[temp[2][0]][1];
+ b[ 9] = T1[temp[3][1]][1];
+ b[10] = T1[temp[0][2]][1];
+ b[11] = T1[temp[1][3]][1];
+ b[12] = T1[temp[3][0]][1];
+ b[13] = T1[temp[0][1]][1];
+ b[14] = T1[temp[1][2]][1];
+ b[15] = T1[temp[2][3]][1];
+ *((UINT32*)(b )) ^= *((UINT32*)m_expandedKey[m_uRounds][0]);
+ *((UINT32*)(b+ 4)) ^= *((UINT32*)m_expandedKey[m_uRounds][1]);
+ *((UINT32*)(b+ 8)) ^= *((UINT32*)m_expandedKey[m_uRounds][2]);
+ *((UINT32*)(b+12)) ^= *((UINT32*)m_expandedKey[m_uRounds][3]);
+}
+
+void Rijndael::decrypt(const UINT8 a[16], UINT8 b[16])
+{
+ int r;
+ UINT8 temp[4][4];
+
+ *((UINT32*)temp[0]) = *((UINT32*)(a )) ^ *((UINT32*)m_expandedKey[m_uRounds][0]);
+ *((UINT32*)temp[1]) = *((UINT32*)(a+ 4)) ^ *((UINT32*)m_expandedKey[m_uRounds][1]);
+ *((UINT32*)temp[2]) = *((UINT32*)(a+ 8)) ^ *((UINT32*)m_expandedKey[m_uRounds][2]);
+ *((UINT32*)temp[3]) = *((UINT32*)(a+12)) ^ *((UINT32*)m_expandedKey[m_uRounds][3]);
+
+ *((UINT32*)(b )) = *((UINT32*)T5[temp[0][0]])
+ ^ *((UINT32*)T6[temp[3][1]])
+ ^ *((UINT32*)T7[temp[2][2]])
+ ^ *((UINT32*)T8[temp[1][3]]);
+ *((UINT32*)(b+ 4)) = *((UINT32*)T5[temp[1][0]])
+ ^ *((UINT32*)T6[temp[0][1]])
+ ^ *((UINT32*)T7[temp[3][2]])
+ ^ *((UINT32*)T8[temp[2][3]]);
+ *((UINT32*)(b+ 8)) = *((UINT32*)T5[temp[2][0]])
+ ^ *((UINT32*)T6[temp[1][1]])
+ ^ *((UINT32*)T7[temp[0][2]])
+ ^ *((UINT32*)T8[temp[3][3]]);
+ *((UINT32*)(b+12)) = *((UINT32*)T5[temp[3][0]])
+ ^ *((UINT32*)T6[temp[2][1]])
+ ^ *((UINT32*)T7[temp[1][2]])
+ ^ *((UINT32*)T8[temp[0][3]]);
+ for(r = m_uRounds-1; r > 1; r--)
+ {
+ *((UINT32*)temp[0]) = *((UINT32*)(b )) ^ *((UINT32*)m_expandedKey[r][0]);
+ *((UINT32*)temp[1]) = *((UINT32*)(b+ 4)) ^ *((UINT32*)m_expandedKey[r][1]);
+ *((UINT32*)temp[2]) = *((UINT32*)(b+ 8)) ^ *((UINT32*)m_expandedKey[r][2]);
+ *((UINT32*)temp[3]) = *((UINT32*)(b+12)) ^ *((UINT32*)m_expandedKey[r][3]);
+ *((UINT32*)(b )) = *((UINT32*)T5[temp[0][0]])
+ ^ *((UINT32*)T6[temp[3][1]])
+ ^ *((UINT32*)T7[temp[2][2]])
+ ^ *((UINT32*)T8[temp[1][3]]);
+ *((UINT32*)(b+ 4)) = *((UINT32*)T5[temp[1][0]])
+ ^ *((UINT32*)T6[temp[0][1]])
+ ^ *((UINT32*)T7[temp[3][2]])
+ ^ *((UINT32*)T8[temp[2][3]]);
+ *((UINT32*)(b+ 8)) = *((UINT32*)T5[temp[2][0]])
+ ^ *((UINT32*)T6[temp[1][1]])
+ ^ *((UINT32*)T7[temp[0][2]])
+ ^ *((UINT32*)T8[temp[3][3]]);
+ *((UINT32*)(b+12)) = *((UINT32*)T5[temp[3][0]])
+ ^ *((UINT32*)T6[temp[2][1]])
+ ^ *((UINT32*)T7[temp[1][2]])
+ ^ *((UINT32*)T8[temp[0][3]]);
+ }
+
+ *((UINT32*)temp[0]) = *((UINT32*)(b )) ^ *((UINT32*)m_expandedKey[1][0]);
+ *((UINT32*)temp[1]) = *((UINT32*)(b+ 4)) ^ *((UINT32*)m_expandedKey[1][1]);
+ *((UINT32*)temp[2]) = *((UINT32*)(b+ 8)) ^ *((UINT32*)m_expandedKey[1][2]);
+ *((UINT32*)temp[3]) = *((UINT32*)(b+12)) ^ *((UINT32*)m_expandedKey[1][3]);
+ b[ 0] = S5[temp[0][0]];
+ b[ 1] = S5[temp[3][1]];
+ b[ 2] = S5[temp[2][2]];
+ b[ 3] = S5[temp[1][3]];
+ b[ 4] = S5[temp[1][0]];
+ b[ 5] = S5[temp[0][1]];
+ b[ 6] = S5[temp[3][2]];
+ b[ 7] = S5[temp[2][3]];
+ b[ 8] = S5[temp[2][0]];
+ b[ 9] = S5[temp[1][1]];
+ b[10] = S5[temp[0][2]];
+ b[11] = S5[temp[3][3]];
+ b[12] = S5[temp[3][0]];
+ b[13] = S5[temp[2][1]];
+ b[14] = S5[temp[1][2]];
+ b[15] = S5[temp[0][3]];
+ *((UINT32*)(b )) ^= *((UINT32*)m_expandedKey[0][0]);
+ *((UINT32*)(b+ 4)) ^= *((UINT32*)m_expandedKey[0][1]);
+ *((UINT32*)(b+ 8)) ^= *((UINT32*)m_expandedKey[0][2]);
+ *((UINT32*)(b+12)) ^= *((UINT32*)m_expandedKey[0][3]);
+}
+
+#endif // COMPILE_CRYPT_SUPPORT
diff --git a/src/modules/rijndael/rijndael.h b/src/modules/rijndael/rijndael.h
new file mode 100644
index 00000000..e720df3e
--- /dev/null
+++ b/src/modules/rijndael/rijndael.h
@@ -0,0 +1,153 @@
+#ifndef _RIJNDAEL_H_
+#define _RIJNDAEL_H_
+
+//
+// File : rijndael.h
+// Creation date : Sun Nov 5 2000 15:42:14 CEST by Szymon Stefanek
+//
+// This file is part of the KVirc irc client distribution
+// Copyright (C) 1999-2000 Szymon Stefanek (pragma at kvirc dot net)
+//
+// This program is FREE software. You can redistribute it and/or
+// modify it under the terms of the GNU General Public License
+// as published by the Free Software Foundation; either version 2
+// of the License, or (at your opinion) any later version.
+//
+// This program is distributed in the HOPE that it will be USEFUL,
+// but WITHOUT ANY WARRANTY; without even the implied warranty of
+// MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.
+// See the GNU General Public License for more details.
+//
+// You should have received a copy of the GNU General Public License
+// along with this program. If not, write to the Free Software Foundation,
+// Inc. ,51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
+//
+
+//
+// Another implementation of the Rijndael cipher.
+// This is intended to be an easily usable library file.
+// Based on the Vincent Rijmen and K.U.Leuven implementation 2.4.
+//
+
+//
+// Original Copyright notice:
+//
+// rijndael-alg-fst.c v2.4 April '2000
+// rijndael-alg-fst.h
+// rijndael-api-fst.c
+// rijndael-api-fst.h
+//
+// Optimised ANSI C code
+//
+// authors: v1.0: Antoon Bosselaers
+// v2.0: Vincent Rijmen, K.U.Leuven
+// v2.3: Paulo Barreto
+// v2.4: Vincent Rijmen, K.U.Leuven
+//
+// This code is placed in the public domain.
+//
+
+//
+// This implementation works on 128 , 192 , 256 bit keys
+// and on 128 bit blocks
+//
+
+//
+// Example of usage:
+//
+// // Input data
+// unsigned char key[32]; // The key
+// initializeYour256BitKey(); // Obviously initialized with sth
+// const unsigned char * plainText = getYourPlainText(); // Your plain text
+// int plainTextLen = strlen(plainText); // Plain text length
+//
+// // Encrypting
+// Rijndael rin;
+// unsigned char output[plainTextLen + 16];
+//
+// rin.init(Rijndael::CBC,Rijndael::Encrypt,key,Rijndael::Key32Bytes);
+// // It is a good idea to check the error code
+// int len = rin.padEncrypt(plainText,len,output);
+// if(len >= 0)useYourEncryptedText();
+// else encryptError(len);
+//
+// // Decrypting: we can reuse the same object
+// unsigned char output2[len];
+// rin.init(Rijndael::ECB,Rijndael::Decrypt,keyMaterial,Rijndael::Key32Bytes));
+// len = rin.padDecrypt(output,len,output2);
+// if(len >= 0)useYourDecryptedText();
+// else decryptError(len);
+//
+
+#include "kvi_settings.h"
+
+#ifdef COMPILE_CRYPT_SUPPORT
+
+#define _MAX_KEY_COLUMNS (256/32)
+#define _MAX_ROUNDS 14
+//#define BITSPERBLOCK 128 /* Default number of bits in a cipher block */
+#define MAX_IV_SIZE 16
+
+// We assume that unsigned int is 32 bits long....
+typedef unsigned char UINT8;
+typedef unsigned int UINT32;
+typedef unsigned short UINT16;
+
+#define RIJNDAEL_SUCCESS 0
+#define RIJNDAEL_UNSUPPORTED_MODE -1
+#define RIJNDAEL_UNSUPPORTED_DIRECTION -2
+#define RIJNDAEL_UNSUPPORTED_KEY_LENGTH -3
+#define RIJNDAEL_BAD_KEY -4
+#define RIJNDAEL_NOT_INITIALIZED -5
+#define RIJNDAEL_BAD_DIRECTION -6
+#define RIJNDAEL_CORRUPTED_DATA -7
+
+class Rijndael
+{
+public:
+ enum Direction { Encrypt , Decrypt };
+ enum Mode { ECB , CBC , CFB1 };
+ enum KeyLength { Key16Bytes , Key24Bytes , Key32Bytes };
+
+ Rijndael();
+ ~Rijndael();
+protected:
+ enum State { Valid , Invalid };
+
+ State m_state;
+ Mode m_mode;
+ Direction m_direction;
+ UINT8 m_initVector[MAX_IV_SIZE];
+ UINT32 m_uRounds;
+ UINT8 m_expandedKey[_MAX_ROUNDS+1][4][4];
+public:
+ // Initializes the crypt session
+ // Returns RIJNDAEL_SUCCESS or an error code
+ int init(Mode mode,Direction dir,const UINT8 *key,KeyLength keyLen,UINT8 * initVector = 0);
+ // Input len is in BITS!
+ // Encrypts inputLen / 128 blocks of input and puts it in outBuffer
+ // outBuffer must be at least inputLen / 8 bytes long.
+ // Returns the encrypted buffer length in BITS or an error code < 0 in case of error
+ int blockEncrypt(const UINT8 *input, int inputLen, UINT8 *outBuffer);
+ // Input len is in BYTES!
+ // outBuffer must be at least inputLen + 16 bytes long
+ // Returns the encrypted buffer length in BYTES or an error code < 0 in case of error
+ int padEncrypt(const UINT8 *input, int inputOctets, UINT8 *outBuffer);
+ // Input len is in BITS!
+ // outBuffer must be at least inputLen / 8 bytes long
+ // Returns the decrypted buffer length in BITS and an error code < 0 in case of error
+ int blockDecrypt(const UINT8 *input, int inputLen, UINT8 *outBuffer);
+ // Input len is in BYTES!
+ // outBuffer must be at least inputLen bytes long
+ // Returns the decrypted buffer length in BYTES and an error code < 0 in case of error
+ int padDecrypt(const UINT8 *input, int inputOctets, UINT8 *outBuffer);
+protected:
+ void keySched(UINT8 key[_MAX_KEY_COLUMNS][4]);
+ void keyEncToDec();
+ void encrypt(const UINT8 a[16], UINT8 b[16]);
+ void decrypt(const UINT8 a[16], UINT8 b[16]);
+};
+
+#endif // COMPILE_CRYPT_SUPPORT
+
+#endif // _RIJNDAEL_H_