cf6fe609400dec5ca0973db6d342cb1188b62abe
[silc.git] / lib / silccrypt / blowfish.c
1 /*
2  * This implementation was taken from the International Kernel (kerneli)
3  * patch for Linux kernel. The author is unknown to me. This
4  * implementation is under the same license as it is in the kerneli patch.
5  * I've modified it a bit to fit to SILC. -Pekka
6  */
7 /*
8  * blowfish.c
9  *
10  * Permission is hereby granted, free of charge, to any person obtaining a
11  * copy of this software and associated documentation files (the
12  * "Software"), to deal in the Software without restriction, including
13  * without limitation the rights to use, copy, modify, merge, publish, dis-
14  * tribute, sublicense, and/or sell copies of the Software, and to permit
15  * persons to whom the Software is furnished to do so, subject to the fol-
16  * lowing conditions:
17  *
18  * The above copyright notice and this permission notice shall be included
19  * in all copies or substantial portions of the Software.
20  *
21  * THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS
22  * OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABIL-
23  * ITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.  IN NO EVENT
24  * SHALL THE OPEN GROUP BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABIL-
25  * ITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
26  * OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS
27  * IN THE SOFTWARE.
28  *
29  * Except as contained in this notice, the name of the authors shall
30  * not be used in advertising or otherwise to promote the sale, use or
31  * other dealings in this Software without prior written authorization from
32  * the authors.
33  *
34  */
35
36 #include "silcincludes.h"
37 #include "blowfish.h"
38
39 /* 
40  * SILC Crypto API for Blowfish
41  */
42
43 /* Sets the key for the cipher. */
44
45 SILC_CIPHER_API_SET_KEY(blowfish)
46 {
47   blowfish_set_key((BlowfishContext *)context, (unsigned char *)key, keylen);
48   return TRUE;
49 }
50
51 /* Sets the string as a new key for the cipher. The string is first
52    hashed and then used as a new key. */
53
54 SILC_CIPHER_API_SET_KEY_WITH_STRING(blowfish)
55 {
56   /*  unsigned char key[md5_hash_len];
57   SilcMarsContext *ctx = (SilcMarsContext *)context;
58
59   make_md5_hash(string, &key);
60   memcpy(&ctx->key, mars_set_key(&key, keylen), keylen);
61   memset(&key, 'F', sizeoof(key));
62   */
63
64   return 1;
65 }
66
67 /* Returns the size of the cipher context. */
68
69 SILC_CIPHER_API_CONTEXT_LEN(blowfish)
70 {
71   return sizeof(BlowfishContext);
72 }
73
74 /* Encrypts with the cipher in CBC mode. Source and destination buffers
75    maybe one and same. */
76
77 SILC_CIPHER_API_ENCRYPT_CBC(blowfish)
78 {
79   uint32 tiv[4];
80   int i;
81
82   SILC_CBC_GET_IV(tiv, iv);
83
84   SILC_CBC_ENC_PRE(tiv, src);
85   blowfish_encrypt((BlowfishContext *)context, tiv, tiv, 16);
86   SILC_CBC_ENC_POST(tiv, dst, src);
87
88   for (i = 16; i < len; i += 16) {
89     SILC_CBC_ENC_PRE(tiv, src);
90     blowfish_encrypt((BlowfishContext *)context, tiv, tiv, 16);
91     SILC_CBC_ENC_POST(tiv, dst, src);
92   }
93
94   SILC_CBC_PUT_IV(tiv, iv);
95
96   return TRUE;
97 }
98
99 /* Decrypts with the cipher in CBC mode. Source and destination buffers
100    maybe one and same. */
101
102 SILC_CIPHER_API_DECRYPT_CBC(blowfish)
103 {
104   uint32 tmp[4], tmp2[4], tiv[4];
105   int i;
106
107   SILC_CBC_GET_IV(tiv, iv);
108
109   SILC_CBC_DEC_PRE(tmp, src);
110   blowfish_decrypt((BlowfishContext *)context, tmp, tmp2, 16);
111   SILC_CBC_DEC_POST(tmp2, dst, src, tmp, tiv);
112
113   for (i = 16; i < len; i += 16) {
114     SILC_CBC_DEC_PRE(tmp, src);
115     blowfish_decrypt((BlowfishContext *)context, tmp, tmp2, 16);
116     SILC_CBC_DEC_POST(tmp2, dst, src, tmp, tiv);
117   }
118   
119   SILC_CBC_PUT_IV(tiv, iv);
120   
121   return TRUE;
122 }
123
124 static u32 bf_pbox[16 + 2] =
125 {
126     0x243f6a88, 0x85a308d3, 0x13198a2e, 0x03707344,
127     0xa4093822, 0x299f31d0, 0x082efa98, 0xec4e6c89,
128     0x452821e6, 0x38d01377, 0xbe5466cf, 0x34e90c6c,
129     0xc0ac29b7, 0xc97c50dd, 0x3f84d5b5, 0xb5470917,
130     0x9216d5d9, 0x8979fb1b,
131 };
132
133 static u32 bf_sbox[256 * 4] =
134 {
135     0xd1310ba6, 0x98dfb5ac, 0x2ffd72db, 0xd01adfb7,
136     0xb8e1afed, 0x6a267e96, 0xba7c9045, 0xf12c7f99,
137     0x24a19947, 0xb3916cf7, 0x0801f2e2, 0x858efc16,
138     0x636920d8, 0x71574e69, 0xa458fea3, 0xf4933d7e,
139     0x0d95748f, 0x728eb658, 0x718bcd58, 0x82154aee,
140     0x7b54a41d, 0xc25a59b5, 0x9c30d539, 0x2af26013,
141     0xc5d1b023, 0x286085f0, 0xca417918, 0xb8db38ef,
142     0x8e79dcb0, 0x603a180e, 0x6c9e0e8b, 0xb01e8a3e,
143     0xd71577c1, 0xbd314b27, 0x78af2fda, 0x55605c60,
144     0xe65525f3, 0xaa55ab94, 0x57489862, 0x63e81440,
145     0x55ca396a, 0x2aab10b6, 0xb4cc5c34, 0x1141e8ce,
146     0xa15486af, 0x7c72e993, 0xb3ee1411, 0x636fbc2a,
147     0x2ba9c55d, 0x741831f6, 0xce5c3e16, 0x9b87931e,
148     0xafd6ba33, 0x6c24cf5c, 0x7a325381, 0x28958677,
149     0x3b8f4898, 0x6b4bb9af, 0xc4bfe81b, 0x66282193,
150     0x61d809cc, 0xfb21a991, 0x487cac60, 0x5dec8032,
151     0xef845d5d, 0xe98575b1, 0xdc262302, 0xeb651b88,
152     0x23893e81, 0xd396acc5, 0x0f6d6ff3, 0x83f44239,
153     0x2e0b4482, 0xa4842004, 0x69c8f04a, 0x9e1f9b5e,
154     0x21c66842, 0xf6e96c9a, 0x670c9c61, 0xabd388f0,
155     0x6a51a0d2, 0xd8542f68, 0x960fa728, 0xab5133a3,
156     0x6eef0b6c, 0x137a3be4, 0xba3bf050, 0x7efb2a98,
157     0xa1f1651d, 0x39af0176, 0x66ca593e, 0x82430e88,
158     0x8cee8619, 0x456f9fb4, 0x7d84a5c3, 0x3b8b5ebe,
159     0xe06f75d8, 0x85c12073, 0x401a449f, 0x56c16aa6,
160     0x4ed3aa62, 0x363f7706, 0x1bfedf72, 0x429b023d,
161     0x37d0d724, 0xd00a1248, 0xdb0fead3, 0x49f1c09b,
162     0x075372c9, 0x80991b7b, 0x25d479d8, 0xf6e8def7,
163     0xe3fe501a, 0xb6794c3b, 0x976ce0bd, 0x04c006ba,
164     0xc1a94fb6, 0x409f60c4, 0x5e5c9ec2, 0x196a2463,
165     0x68fb6faf, 0x3e6c53b5, 0x1339b2eb, 0x3b52ec6f,
166     0x6dfc511f, 0x9b30952c, 0xcc814544, 0xaf5ebd09,
167     0xbee3d004, 0xde334afd, 0x660f2807, 0x192e4bb3,
168     0xc0cba857, 0x45c8740f, 0xd20b5f39, 0xb9d3fbdb,
169     0x5579c0bd, 0x1a60320a, 0xd6a100c6, 0x402c7279,
170     0x679f25fe, 0xfb1fa3cc, 0x8ea5e9f8, 0xdb3222f8,
171     0x3c7516df, 0xfd616b15, 0x2f501ec8, 0xad0552ab,
172     0x323db5fa, 0xfd238760, 0x53317b48, 0x3e00df82,
173     0x9e5c57bb, 0xca6f8ca0, 0x1a87562e, 0xdf1769db,
174     0xd542a8f6, 0x287effc3, 0xac6732c6, 0x8c4f5573,
175     0x695b27b0, 0xbbca58c8, 0xe1ffa35d, 0xb8f011a0,
176     0x10fa3d98, 0xfd2183b8, 0x4afcb56c, 0x2dd1d35b,
177     0x9a53e479, 0xb6f84565, 0xd28e49bc, 0x4bfb9790,
178     0xe1ddf2da, 0xa4cb7e33, 0x62fb1341, 0xcee4c6e8,
179     0xef20cada, 0x36774c01, 0xd07e9efe, 0x2bf11fb4,
180     0x95dbda4d, 0xae909198, 0xeaad8e71, 0x6b93d5a0,
181     0xd08ed1d0, 0xafc725e0, 0x8e3c5b2f, 0x8e7594b7,
182     0x8ff6e2fb, 0xf2122b64, 0x8888b812, 0x900df01c,
183     0x4fad5ea0, 0x688fc31c, 0xd1cff191, 0xb3a8c1ad,
184     0x2f2f2218, 0xbe0e1777, 0xea752dfe, 0x8b021fa1,
185     0xe5a0cc0f, 0xb56f74e8, 0x18acf3d6, 0xce89e299,
186     0xb4a84fe0, 0xfd13e0b7, 0x7cc43b81, 0xd2ada8d9,
187     0x165fa266, 0x80957705, 0x93cc7314, 0x211a1477,
188     0xe6ad2065, 0x77b5fa86, 0xc75442f5, 0xfb9d35cf,
189     0xebcdaf0c, 0x7b3e89a0, 0xd6411bd3, 0xae1e7e49,
190     0x00250e2d, 0x2071b35e, 0x226800bb, 0x57b8e0af,
191     0x2464369b, 0xf009b91e, 0x5563911d, 0x59dfa6aa,
192     0x78c14389, 0xd95a537f, 0x207d5ba2, 0x02e5b9c5,
193     0x83260376, 0x6295cfa9, 0x11c81968, 0x4e734a41,
194     0xb3472dca, 0x7b14a94a, 0x1b510052, 0x9a532915,
195     0xd60f573f, 0xbc9bc6e4, 0x2b60a476, 0x81e67400,
196     0x08ba6fb5, 0x571be91f, 0xf296ec6b, 0x2a0dd915,
197     0xb6636521, 0xe7b9f9b6, 0xff34052e, 0xc5855664,
198     0x53b02d5d, 0xa99f8fa1, 0x08ba4799, 0x6e85076a,
199     0x4b7a70e9, 0xb5b32944, 0xdb75092e, 0xc4192623,
200     0xad6ea6b0, 0x49a7df7d, 0x9cee60b8, 0x8fedb266,
201     0xecaa8c71, 0x699a17ff, 0x5664526c, 0xc2b19ee1,
202     0x193602a5, 0x75094c29, 0xa0591340, 0xe4183a3e,
203     0x3f54989a, 0x5b429d65, 0x6b8fe4d6, 0x99f73fd6,
204     0xa1d29c07, 0xefe830f5, 0x4d2d38e6, 0xf0255dc1,
205     0x4cdd2086, 0x8470eb26, 0x6382e9c6, 0x021ecc5e,
206     0x09686b3f, 0x3ebaefc9, 0x3c971814, 0x6b6a70a1,
207     0x687f3584, 0x52a0e286, 0xb79c5305, 0xaa500737,
208     0x3e07841c, 0x7fdeae5c, 0x8e7d44ec, 0x5716f2b8,
209     0xb03ada37, 0xf0500c0d, 0xf01c1f04, 0x0200b3ff,
210     0xae0cf51a, 0x3cb574b2, 0x25837a58, 0xdc0921bd,
211     0xd19113f9, 0x7ca92ff6, 0x94324773, 0x22f54701,
212     0x3ae5e581, 0x37c2dadc, 0xc8b57634, 0x9af3dda7,
213     0xa9446146, 0x0fd0030e, 0xecc8c73e, 0xa4751e41,
214     0xe238cd99, 0x3bea0e2f, 0x3280bba1, 0x183eb331,
215     0x4e548b38, 0x4f6db908, 0x6f420d03, 0xf60a04bf,
216     0x2cb81290, 0x24977c79, 0x5679b072, 0xbcaf89af,
217     0xde9a771f, 0xd9930810, 0xb38bae12, 0xdccf3f2e,
218     0x5512721f, 0x2e6b7124, 0x501adde6, 0x9f84cd87,
219     0x7a584718, 0x7408da17, 0xbc9f9abc, 0xe94b7d8c,
220     0xec7aec3a, 0xdb851dfa, 0x63094366, 0xc464c3d2,
221     0xef1c1847, 0x3215d908, 0xdd433b37, 0x24c2ba16,
222     0x12a14d43, 0x2a65c451, 0x50940002, 0x133ae4dd,
223     0x71dff89e, 0x10314e55, 0x81ac77d6, 0x5f11199b,
224     0x043556f1, 0xd7a3c76b, 0x3c11183b, 0x5924a509,
225     0xf28fe6ed, 0x97f1fbfa, 0x9ebabf2c, 0x1e153c6e,
226     0x86e34570, 0xeae96fb1, 0x860e5e0a, 0x5a3e2ab3,
227     0x771fe71c, 0x4e3d06fa, 0x2965dcb9, 0x99e71d0f,
228     0x803e89d6, 0x5266c825, 0x2e4cc978, 0x9c10b36a,
229     0xc6150eba, 0x94e2ea78, 0xa5fc3c53, 0x1e0a2df4,
230     0xf2f74ea7, 0x361d2b3d, 0x1939260f, 0x19c27960,
231     0x5223a708, 0xf71312b6, 0xebadfe6e, 0xeac31f66,
232     0xe3bc4595, 0xa67bc883, 0xb17f37d1, 0x018cff28,
233     0xc332ddef, 0xbe6c5aa5, 0x65582185, 0x68ab9802,
234     0xeecea50f, 0xdb2f953b, 0x2aef7dad, 0x5b6e2f84,
235     0x1521b628, 0x29076170, 0xecdd4775, 0x619f1510,
236     0x13cca830, 0xeb61bd96, 0x0334fe1e, 0xaa0363cf,
237     0xb5735c90, 0x4c70a239, 0xd59e9e0b, 0xcbaade14,
238     0xeecc86bc, 0x60622ca7, 0x9cab5cab, 0xb2f3846e,
239     0x648b1eaf, 0x19bdf0ca, 0xa02369b9, 0x655abb50,
240     0x40685a32, 0x3c2ab4b3, 0x319ee9d5, 0xc021b8f7,
241     0x9b540b19, 0x875fa099, 0x95f7997e, 0x623d7da8,
242     0xf837889a, 0x97e32d77, 0x11ed935f, 0x16681281,
243     0x0e358829, 0xc7e61fd6, 0x96dedfa1, 0x7858ba99,
244     0x57f584a5, 0x1b227263, 0x9b83c3ff, 0x1ac24696,
245     0xcdb30aeb, 0x532e3054, 0x8fd948e4, 0x6dbc3128,
246     0x58ebf2ef, 0x34c6ffea, 0xfe28ed61, 0xee7c3c73,
247     0x5d4a14d9, 0xe864b7e3, 0x42105d14, 0x203e13e0,
248     0x45eee2b6, 0xa3aaabea, 0xdb6c4f15, 0xfacb4fd0,
249     0xc742f442, 0xef6abbb5, 0x654f3b1d, 0x41cd2105,
250     0xd81e799e, 0x86854dc7, 0xe44b476a, 0x3d816250,
251     0xcf62a1f2, 0x5b8d2646, 0xfc8883a0, 0xc1c7b6a3,
252     0x7f1524c3, 0x69cb7492, 0x47848a0b, 0x5692b285,
253     0x095bbf00, 0xad19489d, 0x1462b174, 0x23820e00,
254     0x58428d2a, 0x0c55f5ea, 0x1dadf43e, 0x233f7061,
255     0x3372f092, 0x8d937e41, 0xd65fecf1, 0x6c223bdb,
256     0x7cde3759, 0xcbee7460, 0x4085f2a7, 0xce77326e,
257     0xa6078084, 0x19f8509e, 0xe8efd855, 0x61d99735,
258     0xa969a7aa, 0xc50c06c2, 0x5a04abfc, 0x800bcadc,
259     0x9e447a2e, 0xc3453484, 0xfdd56705, 0x0e1e9ec9,
260     0xdb73dbd3, 0x105588cd, 0x675fda79, 0xe3674340,
261     0xc5c43465, 0x713e38d8, 0x3d28f89e, 0xf16dff20,
262     0x153e21e7, 0x8fb03d4a, 0xe6e39f2b, 0xdb83adf7,
263     0xe93d5a68, 0x948140f7, 0xf64c261c, 0x94692934,
264     0x411520f7, 0x7602d4f7, 0xbcf46b2e, 0xd4a20068,
265     0xd4082471, 0x3320f46a, 0x43b7d4b7, 0x500061af,
266     0x1e39f62e, 0x97244546, 0x14214f74, 0xbf8b8840,
267     0x4d95fc1d, 0x96b591af, 0x70f4ddd3, 0x66a02f45,
268     0xbfbc09ec, 0x03bd9785, 0x7fac6dd0, 0x31cb8504,
269     0x96eb27b3, 0x55fd3941, 0xda2547e6, 0xabca0a9a,
270     0x28507825, 0x530429f4, 0x0a2c86da, 0xe9b66dfb,
271     0x68dc1462, 0xd7486900, 0x680ec0a4, 0x27a18dee,
272     0x4f3ffea2, 0xe887ad8c, 0xb58ce006, 0x7af4d6b6,
273     0xaace1e7c, 0xd3375fec, 0xce78a399, 0x406b2a42,
274     0x20fe9e35, 0xd9f385b9, 0xee39d7ab, 0x3b124e8b,
275     0x1dc9faf7, 0x4b6d1856, 0x26a36631, 0xeae397b2,
276     0x3a6efa74, 0xdd5b4332, 0x6841e7f7, 0xca7820fb,
277     0xfb0af54e, 0xd8feb397, 0x454056ac, 0xba489527,
278     0x55533a3a, 0x20838d87, 0xfe6ba9b7, 0xd096954b,
279     0x55a867bc, 0xa1159a58, 0xcca92963, 0x99e1db33,
280     0xa62a4a56, 0x3f3125f9, 0x5ef47e1c, 0x9029317c,
281     0xfdf8e802, 0x04272f70, 0x80bb155c, 0x05282ce3,
282     0x95c11548, 0xe4c66d22, 0x48c1133f, 0xc70f86dc,
283     0x07f9c9ee, 0x41041f0f, 0x404779a4, 0x5d886e17,
284     0x325f51eb, 0xd59bc0d1, 0xf2bcc18f, 0x41113564,
285     0x257b7834, 0x602a9c60, 0xdff8e8a3, 0x1f636c1b,
286     0x0e12b4c2, 0x02e1329e, 0xaf664fd1, 0xcad18115,
287     0x6b2395e0, 0x333e92e1, 0x3b240b62, 0xeebeb922,
288     0x85b2a20e, 0xe6ba0d99, 0xde720c8c, 0x2da2f728,
289     0xd0127845, 0x95b794fd, 0x647d0862, 0xe7ccf5f0,
290     0x5449a36f, 0x877d48fa, 0xc39dfd27, 0xf33e8d1e,
291     0x0a476341, 0x992eff74, 0x3a6f6eab, 0xf4f8fd37,
292     0xa812dc60, 0xa1ebddf8, 0x991be14c, 0xdb6e6b0d,
293     0xc67b5510, 0x6d672c37, 0x2765d43b, 0xdcd0e804,
294     0xf1290dc7, 0xcc00ffa3, 0xb5390f92, 0x690fed0b,
295     0x667b9ffb, 0xcedb7d9c, 0xa091cf0b, 0xd9155ea3,
296     0xbb132f88, 0x515bad24, 0x7b9479bf, 0x763bd6eb,
297     0x37392eb3, 0xcc115979, 0x8026e297, 0xf42e312d,
298     0x6842ada7, 0xc66a2b3b, 0x12754ccc, 0x782ef11c,
299     0x6a124237, 0xb79251e7, 0x06a1bbe6, 0x4bfb6350,
300     0x1a6b1018, 0x11caedfa, 0x3d25bdd8, 0xe2e1c3c9,
301     0x44421659, 0x0a121386, 0xd90cec6e, 0xd5abea2a,
302     0x64af674e, 0xda86a85f, 0xbebfe988, 0x64e4c3fe,
303     0x9dbc8057, 0xf0f7c086, 0x60787bf8, 0x6003604d,
304     0xd1fd8346, 0xf6381fb0, 0x7745ae04, 0xd736fccc,
305     0x83426b33, 0xf01eab71, 0xb0804187, 0x3c005e5f,
306     0x77a057be, 0xbde8ae24, 0x55464299, 0xbf582e61,
307     0x4e58f48f, 0xf2ddfda2, 0xf474ef38, 0x8789bdc2,
308     0x5366f9c3, 0xc8b38e74, 0xb475f255, 0x46fcd9b9,
309     0x7aeb2661, 0x8b1ddf84, 0x846a0e79, 0x915f95e2,
310     0x466e598e, 0x20b45770, 0x8cd55591, 0xc902de4c,
311     0xb90bace1, 0xbb8205d0, 0x11a86248, 0x7574a99e,
312     0xb77f19b6, 0xe0a9dc09, 0x662d09a1, 0xc4324633,
313     0xe85a1f02, 0x09f0be8c, 0x4a99a025, 0x1d6efe10,
314     0x1ab93d1d, 0x0ba5a4df, 0xa186f20f, 0x2868f169,
315     0xdcb7da83, 0x573906fe, 0xa1e2ce9b, 0x4fcd7f52,
316     0x50115e01, 0xa70683fa, 0xa002b5c4, 0x0de6d027,
317     0x9af88c27, 0x773f8641, 0xc3604c06, 0x61a806b5,
318     0xf0177a28, 0xc0f586e0, 0x006058aa, 0x30dc7d62,
319     0x11e69ed7, 0x2338ea63, 0x53c2dd94, 0xc2c21634,
320     0xbbcbee56, 0x90bcb6de, 0xebfc7da1, 0xce591d76,
321     0x6f05e409, 0x4b7c0188, 0x39720a3d, 0x7c927c24,
322     0x86e3725f, 0x724d9db9, 0x1ac15bb4, 0xd39eb8fc,
323     0xed545578, 0x08fca5b5, 0xd83d7cd3, 0x4dad0fc4,
324     0x1e50ef5e, 0xb161e6f8, 0xa28514d9, 0x6c51133c,
325     0x6fd5c7e7, 0x56e14ec4, 0x362abfce, 0xddc6c837,
326     0xd79a3234, 0x92638212, 0x670efa8e, 0x406000e0,
327     0x3a39ce37, 0xd3faf5cf, 0xabc27737, 0x5ac52d1b,
328     0x5cb0679e, 0x4fa33742, 0xd3822740, 0x99bc9bbe,
329     0xd5118e9d, 0xbf0f7315, 0xd62d1c7e, 0xc700c47b,
330     0xb78c1b6b, 0x21a19045, 0xb26eb1be, 0x6a366eb4,
331     0x5748ab2f, 0xbc946e79, 0xc6a376d2, 0x6549c2c8,
332     0x530ff8ee, 0x468dde7d, 0xd5730a1d, 0x4cd04dc6,
333     0x2939bbdb, 0xa9ba4650, 0xac9526e8, 0xbe5ee304,
334     0xa1fad5f0, 0x6a2d519a, 0x63ef8ce2, 0x9a86ee22,
335     0xc089c2b8, 0x43242ef6, 0xa51e03aa, 0x9cf2d0a4,
336     0x83c061ba, 0x9be96a4d, 0x8fe51550, 0xba645bd6,
337     0x2826a2f9, 0xa73a3ae1, 0x4ba99586, 0xef5562e9,
338     0xc72fefd3, 0xf752f7da, 0x3f046f69, 0x77fa0a59,
339     0x80e4a915, 0x87b08601, 0x9b09e6ad, 0x3b3ee593,
340     0xe990fd5a, 0x9e34d797, 0x2cf0b7d9, 0x022b8b51,
341     0x96d5ac3a, 0x017da67d, 0xd1cf3ed6, 0x7c7d2d28,
342     0x1f9f25cf, 0xadf2b89b, 0x5ad6b472, 0x5a88f54c,
343     0xe029ac71, 0xe019a5e6, 0x47b0acfd, 0xed93fa9b,
344     0xe8d3c48d, 0x283b57cc, 0xf8d56629, 0x79132e28,
345     0x785f0191, 0xed756055, 0xf7960e44, 0xe3d35e8c,
346     0x15056dd4, 0x88f46dba, 0x03a16125, 0x0564f0bd,
347     0xc3eb9e15, 0x3c9057a2, 0x97271aec, 0xa93a072a,
348     0x1b3f6d9b, 0x1e6321f5, 0xf59c66fb, 0x26dcf319,
349     0x7533d928, 0xb155fdf5, 0x03563482, 0x8aba3cbb,
350     0x28517711, 0xc20ad9f8, 0xabcc5167, 0xccad925f,
351     0x4de81751, 0x3830dc8e, 0x379d5862, 0x9320f991,
352     0xea7a90c2, 0xfb3e7bce, 0x5121ce64, 0x774fbe32,
353     0xa8b6e37e, 0xc3293d46, 0x48de5369, 0x6413e680,
354     0xa2ae0810, 0xdd6db224, 0x69852dfd, 0x09072166,
355     0xb39a460a, 0x6445c0dd, 0x586cdecf, 0x1c20c8ae,
356     0x5bbef7dd, 0x1b588d40, 0xccd2017f, 0x6bb4e3bb,
357     0xdda26a7e, 0x3a59ff45, 0x3e350a44, 0xbcb4cdd5,
358     0x72eacea8, 0xfa6484bb, 0x8d6612ae, 0xbf3c6f47,
359     0xd29be463, 0x542f5d9e, 0xaec2771b, 0xf64e6370,
360     0x740e0d8d, 0xe75b1357, 0xf8721671, 0xaf537d5d,
361     0x4040cb08, 0x4eb4e2cc, 0x34d2466a, 0x0115af84,
362     0xe1b00428, 0x95983a1d, 0x06b89fb4, 0xce6ea048,
363     0x6f3f3b82, 0x3520ab82, 0x011a1d4b, 0x277227f8,
364     0x611560b1, 0xe7933fdc, 0xbb3a792b, 0x344525bd,
365     0xa08839e1, 0x51ce794b, 0x2f32c9b7, 0xa01fbac9,
366     0xe01cc87e, 0xbcc7d1f6, 0xcf0111c3, 0xa1e8aac7,
367     0x1a908749, 0xd44fbd9a, 0xd0dadecb, 0xd50ada38,
368     0x0339c32a, 0xc6913667, 0x8df9317c, 0xe0b12b4f,
369     0xf79e59b7, 0x43f5bb3a, 0xf2d519ff, 0x27d9459c,
370     0xbf97222c, 0x15e6fc2a, 0x0f91fc71, 0x9b941525,
371     0xfae59361, 0xceb69ceb, 0xc2a86459, 0x12baa8d1,
372     0xb6c1075e, 0xe3056a0c, 0x10d25065, 0xcb03a442,
373     0xe0ec6e0e, 0x1698db3b, 0x4c98a0be, 0x3278e964,
374     0x9f1f9532, 0xe0d392df, 0xd3a0342b, 0x8971f21e,
375     0x1b0a7441, 0x4ba3348c, 0xc5be7120, 0xc37632d8,
376     0xdf359f8d, 0x9b992f2e, 0xe60b6f47, 0x0fe3f11d,
377     0xe54cda54, 0x1edad891, 0xce6279cf, 0xcd3e7e6f,
378     0x1618b166, 0xfd2c1d05, 0x848fd2c5, 0xf6fb2299,
379     0xf523f357, 0xa6327623, 0x93a83531, 0x56cccd02,
380     0xacf08162, 0x5a75ebb5, 0x6e163697, 0x88d273cc,
381     0xde966292, 0x81b949d0, 0x4c50901b, 0x71c65614,
382     0xe6c6c7bd, 0x327a140a, 0x45e1d006, 0xc3f27b9a,
383     0xc9aa53fd, 0x62a80f00, 0xbb25bfe2, 0x35bdd2f6,
384     0x71126905, 0xb2040222, 0xb6cbcf7c, 0xcd769c2b,
385     0x53113ec0, 0x1640e3d3, 0x38abbd60, 0x2547adf0,
386     0xba38209c, 0xf746ce76, 0x77afa1c5, 0x20756060,
387     0x85cbfe4e, 0x8ae88dd8, 0x7aaaf9b0, 0x4cf9aa7e,
388     0x1948c25c, 0x02fb8a8c, 0x01c36ae4, 0xd6ebe1f9,
389     0x90d4f869, 0xa65cdea0, 0x3f09252d, 0xc208e69f,
390     0xb74e6132, 0xce77e25b, 0x578fdfe3, 0x3ac372e6,
391 };
392
393 /* 
394  * Round loop unrolling macros, S is a pointer to a S-Box array
395  * organized in 4 uint32s at a row.
396  */
397
398 #define GET32_3(x) (((x) & 0xff))
399 #define GET32_2(x) (((x) >> (8)) & (0xff))
400 #define GET32_1(x) (((x) >> (16)) & (0xff))
401 #define GET32_0(x) (((x) >> (24)) & (0xff))
402
403 #define bf_F(x) (((S[GET32_0(x)] + S[256 + GET32_1(x)]) ^ \
404           S[512 + GET32_2(x)]) + S[768 + GET32_3(x)])
405
406 #define ROUND(a, b, n) b^=P[n];a ^= bf_F(b)
407
408 /*
409  * The blowfish encipher, processes 64-bit blocks.
410  * NOTE: This function MUSTN'T respect endianess 
411  */
412
413 int blowfish_encrypt(BlowfishContext *ctx,
414                      u32 *in_blk, u32 *out_blk, int size)
415 {
416     u32 yl,yr;
417
418     u32 *P = ctx->P;
419     u32 *S = ctx->S;
420
421     for (; size >= 8; size -= 8) {
422         yl = *(in_blk++);
423         yr = *(in_blk++);
424
425         ROUND(yr, yl, 0);
426         ROUND(yl, yr, 1);
427         ROUND(yr, yl, 2);
428         ROUND(yl, yr, 3);
429         ROUND(yr, yl, 4);
430         ROUND(yl, yr, 5);
431         ROUND(yr, yl, 6);
432         ROUND(yl, yr, 7);
433         ROUND(yr, yl, 8);
434         ROUND(yl, yr, 9);
435         ROUND(yr, yl, 10);
436         ROUND(yl, yr, 11);
437         ROUND(yr, yl, 12);
438         ROUND(yl, yr, 13);
439         ROUND(yr, yl, 14);
440         ROUND(yl, yr, 15);
441
442         /* yl and yr are switched */
443         yl ^= P[16];
444         yr ^= P[17];
445
446         *(out_blk++) = yr;
447         *(out_blk++) = yl;
448     }
449
450     return 0;
451 }
452
453 int blowfish_decrypt(BlowfishContext *ctx,
454                      u32 *in_blk, u32 *out_blk, int size)
455 {
456     u32 yl,yr;
457
458     u32 *P = ctx->P;
459     u32 *S = ctx->S;
460
461     for (; size >= 8; size -= 8) {
462         yl = *(in_blk++);
463         yr = *(in_blk++);
464
465         ROUND(yr, yl, 17);
466         ROUND(yl, yr, 16);
467         ROUND(yr, yl, 15);
468         ROUND(yl, yr, 14);
469         ROUND(yr, yl, 13);
470         ROUND(yl, yr, 12);
471         ROUND(yr, yl, 11);
472         ROUND(yl, yr, 10);
473         ROUND(yr, yl, 9);
474         ROUND(yl, yr, 8);
475         ROUND(yr, yl, 7);
476         ROUND(yl, yr, 6);
477         ROUND(yr, yl, 5);
478         ROUND(yl, yr, 4);
479         ROUND(yr, yl, 3);
480         ROUND(yl, yr, 2);
481
482         /* yl and yr are switched */
483         yl ^= P[1];
484         yr ^= P[0];
485
486         *(out_blk++) = yr;
487         *(out_blk++) = yl;
488     }
489
490     return 0;
491 }
492
493 /* Sets the blowfish S and P boxes for encryption and decryption. */
494
495 int blowfish_set_key(BlowfishContext *ctx,
496                      unsigned char *key, int keybytes)
497 {
498     short i;
499     short j;
500     short count;
501     u32 data[2];
502     u32 temp;
503     u32 *P = ctx->P;
504     u32 *S = ctx->S;
505
506     /* Copy the initialization s-boxes */
507
508     for (i = 0, count = 0; i < 256; i++)
509         for (j = 0; j < 4; j++, count++)
510             S[count] = bf_sbox[count];
511
512     /* Set the p-boxes */
513
514     for (i = 0; i < 16 + 2; i++)
515         P[i] = bf_pbox[i];
516
517     /* Actual subkey generation */
518
519     for (j = 0, i = 0; i < 16 + 2; i++)
520     {
521         temp = (((u32) key[j] << 24) |
522                 ((u32) key[(j + 1) % keybytes] << 16) |
523                 ((u32) key[(j + 2) % keybytes] << 8) |
524                 ((u32) key[(j + 3) % keybytes] ));
525
526         P[i] = P[i] ^ temp;
527         j = (j + 4) % keybytes;
528     }
529
530     data[0] = 0x00000000;
531     data[1] = 0x00000000;
532
533     for (i = 0; i < 16 + 2; i += 2)
534     {
535         blowfish_encrypt(ctx, data, data, 8);
536         
537         P[i] = data[0];
538         P[i + 1] = data[1];
539     }
540
541     for (i = 0; i < 4; i++)
542     {
543         for (j = 0, count = i * 256; j < 256; j += 2, count += 2)
544         {
545             blowfish_encrypt(ctx, data, data, 8);
546
547             S[count] = data[0];
548             S[count + 1] = data[1];
549         }
550     }
551     return 0;
552 }