summaryrefslogtreecommitdiff
path: root/utils/mkzenboot/utils.c
diff options
context:
space:
mode:
Diffstat (limited to 'utils/mkzenboot/utils.c')
-rw-r--r--utils/mkzenboot/utils.c896
1 files changed, 896 insertions, 0 deletions
diff --git a/utils/mkzenboot/utils.c b/utils/mkzenboot/utils.c
new file mode 100644
index 0000000000..b8ef3be237
--- /dev/null
+++ b/utils/mkzenboot/utils.c
@@ -0,0 +1,896 @@
1/***************************************************************************
2 * __________ __ ___.
3 * Open \______ \ ____ ____ | | _\_ |__ _______ ___
4 * Source | _// _ \_/ ___\| |/ /| __ \ / _ \ \/ /
5 * Jukebox | | ( <_> ) \___| < | \_\ ( <_> > < <
6 * Firmware |____|_ /\____/ \___ >__|_ \|___ /\____/__/\_ \
7 * \/ \/ \/ \/ \/
8 * $Id$
9 *
10 * Copyright (C) 2008 by Maurus Cuelenaere
11 * Based on zenutils by Rasmus Ry <rasmus.ry{at}gmail.com>
12 * Copyright (C) 2013 by Amaury Pouly
13 *
14 * This program is free software; you can redistribute it and/or
15 * modify it under the terms of the GNU General Public License
16 * as published by the Free Software Foundation; either version 2
17 * of the License, or (at your option) any later version.
18 *
19 * This software is distributed on an "AS IS" basis, WITHOUT WARRANTY OF ANY
20 * KIND, either express or implied.
21 *
22 ****************************************************************************/
23#include "utils.h"
24#include "md5.h"
25#include <zlib.h>
26//#include "hmac-sha1.h"
27
28int filesize(FILE* fd)
29{
30 int tmp, tmp2 = ftell(fd);
31 fseek(fd, 0, SEEK_END);
32 tmp = ftell(fd);
33 fseek(fd, tmp2, SEEK_SET);
34 return tmp;
35}
36
37unsigned int le2int(unsigned char* buf)
38{
39 return ((buf[3] << 24) | (buf[2] << 16) | (buf[1] << 8) | buf[0]);
40}
41
42unsigned int be2int(unsigned char* buf)
43{
44 return ((buf[0] << 24) | (buf[1] << 16) | (buf[2] << 8) | buf[3]);
45}
46
47void int2le(unsigned int val, unsigned char* addr)
48{
49 addr[0] = val & 0xFF;
50 addr[1] = (val >> 8) & 0xff;
51 addr[2] = (val >> 16) & 0xff;
52 addr[3] = (val >> 24) & 0xff;
53}
54
55const char* find_firmware_key(const unsigned char* buffer, size_t len)
56{
57 char szkey1[] = "34d1";
58 size_t cchkey1 = strlen(szkey1);
59 char szkey2[] = "TbnCboEbn";
60 size_t cchkey2 = strlen(szkey2);
61 uint32_t i;
62 for (i = 0; i < (uint32_t)len; i++)
63 {
64 if (len >= cchkey1)
65 {
66 if (!strncmp((char*)&buffer[i], szkey1, cchkey1))
67 return (const char*)&buffer[i];
68 }
69 if (len >= cchkey2)
70 {
71 if (!strncmp((char*)&buffer[i], szkey2, cchkey2))
72 return (const char*)&buffer[i];
73 }
74 }
75 return NULL;
76}
77
78uint32_t find_firmware_offset(unsigned char* buffer, size_t len)
79{
80 uint32_t i;
81 for (i = 0; i < (uint32_t)len; i += 0x10)
82 {
83 if (buffer[i + sizeof(uint32_t)] != 0
84 && buffer[i + sizeof(uint32_t) + 1] != 0
85 && buffer[i + sizeof(uint32_t) + 2] != 0
86 && buffer[i + sizeof(uint32_t) + 3] != 0)
87 {
88 return i;
89 }
90 if(i > 0xFF) /* Arbitrary guess */
91 return 0;
92 }
93 return 0;
94}
95
96bool crypt_firmware(const char* key, unsigned char* buffer, size_t len)
97{
98 char key_cpy[255];
99 unsigned int i;
100 unsigned int tmp = 0;
101 int key_length = strlen(key);
102
103 strcpy(key_cpy, key);
104 for(i=0; i < strlen(key); i++)
105 key_cpy[i] = key[i] - 1;
106
107 for(i=0; i < len; i++)
108 {
109 buffer[i] ^= key_cpy[tmp] | 0x80;
110 tmp = (tmp + 1) % key_length;
111 }
112
113 return true;
114}
115
116bool inflate_to_buffer(const unsigned char *buffer, size_t len, unsigned char* out_buffer, size_t out_len, char** err_msg)
117{
118 /* Initialize Zlib */
119 z_stream d_stream;
120 int ret;
121
122 d_stream.zalloc = Z_NULL;
123 d_stream.zfree = Z_NULL;
124 d_stream.opaque = Z_NULL;
125
126 d_stream.next_in = (unsigned char*)buffer;
127 d_stream.avail_in = len;
128
129 ret = inflateInit(&d_stream);
130 if (ret != Z_OK)
131 {
132 *err_msg = d_stream.msg;
133 return false;
134 }
135
136 d_stream.next_out = out_buffer;
137 d_stream.avail_out = out_len;
138
139 ret = inflate(&d_stream, Z_SYNC_FLUSH);
140 if(ret < 0)
141 {
142 *err_msg = d_stream.msg;
143 return false;
144 }
145 else
146 inflateEnd(&d_stream);
147
148 return true;
149}
150
151#define CODE_MASK 0xC0
152#define ARGS_MASK 0x3F
153
154#define REPEAT_CODE 0x00
155#define BLOCK_CODE 0x40
156#define LONG_RUN_CODE 0x80
157#define SHORT_RUN_CODE 0xC0
158
159#define BLOCK_ARGS 0x1F
160#define BLOCK_MODE 0x20
161
162
163static void decode_run(unsigned char* dst, uint16_t len, unsigned char val,
164 int* dstidx)
165{
166 memset(dst + *dstidx, val, len);
167 *dstidx += len;
168}
169
170static void decode_pattern(unsigned char* src, unsigned char* dst,
171 uint16_t len, int* srcidx, int* dstidx,
172 bool bdecode, int npasses)
173{
174 int i, j;
175 for (i = 0; i < npasses; i++)
176 {
177 if (bdecode)
178 {
179 for (j = 0; j < len; j++)
180 {
181 uint16_t c, d;
182 c = src[*srcidx + j];
183 d = (c >> 5) & 7;
184 c = (c << 3) & 0xF8;
185 src[*srcidx + j] = (unsigned char)(c | d);
186 }
187 bdecode = false;
188 }
189 memcpy(dst + *dstidx, src + *srcidx, len);
190 *dstidx += len;
191 }
192 *srcidx += len;
193}
194
195int cenc_decode(unsigned char* src, int srclen, unsigned char* dst, int dstlen)
196{
197 int i = 0, j = 0;
198 do
199 {
200 uint16_t c, d, e;
201 c = src[i++];
202 switch (c & CODE_MASK)
203 {
204 case REPEAT_CODE: /* 2 unsigned chars */
205 d = src[i++];
206 d = d + 2;
207
208 e = (c & ARGS_MASK) + 2;
209
210 decode_pattern(src, dst, e, &i, &j, false, d);
211 break;
212
213 case BLOCK_CODE: /* 1/2/3 unsigned chars */
214 d = c & BLOCK_ARGS;
215 if (!(c & BLOCK_MODE))
216 {
217 e = src[i++];
218 e = (d << 8) + (e + 0x21);
219
220 d = (uint16_t)(i ^ j);
221 }
222 else
223 {
224 e = d + 1;
225
226 d = (uint16_t)(i ^ j);
227 }
228 if (d & 1)
229 {
230 i++;
231 }
232
233 decode_pattern(src, dst, e, &i, &j, true, 1);
234 break;
235
236 case LONG_RUN_CODE: /* 3 unsigned chars */
237 d = src[i++];
238 e = ((c & ARGS_MASK) << 8) + (d + 0x42);
239
240 d = src[i++];
241 d = ((d & 7) << 5) | ((d >> 3) & 0x1F);
242
243 decode_run(dst, e, (unsigned char)(d), &j);
244 break;
245
246 case SHORT_RUN_CODE: /* 2 unsigned chars */
247 d = src[i++];
248 d = ((d & 3) << 6) | ((d >> 2) & 0x3F);
249
250 e = (c & ARGS_MASK) + 2;
251
252 decode_run(dst, e, (unsigned char)(d), &j);
253 break;
254 };
255 } while (i < srclen && j < dstlen);
256
257 return j;
258}
259
260/*
261 * Copyright (c) 1999, 2000, 2002 Virtual Unlimited B.V.
262 *
263 * This library is free software; you can redistribute it and/or
264 * modify it under the terms of the GNU Lesser General Public
265 * License as published by the Free Software Foundation; either
266 * version 2.1 of the License, or (at your option) any later version.
267 *
268 * This library is distributed in the hope that it will be useful,
269 * but WITHOUT ANY WARRANTY; without even the implied warranty of
270 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
271 * Lesser General Public License for more details.
272 *
273 * You should have received a copy of the GNU Lesser General Public
274 * License along with this library; if not, write to the Free Software
275 * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
276 *
277 */
278
279#define BLOWFISHROUNDS 16
280#define BLOWFISHPSIZE (BLOWFISHROUNDS+2)
281#define WORDS_BIGENDIAN 0
282
283struct blowfishParam
284{
285 uint32_t p[BLOWFISHPSIZE];
286 uint32_t s[1024];
287 uint32_t fdback[2];
288};
289
290typedef enum
291{
292 NOCRYPT,
293 ENCRYPT,
294 DECRYPT
295} cipherOperation;
296
297static inline uint32_t swapu32(uint32_t n)
298{
299 return ( ((n & 0xffU) << 24) |
300 ((n & 0xff00U) << 8) |
301 ((n & 0xff0000U) >> 8) |
302 ((n & 0xff000000U) >> 24) );
303}
304
305static uint32_t _bf_p[BLOWFISHPSIZE] = {
306 0x243f6a88, 0x85a308d3, 0x13198a2e, 0x03707344,
307 0xa4093822, 0x299f31d0, 0x082efa98, 0xec4e6c89,
308 0x452821e6, 0x38d01377, 0xbe5466cf, 0x34e90c6c,
309 0xc0ac29b7, 0xc97c50dd, 0x3f84d5b5, 0xb5470917,
310 0x9216d5d9, 0x8979fb1b
311};
312
313static uint32_t _bf_s[1024] = {
314 0xd1310ba6, 0x98dfb5ac, 0x2ffd72db, 0xd01adfb7,
315 0xb8e1afed, 0x6a267e96, 0xba7c9045, 0xf12c7f99,
316 0x24a19947, 0xb3916cf7, 0x0801f2e2, 0x858efc16,
317 0x636920d8, 0x71574e69, 0xa458fea3, 0xf4933d7e,
318 0x0d95748f, 0x728eb658, 0x718bcd58, 0x82154aee,
319 0x7b54a41d, 0xc25a59b5, 0x9c30d539, 0x2af26013,
320 0xc5d1b023, 0x286085f0, 0xca417918, 0xb8db38ef,
321 0x8e79dcb0, 0x603a180e, 0x6c9e0e8b, 0xb01e8a3e,
322 0xd71577c1, 0xbd314b27, 0x78af2fda, 0x55605c60,
323 0xe65525f3, 0xaa55ab94, 0x57489862, 0x63e81440,
324 0x55ca396a, 0x2aab10b6, 0xb4cc5c34, 0x1141e8ce,
325 0xa15486af, 0x7c72e993, 0xb3ee1411, 0x636fbc2a,
326 0x2ba9c55d, 0x741831f6, 0xce5c3e16, 0x9b87931e,
327 0xafd6ba33, 0x6c24cf5c, 0x7a325381, 0x28958677,
328 0x3b8f4898, 0x6b4bb9af, 0xc4bfe81b, 0x66282193,
329 0x61d809cc, 0xfb21a991, 0x487cac60, 0x5dec8032,
330 0xef845d5d, 0xe98575b1, 0xdc262302, 0xeb651b88,
331 0x23893e81, 0xd396acc5, 0x0f6d6ff3, 0x83f44239,
332 0x2e0b4482, 0xa4842004, 0x69c8f04a, 0x9e1f9b5e,
333 0x21c66842, 0xf6e96c9a, 0x670c9c61, 0xabd388f0,
334 0x6a51a0d2, 0xd8542f68, 0x960fa728, 0xab5133a3,
335 0x6eef0b6c, 0x137a3be4, 0xba3bf050, 0x7efb2a98,
336 0xa1f1651d, 0x39af0176, 0x66ca593e, 0x82430e88,
337 0x8cee8619, 0x456f9fb4, 0x7d84a5c3, 0x3b8b5ebe,
338 0xe06f75d8, 0x85c12073, 0x401a449f, 0x56c16aa6,
339 0x4ed3aa62, 0x363f7706, 0x1bfedf72, 0x429b023d,
340 0x37d0d724, 0xd00a1248, 0xdb0fead3, 0x49f1c09b,
341 0x075372c9, 0x80991b7b, 0x25d479d8, 0xf6e8def7,
342 0xe3fe501a, 0xb6794c3b, 0x976ce0bd, 0x04c006ba,
343 0xc1a94fb6, 0x409f60c4, 0x5e5c9ec2, 0x196a2463,
344 0x68fb6faf, 0x3e6c53b5, 0x1339b2eb, 0x3b52ec6f,
345 0x6dfc511f, 0x9b30952c, 0xcc814544, 0xaf5ebd09,
346 0xbee3d004, 0xde334afd, 0x660f2807, 0x192e4bb3,
347 0xc0cba857, 0x45c8740f, 0xd20b5f39, 0xb9d3fbdb,
348 0x5579c0bd, 0x1a60320a, 0xd6a100c6, 0x402c7279,
349 0x679f25fe, 0xfb1fa3cc, 0x8ea5e9f8, 0xdb3222f8,
350 0x3c7516df, 0xfd616b15, 0x2f501ec8, 0xad0552ab,
351 0x323db5fa, 0xfd238760, 0x53317b48, 0x3e00df82,
352 0x9e5c57bb, 0xca6f8ca0, 0x1a87562e, 0xdf1769db,
353 0xd542a8f6, 0x287effc3, 0xac6732c6, 0x8c4f5573,
354 0x695b27b0, 0xbbca58c8, 0xe1ffa35d, 0xb8f011a0,
355 0x10fa3d98, 0xfd2183b8, 0x4afcb56c, 0x2dd1d35b,
356 0x9a53e479, 0xb6f84565, 0xd28e49bc, 0x4bfb9790,
357 0xe1ddf2da, 0xa4cb7e33, 0x62fb1341, 0xcee4c6e8,
358 0xef20cada, 0x36774c01, 0xd07e9efe, 0x2bf11fb4,
359 0x95dbda4d, 0xae909198, 0xeaad8e71, 0x6b93d5a0,
360 0xd08ed1d0, 0xafc725e0, 0x8e3c5b2f, 0x8e7594b7,
361 0x8ff6e2fb, 0xf2122b64, 0x8888b812, 0x900df01c,
362 0x4fad5ea0, 0x688fc31c, 0xd1cff191, 0xb3a8c1ad,
363 0x2f2f2218, 0xbe0e1777, 0xea752dfe, 0x8b021fa1,
364 0xe5a0cc0f, 0xb56f74e8, 0x18acf3d6, 0xce89e299,
365 0xb4a84fe0, 0xfd13e0b7, 0x7cc43b81, 0xd2ada8d9,
366 0x165fa266, 0x80957705, 0x93cc7314, 0x211a1477,
367 0xe6ad2065, 0x77b5fa86, 0xc75442f5, 0xfb9d35cf,
368 0xebcdaf0c, 0x7b3e89a0, 0xd6411bd3, 0xae1e7e49,
369 0x00250e2d, 0x2071b35e, 0x226800bb, 0x57b8e0af,
370 0x2464369b, 0xf009b91e, 0x5563911d, 0x59dfa6aa,
371 0x78c14389, 0xd95a537f, 0x207d5ba2, 0x02e5b9c5,
372 0x83260376, 0x6295cfa9, 0x11c81968, 0x4e734a41,
373 0xb3472dca, 0x7b14a94a, 0x1b510052, 0x9a532915,
374 0xd60f573f, 0xbc9bc6e4, 0x2b60a476, 0x81e67400,
375 0x08ba6fb5, 0x571be91f, 0xf296ec6b, 0x2a0dd915,
376 0xb6636521, 0xe7b9f9b6, 0xff34052e, 0xc5855664,
377 0x53b02d5d, 0xa99f8fa1, 0x08ba4799, 0x6e85076a,
378 0x4b7a70e9, 0xb5b32944, 0xdb75092e, 0xc4192623,
379 0xad6ea6b0, 0x49a7df7d, 0x9cee60b8, 0x8fedb266,
380 0xecaa8c71, 0x699a17ff, 0x5664526c, 0xc2b19ee1,
381 0x193602a5, 0x75094c29, 0xa0591340, 0xe4183a3e,
382 0x3f54989a, 0x5b429d65, 0x6b8fe4d6, 0x99f73fd6,
383 0xa1d29c07, 0xefe830f5, 0x4d2d38e6, 0xf0255dc1,
384 0x4cdd2086, 0x8470eb26, 0x6382e9c6, 0x021ecc5e,
385 0x09686b3f, 0x3ebaefc9, 0x3c971814, 0x6b6a70a1,
386 0x687f3584, 0x52a0e286, 0xb79c5305, 0xaa500737,
387 0x3e07841c, 0x7fdeae5c, 0x8e7d44ec, 0x5716f2b8,
388 0xb03ada37, 0xf0500c0d, 0xf01c1f04, 0x0200b3ff,
389 0xae0cf51a, 0x3cb574b2, 0x25837a58, 0xdc0921bd,
390 0xd19113f9, 0x7ca92ff6, 0x94324773, 0x22f54701,
391 0x3ae5e581, 0x37c2dadc, 0xc8b57634, 0x9af3dda7,
392 0xa9446146, 0x0fd0030e, 0xecc8c73e, 0xa4751e41,
393 0xe238cd99, 0x3bea0e2f, 0x3280bba1, 0x183eb331,
394 0x4e548b38, 0x4f6db908, 0x6f420d03, 0xf60a04bf,
395 0x2cb81290, 0x24977c79, 0x5679b072, 0xbcaf89af,
396 0xde9a771f, 0xd9930810, 0xb38bae12, 0xdccf3f2e,
397 0x5512721f, 0x2e6b7124, 0x501adde6, 0x9f84cd87,
398 0x7a584718, 0x7408da17, 0xbc9f9abc, 0xe94b7d8c,
399 0xec7aec3a, 0xdb851dfa, 0x63094366, 0xc464c3d2,
400 0xef1c1847, 0x3215d908, 0xdd433b37, 0x24c2ba16,
401 0x12a14d43, 0x2a65c451, 0x50940002, 0x133ae4dd,
402 0x71dff89e, 0x10314e55, 0x81ac77d6, 0x5f11199b,
403 0x043556f1, 0xd7a3c76b, 0x3c11183b, 0x5924a509,
404 0xf28fe6ed, 0x97f1fbfa, 0x9ebabf2c, 0x1e153c6e,
405 0x86e34570, 0xeae96fb1, 0x860e5e0a, 0x5a3e2ab3,
406 0x771fe71c, 0x4e3d06fa, 0x2965dcb9, 0x99e71d0f,
407 0x803e89d6, 0x5266c825, 0x2e4cc978, 0x9c10b36a,
408 0xc6150eba, 0x94e2ea78, 0xa5fc3c53, 0x1e0a2df4,
409 0xf2f74ea7, 0x361d2b3d, 0x1939260f, 0x19c27960,
410 0x5223a708, 0xf71312b6, 0xebadfe6e, 0xeac31f66,
411 0xe3bc4595, 0xa67bc883, 0xb17f37d1, 0x018cff28,
412 0xc332ddef, 0xbe6c5aa5, 0x65582185, 0x68ab9802,
413 0xeecea50f, 0xdb2f953b, 0x2aef7dad, 0x5b6e2f84,
414 0x1521b628, 0x29076170, 0xecdd4775, 0x619f1510,
415 0x13cca830, 0xeb61bd96, 0x0334fe1e, 0xaa0363cf,
416 0xb5735c90, 0x4c70a239, 0xd59e9e0b, 0xcbaade14,
417 0xeecc86bc, 0x60622ca7, 0x9cab5cab, 0xb2f3846e,
418 0x648b1eaf, 0x19bdf0ca, 0xa02369b9, 0x655abb50,
419 0x40685a32, 0x3c2ab4b3, 0x319ee9d5, 0xc021b8f7,
420 0x9b540b19, 0x875fa099, 0x95f7997e, 0x623d7da8,
421 0xf837889a, 0x97e32d77, 0x11ed935f, 0x16681281,
422 0x0e358829, 0xc7e61fd6, 0x96dedfa1, 0x7858ba99,
423 0x57f584a5, 0x1b227263, 0x9b83c3ff, 0x1ac24696,
424 0xcdb30aeb, 0x532e3054, 0x8fd948e4, 0x6dbc3128,
425 0x58ebf2ef, 0x34c6ffea, 0xfe28ed61, 0xee7c3c73,
426 0x5d4a14d9, 0xe864b7e3, 0x42105d14, 0x203e13e0,
427 0x45eee2b6, 0xa3aaabea, 0xdb6c4f15, 0xfacb4fd0,
428 0xc742f442, 0xef6abbb5, 0x654f3b1d, 0x41cd2105,
429 0xd81e799e, 0x86854dc7, 0xe44b476a, 0x3d816250,
430 0xcf62a1f2, 0x5b8d2646, 0xfc8883a0, 0xc1c7b6a3,
431 0x7f1524c3, 0x69cb7492, 0x47848a0b, 0x5692b285,
432 0x095bbf00, 0xad19489d, 0x1462b174, 0x23820e00,
433 0x58428d2a, 0x0c55f5ea, 0x1dadf43e, 0x233f7061,
434 0x3372f092, 0x8d937e41, 0xd65fecf1, 0x6c223bdb,
435 0x7cde3759, 0xcbee7460, 0x4085f2a7, 0xce77326e,
436 0xa6078084, 0x19f8509e, 0xe8efd855, 0x61d99735,
437 0xa969a7aa, 0xc50c06c2, 0x5a04abfc, 0x800bcadc,
438 0x9e447a2e, 0xc3453484, 0xfdd56705, 0x0e1e9ec9,
439 0xdb73dbd3, 0x105588cd, 0x675fda79, 0xe3674340,
440 0xc5c43465, 0x713e38d8, 0x3d28f89e, 0xf16dff20,
441 0x153e21e7, 0x8fb03d4a, 0xe6e39f2b, 0xdb83adf7,
442 0xe93d5a68, 0x948140f7, 0xf64c261c, 0x94692934,
443 0x411520f7, 0x7602d4f7, 0xbcf46b2e, 0xd4a20068,
444 0xd4082471, 0x3320f46a, 0x43b7d4b7, 0x500061af,
445 0x1e39f62e, 0x97244546, 0x14214f74, 0xbf8b8840,
446 0x4d95fc1d, 0x96b591af, 0x70f4ddd3, 0x66a02f45,
447 0xbfbc09ec, 0x03bd9785, 0x7fac6dd0, 0x31cb8504,
448 0x96eb27b3, 0x55fd3941, 0xda2547e6, 0xabca0a9a,
449 0x28507825, 0x530429f4, 0x0a2c86da, 0xe9b66dfb,
450 0x68dc1462, 0xd7486900, 0x680ec0a4, 0x27a18dee,
451 0x4f3ffea2, 0xe887ad8c, 0xb58ce006, 0x7af4d6b6,
452 0xaace1e7c, 0xd3375fec, 0xce78a399, 0x406b2a42,
453 0x20fe9e35, 0xd9f385b9, 0xee39d7ab, 0x3b124e8b,
454 0x1dc9faf7, 0x4b6d1856, 0x26a36631, 0xeae397b2,
455 0x3a6efa74, 0xdd5b4332, 0x6841e7f7, 0xca7820fb,
456 0xfb0af54e, 0xd8feb397, 0x454056ac, 0xba489527,
457 0x55533a3a, 0x20838d87, 0xfe6ba9b7, 0xd096954b,
458 0x55a867bc, 0xa1159a58, 0xcca92963, 0x99e1db33,
459 0xa62a4a56, 0x3f3125f9, 0x5ef47e1c, 0x9029317c,
460 0xfdf8e802, 0x04272f70, 0x80bb155c, 0x05282ce3,
461 0x95c11548, 0xe4c66d22, 0x48c1133f, 0xc70f86dc,
462 0x07f9c9ee, 0x41041f0f, 0x404779a4, 0x5d886e17,
463 0x325f51eb, 0xd59bc0d1, 0xf2bcc18f, 0x41113564,
464 0x257b7834, 0x602a9c60, 0xdff8e8a3, 0x1f636c1b,
465 0x0e12b4c2, 0x02e1329e, 0xaf664fd1, 0xcad18115,
466 0x6b2395e0, 0x333e92e1, 0x3b240b62, 0xeebeb922,
467 0x85b2a20e, 0xe6ba0d99, 0xde720c8c, 0x2da2f728,
468 0xd0127845, 0x95b794fd, 0x647d0862, 0xe7ccf5f0,
469 0x5449a36f, 0x877d48fa, 0xc39dfd27, 0xf33e8d1e,
470 0x0a476341, 0x992eff74, 0x3a6f6eab, 0xf4f8fd37,
471 0xa812dc60, 0xa1ebddf8, 0x991be14c, 0xdb6e6b0d,
472 0xc67b5510, 0x6d672c37, 0x2765d43b, 0xdcd0e804,
473 0xf1290dc7, 0xcc00ffa3, 0xb5390f92, 0x690fed0b,
474 0x667b9ffb, 0xcedb7d9c, 0xa091cf0b, 0xd9155ea3,
475 0xbb132f88, 0x515bad24, 0x7b9479bf, 0x763bd6eb,
476 0x37392eb3, 0xcc115979, 0x8026e297, 0xf42e312d,
477 0x6842ada7, 0xc66a2b3b, 0x12754ccc, 0x782ef11c,
478 0x6a124237, 0xb79251e7, 0x06a1bbe6, 0x4bfb6350,
479 0x1a6b1018, 0x11caedfa, 0x3d25bdd8, 0xe2e1c3c9,
480 0x44421659, 0x0a121386, 0xd90cec6e, 0xd5abea2a,
481 0x64af674e, 0xda86a85f, 0xbebfe988, 0x64e4c3fe,
482 0x9dbc8057, 0xf0f7c086, 0x60787bf8, 0x6003604d,
483 0xd1fd8346, 0xf6381fb0, 0x7745ae04, 0xd736fccc,
484 0x83426b33, 0xf01eab71, 0xb0804187, 0x3c005e5f,
485 0x77a057be, 0xbde8ae24, 0x55464299, 0xbf582e61,
486 0x4e58f48f, 0xf2ddfda2, 0xf474ef38, 0x8789bdc2,
487 0x5366f9c3, 0xc8b38e74, 0xb475f255, 0x46fcd9b9,
488 0x7aeb2661, 0x8b1ddf84, 0x846a0e79, 0x915f95e2,
489 0x466e598e, 0x20b45770, 0x8cd55591, 0xc902de4c,
490 0xb90bace1, 0xbb8205d0, 0x11a86248, 0x7574a99e,
491 0xb77f19b6, 0xe0a9dc09, 0x662d09a1, 0xc4324633,
492 0xe85a1f02, 0x09f0be8c, 0x4a99a025, 0x1d6efe10,
493 0x1ab93d1d, 0x0ba5a4df, 0xa186f20f, 0x2868f169,
494 0xdcb7da83, 0x573906fe, 0xa1e2ce9b, 0x4fcd7f52,
495 0x50115e01, 0xa70683fa, 0xa002b5c4, 0x0de6d027,
496 0x9af88c27, 0x773f8641, 0xc3604c06, 0x61a806b5,
497 0xf0177a28, 0xc0f586e0, 0x006058aa, 0x30dc7d62,
498 0x11e69ed7, 0x2338ea63, 0x53c2dd94, 0xc2c21634,
499 0xbbcbee56, 0x90bcb6de, 0xebfc7da1, 0xce591d76,
500 0x6f05e409, 0x4b7c0188, 0x39720a3d, 0x7c927c24,
501 0x86e3725f, 0x724d9db9, 0x1ac15bb4, 0xd39eb8fc,
502 0xed545578, 0x08fca5b5, 0xd83d7cd3, 0x4dad0fc4,
503 0x1e50ef5e, 0xb161e6f8, 0xa28514d9, 0x6c51133c,
504 0x6fd5c7e7, 0x56e14ec4, 0x362abfce, 0xddc6c837,
505 0xd79a3234, 0x92638212, 0x670efa8e, 0x406000e0,
506 0x3a39ce37, 0xd3faf5cf, 0xabc27737, 0x5ac52d1b,
507 0x5cb0679e, 0x4fa33742, 0xd3822740, 0x99bc9bbe,
508 0xd5118e9d, 0xbf0f7315, 0xd62d1c7e, 0xc700c47b,
509 0xb78c1b6b, 0x21a19045, 0xb26eb1be, 0x6a366eb4,
510 0x5748ab2f, 0xbc946e79, 0xc6a376d2, 0x6549c2c8,
511 0x530ff8ee, 0x468dde7d, 0xd5730a1d, 0x4cd04dc6,
512 0x2939bbdb, 0xa9ba4650, 0xac9526e8, 0xbe5ee304,
513 0xa1fad5f0, 0x6a2d519a, 0x63ef8ce2, 0x9a86ee22,
514 0xc089c2b8, 0x43242ef6, 0xa51e03aa, 0x9cf2d0a4,
515 0x83c061ba, 0x9be96a4d, 0x8fe51550, 0xba645bd6,
516 0x2826a2f9, 0xa73a3ae1, 0x4ba99586, 0xef5562e9,
517 0xc72fefd3, 0xf752f7da, 0x3f046f69, 0x77fa0a59,
518 0x80e4a915, 0x87b08601, 0x9b09e6ad, 0x3b3ee593,
519 0xe990fd5a, 0x9e34d797, 0x2cf0b7d9, 0x022b8b51,
520 0x96d5ac3a, 0x017da67d, 0xd1cf3ed6, 0x7c7d2d28,
521 0x1f9f25cf, 0xadf2b89b, 0x5ad6b472, 0x5a88f54c,
522 0xe029ac71, 0xe019a5e6, 0x47b0acfd, 0xed93fa9b,
523 0xe8d3c48d, 0x283b57cc, 0xf8d56629, 0x79132e28,
524 0x785f0191, 0xed756055, 0xf7960e44, 0xe3d35e8c,
525 0x15056dd4, 0x88f46dba, 0x03a16125, 0x0564f0bd,
526 0xc3eb9e15, 0x3c9057a2, 0x97271aec, 0xa93a072a,
527 0x1b3f6d9b, 0x1e6321f5, 0xf59c66fb, 0x26dcf319,
528 0x7533d928, 0xb155fdf5, 0x03563482, 0x8aba3cbb,
529 0x28517711, 0xc20ad9f8, 0xabcc5167, 0xccad925f,
530 0x4de81751, 0x3830dc8e, 0x379d5862, 0x9320f991,
531 0xea7a90c2, 0xfb3e7bce, 0x5121ce64, 0x774fbe32,
532 0xa8b6e37e, 0xc3293d46, 0x48de5369, 0x6413e680,
533 0xa2ae0810, 0xdd6db224, 0x69852dfd, 0x09072166,
534 0xb39a460a, 0x6445c0dd, 0x586cdecf, 0x1c20c8ae,
535 0x5bbef7dd, 0x1b588d40, 0xccd2017f, 0x6bb4e3bb,
536 0xdda26a7e, 0x3a59ff45, 0x3e350a44, 0xbcb4cdd5,
537 0x72eacea8, 0xfa6484bb, 0x8d6612ae, 0xbf3c6f47,
538 0xd29be463, 0x542f5d9e, 0xaec2771b, 0xf64e6370,
539 0x740e0d8d, 0xe75b1357, 0xf8721671, 0xaf537d5d,
540 0x4040cb08, 0x4eb4e2cc, 0x34d2466a, 0x0115af84,
541 0xe1b00428, 0x95983a1d, 0x06b89fb4, 0xce6ea048,
542 0x6f3f3b82, 0x3520ab82, 0x011a1d4b, 0x277227f8,
543 0x611560b1, 0xe7933fdc, 0xbb3a792b, 0x344525bd,
544 0xa08839e1, 0x51ce794b, 0x2f32c9b7, 0xa01fbac9,
545 0xe01cc87e, 0xbcc7d1f6, 0xcf0111c3, 0xa1e8aac7,
546 0x1a908749, 0xd44fbd9a, 0xd0dadecb, 0xd50ada38,
547 0x0339c32a, 0xc6913667, 0x8df9317c, 0xe0b12b4f,
548 0xf79e59b7, 0x43f5bb3a, 0xf2d519ff, 0x27d9459c,
549 0xbf97222c, 0x15e6fc2a, 0x0f91fc71, 0x9b941525,
550 0xfae59361, 0xceb69ceb, 0xc2a86459, 0x12baa8d1,
551 0xb6c1075e, 0xe3056a0c, 0x10d25065, 0xcb03a442,
552 0xe0ec6e0e, 0x1698db3b, 0x4c98a0be, 0x3278e964,
553 0x9f1f9532, 0xe0d392df, 0xd3a0342b, 0x8971f21e,
554 0x1b0a7441, 0x4ba3348c, 0xc5be7120, 0xc37632d8,
555 0xdf359f8d, 0x9b992f2e, 0xe60b6f47, 0x0fe3f11d,
556 0xe54cda54, 0x1edad891, 0xce6279cf, 0xcd3e7e6f,
557 0x1618b166, 0xfd2c1d05, 0x848fd2c5, 0xf6fb2299,
558 0xf523f357, 0xa6327623, 0x93a83531, 0x56cccd02,
559 0xacf08162, 0x5a75ebb5, 0x6e163697, 0x88d273cc,
560 0xde966292, 0x81b949d0, 0x4c50901b, 0x71c65614,
561 0xe6c6c7bd, 0x327a140a, 0x45e1d006, 0xc3f27b9a,
562 0xc9aa53fd, 0x62a80f00, 0xbb25bfe2, 0x35bdd2f6,
563 0x71126905, 0xb2040222, 0xb6cbcf7c, 0xcd769c2b,
564 0x53113ec0, 0x1640e3d3, 0x38abbd60, 0x2547adf0,
565 0xba38209c, 0xf746ce76, 0x77afa1c5, 0x20756060,
566 0x85cbfe4e, 0x8ae88dd8, 0x7aaaf9b0, 0x4cf9aa7e,
567 0x1948c25c, 0x02fb8a8c, 0x01c36ae4, 0xd6ebe1f9,
568 0x90d4f869, 0xa65cdea0, 0x3f09252d, 0xc208e69f,
569 0xb74e6132, 0xce77e25b, 0x578fdfe3, 0x3ac372e6
570};
571
572#define EROUND(l,r) l ^= *(p++); r ^= ((s[((l>>24)&0xff)+0x000]+s[((l>>16)&0xff)+0x100])^s[((l>>8)&0xff)+0x200])+s[((l>>0)&0xff)+0x300]
573#define DROUND(l,r) l ^= *(p--); r ^= ((s[((l>>24)&0xff)+0x000]+s[((l>>16)&0xff)+0x100])^s[((l>>8)&0xff)+0x200])+s[((l>>0)&0xff)+0x300]
574
575static int blowfishEncrypt(struct blowfishParam* bp, uint32_t* dst, const uint32_t* src)
576{
577 #if WORDS_BIGENDIAN
578 register uint32_t xl = src[0], xr = src[1];
579 #else
580 register uint32_t xl = swapu32(src[0]), xr = swapu32(src[1]);
581 #endif
582 register uint32_t* p = bp->p;
583 register uint32_t* s = bp->s;
584
585 EROUND(xl, xr); EROUND(xr, xl);
586 EROUND(xl, xr); EROUND(xr, xl);
587 EROUND(xl, xr); EROUND(xr, xl);
588 EROUND(xl, xr); EROUND(xr, xl);
589 EROUND(xl, xr); EROUND(xr, xl);
590 EROUND(xl, xr); EROUND(xr, xl);
591 EROUND(xl, xr); EROUND(xr, xl);
592 EROUND(xl, xr); EROUND(xr, xl);
593
594 #if WORDS_BIGENDIAN
595 dst[1] = xl ^ *(p++);
596 dst[0] = xr ^ *(p++);
597 #else
598 dst[1] = swapu32(xl ^ *(p++));
599 dst[0] = swapu32(xr ^ *(p++));
600 #endif
601
602 return 0;
603}
604
605static int blowfishDecrypt(struct blowfishParam* bp, uint32_t* dst, const uint32_t* src)
606{
607 #if WORDS_BIGENDIAN
608 register uint32_t xl = src[0], xr = src[1];
609 #else
610 register uint32_t xl = swapu32(src[0]), xr = swapu32(src[1]);
611 #endif
612 register uint32_t* p = bp->p+BLOWFISHPSIZE-1;
613 register uint32_t* s = bp->s;
614
615 DROUND(xl, xr); DROUND(xr, xl);
616 DROUND(xl, xr); DROUND(xr, xl);
617 DROUND(xl, xr); DROUND(xr, xl);
618 DROUND(xl, xr); DROUND(xr, xl);
619 DROUND(xl, xr); DROUND(xr, xl);
620 DROUND(xl, xr); DROUND(xr, xl);
621 DROUND(xl, xr); DROUND(xr, xl);
622 DROUND(xl, xr); DROUND(xr, xl);
623
624 #if WORDS_BIGENDIAN
625 dst[1] = xl ^ *(p--);
626 dst[0] = xr ^ *(p--);
627 #else
628 dst[1] = swapu32(xl ^ *(p--));
629 dst[0] = swapu32(xr ^ *(p--));
630 #endif
631
632 return 0;
633}
634
635static int blowfishSetup(struct blowfishParam* bp, const unsigned char* key, size_t keybits, cipherOperation op)
636{
637 if ((op != ENCRYPT) && (op != DECRYPT))
638 return -1;
639
640 if (((keybits & 7) == 0) && (keybits >= 32) && (keybits <= 448))
641 {
642 register uint32_t* p = bp->p;
643 register uint32_t* s = bp->s;
644 register unsigned int i, j, k;
645
646 uint32_t tmp, work[2];
647
648 memcpy(s, _bf_s, 1024 * sizeof(uint32_t));
649
650 for (i = 0, k = 0; i < BLOWFISHPSIZE; i++)
651 {
652 tmp = 0;
653 for (j = 0; j < 4; j++)
654 {
655 tmp <<= 8;
656 tmp |= key[k++];
657 if (k >= (keybits >> 3))
658 k = 0;
659 }
660 p[i] = _bf_p[i] ^ tmp;
661 }
662
663 work[0] = work[1] = 0;
664
665 for (i = 0; i < BLOWFISHPSIZE; i += 2, p += 2)
666 {
667 blowfishEncrypt(bp, work, work);
668 #if WORDS_BIGENDIAN
669 p[0] = work[0];
670 p[1] = work[1];
671 #else
672 p[0] = swapu32(work[0]);
673 p[1] = swapu32(work[1]);
674 #endif
675 }
676
677 for (i = 0; i < 1024; i += 2, s += 2)
678 {
679 blowfishEncrypt(bp, work, work);
680 #if WORDS_BIGENDIAN
681 s[0] = work[0];
682 s[1] = work[1];
683 #else
684 s[0] = swapu32(work[0]);
685 s[1] = swapu32(work[1]);
686 #endif
687 }
688
689 /* clear fdback/iv */
690 bp->fdback[0] = 0;
691 bp->fdback[1] = 0;
692
693 return 0;
694 }
695 return -1;
696}
697
698static int blowfishSetIV(struct blowfishParam* bp, const unsigned char* iv)
699{
700 if (iv)
701 memcpy(bp->fdback, iv, 8);
702 else
703 memset(bp->fdback, 0, 8);
704
705 return 0;
706}
707
708#define BLOWFISH_BLOCKSIZE 8
709static int blowfishDecryptCBC(struct blowfishParam* bp, uint32_t* dst, const uint32_t* src, unsigned int nblocks)
710{
711 register const unsigned int blockwords = BLOWFISH_BLOCKSIZE >> 2;
712 register uint32_t* fdback = bp->fdback;
713 register uint32_t* buf = (uint32_t*) malloc(blockwords * sizeof(uint32_t));
714
715 if (buf)
716 {
717 while (nblocks > 0)
718 {
719 register uint32_t tmp;
720 register unsigned int i;
721
722 blowfishDecrypt(bp, buf, src);
723
724 for (i = 0; i < blockwords; i++)
725 {
726 tmp = src[i];
727 dst[i] = buf[i] ^ fdback[i];
728 fdback[i] = tmp;
729 }
730
731 dst += blockwords;
732 src += blockwords;
733
734 nblocks--;
735 }
736 free(buf);
737 return 0;
738 }
739
740 return -1;
741}
742
743bool bf_cbc_decrypt(const unsigned char* key, size_t keylen,
744 unsigned char* data, size_t datalen,
745 const unsigned char* iv)
746{
747 struct blowfishParam param;
748 unsigned char *cipher;
749 unsigned int nblocks;
750
751 if (datalen % BLOWFISH_BLOCKSIZE)
752 return false;
753
754 if (blowfishSetup(&param, key, keylen * 8, ENCRYPT))
755 return false;
756 if (blowfishSetIV(&param, iv))
757 return false;
758
759 cipher = malloc(datalen);
760 memcpy(cipher, data, datalen);
761
762 nblocks = datalen / BLOWFISH_BLOCKSIZE;
763 if (blowfishDecryptCBC(&param, (uint32_t*)data, (uint32_t*)cipher,
764 nblocks))
765 {
766 free(cipher);
767 return false;
768 }
769
770 free(cipher);
771 return true;
772}
773
774uint32_t swap(uint32_t val)
775{
776 return ((val & 0xFF) << 24)
777 | ((val & 0xFF00) << 8)
778 | ((val & 0xFF0000) >> 8)
779 | ((val & 0xFF000000) >> 24);
780}
781
782/* read a file to a buffer */
783enum zen_error_t read_file(const char *file, void **buffer, size_t *size)
784{
785 FILE *f = fopen(file, "rb");
786 if(f == NULL)
787 {
788 printf("[ERR] Cannot open file '%s' for reading: %m\n", file);
789 return ZEN_OPEN_ERROR;
790 }
791 fseek(f, 0, SEEK_END);
792 *size = ftell(f);
793 fseek(f, 0, SEEK_SET);
794 *buffer = malloc(*size);
795 if(fread(*buffer, *size, 1, f) != 1)
796 {
797 free(*buffer);
798 fclose(f);
799 printf("[ERR] Cannot read file '%s': %m\n", file);
800 return ZEN_READ_ERROR;
801 }
802 fclose(f);
803 return ZEN_SUCCESS;
804}
805
806/* write a file from a buffer */
807enum zen_error_t write_file(const char *file, void *buffer, size_t size)
808{
809 FILE *f = fopen(file, "wb");
810 if(f == NULL)
811 {
812 printf("[ERR] Cannot open file '%s' for writing: %m\n", file);
813 return ZEN_OPEN_ERROR;
814 }
815 if(fwrite(buffer, size, 1, f) != 1)
816 {
817 fclose(f);
818 printf("[ERR] Cannot write file '%s': %m\n", file);
819 return ZEN_WRITE_ERROR;
820 }
821 fclose(f);
822 return ZEN_SUCCESS;
823}
824
825/* compute MD5 sum of a buffer */
826enum zen_error_t compute_md5sum_buf(void *buf, size_t sz, uint8_t file_md5sum[16])
827{
828 md5_context ctx;
829 md5_starts(&ctx);
830 md5_update(&ctx, buf, sz);
831 md5_finish(&ctx, file_md5sum);
832 return ZEN_SUCCESS;
833}
834
835/* compute MD5 of a file */
836enum zen_error_t compute_md5sum(const char *file, uint8_t file_md5sum[16])
837{
838 void *buf;
839 size_t sz;
840 enum zen_error_t err = read_file(file, &buf, &sz);
841 if(err != ZEN_SUCCESS)
842 return err;
843 compute_md5sum_buf(buf, sz, file_md5sum);
844 free(buf);
845 return ZEN_SUCCESS;
846}
847
848enum zen_error_t find_pe_data(void *fw, size_t fw_size, uint32_t *data_ptr, uint32_t *data_size)
849{
850 uint8_t *buffer = fw;
851 /* Rudimentary Win32 PE reading to find .data section */
852 if(memcmp(&buffer[0], "MZ", 2) != 0 && memcmp(&buffer[0x118], "PE", 2) != 0)
853 {
854 printf("[ERR] Input file isn't an executable\n");
855 return ZEN_FW_INVALID;
856 }
857 *data_ptr = 0, *data_size = 0;
858 uint32_t start_sec_addr = /*sizeof NT headers */ 0xf8 +
859 /* address of opt header */*(uint32_t *)&buffer[0x3c];
860 for(uint32_t i = start_sec_addr; i < 0x1000; i += 0x28)
861 {
862 if(strcmp((char*)&buffer[i], ".data") == 0)
863 {
864 *data_ptr = le2int(&buffer[i + 0x14]);
865 *data_size = le2int(&buffer[i + 0x10]);
866 break;
867 }
868 }
869 if(*data_ptr == 0 || *data_size == 0)
870 {
871 printf("[ERR] Couldn't find .data section\n");
872 return ZEN_FW_INVALID;
873 }
874 return ZEN_SUCCESS;
875}
876
877int convxdigit(char digit, uint8_t *val)
878{
879 if(digit >= '0' && digit <= '9')
880 {
881 *val = digit - '0';
882 return 0;
883 }
884 else if(digit >= 'A' && digit <= 'F')
885 {
886 *val = digit - 'A' + 10;
887 return 0;
888 }
889 else if(digit >= 'a' && digit <= 'f')
890 {
891 *val = digit - 'a' + 10;
892 return 0;
893 }
894 else
895 return 1;
896}