1 /*	$OpenBSD: blf.c,v 1.7 2007/11/26 09:28:34 martynas Exp $	*/
2 
3 /*
4  * Blowfish block cipher for OpenBSD
5  * Copyright 1997 Niels Provos <provos@physnet.uni-hamburg.de>
6  * All rights reserved.
7  *
8  * Implementation advice by David Mazieres <dm@lcs.mit.edu>.
9  *
10  * Redistribution and use in source and binary forms, with or without
11  * modification, are permitted provided that the following conditions
12  * are met:
13  * 1. Redistributions of source code must retain the above copyright
14  *    notice, this list of conditions and the following disclaimer.
15  * 2. Redistributions in binary form must reproduce the above copyright
16  *    notice, this list of conditions and the following disclaimer in the
17  *    documentation and/or other materials provided with the distribution.
18  * 3. All advertising materials mentioning features or use of this software
19  *    must display the following acknowledgement:
20  *      This product includes software developed by Niels Provos.
21  * 4. The name of the author may not be used to endorse or promote products
22  *    derived from this software without specific prior written permission.
23  *
24  * THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
25  * IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
26  * OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
27  * IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
28  * INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
29  * NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
30  * DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
31  * THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
32  * (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
33  * THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
34  */
35 
36 /*
37  * This code is derived from section 14.3 and the given source
38  * in section V of Applied Cryptography, second edition.
39  * Blowfish is an unpatented fast block cipher designed by
40  * Bruce Schneier.
41  */
42 
43 #include <sys/param.h>
44 
45 #include "blf.h"
46 
47 #undef inline
48 #ifdef __GNUC__
49 #define inline __inline
50 #else				/* !__GNUC__ */
51 #define inline
52 #endif				/* !__GNUC__ */
53 
54 /* Function for Feistel Networks */
55 
56 #define F(s, x) ((((s)[        (((x)>>24)&0xFF)]  \
57 		 + (s)[0x100 + (((x)>>16)&0xFF)]) \
58 		 ^ (s)[0x200 + (((x)>> 8)&0xFF)]) \
59 		 + (s)[0x300 + ( (x)     &0xFF)])
60 
61 #define BLFRND(s,p,i,j,n) (i ^= F(s,j) ^ (p)[n])
62 
63 void
Blowfish_encipher(blf_ctx * c,u_int32_t * x)64 Blowfish_encipher(blf_ctx *c, u_int32_t *x)
65 {
66 	u_int32_t Xl;
67 	u_int32_t Xr;
68 	u_int32_t *s = c->S[0];
69 	u_int32_t *p = c->P;
70 
71 	Xl = x[0];
72 	Xr = x[1];
73 
74 	Xl ^= p[0];
75 	BLFRND(s, p, Xr, Xl, 1); BLFRND(s, p, Xl, Xr, 2);
76 	BLFRND(s, p, Xr, Xl, 3); BLFRND(s, p, Xl, Xr, 4);
77 	BLFRND(s, p, Xr, Xl, 5); BLFRND(s, p, Xl, Xr, 6);
78 	BLFRND(s, p, Xr, Xl, 7); BLFRND(s, p, Xl, Xr, 8);
79 	BLFRND(s, p, Xr, Xl, 9); BLFRND(s, p, Xl, Xr, 10);
80 	BLFRND(s, p, Xr, Xl, 11); BLFRND(s, p, Xl, Xr, 12);
81 	BLFRND(s, p, Xr, Xl, 13); BLFRND(s, p, Xl, Xr, 14);
82 	BLFRND(s, p, Xr, Xl, 15); BLFRND(s, p, Xl, Xr, 16);
83 
84 	x[0] = Xr ^ p[17];
85 	x[1] = Xl;
86 }
87 
88 void
Blowfish_decipher(blf_ctx * c,u_int32_t * x)89 Blowfish_decipher(blf_ctx *c, u_int32_t *x)
90 {
91 	u_int32_t Xl;
92 	u_int32_t Xr;
93 	u_int32_t *s = c->S[0];
94 	u_int32_t *p = c->P;
95 
96 	Xl = x[0];
97 	Xr = x[1];
98 
99 	Xl ^= p[17];
100 	BLFRND(s, p, Xr, Xl, 16); BLFRND(s, p, Xl, Xr, 15);
101 	BLFRND(s, p, Xr, Xl, 14); BLFRND(s, p, Xl, Xr, 13);
102 	BLFRND(s, p, Xr, Xl, 12); BLFRND(s, p, Xl, Xr, 11);
103 	BLFRND(s, p, Xr, Xl, 10); BLFRND(s, p, Xl, Xr, 9);
104 	BLFRND(s, p, Xr, Xl, 8); BLFRND(s, p, Xl, Xr, 7);
105 	BLFRND(s, p, Xr, Xl, 6); BLFRND(s, p, Xl, Xr, 5);
106 	BLFRND(s, p, Xr, Xl, 4); BLFRND(s, p, Xl, Xr, 3);
107 	BLFRND(s, p, Xr, Xl, 2); BLFRND(s, p, Xl, Xr, 1);
108 
109 	x[0] = Xr ^ p[0];
110 	x[1] = Xl;
111 }
112 
113 void
Blowfish_initstate(blf_ctx * c)114 Blowfish_initstate(blf_ctx *c)
115 {
116 	/* P-box and S-box tables initialized with digits of Pi */
117 
118 	static const blf_ctx initstate =
119 
120 	{ {
121 		{
122 			0xd1310ba6, 0x98dfb5ac, 0x2ffd72db, 0xd01adfb7,
123 			0xb8e1afed, 0x6a267e96, 0xba7c9045, 0xf12c7f99,
124 			0x24a19947, 0xb3916cf7, 0x0801f2e2, 0x858efc16,
125 			0x636920d8, 0x71574e69, 0xa458fea3, 0xf4933d7e,
126 			0x0d95748f, 0x728eb658, 0x718bcd58, 0x82154aee,
127 			0x7b54a41d, 0xc25a59b5, 0x9c30d539, 0x2af26013,
128 			0xc5d1b023, 0x286085f0, 0xca417918, 0xb8db38ef,
129 			0x8e79dcb0, 0x603a180e, 0x6c9e0e8b, 0xb01e8a3e,
130 			0xd71577c1, 0xbd314b27, 0x78af2fda, 0x55605c60,
131 			0xe65525f3, 0xaa55ab94, 0x57489862, 0x63e81440,
132 			0x55ca396a, 0x2aab10b6, 0xb4cc5c34, 0x1141e8ce,
133 			0xa15486af, 0x7c72e993, 0xb3ee1411, 0x636fbc2a,
134 			0x2ba9c55d, 0x741831f6, 0xce5c3e16, 0x9b87931e,
135 			0xafd6ba33, 0x6c24cf5c, 0x7a325381, 0x28958677,
136 			0x3b8f4898, 0x6b4bb9af, 0xc4bfe81b, 0x66282193,
137 			0x61d809cc, 0xfb21a991, 0x487cac60, 0x5dec8032,
138 			0xef845d5d, 0xe98575b1, 0xdc262302, 0xeb651b88,
139 			0x23893e81, 0xd396acc5, 0x0f6d6ff3, 0x83f44239,
140 			0x2e0b4482, 0xa4842004, 0x69c8f04a, 0x9e1f9b5e,
141 			0x21c66842, 0xf6e96c9a, 0x670c9c61, 0xabd388f0,
142 			0x6a51a0d2, 0xd8542f68, 0x960fa728, 0xab5133a3,
143 			0x6eef0b6c, 0x137a3be4, 0xba3bf050, 0x7efb2a98,
144 			0xa1f1651d, 0x39af0176, 0x66ca593e, 0x82430e88,
145 			0x8cee8619, 0x456f9fb4, 0x7d84a5c3, 0x3b8b5ebe,
146 			0xe06f75d8, 0x85c12073, 0x401a449f, 0x56c16aa6,
147 			0x4ed3aa62, 0x363f7706, 0x1bfedf72, 0x429b023d,
148 			0x37d0d724, 0xd00a1248, 0xdb0fead3, 0x49f1c09b,
149 			0x075372c9, 0x80991b7b, 0x25d479d8, 0xf6e8def7,
150 			0xe3fe501a, 0xb6794c3b, 0x976ce0bd, 0x04c006ba,
151 			0xc1a94fb6, 0x409f60c4, 0x5e5c9ec2, 0x196a2463,
152 			0x68fb6faf, 0x3e6c53b5, 0x1339b2eb, 0x3b52ec6f,
153 			0x6dfc511f, 0x9b30952c, 0xcc814544, 0xaf5ebd09,
154 			0xbee3d004, 0xde334afd, 0x660f2807, 0x192e4bb3,
155 			0xc0cba857, 0x45c8740f, 0xd20b5f39, 0xb9d3fbdb,
156 			0x5579c0bd, 0x1a60320a, 0xd6a100c6, 0x402c7279,
157 			0x679f25fe, 0xfb1fa3cc, 0x8ea5e9f8, 0xdb3222f8,
158 			0x3c7516df, 0xfd616b15, 0x2f501ec8, 0xad0552ab,
159 			0x323db5fa, 0xfd238760, 0x53317b48, 0x3e00df82,
160 			0x9e5c57bb, 0xca6f8ca0, 0x1a87562e, 0xdf1769db,
161 			0xd542a8f6, 0x287effc3, 0xac6732c6, 0x8c4f5573,
162 			0x695b27b0, 0xbbca58c8, 0xe1ffa35d, 0xb8f011a0,
163 			0x10fa3d98, 0xfd2183b8, 0x4afcb56c, 0x2dd1d35b,
164 			0x9a53e479, 0xb6f84565, 0xd28e49bc, 0x4bfb9790,
165 			0xe1ddf2da, 0xa4cb7e33, 0x62fb1341, 0xcee4c6e8,
166 			0xef20cada, 0x36774c01, 0xd07e9efe, 0x2bf11fb4,
167 			0x95dbda4d, 0xae909198, 0xeaad8e71, 0x6b93d5a0,
168 			0xd08ed1d0, 0xafc725e0, 0x8e3c5b2f, 0x8e7594b7,
169 			0x8ff6e2fb, 0xf2122b64, 0x8888b812, 0x900df01c,
170 			0x4fad5ea0, 0x688fc31c, 0xd1cff191, 0xb3a8c1ad,
171 			0x2f2f2218, 0xbe0e1777, 0xea752dfe, 0x8b021fa1,
172 			0xe5a0cc0f, 0xb56f74e8, 0x18acf3d6, 0xce89e299,
173 			0xb4a84fe0, 0xfd13e0b7, 0x7cc43b81, 0xd2ada8d9,
174 			0x165fa266, 0x80957705, 0x93cc7314, 0x211a1477,
175 			0xe6ad2065, 0x77b5fa86, 0xc75442f5, 0xfb9d35cf,
176 			0xebcdaf0c, 0x7b3e89a0, 0xd6411bd3, 0xae1e7e49,
177 			0x00250e2d, 0x2071b35e, 0x226800bb, 0x57b8e0af,
178 			0x2464369b, 0xf009b91e, 0x5563911d, 0x59dfa6aa,
179 			0x78c14389, 0xd95a537f, 0x207d5ba2, 0x02e5b9c5,
180 			0x83260376, 0x6295cfa9, 0x11c81968, 0x4e734a41,
181 			0xb3472dca, 0x7b14a94a, 0x1b510052, 0x9a532915,
182 			0xd60f573f, 0xbc9bc6e4, 0x2b60a476, 0x81e67400,
183 			0x08ba6fb5, 0x571be91f, 0xf296ec6b, 0x2a0dd915,
184 			0xb6636521, 0xe7b9f9b6, 0xff34052e, 0xc5855664,
185 		0x53b02d5d, 0xa99f8fa1, 0x08ba4799, 0x6e85076a},
186 		{
187 			0x4b7a70e9, 0xb5b32944, 0xdb75092e, 0xc4192623,
188 			0xad6ea6b0, 0x49a7df7d, 0x9cee60b8, 0x8fedb266,
189 			0xecaa8c71, 0x699a17ff, 0x5664526c, 0xc2b19ee1,
190 			0x193602a5, 0x75094c29, 0xa0591340, 0xe4183a3e,
191 			0x3f54989a, 0x5b429d65, 0x6b8fe4d6, 0x99f73fd6,
192 			0xa1d29c07, 0xefe830f5, 0x4d2d38e6, 0xf0255dc1,
193 			0x4cdd2086, 0x8470eb26, 0x6382e9c6, 0x021ecc5e,
194 			0x09686b3f, 0x3ebaefc9, 0x3c971814, 0x6b6a70a1,
195 			0x687f3584, 0x52a0e286, 0xb79c5305, 0xaa500737,
196 			0x3e07841c, 0x7fdeae5c, 0x8e7d44ec, 0x5716f2b8,
197 			0xb03ada37, 0xf0500c0d, 0xf01c1f04, 0x0200b3ff,
198 			0xae0cf51a, 0x3cb574b2, 0x25837a58, 0xdc0921bd,
199 			0xd19113f9, 0x7ca92ff6, 0x94324773, 0x22f54701,
200 			0x3ae5e581, 0x37c2dadc, 0xc8b57634, 0x9af3dda7,
201 			0xa9446146, 0x0fd0030e, 0xecc8c73e, 0xa4751e41,
202 			0xe238cd99, 0x3bea0e2f, 0x3280bba1, 0x183eb331,
203 			0x4e548b38, 0x4f6db908, 0x6f420d03, 0xf60a04bf,
204 			0x2cb81290, 0x24977c79, 0x5679b072, 0xbcaf89af,
205 			0xde9a771f, 0xd9930810, 0xb38bae12, 0xdccf3f2e,
206 			0x5512721f, 0x2e6b7124, 0x501adde6, 0x9f84cd87,
207 			0x7a584718, 0x7408da17, 0xbc9f9abc, 0xe94b7d8c,
208 			0xec7aec3a, 0xdb851dfa, 0x63094366, 0xc464c3d2,
209 			0xef1c1847, 0x3215d908, 0xdd433b37, 0x24c2ba16,
210 			0x12a14d43, 0x2a65c451, 0x50940002, 0x133ae4dd,
211 			0x71dff89e, 0x10314e55, 0x81ac77d6, 0x5f11199b,
212 			0x043556f1, 0xd7a3c76b, 0x3c11183b, 0x5924a509,
213 			0xf28fe6ed, 0x97f1fbfa, 0x9ebabf2c, 0x1e153c6e,
214 			0x86e34570, 0xeae96fb1, 0x860e5e0a, 0x5a3e2ab3,
215 			0x771fe71c, 0x4e3d06fa, 0x2965dcb9, 0x99e71d0f,
216 			0x803e89d6, 0x5266c825, 0x2e4cc978, 0x9c10b36a,
217 			0xc6150eba, 0x94e2ea78, 0xa5fc3c53, 0x1e0a2df4,
218 			0xf2f74ea7, 0x361d2b3d, 0x1939260f, 0x19c27960,
219 			0x5223a708, 0xf71312b6, 0xebadfe6e, 0xeac31f66,
220 			0xe3bc4595, 0xa67bc883, 0xb17f37d1, 0x018cff28,
221 			0xc332ddef, 0xbe6c5aa5, 0x65582185, 0x68ab9802,
222 			0xeecea50f, 0xdb2f953b, 0x2aef7dad, 0x5b6e2f84,
223 			0x1521b628, 0x29076170, 0xecdd4775, 0x619f1510,
224 			0x13cca830, 0xeb61bd96, 0x0334fe1e, 0xaa0363cf,
225 			0xb5735c90, 0x4c70a239, 0xd59e9e0b, 0xcbaade14,
226 			0xeecc86bc, 0x60622ca7, 0x9cab5cab, 0xb2f3846e,
227 			0x648b1eaf, 0x19bdf0ca, 0xa02369b9, 0x655abb50,
228 			0x40685a32, 0x3c2ab4b3, 0x319ee9d5, 0xc021b8f7,
229 			0x9b540b19, 0x875fa099, 0x95f7997e, 0x623d7da8,
230 			0xf837889a, 0x97e32d77, 0x11ed935f, 0x16681281,
231 			0x0e358829, 0xc7e61fd6, 0x96dedfa1, 0x7858ba99,
232 			0x57f584a5, 0x1b227263, 0x9b83c3ff, 0x1ac24696,
233 			0xcdb30aeb, 0x532e3054, 0x8fd948e4, 0x6dbc3128,
234 			0x58ebf2ef, 0x34c6ffea, 0xfe28ed61, 0xee7c3c73,
235 			0x5d4a14d9, 0xe864b7e3, 0x42105d14, 0x203e13e0,
236 			0x45eee2b6, 0xa3aaabea, 0xdb6c4f15, 0xfacb4fd0,
237 			0xc742f442, 0xef6abbb5, 0x654f3b1d, 0x41cd2105,
238 			0xd81e799e, 0x86854dc7, 0xe44b476a, 0x3d816250,
239 			0xcf62a1f2, 0x5b8d2646, 0xfc8883a0, 0xc1c7b6a3,
240 			0x7f1524c3, 0x69cb7492, 0x47848a0b, 0x5692b285,
241 			0x095bbf00, 0xad19489d, 0x1462b174, 0x23820e00,
242 			0x58428d2a, 0x0c55f5ea, 0x1dadf43e, 0x233f7061,
243 			0x3372f092, 0x8d937e41, 0xd65fecf1, 0x6c223bdb,
244 			0x7cde3759, 0xcbee7460, 0x4085f2a7, 0xce77326e,
245 			0xa6078084, 0x19f8509e, 0xe8efd855, 0x61d99735,
246 			0xa969a7aa, 0xc50c06c2, 0x5a04abfc, 0x800bcadc,
247 			0x9e447a2e, 0xc3453484, 0xfdd56705, 0x0e1e9ec9,
248 			0xdb73dbd3, 0x105588cd, 0x675fda79, 0xe3674340,
249 			0xc5c43465, 0x713e38d8, 0x3d28f89e, 0xf16dff20,
250 		0x153e21e7, 0x8fb03d4a, 0xe6e39f2b, 0xdb83adf7},
251 		{
252 			0xe93d5a68, 0x948140f7, 0xf64c261c, 0x94692934,
253 			0x411520f7, 0x7602d4f7, 0xbcf46b2e, 0xd4a20068,
254 			0xd4082471, 0x3320f46a, 0x43b7d4b7, 0x500061af,
255 			0x1e39f62e, 0x97244546, 0x14214f74, 0xbf8b8840,
256 			0x4d95fc1d, 0x96b591af, 0x70f4ddd3, 0x66a02f45,
257 			0xbfbc09ec, 0x03bd9785, 0x7fac6dd0, 0x31cb8504,
258 			0x96eb27b3, 0x55fd3941, 0xda2547e6, 0xabca0a9a,
259 			0x28507825, 0x530429f4, 0x0a2c86da, 0xe9b66dfb,
260 			0x68dc1462, 0xd7486900, 0x680ec0a4, 0x27a18dee,
261 			0x4f3ffea2, 0xe887ad8c, 0xb58ce006, 0x7af4d6b6,
262 			0xaace1e7c, 0xd3375fec, 0xce78a399, 0x406b2a42,
263 			0x20fe9e35, 0xd9f385b9, 0xee39d7ab, 0x3b124e8b,
264 			0x1dc9faf7, 0x4b6d1856, 0x26a36631, 0xeae397b2,
265 			0x3a6efa74, 0xdd5b4332, 0x6841e7f7, 0xca7820fb,
266 			0xfb0af54e, 0xd8feb397, 0x454056ac, 0xba489527,
267 			0x55533a3a, 0x20838d87, 0xfe6ba9b7, 0xd096954b,
268 			0x55a867bc, 0xa1159a58, 0xcca92963, 0x99e1db33,
269 			0xa62a4a56, 0x3f3125f9, 0x5ef47e1c, 0x9029317c,
270 			0xfdf8e802, 0x04272f70, 0x80bb155c, 0x05282ce3,
271 			0x95c11548, 0xe4c66d22, 0x48c1133f, 0xc70f86dc,
272 			0x07f9c9ee, 0x41041f0f, 0x404779a4, 0x5d886e17,
273 			0x325f51eb, 0xd59bc0d1, 0xf2bcc18f, 0x41113564,
274 			0x257b7834, 0x602a9c60, 0xdff8e8a3, 0x1f636c1b,
275 			0x0e12b4c2, 0x02e1329e, 0xaf664fd1, 0xcad18115,
276 			0x6b2395e0, 0x333e92e1, 0x3b240b62, 0xeebeb922,
277 			0x85b2a20e, 0xe6ba0d99, 0xde720c8c, 0x2da2f728,
278 			0xd0127845, 0x95b794fd, 0x647d0862, 0xe7ccf5f0,
279 			0x5449a36f, 0x877d48fa, 0xc39dfd27, 0xf33e8d1e,
280 			0x0a476341, 0x992eff74, 0x3a6f6eab, 0xf4f8fd37,
281 			0xa812dc60, 0xa1ebddf8, 0x991be14c, 0xdb6e6b0d,
282 			0xc67b5510, 0x6d672c37, 0x2765d43b, 0xdcd0e804,
283 			0xf1290dc7, 0xcc00ffa3, 0xb5390f92, 0x690fed0b,
284 			0x667b9ffb, 0xcedb7d9c, 0xa091cf0b, 0xd9155ea3,
285 			0xbb132f88, 0x515bad24, 0x7b9479bf, 0x763bd6eb,
286 			0x37392eb3, 0xcc115979, 0x8026e297, 0xf42e312d,
287 			0x6842ada7, 0xc66a2b3b, 0x12754ccc, 0x782ef11c,
288 			0x6a124237, 0xb79251e7, 0x06a1bbe6, 0x4bfb6350,
289 			0x1a6b1018, 0x11caedfa, 0x3d25bdd8, 0xe2e1c3c9,
290 			0x44421659, 0x0a121386, 0xd90cec6e, 0xd5abea2a,
291 			0x64af674e, 0xda86a85f, 0xbebfe988, 0x64e4c3fe,
292 			0x9dbc8057, 0xf0f7c086, 0x60787bf8, 0x6003604d,
293 			0xd1fd8346, 0xf6381fb0, 0x7745ae04, 0xd736fccc,
294 			0x83426b33, 0xf01eab71, 0xb0804187, 0x3c005e5f,
295 			0x77a057be, 0xbde8ae24, 0x55464299, 0xbf582e61,
296 			0x4e58f48f, 0xf2ddfda2, 0xf474ef38, 0x8789bdc2,
297 			0x5366f9c3, 0xc8b38e74, 0xb475f255, 0x46fcd9b9,
298 			0x7aeb2661, 0x8b1ddf84, 0x846a0e79, 0x915f95e2,
299 			0x466e598e, 0x20b45770, 0x8cd55591, 0xc902de4c,
300 			0xb90bace1, 0xbb8205d0, 0x11a86248, 0x7574a99e,
301 			0xb77f19b6, 0xe0a9dc09, 0x662d09a1, 0xc4324633,
302 			0xe85a1f02, 0x09f0be8c, 0x4a99a025, 0x1d6efe10,
303 			0x1ab93d1d, 0x0ba5a4df, 0xa186f20f, 0x2868f169,
304 			0xdcb7da83, 0x573906fe, 0xa1e2ce9b, 0x4fcd7f52,
305 			0x50115e01, 0xa70683fa, 0xa002b5c4, 0x0de6d027,
306 			0x9af88c27, 0x773f8641, 0xc3604c06, 0x61a806b5,
307 			0xf0177a28, 0xc0f586e0, 0x006058aa, 0x30dc7d62,
308 			0x11e69ed7, 0x2338ea63, 0x53c2dd94, 0xc2c21634,
309 			0xbbcbee56, 0x90bcb6de, 0xebfc7da1, 0xce591d76,
310 			0x6f05e409, 0x4b7c0188, 0x39720a3d, 0x7c927c24,
311 			0x86e3725f, 0x724d9db9, 0x1ac15bb4, 0xd39eb8fc,
312 			0xed545578, 0x08fca5b5, 0xd83d7cd3, 0x4dad0fc4,
313 			0x1e50ef5e, 0xb161e6f8, 0xa28514d9, 0x6c51133c,
314 			0x6fd5c7e7, 0x56e14ec4, 0x362abfce, 0xddc6c837,
315 		0xd79a3234, 0x92638212, 0x670efa8e, 0x406000e0},
316 		{
317 			0x3a39ce37, 0xd3faf5cf, 0xabc27737, 0x5ac52d1b,
318 			0x5cb0679e, 0x4fa33742, 0xd3822740, 0x99bc9bbe,
319 			0xd5118e9d, 0xbf0f7315, 0xd62d1c7e, 0xc700c47b,
320 			0xb78c1b6b, 0x21a19045, 0xb26eb1be, 0x6a366eb4,
321 			0x5748ab2f, 0xbc946e79, 0xc6a376d2, 0x6549c2c8,
322 			0x530ff8ee, 0x468dde7d, 0xd5730a1d, 0x4cd04dc6,
323 			0x2939bbdb, 0xa9ba4650, 0xac9526e8, 0xbe5ee304,
324 			0xa1fad5f0, 0x6a2d519a, 0x63ef8ce2, 0x9a86ee22,
325 			0xc089c2b8, 0x43242ef6, 0xa51e03aa, 0x9cf2d0a4,
326 			0x83c061ba, 0x9be96a4d, 0x8fe51550, 0xba645bd6,
327 			0x2826a2f9, 0xa73a3ae1, 0x4ba99586, 0xef5562e9,
328 			0xc72fefd3, 0xf752f7da, 0x3f046f69, 0x77fa0a59,
329 			0x80e4a915, 0x87b08601, 0x9b09e6ad, 0x3b3ee593,
330 			0xe990fd5a, 0x9e34d797, 0x2cf0b7d9, 0x022b8b51,
331 			0x96d5ac3a, 0x017da67d, 0xd1cf3ed6, 0x7c7d2d28,
332 			0x1f9f25cf, 0xadf2b89b, 0x5ad6b472, 0x5a88f54c,
333 			0xe029ac71, 0xe019a5e6, 0x47b0acfd, 0xed93fa9b,
334 			0xe8d3c48d, 0x283b57cc, 0xf8d56629, 0x79132e28,
335 			0x785f0191, 0xed756055, 0xf7960e44, 0xe3d35e8c,
336 			0x15056dd4, 0x88f46dba, 0x03a16125, 0x0564f0bd,
337 			0xc3eb9e15, 0x3c9057a2, 0x97271aec, 0xa93a072a,
338 			0x1b3f6d9b, 0x1e6321f5, 0xf59c66fb, 0x26dcf319,
339 			0x7533d928, 0xb155fdf5, 0x03563482, 0x8aba3cbb,
340 			0x28517711, 0xc20ad9f8, 0xabcc5167, 0xccad925f,
341 			0x4de81751, 0x3830dc8e, 0x379d5862, 0x9320f991,
342 			0xea7a90c2, 0xfb3e7bce, 0x5121ce64, 0x774fbe32,
343 			0xa8b6e37e, 0xc3293d46, 0x48de5369, 0x6413e680,
344 			0xa2ae0810, 0xdd6db224, 0x69852dfd, 0x09072166,
345 			0xb39a460a, 0x6445c0dd, 0x586cdecf, 0x1c20c8ae,
346 			0x5bbef7dd, 0x1b588d40, 0xccd2017f, 0x6bb4e3bb,
347 			0xdda26a7e, 0x3a59ff45, 0x3e350a44, 0xbcb4cdd5,
348 			0x72eacea8, 0xfa6484bb, 0x8d6612ae, 0xbf3c6f47,
349 			0xd29be463, 0x542f5d9e, 0xaec2771b, 0xf64e6370,
350 			0x740e0d8d, 0xe75b1357, 0xf8721671, 0xaf537d5d,
351 			0x4040cb08, 0x4eb4e2cc, 0x34d2466a, 0x0115af84,
352 			0xe1b00428, 0x95983a1d, 0x06b89fb4, 0xce6ea048,
353 			0x6f3f3b82, 0x3520ab82, 0x011a1d4b, 0x277227f8,
354 			0x611560b1, 0xe7933fdc, 0xbb3a792b, 0x344525bd,
355 			0xa08839e1, 0x51ce794b, 0x2f32c9b7, 0xa01fbac9,
356 			0xe01cc87e, 0xbcc7d1f6, 0xcf0111c3, 0xa1e8aac7,
357 			0x1a908749, 0xd44fbd9a, 0xd0dadecb, 0xd50ada38,
358 			0x0339c32a, 0xc6913667, 0x8df9317c, 0xe0b12b4f,
359 			0xf79e59b7, 0x43f5bb3a, 0xf2d519ff, 0x27d9459c,
360 			0xbf97222c, 0x15e6fc2a, 0x0f91fc71, 0x9b941525,
361 			0xfae59361, 0xceb69ceb, 0xc2a86459, 0x12baa8d1,
362 			0xb6c1075e, 0xe3056a0c, 0x10d25065, 0xcb03a442,
363 			0xe0ec6e0e, 0x1698db3b, 0x4c98a0be, 0x3278e964,
364 			0x9f1f9532, 0xe0d392df, 0xd3a0342b, 0x8971f21e,
365 			0x1b0a7441, 0x4ba3348c, 0xc5be7120, 0xc37632d8,
366 			0xdf359f8d, 0x9b992f2e, 0xe60b6f47, 0x0fe3f11d,
367 			0xe54cda54, 0x1edad891, 0xce6279cf, 0xcd3e7e6f,
368 			0x1618b166, 0xfd2c1d05, 0x848fd2c5, 0xf6fb2299,
369 			0xf523f357, 0xa6327623, 0x93a83531, 0x56cccd02,
370 			0xacf08162, 0x5a75ebb5, 0x6e163697, 0x88d273cc,
371 			0xde966292, 0x81b949d0, 0x4c50901b, 0x71c65614,
372 			0xe6c6c7bd, 0x327a140a, 0x45e1d006, 0xc3f27b9a,
373 			0xc9aa53fd, 0x62a80f00, 0xbb25bfe2, 0x35bdd2f6,
374 			0x71126905, 0xb2040222, 0xb6cbcf7c, 0xcd769c2b,
375 			0x53113ec0, 0x1640e3d3, 0x38abbd60, 0x2547adf0,
376 			0xba38209c, 0xf746ce76, 0x77afa1c5, 0x20756060,
377 			0x85cbfe4e, 0x8ae88dd8, 0x7aaaf9b0, 0x4cf9aa7e,
378 			0x1948c25c, 0x02fb8a8c, 0x01c36ae4, 0xd6ebe1f9,
379 			0x90d4f869, 0xa65cdea0, 0x3f09252d, 0xc208e69f,
380 		0xb74e6132, 0xce77e25b, 0x578fdfe3, 0x3ac372e6}
381 	},
382 	{
383 		0x243f6a88, 0x85a308d3, 0x13198a2e, 0x03707344,
384 		0xa4093822, 0x299f31d0, 0x082efa98, 0xec4e6c89,
385 		0x452821e6, 0x38d01377, 0xbe5466cf, 0x34e90c6c,
386 		0xc0ac29b7, 0xc97c50dd, 0x3f84d5b5, 0xb5470917,
387 		0x9216d5d9, 0x8979fb1b
388 	} };
389 
390 	*c = initstate;
391 }
392 
393 u_int32_t
Blowfish_stream2word(const u_int8_t * data,u_int16_t databytes,u_int16_t * current)394 Blowfish_stream2word(const u_int8_t *data, u_int16_t databytes,
395     u_int16_t *current)
396 {
397 	u_int8_t i;
398 	u_int16_t j;
399 	u_int32_t temp;
400 
401 	temp = 0x00000000;
402 	j = *current;
403 
404 	for (i = 0; i < 4; i++, j++) {
405 		if (j >= databytes)
406 			j = 0;
407 		temp = (temp << 8) | data[j];
408 	}
409 
410 	*current = j;
411 	return temp;
412 }
413 
414 void
Blowfish_expand0state(blf_ctx * c,const u_int8_t * key,u_int16_t keybytes)415 Blowfish_expand0state(blf_ctx *c, const u_int8_t *key, u_int16_t keybytes)
416 {
417 	u_int16_t i;
418 	u_int16_t j;
419 	u_int16_t k;
420 	u_int32_t temp;
421 	u_int32_t data[2];
422 
423 	j = 0;
424 	for (i = 0; i < BLF_N + 2; i++) {
425 		/* Extract 4 int8 to 1 int32 from keystream */
426 		temp = Blowfish_stream2word(key, keybytes, &j);
427 		c->P[i] = c->P[i] ^ temp;
428 	}
429 
430 	j = 0;
431 	data[0] = 0x00000000;
432 	data[1] = 0x00000000;
433 	for (i = 0; i < BLF_N + 2; i += 2) {
434 		Blowfish_encipher(c, data);
435 
436 		c->P[i] = data[0];
437 		c->P[i + 1] = data[1];
438 	}
439 
440 	for (i = 0; i < 4; i++) {
441 		for (k = 0; k < 256; k += 2) {
442 			Blowfish_encipher(c, data);
443 
444 			c->S[i][k] = data[0];
445 			c->S[i][k + 1] = data[1];
446 		}
447 	}
448 }
449 
450 
451 void
Blowfish_expandstate(blf_ctx * c,const u_int8_t * data,u_int16_t databytes,const u_int8_t * key,u_int16_t keybytes)452 Blowfish_expandstate(blf_ctx *c, const u_int8_t *data, u_int16_t databytes,
453     const u_int8_t *key, u_int16_t keybytes)
454 {
455 	u_int16_t i;
456 	u_int16_t j;
457 	u_int16_t k;
458 	u_int32_t temp;
459 	u_int32_t d[2];
460 
461 	j = 0;
462 	for (i = 0; i < BLF_N + 2; i++) {
463 		/* Extract 4 int8 to 1 int32 from keystream */
464 		temp = Blowfish_stream2word(key, keybytes, &j);
465 		c->P[i] = c->P[i] ^ temp;
466 	}
467 
468 	j = 0;
469 	d[0] = 0x00000000;
470 	d[1] = 0x00000000;
471 	for (i = 0; i < BLF_N + 2; i += 2) {
472 		d[0] ^= Blowfish_stream2word(data, databytes, &j);
473 		d[1] ^= Blowfish_stream2word(data, databytes, &j);
474 		Blowfish_encipher(c, d);
475 
476 		c->P[i] = d[0];
477 		c->P[i + 1] = d[1];
478 	}
479 
480 	for (i = 0; i < 4; i++) {
481 		for (k = 0; k < 256; k += 2) {
482 			d[0]^= Blowfish_stream2word(data, databytes, &j);
483 			d[1] ^= Blowfish_stream2word(data, databytes, &j);
484 			Blowfish_encipher(c, d);
485 
486 			c->S[i][k] = d[0];
487 			c->S[i][k + 1] = d[1];
488 		}
489 	}
490 
491 }
492 
493 void
blf_key(blf_ctx * c,const u_int8_t * k,u_int16_t len)494 blf_key(blf_ctx *c, const u_int8_t *k, u_int16_t len)
495 {
496 	/* Initialize S-boxes and subkeys with Pi */
497 	Blowfish_initstate(c);
498 
499 	/* Transform S-boxes and subkeys with key */
500 	Blowfish_expand0state(c, k, len);
501 }
502 
503 void
blf_enc(blf_ctx * c,u_int32_t * data,u_int16_t blocks)504 blf_enc(blf_ctx *c, u_int32_t *data, u_int16_t blocks)
505 {
506 	u_int32_t *d;
507 	u_int16_t i;
508 
509 	d = data;
510 	for (i = 0; i < blocks; i++) {
511 		Blowfish_encipher(c, d);
512 		d += 2;
513 	}
514 }
515 
516 void
blf_dec(blf_ctx * c,u_int32_t * data,u_int16_t blocks)517 blf_dec(blf_ctx *c, u_int32_t *data, u_int16_t blocks)
518 {
519 	u_int32_t *d;
520 	u_int16_t i;
521 
522 	d = data;
523 	for (i = 0; i < blocks; i++) {
524 		Blowfish_decipher(c, d);
525 		d += 2;
526 	}
527 }
528 
529 void
blf_ecb_encrypt(blf_ctx * c,u_int8_t * data,u_int32_t len)530 blf_ecb_encrypt(blf_ctx *c, u_int8_t *data, u_int32_t len)
531 {
532 	u_int32_t l, r, d[2];
533 	u_int32_t i;
534 
535 	for (i = 0; i < len; i += 8) {
536 		l = data[0] << 24 | data[1] << 16 | data[2] << 8 | data[3];
537 		r = data[4] << 24 | data[5] << 16 | data[6] << 8 | data[7];
538 		d[0] = l;
539 		d[1] = r;
540 		Blowfish_encipher(c, d);
541 		l = d[0];
542 		r = d[1];
543 		data[0] = l >> 24 & 0xff;
544 		data[1] = l >> 16 & 0xff;
545 		data[2] = l >> 8 & 0xff;
546 		data[3] = l & 0xff;
547 		data[4] = r >> 24 & 0xff;
548 		data[5] = r >> 16 & 0xff;
549 		data[6] = r >> 8 & 0xff;
550 		data[7] = r & 0xff;
551 		data += 8;
552 	}
553 }
554 
555 void
blf_ecb_decrypt(blf_ctx * c,u_int8_t * data,u_int32_t len)556 blf_ecb_decrypt(blf_ctx *c, u_int8_t *data, u_int32_t len)
557 {
558 	u_int32_t l, r, d[2];
559 	u_int32_t i;
560 
561 	for (i = 0; i < len; i += 8) {
562 		l = data[0] << 24 | data[1] << 16 | data[2] << 8 | data[3];
563 		r = data[4] << 24 | data[5] << 16 | data[6] << 8 | data[7];
564 		d[0] = l;
565 		d[1] = r;
566 		Blowfish_decipher(c, d);
567 		l = d[0];
568 		r = d[1];
569 		data[0] = l >> 24 & 0xff;
570 		data[1] = l >> 16 & 0xff;
571 		data[2] = l >> 8 & 0xff;
572 		data[3] = l & 0xff;
573 		data[4] = r >> 24 & 0xff;
574 		data[5] = r >> 16 & 0xff;
575 		data[6] = r >> 8 & 0xff;
576 		data[7] = r & 0xff;
577 		data += 8;
578 	}
579 }
580 
581 void
blf_cbc_encrypt(blf_ctx * c,u_int8_t * iv,u_int8_t * data,u_int32_t len)582 blf_cbc_encrypt(blf_ctx *c, u_int8_t *iv, u_int8_t *data, u_int32_t len)
583 {
584 	u_int32_t l, r, d[2];
585 	u_int32_t i, j;
586 
587 	for (i = 0; i < len; i += 8) {
588 		for (j = 0; j < 8; j++)
589 			data[j] ^= iv[j];
590 		l = data[0] << 24 | data[1] << 16 | data[2] << 8 | data[3];
591 		r = data[4] << 24 | data[5] << 16 | data[6] << 8 | data[7];
592 		d[0] = l;
593 		d[1] = r;
594 		Blowfish_encipher(c, d);
595 		l = d[0];
596 		r = d[1];
597 		data[0] = l >> 24 & 0xff;
598 		data[1] = l >> 16 & 0xff;
599 		data[2] = l >> 8 & 0xff;
600 		data[3] = l & 0xff;
601 		data[4] = r >> 24 & 0xff;
602 		data[5] = r >> 16 & 0xff;
603 		data[6] = r >> 8 & 0xff;
604 		data[7] = r & 0xff;
605 		iv = data;
606 		data += 8;
607 	}
608 }
609 
610 void
blf_cbc_decrypt(blf_ctx * c,u_int8_t * iva,u_int8_t * data,u_int32_t len)611 blf_cbc_decrypt(blf_ctx *c, u_int8_t *iva, u_int8_t *data, u_int32_t len)
612 {
613 	u_int32_t l, r, d[2];
614 	u_int8_t *iv;
615 	u_int32_t i, j;
616 
617 	iv = data + len - 16;
618 	data = data + len - 8;
619 	for (i = len - 8; i >= 8; i -= 8) {
620 		l = data[0] << 24 | data[1] << 16 | data[2] << 8 | data[3];
621 		r = data[4] << 24 | data[5] << 16 | data[6] << 8 | data[7];
622 		d[0] = l;
623 		d[1] = r;
624 		Blowfish_decipher(c, d);
625 		l = d[0];
626 		r = d[1];
627 		data[0] = l >> 24 & 0xff;
628 		data[1] = l >> 16 & 0xff;
629 		data[2] = l >> 8 & 0xff;
630 		data[3] = l & 0xff;
631 		data[4] = r >> 24 & 0xff;
632 		data[5] = r >> 16 & 0xff;
633 		data[6] = r >> 8 & 0xff;
634 		data[7] = r & 0xff;
635 		for (j = 0; j < 8; j++)
636 			data[j] ^= iv[j];
637 		iv -= 8;
638 		data -= 8;
639 	}
640 	l = data[0] << 24 | data[1] << 16 | data[2] << 8 | data[3];
641 	r = data[4] << 24 | data[5] << 16 | data[6] << 8 | data[7];
642 	d[0] = l;
643 	d[1] = r;
644 	Blowfish_decipher(c, d);
645 	l = d[0];
646 	r = d[1];
647 	data[0] = l >> 24 & 0xff;
648 	data[1] = l >> 16 & 0xff;
649 	data[2] = l >> 8 & 0xff;
650 	data[3] = l & 0xff;
651 	data[4] = r >> 24 & 0xff;
652 	data[5] = r >> 16 & 0xff;
653 	data[6] = r >> 8 & 0xff;
654 	data[7] = r & 0xff;
655 	for (j = 0; j < 8; j++)
656 		data[j] ^= iva[j];
657 }
658