]> git.proxmox.com Git - efi-boot-shim.git/blame - crypt_blowfish.c
d/control: add empty version pinning package
[efi-boot-shim.git] / crypt_blowfish.c
CommitLineData
031e5cce 1// SPDX-License-Identifier: BSD-2-Clause-Patent
72bb39c0
SL
2/*
3 * The crypt_blowfish homepage is:
4 *
5 * http://www.openwall.com/crypt/
6 *
7 * This code comes from John the Ripper password cracker, with reentrant
8 * and crypt(3) interfaces added, but optimizations specific to password
9 * cracking removed.
10 *
11 * Written by Solar Designer <solar at openwall.com> in 1998-2011.
12 * No copyright is claimed, and the software is hereby placed in the public
13 * domain. In case this attempt to disclaim copyright and place the software
14 * in the public domain is deemed null and void, then the software is
15 * Copyright (c) 1998-2011 Solar Designer and it is hereby released to the
16 * general public under the following terms:
17 *
18 * Redistribution and use in source and binary forms, with or without
19 * modification, are permitted.
20 *
21 * There's ABSOLUTELY NO WARRANTY, express or implied.
22 *
23 * It is my intent that you should be able to use this on your system,
24 * as part of a software package, or anywhere else to improve security,
25 * ensure compatibility, or for any other purpose. I would appreciate
26 * it if you give credit where it is due and keep your modifications in
27 * the public domain as well, but I don't require that in order to let
28 * you place this code and any modifications you make under a license
29 * of your choice.
30 *
31 * This implementation is mostly compatible with OpenBSD's bcrypt.c (prefix
32 * "$2a$") by Niels Provos <provos at citi.umich.edu>, and uses some of his
33 * ideas. The password hashing algorithm was designed by David Mazieres
34 * <dm at lcs.mit.edu>. For more information on the level of compatibility,
35 * prefer refer to the comments in BF_set_key() below and to the included
36 * crypt(3) man page.
37 *
38 * There's a paper on the algorithm that explains its design decisions:
39 *
40 * http://www.usenix.org/events/usenix99/provos.html
41 *
42 * Some of the tricks in BF_ROUND might be inspired by Eric Young's
43 * Blowfish library (I can't be sure if I would think of something if I
44 * hadn't seen his code).
45 */
f892ac66 46#include "shim.h"
72bb39c0
SL
47
48typedef unsigned int BF_word;
49typedef signed int BF_word_signed;
50
51/* Number of Blowfish rounds, this is also hardcoded into a few places */
52#define BF_N 16
53
54typedef BF_word BF_key[BF_N + 2];
55
56typedef struct {
57 BF_word S[4][0x100];
58 BF_key P;
59} BF_ctx;
60
61/*
62 * Magic IV for 64 Blowfish encryptions that we do at the end.
63 * The string is "OrpheanBeholderScryDoubt" on big-endian.
64 */
65static BF_word BF_magic_w[6] = {
66 0x4F727068, 0x65616E42, 0x65686F6C,
67 0x64657253, 0x63727944, 0x6F756274
68};
69
70/*
71 * P-box and S-box tables initialized with digits of Pi.
72 */
73static BF_ctx BF_init_state = {
74 {
75 {
76 0xd1310ba6, 0x98dfb5ac, 0x2ffd72db, 0xd01adfb7,
77 0xb8e1afed, 0x6a267e96, 0xba7c9045, 0xf12c7f99,
78 0x24a19947, 0xb3916cf7, 0x0801f2e2, 0x858efc16,
79 0x636920d8, 0x71574e69, 0xa458fea3, 0xf4933d7e,
80 0x0d95748f, 0x728eb658, 0x718bcd58, 0x82154aee,
81 0x7b54a41d, 0xc25a59b5, 0x9c30d539, 0x2af26013,
82 0xc5d1b023, 0x286085f0, 0xca417918, 0xb8db38ef,
83 0x8e79dcb0, 0x603a180e, 0x6c9e0e8b, 0xb01e8a3e,
84 0xd71577c1, 0xbd314b27, 0x78af2fda, 0x55605c60,
85 0xe65525f3, 0xaa55ab94, 0x57489862, 0x63e81440,
86 0x55ca396a, 0x2aab10b6, 0xb4cc5c34, 0x1141e8ce,
87 0xa15486af, 0x7c72e993, 0xb3ee1411, 0x636fbc2a,
88 0x2ba9c55d, 0x741831f6, 0xce5c3e16, 0x9b87931e,
89 0xafd6ba33, 0x6c24cf5c, 0x7a325381, 0x28958677,
90 0x3b8f4898, 0x6b4bb9af, 0xc4bfe81b, 0x66282193,
91 0x61d809cc, 0xfb21a991, 0x487cac60, 0x5dec8032,
92 0xef845d5d, 0xe98575b1, 0xdc262302, 0xeb651b88,
93 0x23893e81, 0xd396acc5, 0x0f6d6ff3, 0x83f44239,
94 0x2e0b4482, 0xa4842004, 0x69c8f04a, 0x9e1f9b5e,
95 0x21c66842, 0xf6e96c9a, 0x670c9c61, 0xabd388f0,
96 0x6a51a0d2, 0xd8542f68, 0x960fa728, 0xab5133a3,
97 0x6eef0b6c, 0x137a3be4, 0xba3bf050, 0x7efb2a98,
98 0xa1f1651d, 0x39af0176, 0x66ca593e, 0x82430e88,
99 0x8cee8619, 0x456f9fb4, 0x7d84a5c3, 0x3b8b5ebe,
100 0xe06f75d8, 0x85c12073, 0x401a449f, 0x56c16aa6,
101 0x4ed3aa62, 0x363f7706, 0x1bfedf72, 0x429b023d,
102 0x37d0d724, 0xd00a1248, 0xdb0fead3, 0x49f1c09b,
103 0x075372c9, 0x80991b7b, 0x25d479d8, 0xf6e8def7,
104 0xe3fe501a, 0xb6794c3b, 0x976ce0bd, 0x04c006ba,
105 0xc1a94fb6, 0x409f60c4, 0x5e5c9ec2, 0x196a2463,
106 0x68fb6faf, 0x3e6c53b5, 0x1339b2eb, 0x3b52ec6f,
107 0x6dfc511f, 0x9b30952c, 0xcc814544, 0xaf5ebd09,
108 0xbee3d004, 0xde334afd, 0x660f2807, 0x192e4bb3,
109 0xc0cba857, 0x45c8740f, 0xd20b5f39, 0xb9d3fbdb,
110 0x5579c0bd, 0x1a60320a, 0xd6a100c6, 0x402c7279,
111 0x679f25fe, 0xfb1fa3cc, 0x8ea5e9f8, 0xdb3222f8,
112 0x3c7516df, 0xfd616b15, 0x2f501ec8, 0xad0552ab,
113 0x323db5fa, 0xfd238760, 0x53317b48, 0x3e00df82,
114 0x9e5c57bb, 0xca6f8ca0, 0x1a87562e, 0xdf1769db,
115 0xd542a8f6, 0x287effc3, 0xac6732c6, 0x8c4f5573,
116 0x695b27b0, 0xbbca58c8, 0xe1ffa35d, 0xb8f011a0,
117 0x10fa3d98, 0xfd2183b8, 0x4afcb56c, 0x2dd1d35b,
118 0x9a53e479, 0xb6f84565, 0xd28e49bc, 0x4bfb9790,
119 0xe1ddf2da, 0xa4cb7e33, 0x62fb1341, 0xcee4c6e8,
120 0xef20cada, 0x36774c01, 0xd07e9efe, 0x2bf11fb4,
121 0x95dbda4d, 0xae909198, 0xeaad8e71, 0x6b93d5a0,
122 0xd08ed1d0, 0xafc725e0, 0x8e3c5b2f, 0x8e7594b7,
123 0x8ff6e2fb, 0xf2122b64, 0x8888b812, 0x900df01c,
124 0x4fad5ea0, 0x688fc31c, 0xd1cff191, 0xb3a8c1ad,
125 0x2f2f2218, 0xbe0e1777, 0xea752dfe, 0x8b021fa1,
126 0xe5a0cc0f, 0xb56f74e8, 0x18acf3d6, 0xce89e299,
127 0xb4a84fe0, 0xfd13e0b7, 0x7cc43b81, 0xd2ada8d9,
128 0x165fa266, 0x80957705, 0x93cc7314, 0x211a1477,
129 0xe6ad2065, 0x77b5fa86, 0xc75442f5, 0xfb9d35cf,
130 0xebcdaf0c, 0x7b3e89a0, 0xd6411bd3, 0xae1e7e49,
131 0x00250e2d, 0x2071b35e, 0x226800bb, 0x57b8e0af,
132 0x2464369b, 0xf009b91e, 0x5563911d, 0x59dfa6aa,
133 0x78c14389, 0xd95a537f, 0x207d5ba2, 0x02e5b9c5,
134 0x83260376, 0x6295cfa9, 0x11c81968, 0x4e734a41,
135 0xb3472dca, 0x7b14a94a, 0x1b510052, 0x9a532915,
136 0xd60f573f, 0xbc9bc6e4, 0x2b60a476, 0x81e67400,
137 0x08ba6fb5, 0x571be91f, 0xf296ec6b, 0x2a0dd915,
138 0xb6636521, 0xe7b9f9b6, 0xff34052e, 0xc5855664,
139 0x53b02d5d, 0xa99f8fa1, 0x08ba4799, 0x6e85076a
140 }, {
141 0x4b7a70e9, 0xb5b32944, 0xdb75092e, 0xc4192623,
142 0xad6ea6b0, 0x49a7df7d, 0x9cee60b8, 0x8fedb266,
143 0xecaa8c71, 0x699a17ff, 0x5664526c, 0xc2b19ee1,
144 0x193602a5, 0x75094c29, 0xa0591340, 0xe4183a3e,
145 0x3f54989a, 0x5b429d65, 0x6b8fe4d6, 0x99f73fd6,
146 0xa1d29c07, 0xefe830f5, 0x4d2d38e6, 0xf0255dc1,
147 0x4cdd2086, 0x8470eb26, 0x6382e9c6, 0x021ecc5e,
148 0x09686b3f, 0x3ebaefc9, 0x3c971814, 0x6b6a70a1,
149 0x687f3584, 0x52a0e286, 0xb79c5305, 0xaa500737,
150 0x3e07841c, 0x7fdeae5c, 0x8e7d44ec, 0x5716f2b8,
151 0xb03ada37, 0xf0500c0d, 0xf01c1f04, 0x0200b3ff,
152 0xae0cf51a, 0x3cb574b2, 0x25837a58, 0xdc0921bd,
153 0xd19113f9, 0x7ca92ff6, 0x94324773, 0x22f54701,
154 0x3ae5e581, 0x37c2dadc, 0xc8b57634, 0x9af3dda7,
155 0xa9446146, 0x0fd0030e, 0xecc8c73e, 0xa4751e41,
156 0xe238cd99, 0x3bea0e2f, 0x3280bba1, 0x183eb331,
157 0x4e548b38, 0x4f6db908, 0x6f420d03, 0xf60a04bf,
158 0x2cb81290, 0x24977c79, 0x5679b072, 0xbcaf89af,
159 0xde9a771f, 0xd9930810, 0xb38bae12, 0xdccf3f2e,
160 0x5512721f, 0x2e6b7124, 0x501adde6, 0x9f84cd87,
161 0x7a584718, 0x7408da17, 0xbc9f9abc, 0xe94b7d8c,
162 0xec7aec3a, 0xdb851dfa, 0x63094366, 0xc464c3d2,
163 0xef1c1847, 0x3215d908, 0xdd433b37, 0x24c2ba16,
164 0x12a14d43, 0x2a65c451, 0x50940002, 0x133ae4dd,
165 0x71dff89e, 0x10314e55, 0x81ac77d6, 0x5f11199b,
166 0x043556f1, 0xd7a3c76b, 0x3c11183b, 0x5924a509,
167 0xf28fe6ed, 0x97f1fbfa, 0x9ebabf2c, 0x1e153c6e,
168 0x86e34570, 0xeae96fb1, 0x860e5e0a, 0x5a3e2ab3,
169 0x771fe71c, 0x4e3d06fa, 0x2965dcb9, 0x99e71d0f,
170 0x803e89d6, 0x5266c825, 0x2e4cc978, 0x9c10b36a,
171 0xc6150eba, 0x94e2ea78, 0xa5fc3c53, 0x1e0a2df4,
172 0xf2f74ea7, 0x361d2b3d, 0x1939260f, 0x19c27960,
173 0x5223a708, 0xf71312b6, 0xebadfe6e, 0xeac31f66,
174 0xe3bc4595, 0xa67bc883, 0xb17f37d1, 0x018cff28,
175 0xc332ddef, 0xbe6c5aa5, 0x65582185, 0x68ab9802,
176 0xeecea50f, 0xdb2f953b, 0x2aef7dad, 0x5b6e2f84,
177 0x1521b628, 0x29076170, 0xecdd4775, 0x619f1510,
178 0x13cca830, 0xeb61bd96, 0x0334fe1e, 0xaa0363cf,
179 0xb5735c90, 0x4c70a239, 0xd59e9e0b, 0xcbaade14,
180 0xeecc86bc, 0x60622ca7, 0x9cab5cab, 0xb2f3846e,
181 0x648b1eaf, 0x19bdf0ca, 0xa02369b9, 0x655abb50,
182 0x40685a32, 0x3c2ab4b3, 0x319ee9d5, 0xc021b8f7,
183 0x9b540b19, 0x875fa099, 0x95f7997e, 0x623d7da8,
184 0xf837889a, 0x97e32d77, 0x11ed935f, 0x16681281,
185 0x0e358829, 0xc7e61fd6, 0x96dedfa1, 0x7858ba99,
186 0x57f584a5, 0x1b227263, 0x9b83c3ff, 0x1ac24696,
187 0xcdb30aeb, 0x532e3054, 0x8fd948e4, 0x6dbc3128,
188 0x58ebf2ef, 0x34c6ffea, 0xfe28ed61, 0xee7c3c73,
189 0x5d4a14d9, 0xe864b7e3, 0x42105d14, 0x203e13e0,
190 0x45eee2b6, 0xa3aaabea, 0xdb6c4f15, 0xfacb4fd0,
191 0xc742f442, 0xef6abbb5, 0x654f3b1d, 0x41cd2105,
192 0xd81e799e, 0x86854dc7, 0xe44b476a, 0x3d816250,
193 0xcf62a1f2, 0x5b8d2646, 0xfc8883a0, 0xc1c7b6a3,
194 0x7f1524c3, 0x69cb7492, 0x47848a0b, 0x5692b285,
195 0x095bbf00, 0xad19489d, 0x1462b174, 0x23820e00,
196 0x58428d2a, 0x0c55f5ea, 0x1dadf43e, 0x233f7061,
197 0x3372f092, 0x8d937e41, 0xd65fecf1, 0x6c223bdb,
198 0x7cde3759, 0xcbee7460, 0x4085f2a7, 0xce77326e,
199 0xa6078084, 0x19f8509e, 0xe8efd855, 0x61d99735,
200 0xa969a7aa, 0xc50c06c2, 0x5a04abfc, 0x800bcadc,
201 0x9e447a2e, 0xc3453484, 0xfdd56705, 0x0e1e9ec9,
202 0xdb73dbd3, 0x105588cd, 0x675fda79, 0xe3674340,
203 0xc5c43465, 0x713e38d8, 0x3d28f89e, 0xf16dff20,
204 0x153e21e7, 0x8fb03d4a, 0xe6e39f2b, 0xdb83adf7
205 }, {
206 0xe93d5a68, 0x948140f7, 0xf64c261c, 0x94692934,
207 0x411520f7, 0x7602d4f7, 0xbcf46b2e, 0xd4a20068,
208 0xd4082471, 0x3320f46a, 0x43b7d4b7, 0x500061af,
209 0x1e39f62e, 0x97244546, 0x14214f74, 0xbf8b8840,
210 0x4d95fc1d, 0x96b591af, 0x70f4ddd3, 0x66a02f45,
211 0xbfbc09ec, 0x03bd9785, 0x7fac6dd0, 0x31cb8504,
212 0x96eb27b3, 0x55fd3941, 0xda2547e6, 0xabca0a9a,
213 0x28507825, 0x530429f4, 0x0a2c86da, 0xe9b66dfb,
214 0x68dc1462, 0xd7486900, 0x680ec0a4, 0x27a18dee,
215 0x4f3ffea2, 0xe887ad8c, 0xb58ce006, 0x7af4d6b6,
216 0xaace1e7c, 0xd3375fec, 0xce78a399, 0x406b2a42,
217 0x20fe9e35, 0xd9f385b9, 0xee39d7ab, 0x3b124e8b,
218 0x1dc9faf7, 0x4b6d1856, 0x26a36631, 0xeae397b2,
219 0x3a6efa74, 0xdd5b4332, 0x6841e7f7, 0xca7820fb,
220 0xfb0af54e, 0xd8feb397, 0x454056ac, 0xba489527,
221 0x55533a3a, 0x20838d87, 0xfe6ba9b7, 0xd096954b,
222 0x55a867bc, 0xa1159a58, 0xcca92963, 0x99e1db33,
223 0xa62a4a56, 0x3f3125f9, 0x5ef47e1c, 0x9029317c,
224 0xfdf8e802, 0x04272f70, 0x80bb155c, 0x05282ce3,
225 0x95c11548, 0xe4c66d22, 0x48c1133f, 0xc70f86dc,
226 0x07f9c9ee, 0x41041f0f, 0x404779a4, 0x5d886e17,
227 0x325f51eb, 0xd59bc0d1, 0xf2bcc18f, 0x41113564,
228 0x257b7834, 0x602a9c60, 0xdff8e8a3, 0x1f636c1b,
229 0x0e12b4c2, 0x02e1329e, 0xaf664fd1, 0xcad18115,
230 0x6b2395e0, 0x333e92e1, 0x3b240b62, 0xeebeb922,
231 0x85b2a20e, 0xe6ba0d99, 0xde720c8c, 0x2da2f728,
232 0xd0127845, 0x95b794fd, 0x647d0862, 0xe7ccf5f0,
233 0x5449a36f, 0x877d48fa, 0xc39dfd27, 0xf33e8d1e,
234 0x0a476341, 0x992eff74, 0x3a6f6eab, 0xf4f8fd37,
235 0xa812dc60, 0xa1ebddf8, 0x991be14c, 0xdb6e6b0d,
236 0xc67b5510, 0x6d672c37, 0x2765d43b, 0xdcd0e804,
237 0xf1290dc7, 0xcc00ffa3, 0xb5390f92, 0x690fed0b,
238 0x667b9ffb, 0xcedb7d9c, 0xa091cf0b, 0xd9155ea3,
239 0xbb132f88, 0x515bad24, 0x7b9479bf, 0x763bd6eb,
240 0x37392eb3, 0xcc115979, 0x8026e297, 0xf42e312d,
241 0x6842ada7, 0xc66a2b3b, 0x12754ccc, 0x782ef11c,
242 0x6a124237, 0xb79251e7, 0x06a1bbe6, 0x4bfb6350,
243 0x1a6b1018, 0x11caedfa, 0x3d25bdd8, 0xe2e1c3c9,
244 0x44421659, 0x0a121386, 0xd90cec6e, 0xd5abea2a,
245 0x64af674e, 0xda86a85f, 0xbebfe988, 0x64e4c3fe,
246 0x9dbc8057, 0xf0f7c086, 0x60787bf8, 0x6003604d,
247 0xd1fd8346, 0xf6381fb0, 0x7745ae04, 0xd736fccc,
248 0x83426b33, 0xf01eab71, 0xb0804187, 0x3c005e5f,
249 0x77a057be, 0xbde8ae24, 0x55464299, 0xbf582e61,
250 0x4e58f48f, 0xf2ddfda2, 0xf474ef38, 0x8789bdc2,
251 0x5366f9c3, 0xc8b38e74, 0xb475f255, 0x46fcd9b9,
252 0x7aeb2661, 0x8b1ddf84, 0x846a0e79, 0x915f95e2,
253 0x466e598e, 0x20b45770, 0x8cd55591, 0xc902de4c,
254 0xb90bace1, 0xbb8205d0, 0x11a86248, 0x7574a99e,
255 0xb77f19b6, 0xe0a9dc09, 0x662d09a1, 0xc4324633,
256 0xe85a1f02, 0x09f0be8c, 0x4a99a025, 0x1d6efe10,
257 0x1ab93d1d, 0x0ba5a4df, 0xa186f20f, 0x2868f169,
258 0xdcb7da83, 0x573906fe, 0xa1e2ce9b, 0x4fcd7f52,
259 0x50115e01, 0xa70683fa, 0xa002b5c4, 0x0de6d027,
260 0x9af88c27, 0x773f8641, 0xc3604c06, 0x61a806b5,
261 0xf0177a28, 0xc0f586e0, 0x006058aa, 0x30dc7d62,
262 0x11e69ed7, 0x2338ea63, 0x53c2dd94, 0xc2c21634,
263 0xbbcbee56, 0x90bcb6de, 0xebfc7da1, 0xce591d76,
264 0x6f05e409, 0x4b7c0188, 0x39720a3d, 0x7c927c24,
265 0x86e3725f, 0x724d9db9, 0x1ac15bb4, 0xd39eb8fc,
266 0xed545578, 0x08fca5b5, 0xd83d7cd3, 0x4dad0fc4,
267 0x1e50ef5e, 0xb161e6f8, 0xa28514d9, 0x6c51133c,
268 0x6fd5c7e7, 0x56e14ec4, 0x362abfce, 0xddc6c837,
269 0xd79a3234, 0x92638212, 0x670efa8e, 0x406000e0
270 }, {
271 0x3a39ce37, 0xd3faf5cf, 0xabc27737, 0x5ac52d1b,
272 0x5cb0679e, 0x4fa33742, 0xd3822740, 0x99bc9bbe,
273 0xd5118e9d, 0xbf0f7315, 0xd62d1c7e, 0xc700c47b,
274 0xb78c1b6b, 0x21a19045, 0xb26eb1be, 0x6a366eb4,
275 0x5748ab2f, 0xbc946e79, 0xc6a376d2, 0x6549c2c8,
276 0x530ff8ee, 0x468dde7d, 0xd5730a1d, 0x4cd04dc6,
277 0x2939bbdb, 0xa9ba4650, 0xac9526e8, 0xbe5ee304,
278 0xa1fad5f0, 0x6a2d519a, 0x63ef8ce2, 0x9a86ee22,
279 0xc089c2b8, 0x43242ef6, 0xa51e03aa, 0x9cf2d0a4,
280 0x83c061ba, 0x9be96a4d, 0x8fe51550, 0xba645bd6,
281 0x2826a2f9, 0xa73a3ae1, 0x4ba99586, 0xef5562e9,
282 0xc72fefd3, 0xf752f7da, 0x3f046f69, 0x77fa0a59,
283 0x80e4a915, 0x87b08601, 0x9b09e6ad, 0x3b3ee593,
284 0xe990fd5a, 0x9e34d797, 0x2cf0b7d9, 0x022b8b51,
285 0x96d5ac3a, 0x017da67d, 0xd1cf3ed6, 0x7c7d2d28,
286 0x1f9f25cf, 0xadf2b89b, 0x5ad6b472, 0x5a88f54c,
287 0xe029ac71, 0xe019a5e6, 0x47b0acfd, 0xed93fa9b,
288 0xe8d3c48d, 0x283b57cc, 0xf8d56629, 0x79132e28,
289 0x785f0191, 0xed756055, 0xf7960e44, 0xe3d35e8c,
290 0x15056dd4, 0x88f46dba, 0x03a16125, 0x0564f0bd,
291 0xc3eb9e15, 0x3c9057a2, 0x97271aec, 0xa93a072a,
292 0x1b3f6d9b, 0x1e6321f5, 0xf59c66fb, 0x26dcf319,
293 0x7533d928, 0xb155fdf5, 0x03563482, 0x8aba3cbb,
294 0x28517711, 0xc20ad9f8, 0xabcc5167, 0xccad925f,
295 0x4de81751, 0x3830dc8e, 0x379d5862, 0x9320f991,
296 0xea7a90c2, 0xfb3e7bce, 0x5121ce64, 0x774fbe32,
297 0xa8b6e37e, 0xc3293d46, 0x48de5369, 0x6413e680,
298 0xa2ae0810, 0xdd6db224, 0x69852dfd, 0x09072166,
299 0xb39a460a, 0x6445c0dd, 0x586cdecf, 0x1c20c8ae,
300 0x5bbef7dd, 0x1b588d40, 0xccd2017f, 0x6bb4e3bb,
301 0xdda26a7e, 0x3a59ff45, 0x3e350a44, 0xbcb4cdd5,
302 0x72eacea8, 0xfa6484bb, 0x8d6612ae, 0xbf3c6f47,
303 0xd29be463, 0x542f5d9e, 0xaec2771b, 0xf64e6370,
304 0x740e0d8d, 0xe75b1357, 0xf8721671, 0xaf537d5d,
305 0x4040cb08, 0x4eb4e2cc, 0x34d2466a, 0x0115af84,
306 0xe1b00428, 0x95983a1d, 0x06b89fb4, 0xce6ea048,
307 0x6f3f3b82, 0x3520ab82, 0x011a1d4b, 0x277227f8,
308 0x611560b1, 0xe7933fdc, 0xbb3a792b, 0x344525bd,
309 0xa08839e1, 0x51ce794b, 0x2f32c9b7, 0xa01fbac9,
310 0xe01cc87e, 0xbcc7d1f6, 0xcf0111c3, 0xa1e8aac7,
311 0x1a908749, 0xd44fbd9a, 0xd0dadecb, 0xd50ada38,
312 0x0339c32a, 0xc6913667, 0x8df9317c, 0xe0b12b4f,
313 0xf79e59b7, 0x43f5bb3a, 0xf2d519ff, 0x27d9459c,
314 0xbf97222c, 0x15e6fc2a, 0x0f91fc71, 0x9b941525,
315 0xfae59361, 0xceb69ceb, 0xc2a86459, 0x12baa8d1,
316 0xb6c1075e, 0xe3056a0c, 0x10d25065, 0xcb03a442,
317 0xe0ec6e0e, 0x1698db3b, 0x4c98a0be, 0x3278e964,
318 0x9f1f9532, 0xe0d392df, 0xd3a0342b, 0x8971f21e,
319 0x1b0a7441, 0x4ba3348c, 0xc5be7120, 0xc37632d8,
320 0xdf359f8d, 0x9b992f2e, 0xe60b6f47, 0x0fe3f11d,
321 0xe54cda54, 0x1edad891, 0xce6279cf, 0xcd3e7e6f,
322 0x1618b166, 0xfd2c1d05, 0x848fd2c5, 0xf6fb2299,
323 0xf523f357, 0xa6327623, 0x93a83531, 0x56cccd02,
324 0xacf08162, 0x5a75ebb5, 0x6e163697, 0x88d273cc,
325 0xde966292, 0x81b949d0, 0x4c50901b, 0x71c65614,
326 0xe6c6c7bd, 0x327a140a, 0x45e1d006, 0xc3f27b9a,
327 0xc9aa53fd, 0x62a80f00, 0xbb25bfe2, 0x35bdd2f6,
328 0x71126905, 0xb2040222, 0xb6cbcf7c, 0xcd769c2b,
329 0x53113ec0, 0x1640e3d3, 0x38abbd60, 0x2547adf0,
330 0xba38209c, 0xf746ce76, 0x77afa1c5, 0x20756060,
331 0x85cbfe4e, 0x8ae88dd8, 0x7aaaf9b0, 0x4cf9aa7e,
332 0x1948c25c, 0x02fb8a8c, 0x01c36ae4, 0xd6ebe1f9,
333 0x90d4f869, 0xa65cdea0, 0x3f09252d, 0xc208e69f,
334 0xb74e6132, 0xce77e25b, 0x578fdfe3, 0x3ac372e6
335 }
336 }, {
337 0x243f6a88, 0x85a308d3, 0x13198a2e, 0x03707344,
338 0xa4093822, 0x299f31d0, 0x082efa98, 0xec4e6c89,
339 0x452821e6, 0x38d01377, 0xbe5466cf, 0x34e90c6c,
340 0xc0ac29b7, 0xc97c50dd, 0x3f84d5b5, 0xb5470917,
341 0x9216d5d9, 0x8979fb1b
342 }
343};
344
345static unsigned char BF_itoa64[64 + 1] =
346 "./ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789";
347
348static unsigned char BF_atoi64[0x60] = {
349 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 0, 1,
350 54, 55, 56, 57, 58, 59, 60, 61, 62, 63, 64, 64, 64, 64, 64, 64,
351 64, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16,
352 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 64, 64, 64, 64, 64,
353 64, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 42,
354 43, 44, 45, 46, 47, 48, 49, 50, 51, 52, 53, 64, 64, 64, 64, 64
355};
356
357#define BF_safe_atoi64(dst, src) \
358{ \
359 tmp = (unsigned char)(src); \
360 if ((unsigned int)(tmp -= 0x20) >= 0x60) return -1; \
361 tmp = BF_atoi64[tmp]; \
362 if (tmp > 63) return -1; \
363 (dst) = tmp; \
364}
365
366static int BF_decode(BF_word *dst, const char *src, int size)
367{
368 unsigned char *dptr = (unsigned char *)dst;
369 unsigned char *end = dptr + size;
370 const unsigned char *sptr = (const unsigned char *)src;
371 unsigned int tmp, c1, c2, c3, c4;
372
373 do {
374 BF_safe_atoi64(c1, *sptr++);
375 BF_safe_atoi64(c2, *sptr++);
376 *dptr++ = (c1 << 2) | ((c2 & 0x30) >> 4);
377 if (dptr >= end) break;
378
379 BF_safe_atoi64(c3, *sptr++);
380 *dptr++ = ((c2 & 0x0F) << 4) | ((c3 & 0x3C) >> 2);
381 if (dptr >= end) break;
382
383 BF_safe_atoi64(c4, *sptr++);
384 *dptr++ = ((c3 & 0x03) << 6) | c4;
385 } while (dptr < end);
386
387 return 0;
388}
389
390static void BF_encode(char *dst, const BF_word *src, int size)
391{
392 const unsigned char *sptr = (const unsigned char *)src;
393 const unsigned char *end = sptr + size;
394 unsigned char *dptr = (unsigned char *)dst;
395 unsigned int c1, c2;
396
397 do {
398 c1 = *sptr++;
399 *dptr++ = BF_itoa64[c1 >> 2];
400 c1 = (c1 & 0x03) << 4;
401 if (sptr >= end) {
402 *dptr++ = BF_itoa64[c1];
403 break;
404 }
405
406 c2 = *sptr++;
407 c1 |= c2 >> 4;
408 *dptr++ = BF_itoa64[c1];
409 c1 = (c2 & 0x0f) << 2;
410 if (sptr >= end) {
411 *dptr++ = BF_itoa64[c1];
412 break;
413 }
414
415 c2 = *sptr++;
416 c1 |= c2 >> 6;
417 *dptr++ = BF_itoa64[c1];
418 *dptr++ = BF_itoa64[c2 & 0x3f];
419 } while (sptr < end);
420}
421
422static void BF_swap(BF_word *x, int count)
423{
424 static int endianness_check = 1;
425 char *is_little_endian = (char *)&endianness_check;
426 BF_word tmp;
427
428 if (*is_little_endian)
429 do {
430 tmp = *x;
431 tmp = (tmp << 16) | (tmp >> 16);
432 *x++ = ((tmp & 0x00FF00FF) << 8) | ((tmp >> 8) & 0x00FF00FF);
433 } while (--count);
434}
435
436/* Architectures which can shift addresses left by 2 bits with no extra cost */
437#define BF_ROUND(L, R, N) \
438 tmp1 = L & 0xFF; \
439 tmp2 = L >> 8; \
440 tmp2 &= 0xFF; \
441 tmp3 = L >> 16; \
442 tmp3 &= 0xFF; \
443 tmp4 = L >> 24; \
444 tmp1 = data.ctx.S[3][tmp1]; \
445 tmp2 = data.ctx.S[2][tmp2]; \
446 tmp3 = data.ctx.S[1][tmp3]; \
447 tmp3 += data.ctx.S[0][tmp4]; \
448 tmp3 ^= tmp2; \
449 R ^= data.ctx.P[N + 1]; \
450 tmp3 += tmp1; \
451 R ^= tmp3;
452
453/*
454 * Encrypt one block, BF_N is hardcoded here.
455 */
456#define BF_ENCRYPT \
457 L ^= data.ctx.P[0]; \
458 BF_ROUND(L, R, 0); \
459 BF_ROUND(R, L, 1); \
460 BF_ROUND(L, R, 2); \
461 BF_ROUND(R, L, 3); \
462 BF_ROUND(L, R, 4); \
463 BF_ROUND(R, L, 5); \
464 BF_ROUND(L, R, 6); \
465 BF_ROUND(R, L, 7); \
466 BF_ROUND(L, R, 8); \
467 BF_ROUND(R, L, 9); \
468 BF_ROUND(L, R, 10); \
469 BF_ROUND(R, L, 11); \
470 BF_ROUND(L, R, 12); \
471 BF_ROUND(R, L, 13); \
472 BF_ROUND(L, R, 14); \
473 BF_ROUND(R, L, 15); \
474 tmp4 = R; \
475 R = L; \
476 L = tmp4 ^ data.ctx.P[BF_N + 1];
477
478#define BF_body() \
479 L = R = 0; \
480 ptr = data.ctx.P; \
481 do { \
482 ptr += 2; \
483 BF_ENCRYPT; \
484 *(ptr - 2) = L; \
485 *(ptr - 1) = R; \
486 } while (ptr < &data.ctx.P[BF_N + 2]); \
487\
488 ptr = data.ctx.S[0]; \
489 do { \
490 ptr += 2; \
491 BF_ENCRYPT; \
492 *(ptr - 2) = L; \
493 *(ptr - 1) = R; \
494 } while (ptr < &data.ctx.S[3][0xFF]);
495
496static void BF_set_key(const char *key, BF_key expanded, BF_key initial,
497 unsigned char flags)
498{
499 const char *ptr = key;
500 unsigned int bug, i, j;
501 BF_word safety, sign, diff, tmp[2];
502
503/*
504 * There was a sign extension bug in older revisions of this function. While
505 * we would have liked to simply fix the bug and move on, we have to provide
506 * a backwards compatibility feature (essentially the bug) for some systems and
507 * a safety measure for some others. The latter is needed because for certain
508 * multiple inputs to the buggy algorithm there exist easily found inputs to
509 * the correct algorithm that produce the same hash. Thus, we optionally
510 * deviate from the correct algorithm just enough to avoid such collisions.
511 * While the bug itself affected the majority of passwords containing
512 * characters with the 8th bit set (although only a percentage of those in a
513 * collision-producing way), the anti-collision safety measure affects
514 * only a subset of passwords containing the '\xff' character (not even all of
515 * those passwords, just some of them). This character is not found in valid
516 * UTF-8 sequences and is rarely used in popular 8-bit character encodings.
517 * Thus, the safety measure is unlikely to cause much annoyance, and is a
518 * reasonable tradeoff to use when authenticating against existing hashes that
519 * are not reliably known to have been computed with the correct algorithm.
520 *
521 * We use an approach that tries to minimize side-channel leaks of password
522 * information - that is, we mostly use fixed-cost bitwise operations instead
523 * of branches or table lookups. (One conditional branch based on password
524 * length remains. It is not part of the bug aftermath, though, and is
525 * difficult and possibly unreasonable to avoid given the use of C strings by
526 * the caller, which results in similar timing leaks anyway.)
527 *
528 * For actual implementation, we set an array index in the variable "bug"
529 * (0 means no bug, 1 means sign extension bug emulation) and a flag in the
530 * variable "safety" (bit 16 is set when the safety measure is requested).
531 * Valid combinations of settings are:
532 *
533 * Prefix "$2a$": bug = 0, safety = 0x10000
534 * Prefix "$2x$": bug = 1, safety = 0
535 * Prefix "$2y$": bug = 0, safety = 0
536 */
537 bug = (unsigned int)flags & 1;
538 safety = ((BF_word)flags & 2) << 15;
539
540 sign = diff = 0;
541
542 for (i = 0; i < BF_N + 2; i++) {
543 tmp[0] = tmp[1] = 0;
544 for (j = 0; j < 4; j++) {
545 tmp[0] <<= 8;
546 tmp[0] |= (unsigned char)*ptr; /* correct */
547 tmp[1] <<= 8;
548 tmp[1] |= (BF_word_signed)(signed char)*ptr; /* bug */
549/*
550 * Sign extension in the first char has no effect - nothing to overwrite yet,
551 * and those extra 24 bits will be fully shifted out of the 32-bit word. For
552 * chars 2, 3, 4 in each four-char block, we set bit 7 of "sign" if sign
553 * extension in tmp[1] occurs. Once this flag is set, it remains set.
554 */
555 if (j)
556 sign |= tmp[1] & 0x80;
557 if (!*ptr)
558 ptr = key;
559 else
560 ptr++;
561 }
562 diff |= tmp[0] ^ tmp[1]; /* Non-zero on any differences */
563
564 expanded[i] = tmp[bug];
565 initial[i] = BF_init_state.P[i] ^ tmp[bug];
566 }
567
568/*
569 * At this point, "diff" is zero iff the correct and buggy algorithms produced
570 * exactly the same result. If so and if "sign" is non-zero, which indicates
571 * that there was a non-benign sign extension, this means that we have a
572 * collision between the correctly computed hash for this password and a set of
573 * passwords that could be supplied to the buggy algorithm. Our safety measure
574 * is meant to protect from such many-buggy to one-correct collisions, by
575 * deviating from the correct algorithm in such cases. Let's check for this.
576 */
577 diff |= diff >> 16; /* still zero iff exact match */
578 diff &= 0xffff; /* ditto */
579 diff += 0xffff; /* bit 16 set iff "diff" was non-zero (on non-match) */
580 sign <<= 9; /* move the non-benign sign extension flag to bit 16 */
581 sign &= ~diff & safety; /* action needed? */
582
583/*
584 * If we have determined that we need to deviate from the correct algorithm,
585 * flip bit 16 in initial expanded key. (The choice of 16 is arbitrary, but
586 * let's stick to it now. It came out of the approach we used above, and it's
587 * not any worse than any other choice we could make.)
588 *
589 * It is crucial that we don't do the same to the expanded key used in the main
590 * Eksblowfish loop. By doing it to only one of these two, we deviate from a
591 * state that could be directly specified by a password to the buggy algorithm
592 * (and to the fully correct one as well, but that's a side-effect).
593 */
594 initial[0] ^= sign;
595}
596
597static char *BF_crypt(const char *key, const char *setting,
598 char *output, int size,
599 BF_word min)
600{
601 static const unsigned char flags_by_subtype[26] =
602 {2, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0,
603 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 4, 0};
604 struct {
605 BF_ctx ctx;
606 BF_key expanded_key;
607 union {
608 BF_word salt[4];
609 BF_word output[6];
610 } binary;
611 } data;
612 BF_word L, R;
613 BF_word tmp1, tmp2, tmp3, tmp4;
614 BF_word *ptr;
615 BF_word count;
616 int i;
617
618 if (size < 7 + 22 + 31 + 1) {
619 return NULL;
620 }
621
622 if (setting[0] != '$' ||
623 setting[1] != '2' ||
624 setting[2] < 'a' || setting[2] > 'z' ||
625 !flags_by_subtype[(unsigned int)(unsigned char)setting[2] - 'a'] ||
626 setting[3] != '$' ||
627 setting[4] < '0' || setting[4] > '3' ||
628 setting[5] < '0' || setting[5] > '9' ||
629 (setting[4] == '3' && setting[5] > '1') ||
630 setting[6] != '$') {
631 return NULL;
632 }
633
634 count = (BF_word)1 << ((setting[4] - '0') * 10 + (setting[5] - '0'));
635 if (count < min || BF_decode(data.binary.salt, &setting[7], 16)) {
636 return NULL;
637 }
638 BF_swap(data.binary.salt, 4);
639
640 BF_set_key(key, data.expanded_key, data.ctx.P,
641 flags_by_subtype[(unsigned int)(unsigned char)setting[2] - 'a']);
642
643 CopyMem(data.ctx.S, BF_init_state.S, sizeof(data.ctx.S));
644
645 L = R = 0;
646 for (i = 0; i < BF_N + 2; i += 2) {
647 L ^= data.binary.salt[i & 2];
648 R ^= data.binary.salt[(i & 2) + 1];
649 BF_ENCRYPT;
650 data.ctx.P[i] = L;
651 data.ctx.P[i + 1] = R;
652 }
653
654 ptr = data.ctx.S[0];
655 do {
656 ptr += 4;
657 L ^= data.binary.salt[(BF_N + 2) & 3];
658 R ^= data.binary.salt[(BF_N + 3) & 3];
659 BF_ENCRYPT;
660 *(ptr - 4) = L;
661 *(ptr - 3) = R;
662
663 L ^= data.binary.salt[(BF_N + 4) & 3];
664 R ^= data.binary.salt[(BF_N + 5) & 3];
665 BF_ENCRYPT;
666 *(ptr - 2) = L;
667 *(ptr - 1) = R;
668 } while (ptr < &data.ctx.S[3][0xFF]);
669
670 do {
671 int done;
672
673 for (i = 0; i < BF_N + 2; i += 2) {
674 data.ctx.P[i] ^= data.expanded_key[i];
675 data.ctx.P[i + 1] ^= data.expanded_key[i + 1];
676 }
677
678 done = 0;
679 do {
680 BF_body();
681 if (done)
682 break;
683 done = 1;
684
685 tmp1 = data.binary.salt[0];
686 tmp2 = data.binary.salt[1];
687 tmp3 = data.binary.salt[2];
688 tmp4 = data.binary.salt[3];
689 for (i = 0; i < BF_N; i += 4) {
690 data.ctx.P[i] ^= tmp1;
691 data.ctx.P[i + 1] ^= tmp2;
692 data.ctx.P[i + 2] ^= tmp3;
693 data.ctx.P[i + 3] ^= tmp4;
694 }
695 data.ctx.P[16] ^= tmp1;
696 data.ctx.P[17] ^= tmp2;
697 } while (1);
698 } while (--count);
699
700 for (i = 0; i < 6; i += 2) {
701 L = BF_magic_w[i];
702 R = BF_magic_w[i + 1];
703
704 count = 64;
705 do {
706 BF_ENCRYPT;
707 } while (--count);
708
709 data.binary.output[i] = L;
710 data.binary.output[i + 1] = R;
711 }
712
713 CopyMem(output, (void *)setting, 7 + 22 - 1);
714 output[7 + 22 - 1] = BF_itoa64[(int)
715 BF_atoi64[(int)setting[7 + 22 - 1] - 0x20] & 0x30];
716
717/* This has to be bug-compatible with the original implementation, so
718 * only encode 23 of the 24 bytes. :-) */
719 BF_swap(data.binary.output, 6);
720 BF_encode(&output[7 + 22], data.binary.output, 23);
721 output[7 + 22 + 31] = '\0';
722
723 return output;
724}
725
726int _crypt_output_magic(const char *setting, char *output, int size)
727{
728 if (size < 3)
729 return -1;
730
731 output[0] = '*';
732 output[1] = '0';
733 output[2] = '\0';
734
735 if (setting[0] == '*' && setting[1] == '0')
736 output[1] = '1';
737
738 return 0;
739}
740
741/*
742 * Please preserve the runtime self-test. It serves two purposes at once:
743 *
744 * 1. We really can't afford the risk of producing incompatible hashes e.g.
745 * when there's something like gcc bug 26587 again, whereas an application or
746 * library integrating this code might not also integrate our external tests or
747 * it might not run them after every build. Even if it does, the miscompile
748 * might only occur on the production build, but not on a testing build (such
749 * as because of different optimization settings). It is painful to recover
750 * from incorrectly-computed hashes - merely fixing whatever broke is not
751 * enough. Thus, a proactive measure like this self-test is needed.
752 *
753 * 2. We don't want to leave sensitive data from our actual password hash
754 * computation on the stack or in registers. Previous revisions of the code
755 * would do explicit cleanups, but simply running the self-test after hash
756 * computation is more reliable.
757 *
758 * The performance cost of this quick self-test is around 0.6% at the "$2a$08"
759 * setting.
760 */
761char *crypt_blowfish_rn(const char *key, const char *setting,
762 char *output, int size)
763{
764 const char *test_key = "8b \xd0\xc1\xd2\xcf\xcc\xd8";
765 const char *test_setting = "$2a$00$abcdefghijklmnopqrstuu";
766 static const char * const test_hash[2] =
767 {"VUrPmXD6q/nVSSp7pNDhCR9071IfIRe\0\x55", /* $2x$ */
768 "i1D709vfamulimlGcq0qq3UvuUasvEa\0\x55"}; /* $2a$, $2y$ */
769 char *retval;
770 const char *p;
771 int ok;
772 struct {
773 char s[7 + 22 + 1];
774 char o[7 + 22 + 31 + 1 + 1 + 1];
775 } buf;
776
777/* Hash the supplied password */
778 _crypt_output_magic(setting, output, size);
779 retval = BF_crypt(key, setting, output, size, 16);
780
781/*
782 * Do a quick self-test. It is important that we make both calls to BF_crypt()
783 * from the same scope such that they likely use the same stack locations,
784 * which makes the second call overwrite the first call's sensitive data on the
785 * stack and makes it more likely that any alignment related issues would be
786 * detected by the self-test.
787 */
788 CopyMem(buf.s, (void *)test_setting, sizeof(buf.s));
789 if (retval)
790 buf.s[2] = setting[2];
791 SetMem(buf.o, sizeof(buf.o), 0x55);
792 buf.o[sizeof(buf.o) - 1] = 0;
793 p = BF_crypt(test_key, buf.s, buf.o, sizeof(buf.o) - (1 + 1), 1);
794
795 ok = (p == buf.o &&
796 !CompareMem((void *)p, (void *)buf.s, 7 + 22) &&
797 !CompareMem((void *)(p + (7 + 22)),
798 (void *)test_hash[(unsigned int)(unsigned char)buf.s[2] & 1],
799 31 + 1 + 1 + 1));
800
801 {
802 const char *k = "\xff\xa3" "34" "\xff\xff\xff\xa3" "345";
803 BF_key ae, ai, ye, yi;
804 BF_set_key(k, ae, ai, 2); /* $2a$ */
805 BF_set_key(k, ye, yi, 4); /* $2y$ */
806 ai[0] ^= 0x10000; /* undo the safety (for comparison) */
807 ok = ok && ai[0] == 0xdb9c59bc && ye[17] == 0x33343500 &&
808 !CompareMem(ae, ye, sizeof(ae)) &&
809 !CompareMem(ai, yi, sizeof(ai));
810 }
811
812 if (ok)
813 return retval;
814
815/* Should not happen */
816 _crypt_output_magic(setting, output, size);
817 return NULL;
818}