OSDN Git Service

Standard pgindent run for 8.1.
[pg-rex/syncrep.git] / contrib / pgcrypto / crypt-blowfish.c
1 /*
2  * This code comes from John the Ripper password cracker, with reentrant
3  * and crypt(3) interfaces added, but optimizations specific to password
4  * cracking removed.
5  *
6  * Written by Solar Designer <solar@openwall.com> in 1998-2001, and placed
7  * in the public domain.
8  *
9  * There's absolutely no warranty.
10  *
11  * It is my intent that you should be able to use this on your system,
12  * as a part of a software package, or anywhere else to improve security,
13  * ensure compatibility, or for any other purpose. I would appreciate
14  * it if you give credit where it is due and keep your modifications in
15  * the public domain as well, but I don't require that in order to let
16  * you place this code and any modifications you make under a license
17  * of your choice.
18  *
19  * This implementation is compatible with OpenBSD bcrypt.c (version 2a)
20  * by Niels Provos <provos@physnet.uni-hamburg.de>, and uses some of his
21  * ideas. The password hashing algorithm was designed by David Mazieres
22  * <dm@lcs.mit.edu>.
23  *
24  * There's a paper on the algorithm that explains its design decisions:
25  *
26  *      http://www.usenix.org/events/usenix99/provos.html
27  *
28  * Some of the tricks in BF_ROUND might be inspired by Eric Young's
29  * Blowfish library (I can't be sure if I would think of something if I
30  * hadn't seen his code).
31  */
32
33 #include "postgres.h"
34
35 #include "px.h"
36 #include "px-crypt.h"
37
38 #ifdef __i386__
39 #define BF_ASM                          0       /* 1 */
40 #define BF_SCALE                        1
41 #elif defined(__alpha__)
42 #define BF_ASM                          0
43 #define BF_SCALE                        1
44 #else
45 #define BF_ASM                          0
46 #define BF_SCALE                        0
47 #endif
48
49 typedef unsigned int BF_word;
50
51 /* Number of Blowfish rounds, this is also hardcoded into a few places */
52 #define BF_N                            16
53
54 typedef BF_word BF_key[BF_N + 2];
55
56 typedef struct
57 {
58         BF_word         S[4][0x100];
59         BF_key          P;
60 }       BF_ctx;
61
62 /*
63  * Magic IV for 64 Blowfish encryptions that we do at the end.
64  * The string is "OrpheanBeholderScryDoubt" on big-endian.
65  */
66 static BF_word BF_magic_w[6] = {
67         0x4F727068, 0x65616E42, 0x65686F6C,
68         0x64657253, 0x63727944, 0x6F756274
69 };
70
71 /*
72  * P-box and S-box tables initialized with digits of Pi.
73  */
74 static BF_ctx BF_init_state = {
75         {
76                 {
77                         0xd1310ba6, 0x98dfb5ac, 0x2ffd72db, 0xd01adfb7,
78                         0xb8e1afed, 0x6a267e96, 0xba7c9045, 0xf12c7f99,
79                         0x24a19947, 0xb3916cf7, 0x0801f2e2, 0x858efc16,
80                         0x636920d8, 0x71574e69, 0xa458fea3, 0xf4933d7e,
81                         0x0d95748f, 0x728eb658, 0x718bcd58, 0x82154aee,
82                         0x7b54a41d, 0xc25a59b5, 0x9c30d539, 0x2af26013,
83                         0xc5d1b023, 0x286085f0, 0xca417918, 0xb8db38ef,
84                         0x8e79dcb0, 0x603a180e, 0x6c9e0e8b, 0xb01e8a3e,
85                         0xd71577c1, 0xbd314b27, 0x78af2fda, 0x55605c60,
86                         0xe65525f3, 0xaa55ab94, 0x57489862, 0x63e81440,
87                         0x55ca396a, 0x2aab10b6, 0xb4cc5c34, 0x1141e8ce,
88                         0xa15486af, 0x7c72e993, 0xb3ee1411, 0x636fbc2a,
89                         0x2ba9c55d, 0x741831f6, 0xce5c3e16, 0x9b87931e,
90                         0xafd6ba33, 0x6c24cf5c, 0x7a325381, 0x28958677,
91                         0x3b8f4898, 0x6b4bb9af, 0xc4bfe81b, 0x66282193,
92                         0x61d809cc, 0xfb21a991, 0x487cac60, 0x5dec8032,
93                         0xef845d5d, 0xe98575b1, 0xdc262302, 0xeb651b88,
94                         0x23893e81, 0xd396acc5, 0x0f6d6ff3, 0x83f44239,
95                         0x2e0b4482, 0xa4842004, 0x69c8f04a, 0x9e1f9b5e,
96                         0x21c66842, 0xf6e96c9a, 0x670c9c61, 0xabd388f0,
97                         0x6a51a0d2, 0xd8542f68, 0x960fa728, 0xab5133a3,
98                         0x6eef0b6c, 0x137a3be4, 0xba3bf050, 0x7efb2a98,
99                         0xa1f1651d, 0x39af0176, 0x66ca593e, 0x82430e88,
100                         0x8cee8619, 0x456f9fb4, 0x7d84a5c3, 0x3b8b5ebe,
101                         0xe06f75d8, 0x85c12073, 0x401a449f, 0x56c16aa6,
102                         0x4ed3aa62, 0x363f7706, 0x1bfedf72, 0x429b023d,
103                         0x37d0d724, 0xd00a1248, 0xdb0fead3, 0x49f1c09b,
104                         0x075372c9, 0x80991b7b, 0x25d479d8, 0xf6e8def7,
105                         0xe3fe501a, 0xb6794c3b, 0x976ce0bd, 0x04c006ba,
106                         0xc1a94fb6, 0x409f60c4, 0x5e5c9ec2, 0x196a2463,
107                         0x68fb6faf, 0x3e6c53b5, 0x1339b2eb, 0x3b52ec6f,
108                         0x6dfc511f, 0x9b30952c, 0xcc814544, 0xaf5ebd09,
109                         0xbee3d004, 0xde334afd, 0x660f2807, 0x192e4bb3,
110                         0xc0cba857, 0x45c8740f, 0xd20b5f39, 0xb9d3fbdb,
111                         0x5579c0bd, 0x1a60320a, 0xd6a100c6, 0x402c7279,
112                         0x679f25fe, 0xfb1fa3cc, 0x8ea5e9f8, 0xdb3222f8,
113                         0x3c7516df, 0xfd616b15, 0x2f501ec8, 0xad0552ab,
114                         0x323db5fa, 0xfd238760, 0x53317b48, 0x3e00df82,
115                         0x9e5c57bb, 0xca6f8ca0, 0x1a87562e, 0xdf1769db,
116                         0xd542a8f6, 0x287effc3, 0xac6732c6, 0x8c4f5573,
117                         0x695b27b0, 0xbbca58c8, 0xe1ffa35d, 0xb8f011a0,
118                         0x10fa3d98, 0xfd2183b8, 0x4afcb56c, 0x2dd1d35b,
119                         0x9a53e479, 0xb6f84565, 0xd28e49bc, 0x4bfb9790,
120                         0xe1ddf2da, 0xa4cb7e33, 0x62fb1341, 0xcee4c6e8,
121                         0xef20cada, 0x36774c01, 0xd07e9efe, 0x2bf11fb4,
122                         0x95dbda4d, 0xae909198, 0xeaad8e71, 0x6b93d5a0,
123                         0xd08ed1d0, 0xafc725e0, 0x8e3c5b2f, 0x8e7594b7,
124                         0x8ff6e2fb, 0xf2122b64, 0x8888b812, 0x900df01c,
125                         0x4fad5ea0, 0x688fc31c, 0xd1cff191, 0xb3a8c1ad,
126                         0x2f2f2218, 0xbe0e1777, 0xea752dfe, 0x8b021fa1,
127                         0xe5a0cc0f, 0xb56f74e8, 0x18acf3d6, 0xce89e299,
128                         0xb4a84fe0, 0xfd13e0b7, 0x7cc43b81, 0xd2ada8d9,
129                         0x165fa266, 0x80957705, 0x93cc7314, 0x211a1477,
130                         0xe6ad2065, 0x77b5fa86, 0xc75442f5, 0xfb9d35cf,
131                         0xebcdaf0c, 0x7b3e89a0, 0xd6411bd3, 0xae1e7e49,
132                         0x00250e2d, 0x2071b35e, 0x226800bb, 0x57b8e0af,
133                         0x2464369b, 0xf009b91e, 0x5563911d, 0x59dfa6aa,
134                         0x78c14389, 0xd95a537f, 0x207d5ba2, 0x02e5b9c5,
135                         0x83260376, 0x6295cfa9, 0x11c81968, 0x4e734a41,
136                         0xb3472dca, 0x7b14a94a, 0x1b510052, 0x9a532915,
137                         0xd60f573f, 0xbc9bc6e4, 0x2b60a476, 0x81e67400,
138                         0x08ba6fb5, 0x571be91f, 0xf296ec6b, 0x2a0dd915,
139                         0xb6636521, 0xe7b9f9b6, 0xff34052e, 0xc5855664,
140                         0x53b02d5d, 0xa99f8fa1, 0x08ba4799, 0x6e85076a
141                 }, {
142                         0x4b7a70e9, 0xb5b32944, 0xdb75092e, 0xc4192623,
143                         0xad6ea6b0, 0x49a7df7d, 0x9cee60b8, 0x8fedb266,
144                         0xecaa8c71, 0x699a17ff, 0x5664526c, 0xc2b19ee1,
145                         0x193602a5, 0x75094c29, 0xa0591340, 0xe4183a3e,
146                         0x3f54989a, 0x5b429d65, 0x6b8fe4d6, 0x99f73fd6,
147                         0xa1d29c07, 0xefe830f5, 0x4d2d38e6, 0xf0255dc1,
148                         0x4cdd2086, 0x8470eb26, 0x6382e9c6, 0x021ecc5e,
149                         0x09686b3f, 0x3ebaefc9, 0x3c971814, 0x6b6a70a1,
150                         0x687f3584, 0x52a0e286, 0xb79c5305, 0xaa500737,
151                         0x3e07841c, 0x7fdeae5c, 0x8e7d44ec, 0x5716f2b8,
152                         0xb03ada37, 0xf0500c0d, 0xf01c1f04, 0x0200b3ff,
153                         0xae0cf51a, 0x3cb574b2, 0x25837a58, 0xdc0921bd,
154                         0xd19113f9, 0x7ca92ff6, 0x94324773, 0x22f54701,
155                         0x3ae5e581, 0x37c2dadc, 0xc8b57634, 0x9af3dda7,
156                         0xa9446146, 0x0fd0030e, 0xecc8c73e, 0xa4751e41,
157                         0xe238cd99, 0x3bea0e2f, 0x3280bba1, 0x183eb331,
158                         0x4e548b38, 0x4f6db908, 0x6f420d03, 0xf60a04bf,
159                         0x2cb81290, 0x24977c79, 0x5679b072, 0xbcaf89af,
160                         0xde9a771f, 0xd9930810, 0xb38bae12, 0xdccf3f2e,
161                         0x5512721f, 0x2e6b7124, 0x501adde6, 0x9f84cd87,
162                         0x7a584718, 0x7408da17, 0xbc9f9abc, 0xe94b7d8c,
163                         0xec7aec3a, 0xdb851dfa, 0x63094366, 0xc464c3d2,
164                         0xef1c1847, 0x3215d908, 0xdd433b37, 0x24c2ba16,
165                         0x12a14d43, 0x2a65c451, 0x50940002, 0x133ae4dd,
166                         0x71dff89e, 0x10314e55, 0x81ac77d6, 0x5f11199b,
167                         0x043556f1, 0xd7a3c76b, 0x3c11183b, 0x5924a509,
168                         0xf28fe6ed, 0x97f1fbfa, 0x9ebabf2c, 0x1e153c6e,
169                         0x86e34570, 0xeae96fb1, 0x860e5e0a, 0x5a3e2ab3,
170                         0x771fe71c, 0x4e3d06fa, 0x2965dcb9, 0x99e71d0f,
171                         0x803e89d6, 0x5266c825, 0x2e4cc978, 0x9c10b36a,
172                         0xc6150eba, 0x94e2ea78, 0xa5fc3c53, 0x1e0a2df4,
173                         0xf2f74ea7, 0x361d2b3d, 0x1939260f, 0x19c27960,
174                         0x5223a708, 0xf71312b6, 0xebadfe6e, 0xeac31f66,
175                         0xe3bc4595, 0xa67bc883, 0xb17f37d1, 0x018cff28,
176                         0xc332ddef, 0xbe6c5aa5, 0x65582185, 0x68ab9802,
177                         0xeecea50f, 0xdb2f953b, 0x2aef7dad, 0x5b6e2f84,
178                         0x1521b628, 0x29076170, 0xecdd4775, 0x619f1510,
179                         0x13cca830, 0xeb61bd96, 0x0334fe1e, 0xaa0363cf,
180                         0xb5735c90, 0x4c70a239, 0xd59e9e0b, 0xcbaade14,
181                         0xeecc86bc, 0x60622ca7, 0x9cab5cab, 0xb2f3846e,
182                         0x648b1eaf, 0x19bdf0ca, 0xa02369b9, 0x655abb50,
183                         0x40685a32, 0x3c2ab4b3, 0x319ee9d5, 0xc021b8f7,
184                         0x9b540b19, 0x875fa099, 0x95f7997e, 0x623d7da8,
185                         0xf837889a, 0x97e32d77, 0x11ed935f, 0x16681281,
186                         0x0e358829, 0xc7e61fd6, 0x96dedfa1, 0x7858ba99,
187                         0x57f584a5, 0x1b227263, 0x9b83c3ff, 0x1ac24696,
188                         0xcdb30aeb, 0x532e3054, 0x8fd948e4, 0x6dbc3128,
189                         0x58ebf2ef, 0x34c6ffea, 0xfe28ed61, 0xee7c3c73,
190                         0x5d4a14d9, 0xe864b7e3, 0x42105d14, 0x203e13e0,
191                         0x45eee2b6, 0xa3aaabea, 0xdb6c4f15, 0xfacb4fd0,
192                         0xc742f442, 0xef6abbb5, 0x654f3b1d, 0x41cd2105,
193                         0xd81e799e, 0x86854dc7, 0xe44b476a, 0x3d816250,
194                         0xcf62a1f2, 0x5b8d2646, 0xfc8883a0, 0xc1c7b6a3,
195                         0x7f1524c3, 0x69cb7492, 0x47848a0b, 0x5692b285,
196                         0x095bbf00, 0xad19489d, 0x1462b174, 0x23820e00,
197                         0x58428d2a, 0x0c55f5ea, 0x1dadf43e, 0x233f7061,
198                         0x3372f092, 0x8d937e41, 0xd65fecf1, 0x6c223bdb,
199                         0x7cde3759, 0xcbee7460, 0x4085f2a7, 0xce77326e,
200                         0xa6078084, 0x19f8509e, 0xe8efd855, 0x61d99735,
201                         0xa969a7aa, 0xc50c06c2, 0x5a04abfc, 0x800bcadc,
202                         0x9e447a2e, 0xc3453484, 0xfdd56705, 0x0e1e9ec9,
203                         0xdb73dbd3, 0x105588cd, 0x675fda79, 0xe3674340,
204                         0xc5c43465, 0x713e38d8, 0x3d28f89e, 0xf16dff20,
205                         0x153e21e7, 0x8fb03d4a, 0xe6e39f2b, 0xdb83adf7
206                 }, {
207                         0xe93d5a68, 0x948140f7, 0xf64c261c, 0x94692934,
208                         0x411520f7, 0x7602d4f7, 0xbcf46b2e, 0xd4a20068,
209                         0xd4082471, 0x3320f46a, 0x43b7d4b7, 0x500061af,
210                         0x1e39f62e, 0x97244546, 0x14214f74, 0xbf8b8840,
211                         0x4d95fc1d, 0x96b591af, 0x70f4ddd3, 0x66a02f45,
212                         0xbfbc09ec, 0x03bd9785, 0x7fac6dd0, 0x31cb8504,
213                         0x96eb27b3, 0x55fd3941, 0xda2547e6, 0xabca0a9a,
214                         0x28507825, 0x530429f4, 0x0a2c86da, 0xe9b66dfb,
215                         0x68dc1462, 0xd7486900, 0x680ec0a4, 0x27a18dee,
216                         0x4f3ffea2, 0xe887ad8c, 0xb58ce006, 0x7af4d6b6,
217                         0xaace1e7c, 0xd3375fec, 0xce78a399, 0x406b2a42,
218                         0x20fe9e35, 0xd9f385b9, 0xee39d7ab, 0x3b124e8b,
219                         0x1dc9faf7, 0x4b6d1856, 0x26a36631, 0xeae397b2,
220                         0x3a6efa74, 0xdd5b4332, 0x6841e7f7, 0xca7820fb,
221                         0xfb0af54e, 0xd8feb397, 0x454056ac, 0xba489527,
222                         0x55533a3a, 0x20838d87, 0xfe6ba9b7, 0xd096954b,
223                         0x55a867bc, 0xa1159a58, 0xcca92963, 0x99e1db33,
224                         0xa62a4a56, 0x3f3125f9, 0x5ef47e1c, 0x9029317c,
225                         0xfdf8e802, 0x04272f70, 0x80bb155c, 0x05282ce3,
226                         0x95c11548, 0xe4c66d22, 0x48c1133f, 0xc70f86dc,
227                         0x07f9c9ee, 0x41041f0f, 0x404779a4, 0x5d886e17,
228                         0x325f51eb, 0xd59bc0d1, 0xf2bcc18f, 0x41113564,
229                         0x257b7834, 0x602a9c60, 0xdff8e8a3, 0x1f636c1b,
230                         0x0e12b4c2, 0x02e1329e, 0xaf664fd1, 0xcad18115,
231                         0x6b2395e0, 0x333e92e1, 0x3b240b62, 0xeebeb922,
232                         0x85b2a20e, 0xe6ba0d99, 0xde720c8c, 0x2da2f728,
233                         0xd0127845, 0x95b794fd, 0x647d0862, 0xe7ccf5f0,
234                         0x5449a36f, 0x877d48fa, 0xc39dfd27, 0xf33e8d1e,
235                         0x0a476341, 0x992eff74, 0x3a6f6eab, 0xf4f8fd37,
236                         0xa812dc60, 0xa1ebddf8, 0x991be14c, 0xdb6e6b0d,
237                         0xc67b5510, 0x6d672c37, 0x2765d43b, 0xdcd0e804,
238                         0xf1290dc7, 0xcc00ffa3, 0xb5390f92, 0x690fed0b,
239                         0x667b9ffb, 0xcedb7d9c, 0xa091cf0b, 0xd9155ea3,
240                         0xbb132f88, 0x515bad24, 0x7b9479bf, 0x763bd6eb,
241                         0x37392eb3, 0xcc115979, 0x8026e297, 0xf42e312d,
242                         0x6842ada7, 0xc66a2b3b, 0x12754ccc, 0x782ef11c,
243                         0x6a124237, 0xb79251e7, 0x06a1bbe6, 0x4bfb6350,
244                         0x1a6b1018, 0x11caedfa, 0x3d25bdd8, 0xe2e1c3c9,
245                         0x44421659, 0x0a121386, 0xd90cec6e, 0xd5abea2a,
246                         0x64af674e, 0xda86a85f, 0xbebfe988, 0x64e4c3fe,
247                         0x9dbc8057, 0xf0f7c086, 0x60787bf8, 0x6003604d,
248                         0xd1fd8346, 0xf6381fb0, 0x7745ae04, 0xd736fccc,
249                         0x83426b33, 0xf01eab71, 0xb0804187, 0x3c005e5f,
250                         0x77a057be, 0xbde8ae24, 0x55464299, 0xbf582e61,
251                         0x4e58f48f, 0xf2ddfda2, 0xf474ef38, 0x8789bdc2,
252                         0x5366f9c3, 0xc8b38e74, 0xb475f255, 0x46fcd9b9,
253                         0x7aeb2661, 0x8b1ddf84, 0x846a0e79, 0x915f95e2,
254                         0x466e598e, 0x20b45770, 0x8cd55591, 0xc902de4c,
255                         0xb90bace1, 0xbb8205d0, 0x11a86248, 0x7574a99e,
256                         0xb77f19b6, 0xe0a9dc09, 0x662d09a1, 0xc4324633,
257                         0xe85a1f02, 0x09f0be8c, 0x4a99a025, 0x1d6efe10,
258                         0x1ab93d1d, 0x0ba5a4df, 0xa186f20f, 0x2868f169,
259                         0xdcb7da83, 0x573906fe, 0xa1e2ce9b, 0x4fcd7f52,
260                         0x50115e01, 0xa70683fa, 0xa002b5c4, 0x0de6d027,
261                         0x9af88c27, 0x773f8641, 0xc3604c06, 0x61a806b5,
262                         0xf0177a28, 0xc0f586e0, 0x006058aa, 0x30dc7d62,
263                         0x11e69ed7, 0x2338ea63, 0x53c2dd94, 0xc2c21634,
264                         0xbbcbee56, 0x90bcb6de, 0xebfc7da1, 0xce591d76,
265                         0x6f05e409, 0x4b7c0188, 0x39720a3d, 0x7c927c24,
266                         0x86e3725f, 0x724d9db9, 0x1ac15bb4, 0xd39eb8fc,
267                         0xed545578, 0x08fca5b5, 0xd83d7cd3, 0x4dad0fc4,
268                         0x1e50ef5e, 0xb161e6f8, 0xa28514d9, 0x6c51133c,
269                         0x6fd5c7e7, 0x56e14ec4, 0x362abfce, 0xddc6c837,
270                         0xd79a3234, 0x92638212, 0x670efa8e, 0x406000e0
271                 }, {
272                         0x3a39ce37, 0xd3faf5cf, 0xabc27737, 0x5ac52d1b,
273                         0x5cb0679e, 0x4fa33742, 0xd3822740, 0x99bc9bbe,
274                         0xd5118e9d, 0xbf0f7315, 0xd62d1c7e, 0xc700c47b,
275                         0xb78c1b6b, 0x21a19045, 0xb26eb1be, 0x6a366eb4,
276                         0x5748ab2f, 0xbc946e79, 0xc6a376d2, 0x6549c2c8,
277                         0x530ff8ee, 0x468dde7d, 0xd5730a1d, 0x4cd04dc6,
278                         0x2939bbdb, 0xa9ba4650, 0xac9526e8, 0xbe5ee304,
279                         0xa1fad5f0, 0x6a2d519a, 0x63ef8ce2, 0x9a86ee22,
280                         0xc089c2b8, 0x43242ef6, 0xa51e03aa, 0x9cf2d0a4,
281                         0x83c061ba, 0x9be96a4d, 0x8fe51550, 0xba645bd6,
282                         0x2826a2f9, 0xa73a3ae1, 0x4ba99586, 0xef5562e9,
283                         0xc72fefd3, 0xf752f7da, 0x3f046f69, 0x77fa0a59,
284                         0x80e4a915, 0x87b08601, 0x9b09e6ad, 0x3b3ee593,
285                         0xe990fd5a, 0x9e34d797, 0x2cf0b7d9, 0x022b8b51,
286                         0x96d5ac3a, 0x017da67d, 0xd1cf3ed6, 0x7c7d2d28,
287                         0x1f9f25cf, 0xadf2b89b, 0x5ad6b472, 0x5a88f54c,
288                         0xe029ac71, 0xe019a5e6, 0x47b0acfd, 0xed93fa9b,
289                         0xe8d3c48d, 0x283b57cc, 0xf8d56629, 0x79132e28,
290                         0x785f0191, 0xed756055, 0xf7960e44, 0xe3d35e8c,
291                         0x15056dd4, 0x88f46dba, 0x03a16125, 0x0564f0bd,
292                         0xc3eb9e15, 0x3c9057a2, 0x97271aec, 0xa93a072a,
293                         0x1b3f6d9b, 0x1e6321f5, 0xf59c66fb, 0x26dcf319,
294                         0x7533d928, 0xb155fdf5, 0x03563482, 0x8aba3cbb,
295                         0x28517711, 0xc20ad9f8, 0xabcc5167, 0xccad925f,
296                         0x4de81751, 0x3830dc8e, 0x379d5862, 0x9320f991,
297                         0xea7a90c2, 0xfb3e7bce, 0x5121ce64, 0x774fbe32,
298                         0xa8b6e37e, 0xc3293d46, 0x48de5369, 0x6413e680,
299                         0xa2ae0810, 0xdd6db224, 0x69852dfd, 0x09072166,
300                         0xb39a460a, 0x6445c0dd, 0x586cdecf, 0x1c20c8ae,
301                         0x5bbef7dd, 0x1b588d40, 0xccd2017f, 0x6bb4e3bb,
302                         0xdda26a7e, 0x3a59ff45, 0x3e350a44, 0xbcb4cdd5,
303                         0x72eacea8, 0xfa6484bb, 0x8d6612ae, 0xbf3c6f47,
304                         0xd29be463, 0x542f5d9e, 0xaec2771b, 0xf64e6370,
305                         0x740e0d8d, 0xe75b1357, 0xf8721671, 0xaf537d5d,
306                         0x4040cb08, 0x4eb4e2cc, 0x34d2466a, 0x0115af84,
307                         0xe1b00428, 0x95983a1d, 0x06b89fb4, 0xce6ea048,
308                         0x6f3f3b82, 0x3520ab82, 0x011a1d4b, 0x277227f8,
309                         0x611560b1, 0xe7933fdc, 0xbb3a792b, 0x344525bd,
310                         0xa08839e1, 0x51ce794b, 0x2f32c9b7, 0xa01fbac9,
311                         0xe01cc87e, 0xbcc7d1f6, 0xcf0111c3, 0xa1e8aac7,
312                         0x1a908749, 0xd44fbd9a, 0xd0dadecb, 0xd50ada38,
313                         0x0339c32a, 0xc6913667, 0x8df9317c, 0xe0b12b4f,
314                         0xf79e59b7, 0x43f5bb3a, 0xf2d519ff, 0x27d9459c,
315                         0xbf97222c, 0x15e6fc2a, 0x0f91fc71, 0x9b941525,
316                         0xfae59361, 0xceb69ceb, 0xc2a86459, 0x12baa8d1,
317                         0xb6c1075e, 0xe3056a0c, 0x10d25065, 0xcb03a442,
318                         0xe0ec6e0e, 0x1698db3b, 0x4c98a0be, 0x3278e964,
319                         0x9f1f9532, 0xe0d392df, 0xd3a0342b, 0x8971f21e,
320                         0x1b0a7441, 0x4ba3348c, 0xc5be7120, 0xc37632d8,
321                         0xdf359f8d, 0x9b992f2e, 0xe60b6f47, 0x0fe3f11d,
322                         0xe54cda54, 0x1edad891, 0xce6279cf, 0xcd3e7e6f,
323                         0x1618b166, 0xfd2c1d05, 0x848fd2c5, 0xf6fb2299,
324                         0xf523f357, 0xa6327623, 0x93a83531, 0x56cccd02,
325                         0xacf08162, 0x5a75ebb5, 0x6e163697, 0x88d273cc,
326                         0xde966292, 0x81b949d0, 0x4c50901b, 0x71c65614,
327                         0xe6c6c7bd, 0x327a140a, 0x45e1d006, 0xc3f27b9a,
328                         0xc9aa53fd, 0x62a80f00, 0xbb25bfe2, 0x35bdd2f6,
329                         0x71126905, 0xb2040222, 0xb6cbcf7c, 0xcd769c2b,
330                         0x53113ec0, 0x1640e3d3, 0x38abbd60, 0x2547adf0,
331                         0xba38209c, 0xf746ce76, 0x77afa1c5, 0x20756060,
332                         0x85cbfe4e, 0x8ae88dd8, 0x7aaaf9b0, 0x4cf9aa7e,
333                         0x1948c25c, 0x02fb8a8c, 0x01c36ae4, 0xd6ebe1f9,
334                         0x90d4f869, 0xa65cdea0, 0x3f09252d, 0xc208e69f,
335                         0xb74e6132, 0xce77e25b, 0x578fdfe3, 0x3ac372e6
336                 }
337         }, {
338                 0x243f6a88, 0x85a308d3, 0x13198a2e, 0x03707344,
339                 0xa4093822, 0x299f31d0, 0x082efa98, 0xec4e6c89,
340                 0x452821e6, 0x38d01377, 0xbe5466cf, 0x34e90c6c,
341                 0xc0ac29b7, 0xc97c50dd, 0x3f84d5b5, 0xb5470917,
342                 0x9216d5d9, 0x8979fb1b
343         }
344 };
345
346 static unsigned char BF_itoa64[64 + 1] =
347 "./ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789";
348
349 static unsigned char BF_atoi64[0x60] = {
350         64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 0, 1,
351         54, 55, 56, 57, 58, 59, 60, 61, 62, 63, 64, 64, 64, 64, 64, 64,
352         64, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16,
353         17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 64, 64, 64, 64, 64,
354         64, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42,
355         43, 44, 45, 46, 47, 48, 49, 50, 51, 52, 53, 64, 64, 64, 64, 64
356 };
357
358 #define BF_safe_atoi64(dst, src) \
359 do { \
360         tmp = (unsigned char)(src); \
361         if ((unsigned int)(tmp -= 0x20) >= 0x60) return -1; \
362         tmp = BF_atoi64[tmp]; \
363         if (tmp > 63) return -1; \
364         (dst) = tmp; \
365 } while (0)
366
367 static int
368 BF_decode(BF_word * dst, const char *src, int size)
369 {
370         unsigned char *dptr = (unsigned char *) dst;
371         unsigned char *end = dptr + size;
372         unsigned char *sptr = (unsigned char *) src;
373         unsigned int tmp,
374                                 c1,
375                                 c2,
376                                 c3,
377                                 c4;
378
379         do
380         {
381                 BF_safe_atoi64(c1, *sptr++);
382                 BF_safe_atoi64(c2, *sptr++);
383                 *dptr++ = (c1 << 2) | ((c2 & 0x30) >> 4);
384                 if (dptr >= end)
385                         break;
386
387                 BF_safe_atoi64(c3, *sptr++);
388                 *dptr++ = ((c2 & 0x0F) << 4) | ((c3 & 0x3C) >> 2);
389                 if (dptr >= end)
390                         break;
391
392                 BF_safe_atoi64(c4, *sptr++);
393                 *dptr++ = ((c3 & 0x03) << 6) | c4;
394         } while (dptr < end);
395
396         return 0;
397 }
398
399 static void
400 BF_encode(char *dst, const BF_word * src, int size)
401 {
402         unsigned char *sptr = (unsigned char *) src;
403         unsigned char *end = sptr + size;
404         unsigned char *dptr = (unsigned char *) dst;
405         unsigned int c1,
406                                 c2;
407
408         do
409         {
410                 c1 = *sptr++;
411                 *dptr++ = BF_itoa64[c1 >> 2];
412                 c1 = (c1 & 0x03) << 4;
413                 if (sptr >= end)
414                 {
415                         *dptr++ = BF_itoa64[c1];
416                         break;
417                 }
418
419                 c2 = *sptr++;
420                 c1 |= c2 >> 4;
421                 *dptr++ = BF_itoa64[c1];
422                 c1 = (c2 & 0x0f) << 2;
423                 if (sptr >= end)
424                 {
425                         *dptr++ = BF_itoa64[c1];
426                         break;
427                 }
428
429                 c2 = *sptr++;
430                 c1 |= c2 >> 6;
431                 *dptr++ = BF_itoa64[c1];
432                 *dptr++ = BF_itoa64[c2 & 0x3f];
433         } while (sptr < end);
434 }
435
436 static void
437 BF_swap(BF_word * x, int count)
438 {
439         static int      endianness_check = 1;
440         char       *is_little_endian = (char *) &endianness_check;
441         BF_word         tmp;
442
443         if (*is_little_endian)
444                 do
445                 {
446                         tmp = *x;
447                         tmp = (tmp << 16) | (tmp >> 16);
448                         *x++ = ((tmp & 0x00FF00FF) << 8) | ((tmp >> 8) & 0x00FF00FF);
449                 } while (--count);
450 }
451
452 #if BF_SCALE
453 /* Architectures which can shift addresses left by 2 bits with no extra cost */
454 #define BF_ROUND(L, R, N) \
455         tmp1 = (L) & 0xFF; \
456         tmp2 = (L) >> 8; \
457         tmp2 &= 0xFF; \
458         tmp3 = (L) >> 16; \
459         tmp3 &= 0xFF; \
460         tmp4 = (L) >> 24; \
461         tmp1 = data.ctx.S[3][tmp1]; \
462         tmp2 = data.ctx.S[2][tmp2]; \
463         tmp3 = data.ctx.S[1][tmp3]; \
464         tmp3 += data.ctx.S[0][tmp4]; \
465         tmp3 ^= tmp2; \
466         (R) ^= data.ctx.P[(N) + 1]; \
467         tmp3 += tmp1; \
468         (R) ^= tmp3;
469 #else
470 /* Architectures with no complicated addressing modes supported */
471 #define BF_INDEX(S, i) \
472         (*((BF_word *)(((unsigned char *)(S)) + (i))))
473 #define BF_ROUND(L, R, N) \
474         tmp1 = (L) & 0xFF; \
475         tmp1 <<= 2; \
476         tmp2 = (L) >> 6; \
477         tmp2 &= 0x3FC; \
478         tmp3 = (L) >> 14; \
479         tmp3 &= 0x3FC; \
480         tmp4 = (L) >> 22; \
481         tmp4 &= 0x3FC; \
482         tmp1 = BF_INDEX(data.ctx.S[3], tmp1); \
483         tmp2 = BF_INDEX(data.ctx.S[2], tmp2); \
484         tmp3 = BF_INDEX(data.ctx.S[1], tmp3); \
485         tmp3 += BF_INDEX(data.ctx.S[0], tmp4); \
486         tmp3 ^= tmp2; \
487         (R) ^= data.ctx.P[(N) + 1]; \
488         tmp3 += tmp1; \
489         (R) ^= tmp3;
490 #endif
491
492 /*
493  * Encrypt one block, BF_N is hardcoded here.
494  */
495 #define BF_ENCRYPT \
496         L ^= data.ctx.P[0]; \
497         BF_ROUND(L, R, 0); \
498         BF_ROUND(R, L, 1); \
499         BF_ROUND(L, R, 2); \
500         BF_ROUND(R, L, 3); \
501         BF_ROUND(L, R, 4); \
502         BF_ROUND(R, L, 5); \
503         BF_ROUND(L, R, 6); \
504         BF_ROUND(R, L, 7); \
505         BF_ROUND(L, R, 8); \
506         BF_ROUND(R, L, 9); \
507         BF_ROUND(L, R, 10); \
508         BF_ROUND(R, L, 11); \
509         BF_ROUND(L, R, 12); \
510         BF_ROUND(R, L, 13); \
511         BF_ROUND(L, R, 14); \
512         BF_ROUND(R, L, 15); \
513         tmp4 = R; \
514         R = L; \
515         L = tmp4 ^ data.ctx.P[BF_N + 1];
516
517 #if BF_ASM
518
519 extern void _BF_body_r(BF_ctx * ctx);
520
521 #define BF_body() \
522         _BF_body_r(&data.ctx);
523 #else
524
525 #define BF_body() \
526         L = R = 0; \
527         ptr = data.ctx.P; \
528         do { \
529                 ptr += 2; \
530                 BF_ENCRYPT; \
531                 *(ptr - 2) = L; \
532                 *(ptr - 1) = R; \
533         } while (ptr < &data.ctx.P[BF_N + 2]); \
534 \
535         ptr = data.ctx.S[0]; \
536         do { \
537                 ptr += 2; \
538                 BF_ENCRYPT; \
539                 *(ptr - 2) = L; \
540                 *(ptr - 1) = R; \
541         } while (ptr < &data.ctx.S[3][0xFF]);
542 #endif
543
544 static void
545 BF_set_key(const char *key, BF_key expanded, BF_key initial)
546 {
547         const char *ptr = key;
548         int                     i,
549                                 j;
550         BF_word         tmp;
551
552         for (i = 0; i < BF_N + 2; i++)
553         {
554                 tmp = 0;
555                 for (j = 0; j < 4; j++)
556                 {
557                         tmp <<= 8;
558                         tmp |= *ptr;
559
560                         if (!*ptr)
561                                 ptr = key;
562                         else
563                                 ptr++;
564                 }
565
566                 expanded[i] = tmp;
567                 initial[i] = BF_init_state.P[i] ^ tmp;
568         }
569 }
570
571 char *
572 _crypt_blowfish_rn(const char *key, const char *setting,
573                                    char *output, int size)
574 {
575         struct
576         {
577                 BF_ctx          ctx;
578                 BF_key          expanded_key;
579                 union
580                 {
581                         BF_word         salt[4];
582                         BF_word         output[6];
583                 }                       binary;
584         }                       data;
585         BF_word         L,
586                                 R;
587         BF_word         tmp1,
588                                 tmp2,
589                                 tmp3,
590                                 tmp4;
591         BF_word    *ptr;
592         BF_word         count;
593         int                     i;
594
595         if (size < 7 + 22 + 31 + 1)
596                 return NULL;
597
598         if (setting[0] != '$' ||
599                 setting[1] != '2' ||
600                 setting[2] != 'a' ||
601                 setting[3] != '$' ||
602                 setting[4] < '0' || setting[4] > '3' ||
603                 setting[5] < '0' || setting[5] > '9' ||
604                 setting[6] != '$')
605         {
606                 return NULL;
607         }
608
609         count = (BF_word) 1 << ((setting[4] - '0') * 10 + (setting[5] - '0'));
610         if (count < 16 || BF_decode(data.binary.salt, &setting[7], 16))
611         {
612                 memset(data.binary.salt, 0, sizeof(data.binary.salt));
613                 return NULL;
614         }
615         BF_swap(data.binary.salt, 4);
616
617         BF_set_key(key, data.expanded_key, data.ctx.P);
618
619         memcpy(data.ctx.S, BF_init_state.S, sizeof(data.ctx.S));
620
621         L = R = 0;
622         for (i = 0; i < BF_N + 2; i += 2)
623         {
624                 L ^= data.binary.salt[i & 2];
625                 R ^= data.binary.salt[(i & 2) + 1];
626                 BF_ENCRYPT;
627                 data.ctx.P[i] = L;
628                 data.ctx.P[i + 1] = R;
629         }
630
631         ptr = data.ctx.S[0];
632         do
633         {
634                 ptr += 4;
635                 L ^= data.binary.salt[(BF_N + 2) & 3];
636                 R ^= data.binary.salt[(BF_N + 3) & 3];
637                 BF_ENCRYPT;
638                 *(ptr - 4) = L;
639                 *(ptr - 3) = R;
640
641                 L ^= data.binary.salt[(BF_N + 4) & 3];
642                 R ^= data.binary.salt[(BF_N + 5) & 3];
643                 BF_ENCRYPT;
644                 *(ptr - 2) = L;
645                 *(ptr - 1) = R;
646         } while (ptr < &data.ctx.S[3][0xFF]);
647
648         do
649         {
650                 data.ctx.P[0] ^= data.expanded_key[0];
651                 data.ctx.P[1] ^= data.expanded_key[1];
652                 data.ctx.P[2] ^= data.expanded_key[2];
653                 data.ctx.P[3] ^= data.expanded_key[3];
654                 data.ctx.P[4] ^= data.expanded_key[4];
655                 data.ctx.P[5] ^= data.expanded_key[5];
656                 data.ctx.P[6] ^= data.expanded_key[6];
657                 data.ctx.P[7] ^= data.expanded_key[7];
658                 data.ctx.P[8] ^= data.expanded_key[8];
659                 data.ctx.P[9] ^= data.expanded_key[9];
660                 data.ctx.P[10] ^= data.expanded_key[10];
661                 data.ctx.P[11] ^= data.expanded_key[11];
662                 data.ctx.P[12] ^= data.expanded_key[12];
663                 data.ctx.P[13] ^= data.expanded_key[13];
664                 data.ctx.P[14] ^= data.expanded_key[14];
665                 data.ctx.P[15] ^= data.expanded_key[15];
666                 data.ctx.P[16] ^= data.expanded_key[16];
667                 data.ctx.P[17] ^= data.expanded_key[17];
668
669                 BF_body();
670
671                 tmp1 = data.binary.salt[0];
672                 tmp2 = data.binary.salt[1];
673                 tmp3 = data.binary.salt[2];
674                 tmp4 = data.binary.salt[3];
675                 data.ctx.P[0] ^= tmp1;
676                 data.ctx.P[1] ^= tmp2;
677                 data.ctx.P[2] ^= tmp3;
678                 data.ctx.P[3] ^= tmp4;
679                 data.ctx.P[4] ^= tmp1;
680                 data.ctx.P[5] ^= tmp2;
681                 data.ctx.P[6] ^= tmp3;
682                 data.ctx.P[7] ^= tmp4;
683                 data.ctx.P[8] ^= tmp1;
684                 data.ctx.P[9] ^= tmp2;
685                 data.ctx.P[10] ^= tmp3;
686                 data.ctx.P[11] ^= tmp4;
687                 data.ctx.P[12] ^= tmp1;
688                 data.ctx.P[13] ^= tmp2;
689                 data.ctx.P[14] ^= tmp3;
690                 data.ctx.P[15] ^= tmp4;
691                 data.ctx.P[16] ^= tmp1;
692                 data.ctx.P[17] ^= tmp2;
693
694                 BF_body();
695         } while (--count);
696
697         for (i = 0; i < 6; i += 2)
698         {
699                 L = BF_magic_w[i];
700                 R = BF_magic_w[i + 1];
701
702                 count = 64;
703                 do
704                 {
705                         BF_ENCRYPT;
706                 } while (--count);
707
708                 data.binary.output[i] = L;
709                 data.binary.output[i + 1] = R;
710         }
711
712         memcpy(output, setting, 7 + 22 - 1);
713         output[7 + 22 - 1] = BF_itoa64[(int)
714                                                  BF_atoi64[(int) setting[7 + 22 - 1] - 0x20] & 0x30];
715
716 /* This has to be bug-compatible with the original implementation, so
717  * only encode 23 of the 24 bytes. :-) */
718         BF_swap(data.binary.output, 6);
719         BF_encode(&output[7 + 22], data.binary.output, 23);
720         output[7 + 22 + 31] = '\0';
721
722 /* Overwrite the most obvious sensitive data we have on the stack. Note
723  * that this does not guarantee there's no sensitive data left on the
724  * stack and/or in registers; I'm not aware of portable code that does. */
725         memset(&data, 0, sizeof(data));
726
727         return output;
728 }