Prepare new maemo release
[maemo-rb.git] / tools / mkzenboot.c
blob1ee9952bf0445b06a7492ac9c587ac60911b8403
1 /***************************************************************************
2 * __________ __ ___.
3 * Open \______ \ ____ ____ | | _\_ |__ _______ ___
4 * Source | _// _ \_/ ___\| |/ /| __ \ / _ \ \/ /
5 * Jukebox | | ( <_> ) \___| < | \_\ ( <_> > < <
6 * Firmware |____|_ /\____/ \___ >__|_ \|___ /\____/__/\_ \
7 * \/ \/ \/ \/ \/
8 * $Id$
10 * Copyright (C) 2008 by Maurus Cuelenaere
12 * Based on zenutils by Rasmus Ry <rasmus.ry{at}gmail.com>
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.
19 * This software is distributed on an "AS IS" basis, WITHOUT WARRANTY OF ANY
20 * KIND, either express or implied.
22 ****************************************************************************/
23 #include <stdio.h>
24 #include <stdarg.h>
25 #include <stdlib.h>
26 #include <string.h>
27 #include <stdbool.h>
28 #include <inttypes.h>
29 #include <zlib.h>
30 #include "hmac-sha1.h"
32 static int filesize(FILE* fd)
34 int tmp, tmp2 = ftell(fd);
35 fseek(fd, 0, SEEK_END);
36 tmp = ftell(fd);
37 fseek(fd, tmp2, SEEK_SET);
38 return tmp;
41 static unsigned int le2int(unsigned char* buf)
43 return ((buf[3] << 24) | (buf[2] << 16) | (buf[1] << 8) | buf[0]);
46 static void int2le(unsigned int val, unsigned char* addr)
48 addr[0] = val & 0xFF;
49 addr[1] = (val >> 8) & 0xff;
50 addr[2] = (val >> 16) & 0xff;
51 addr[3] = (val >> 24) & 0xff;
54 static const char* find_firmware_key(const unsigned char* buffer, size_t len)
56 char szkey1[] = "34d1";
57 size_t cchkey1 = strlen(szkey1);
58 char szkey2[] = "TbnCboEbn";
59 size_t cchkey2 = strlen(szkey2);
60 uint32_t i;
61 for (i = 0; i < (uint32_t)len; i++)
63 if (len >= cchkey1)
65 if (!strncmp((char*)&buffer[i], szkey1, cchkey1))
66 return (const char*)&buffer[i];
68 if (len >= cchkey2)
70 if (!strncmp((char*)&buffer[i], szkey2, cchkey2))
71 return (const char*)&buffer[i];
74 return NULL;
77 static uint32_t find_firmware_offset(unsigned char* buffer, size_t len)
79 uint32_t i;
80 for (i = 0; i < (uint32_t)len; i += 0x10)
82 if (buffer[i + sizeof(uint32_t)] != 0
83 && buffer[i + sizeof(uint32_t) + 1] != 0
84 && buffer[i + sizeof(uint32_t) + 2] != 0
85 && buffer[i + sizeof(uint32_t) + 3] != 0)
87 return i;
89 if(i > 0xFF) /* Arbitrary guess */
90 return 0;
92 return 0;
95 static bool crypt_firmware(const char* key, unsigned char* buffer, size_t len)
97 char key_cpy[255];
98 unsigned int i;
99 unsigned int tmp = 0;
100 int key_length = strlen(key);
102 strcpy(key_cpy, key);
103 for(i=0; i < strlen(key); i++)
104 key_cpy[i] = key[i] - 1;
106 for(i=0; i < len; i++)
108 buffer[i] ^= key_cpy[tmp] | 0x80;
109 tmp = (tmp + 1) % key_length;
112 return true;
115 static bool inflate_to_buffer(const unsigned char *buffer, size_t len, unsigned char* out_buffer, size_t out_len, char** err_msg)
117 /* Initialize Zlib */
118 z_stream d_stream;
119 int ret;
121 d_stream.zalloc = Z_NULL;
122 d_stream.zfree = Z_NULL;
123 d_stream.opaque = Z_NULL;
125 d_stream.next_in = (unsigned char*)buffer;
126 d_stream.avail_in = len;
128 ret = inflateInit(&d_stream);
129 if (ret != Z_OK)
131 *err_msg = d_stream.msg;
132 return false;
135 d_stream.next_out = out_buffer;
136 d_stream.avail_out = out_len;
138 ret = inflate(&d_stream, Z_SYNC_FLUSH);
139 if(ret < 0)
141 *err_msg = d_stream.msg;
142 return false;
144 else
145 inflateEnd(&d_stream);
147 return true;
150 #define CODE_MASK 0xC0
151 #define ARGS_MASK 0x3F
153 #define REPEAT_CODE 0x00
154 #define BLOCK_CODE 0x40
155 #define LONG_RUN_CODE 0x80
156 #define SHORT_RUN_CODE 0xC0
158 #define BLOCK_ARGS 0x1F
159 #define BLOCK_MODE 0x20
162 static void decode_run(unsigned char* dst, uint16_t len, unsigned char val,
163 int* dstidx)
165 memset(dst + *dstidx, val, len);
166 *dstidx += len;
169 static void decode_pattern(unsigned char* src, unsigned char* dst,
170 uint16_t len, int* srcidx, int* dstidx,
171 bool bdecode, int npasses)
173 int i, j;
174 for (i = 0; i < npasses; i++)
176 if (bdecode)
178 for (j = 0; j < len; j++)
180 uint16_t c, d;
181 c = src[*srcidx + j];
182 d = (c >> 5) & 7;
183 c = (c << 3) & 0xF8;
184 src[*srcidx + j] = (unsigned char)(c | d);
186 bdecode = false;
188 memcpy(dst + *dstidx, src + *srcidx, len);
189 *dstidx += len;
191 *srcidx += len;
194 static int cenc_decode(unsigned char* src, int srclen, unsigned char* dst, int dstlen)
196 int i = 0, j = 0;
199 uint16_t c, d, e;
200 c = src[i++];
201 switch (c & CODE_MASK)
203 case REPEAT_CODE: /* 2 unsigned chars */
204 d = src[i++];
205 d = d + 2;
207 e = (c & ARGS_MASK) + 2;
209 decode_pattern(src, dst, e, &i, &j, false, d);
210 break;
212 case BLOCK_CODE: /* 1/2/3 unsigned chars */
213 d = c & BLOCK_ARGS;
214 if (!(c & BLOCK_MODE))
216 e = src[i++];
217 e = (d << 8) + (e + 0x21);
219 d = (uint16_t)(i ^ j);
221 else
223 e = d + 1;
225 d = (uint16_t)(i ^ j);
227 if (d & 1)
229 i++;
232 decode_pattern(src, dst, e, &i, &j, true, 1);
233 break;
235 case LONG_RUN_CODE: /* 3 unsigned chars */
236 d = src[i++];
237 e = ((c & ARGS_MASK) << 8) + (d + 0x42);
239 d = src[i++];
240 d = ((d & 7) << 5) | ((d >> 3) & 0x1F);
242 decode_run(dst, e, (unsigned char)(d), &j);
243 break;
245 case SHORT_RUN_CODE: /* 2 unsigned chars */
246 d = src[i++];
247 d = ((d & 3) << 6) | ((d >> 2) & 0x3F);
249 e = (c & ARGS_MASK) + 2;
251 decode_run(dst, e, (unsigned char)(d), &j);
252 break;
254 } while (i < srclen && j < dstlen);
256 return j;
260 * Copyright (c) 1999, 2000, 2002 Virtual Unlimited B.V.
262 * This library is free software; you can redistribute it and/or
263 * modify it under the terms of the GNU Lesser General Public
264 * License as published by the Free Software Foundation; either
265 * version 2.1 of the License, or (at your option) any later version.
267 * This library is distributed in the hope that it will be useful,
268 * but WITHOUT ANY WARRANTY; without even the implied warranty of
269 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
270 * Lesser General Public License for more details.
272 * You should have received a copy of the GNU Lesser General Public
273 * License along with this library; if not, write to the Free Software
274 * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
278 #define BLOWFISHROUNDS 16
279 #define BLOWFISHPSIZE (BLOWFISHROUNDS+2)
280 #define WORDS_BIGENDIAN 0
282 struct blowfishParam
284 uint32_t p[BLOWFISHPSIZE];
285 uint32_t s[1024];
286 uint32_t fdback[2];
289 typedef enum
291 NOCRYPT,
292 ENCRYPT,
293 DECRYPT
294 } cipherOperation;
296 static inline uint32_t swapu32(uint32_t n)
298 return ( ((n & 0xffU) << 24) |
299 ((n & 0xff00U) << 8) |
300 ((n & 0xff0000U) >> 8) |
301 ((n & 0xff000000U) >> 24) );
304 static uint32_t _bf_p[BLOWFISHPSIZE] = {
305 0x243f6a88, 0x85a308d3, 0x13198a2e, 0x03707344,
306 0xa4093822, 0x299f31d0, 0x082efa98, 0xec4e6c89,
307 0x452821e6, 0x38d01377, 0xbe5466cf, 0x34e90c6c,
308 0xc0ac29b7, 0xc97c50dd, 0x3f84d5b5, 0xb5470917,
309 0x9216d5d9, 0x8979fb1b
312 static uint32_t _bf_s[1024] = {
313 0xd1310ba6, 0x98dfb5ac, 0x2ffd72db, 0xd01adfb7,
314 0xb8e1afed, 0x6a267e96, 0xba7c9045, 0xf12c7f99,
315 0x24a19947, 0xb3916cf7, 0x0801f2e2, 0x858efc16,
316 0x636920d8, 0x71574e69, 0xa458fea3, 0xf4933d7e,
317 0x0d95748f, 0x728eb658, 0x718bcd58, 0x82154aee,
318 0x7b54a41d, 0xc25a59b5, 0x9c30d539, 0x2af26013,
319 0xc5d1b023, 0x286085f0, 0xca417918, 0xb8db38ef,
320 0x8e79dcb0, 0x603a180e, 0x6c9e0e8b, 0xb01e8a3e,
321 0xd71577c1, 0xbd314b27, 0x78af2fda, 0x55605c60,
322 0xe65525f3, 0xaa55ab94, 0x57489862, 0x63e81440,
323 0x55ca396a, 0x2aab10b6, 0xb4cc5c34, 0x1141e8ce,
324 0xa15486af, 0x7c72e993, 0xb3ee1411, 0x636fbc2a,
325 0x2ba9c55d, 0x741831f6, 0xce5c3e16, 0x9b87931e,
326 0xafd6ba33, 0x6c24cf5c, 0x7a325381, 0x28958677,
327 0x3b8f4898, 0x6b4bb9af, 0xc4bfe81b, 0x66282193,
328 0x61d809cc, 0xfb21a991, 0x487cac60, 0x5dec8032,
329 0xef845d5d, 0xe98575b1, 0xdc262302, 0xeb651b88,
330 0x23893e81, 0xd396acc5, 0x0f6d6ff3, 0x83f44239,
331 0x2e0b4482, 0xa4842004, 0x69c8f04a, 0x9e1f9b5e,
332 0x21c66842, 0xf6e96c9a, 0x670c9c61, 0xabd388f0,
333 0x6a51a0d2, 0xd8542f68, 0x960fa728, 0xab5133a3,
334 0x6eef0b6c, 0x137a3be4, 0xba3bf050, 0x7efb2a98,
335 0xa1f1651d, 0x39af0176, 0x66ca593e, 0x82430e88,
336 0x8cee8619, 0x456f9fb4, 0x7d84a5c3, 0x3b8b5ebe,
337 0xe06f75d8, 0x85c12073, 0x401a449f, 0x56c16aa6,
338 0x4ed3aa62, 0x363f7706, 0x1bfedf72, 0x429b023d,
339 0x37d0d724, 0xd00a1248, 0xdb0fead3, 0x49f1c09b,
340 0x075372c9, 0x80991b7b, 0x25d479d8, 0xf6e8def7,
341 0xe3fe501a, 0xb6794c3b, 0x976ce0bd, 0x04c006ba,
342 0xc1a94fb6, 0x409f60c4, 0x5e5c9ec2, 0x196a2463,
343 0x68fb6faf, 0x3e6c53b5, 0x1339b2eb, 0x3b52ec6f,
344 0x6dfc511f, 0x9b30952c, 0xcc814544, 0xaf5ebd09,
345 0xbee3d004, 0xde334afd, 0x660f2807, 0x192e4bb3,
346 0xc0cba857, 0x45c8740f, 0xd20b5f39, 0xb9d3fbdb,
347 0x5579c0bd, 0x1a60320a, 0xd6a100c6, 0x402c7279,
348 0x679f25fe, 0xfb1fa3cc, 0x8ea5e9f8, 0xdb3222f8,
349 0x3c7516df, 0xfd616b15, 0x2f501ec8, 0xad0552ab,
350 0x323db5fa, 0xfd238760, 0x53317b48, 0x3e00df82,
351 0x9e5c57bb, 0xca6f8ca0, 0x1a87562e, 0xdf1769db,
352 0xd542a8f6, 0x287effc3, 0xac6732c6, 0x8c4f5573,
353 0x695b27b0, 0xbbca58c8, 0xe1ffa35d, 0xb8f011a0,
354 0x10fa3d98, 0xfd2183b8, 0x4afcb56c, 0x2dd1d35b,
355 0x9a53e479, 0xb6f84565, 0xd28e49bc, 0x4bfb9790,
356 0xe1ddf2da, 0xa4cb7e33, 0x62fb1341, 0xcee4c6e8,
357 0xef20cada, 0x36774c01, 0xd07e9efe, 0x2bf11fb4,
358 0x95dbda4d, 0xae909198, 0xeaad8e71, 0x6b93d5a0,
359 0xd08ed1d0, 0xafc725e0, 0x8e3c5b2f, 0x8e7594b7,
360 0x8ff6e2fb, 0xf2122b64, 0x8888b812, 0x900df01c,
361 0x4fad5ea0, 0x688fc31c, 0xd1cff191, 0xb3a8c1ad,
362 0x2f2f2218, 0xbe0e1777, 0xea752dfe, 0x8b021fa1,
363 0xe5a0cc0f, 0xb56f74e8, 0x18acf3d6, 0xce89e299,
364 0xb4a84fe0, 0xfd13e0b7, 0x7cc43b81, 0xd2ada8d9,
365 0x165fa266, 0x80957705, 0x93cc7314, 0x211a1477,
366 0xe6ad2065, 0x77b5fa86, 0xc75442f5, 0xfb9d35cf,
367 0xebcdaf0c, 0x7b3e89a0, 0xd6411bd3, 0xae1e7e49,
368 0x00250e2d, 0x2071b35e, 0x226800bb, 0x57b8e0af,
369 0x2464369b, 0xf009b91e, 0x5563911d, 0x59dfa6aa,
370 0x78c14389, 0xd95a537f, 0x207d5ba2, 0x02e5b9c5,
371 0x83260376, 0x6295cfa9, 0x11c81968, 0x4e734a41,
372 0xb3472dca, 0x7b14a94a, 0x1b510052, 0x9a532915,
373 0xd60f573f, 0xbc9bc6e4, 0x2b60a476, 0x81e67400,
374 0x08ba6fb5, 0x571be91f, 0xf296ec6b, 0x2a0dd915,
375 0xb6636521, 0xe7b9f9b6, 0xff34052e, 0xc5855664,
376 0x53b02d5d, 0xa99f8fa1, 0x08ba4799, 0x6e85076a,
377 0x4b7a70e9, 0xb5b32944, 0xdb75092e, 0xc4192623,
378 0xad6ea6b0, 0x49a7df7d, 0x9cee60b8, 0x8fedb266,
379 0xecaa8c71, 0x699a17ff, 0x5664526c, 0xc2b19ee1,
380 0x193602a5, 0x75094c29, 0xa0591340, 0xe4183a3e,
381 0x3f54989a, 0x5b429d65, 0x6b8fe4d6, 0x99f73fd6,
382 0xa1d29c07, 0xefe830f5, 0x4d2d38e6, 0xf0255dc1,
383 0x4cdd2086, 0x8470eb26, 0x6382e9c6, 0x021ecc5e,
384 0x09686b3f, 0x3ebaefc9, 0x3c971814, 0x6b6a70a1,
385 0x687f3584, 0x52a0e286, 0xb79c5305, 0xaa500737,
386 0x3e07841c, 0x7fdeae5c, 0x8e7d44ec, 0x5716f2b8,
387 0xb03ada37, 0xf0500c0d, 0xf01c1f04, 0x0200b3ff,
388 0xae0cf51a, 0x3cb574b2, 0x25837a58, 0xdc0921bd,
389 0xd19113f9, 0x7ca92ff6, 0x94324773, 0x22f54701,
390 0x3ae5e581, 0x37c2dadc, 0xc8b57634, 0x9af3dda7,
391 0xa9446146, 0x0fd0030e, 0xecc8c73e, 0xa4751e41,
392 0xe238cd99, 0x3bea0e2f, 0x3280bba1, 0x183eb331,
393 0x4e548b38, 0x4f6db908, 0x6f420d03, 0xf60a04bf,
394 0x2cb81290, 0x24977c79, 0x5679b072, 0xbcaf89af,
395 0xde9a771f, 0xd9930810, 0xb38bae12, 0xdccf3f2e,
396 0x5512721f, 0x2e6b7124, 0x501adde6, 0x9f84cd87,
397 0x7a584718, 0x7408da17, 0xbc9f9abc, 0xe94b7d8c,
398 0xec7aec3a, 0xdb851dfa, 0x63094366, 0xc464c3d2,
399 0xef1c1847, 0x3215d908, 0xdd433b37, 0x24c2ba16,
400 0x12a14d43, 0x2a65c451, 0x50940002, 0x133ae4dd,
401 0x71dff89e, 0x10314e55, 0x81ac77d6, 0x5f11199b,
402 0x043556f1, 0xd7a3c76b, 0x3c11183b, 0x5924a509,
403 0xf28fe6ed, 0x97f1fbfa, 0x9ebabf2c, 0x1e153c6e,
404 0x86e34570, 0xeae96fb1, 0x860e5e0a, 0x5a3e2ab3,
405 0x771fe71c, 0x4e3d06fa, 0x2965dcb9, 0x99e71d0f,
406 0x803e89d6, 0x5266c825, 0x2e4cc978, 0x9c10b36a,
407 0xc6150eba, 0x94e2ea78, 0xa5fc3c53, 0x1e0a2df4,
408 0xf2f74ea7, 0x361d2b3d, 0x1939260f, 0x19c27960,
409 0x5223a708, 0xf71312b6, 0xebadfe6e, 0xeac31f66,
410 0xe3bc4595, 0xa67bc883, 0xb17f37d1, 0x018cff28,
411 0xc332ddef, 0xbe6c5aa5, 0x65582185, 0x68ab9802,
412 0xeecea50f, 0xdb2f953b, 0x2aef7dad, 0x5b6e2f84,
413 0x1521b628, 0x29076170, 0xecdd4775, 0x619f1510,
414 0x13cca830, 0xeb61bd96, 0x0334fe1e, 0xaa0363cf,
415 0xb5735c90, 0x4c70a239, 0xd59e9e0b, 0xcbaade14,
416 0xeecc86bc, 0x60622ca7, 0x9cab5cab, 0xb2f3846e,
417 0x648b1eaf, 0x19bdf0ca, 0xa02369b9, 0x655abb50,
418 0x40685a32, 0x3c2ab4b3, 0x319ee9d5, 0xc021b8f7,
419 0x9b540b19, 0x875fa099, 0x95f7997e, 0x623d7da8,
420 0xf837889a, 0x97e32d77, 0x11ed935f, 0x16681281,
421 0x0e358829, 0xc7e61fd6, 0x96dedfa1, 0x7858ba99,
422 0x57f584a5, 0x1b227263, 0x9b83c3ff, 0x1ac24696,
423 0xcdb30aeb, 0x532e3054, 0x8fd948e4, 0x6dbc3128,
424 0x58ebf2ef, 0x34c6ffea, 0xfe28ed61, 0xee7c3c73,
425 0x5d4a14d9, 0xe864b7e3, 0x42105d14, 0x203e13e0,
426 0x45eee2b6, 0xa3aaabea, 0xdb6c4f15, 0xfacb4fd0,
427 0xc742f442, 0xef6abbb5, 0x654f3b1d, 0x41cd2105,
428 0xd81e799e, 0x86854dc7, 0xe44b476a, 0x3d816250,
429 0xcf62a1f2, 0x5b8d2646, 0xfc8883a0, 0xc1c7b6a3,
430 0x7f1524c3, 0x69cb7492, 0x47848a0b, 0x5692b285,
431 0x095bbf00, 0xad19489d, 0x1462b174, 0x23820e00,
432 0x58428d2a, 0x0c55f5ea, 0x1dadf43e, 0x233f7061,
433 0x3372f092, 0x8d937e41, 0xd65fecf1, 0x6c223bdb,
434 0x7cde3759, 0xcbee7460, 0x4085f2a7, 0xce77326e,
435 0xa6078084, 0x19f8509e, 0xe8efd855, 0x61d99735,
436 0xa969a7aa, 0xc50c06c2, 0x5a04abfc, 0x800bcadc,
437 0x9e447a2e, 0xc3453484, 0xfdd56705, 0x0e1e9ec9,
438 0xdb73dbd3, 0x105588cd, 0x675fda79, 0xe3674340,
439 0xc5c43465, 0x713e38d8, 0x3d28f89e, 0xf16dff20,
440 0x153e21e7, 0x8fb03d4a, 0xe6e39f2b, 0xdb83adf7,
441 0xe93d5a68, 0x948140f7, 0xf64c261c, 0x94692934,
442 0x411520f7, 0x7602d4f7, 0xbcf46b2e, 0xd4a20068,
443 0xd4082471, 0x3320f46a, 0x43b7d4b7, 0x500061af,
444 0x1e39f62e, 0x97244546, 0x14214f74, 0xbf8b8840,
445 0x4d95fc1d, 0x96b591af, 0x70f4ddd3, 0x66a02f45,
446 0xbfbc09ec, 0x03bd9785, 0x7fac6dd0, 0x31cb8504,
447 0x96eb27b3, 0x55fd3941, 0xda2547e6, 0xabca0a9a,
448 0x28507825, 0x530429f4, 0x0a2c86da, 0xe9b66dfb,
449 0x68dc1462, 0xd7486900, 0x680ec0a4, 0x27a18dee,
450 0x4f3ffea2, 0xe887ad8c, 0xb58ce006, 0x7af4d6b6,
451 0xaace1e7c, 0xd3375fec, 0xce78a399, 0x406b2a42,
452 0x20fe9e35, 0xd9f385b9, 0xee39d7ab, 0x3b124e8b,
453 0x1dc9faf7, 0x4b6d1856, 0x26a36631, 0xeae397b2,
454 0x3a6efa74, 0xdd5b4332, 0x6841e7f7, 0xca7820fb,
455 0xfb0af54e, 0xd8feb397, 0x454056ac, 0xba489527,
456 0x55533a3a, 0x20838d87, 0xfe6ba9b7, 0xd096954b,
457 0x55a867bc, 0xa1159a58, 0xcca92963, 0x99e1db33,
458 0xa62a4a56, 0x3f3125f9, 0x5ef47e1c, 0x9029317c,
459 0xfdf8e802, 0x04272f70, 0x80bb155c, 0x05282ce3,
460 0x95c11548, 0xe4c66d22, 0x48c1133f, 0xc70f86dc,
461 0x07f9c9ee, 0x41041f0f, 0x404779a4, 0x5d886e17,
462 0x325f51eb, 0xd59bc0d1, 0xf2bcc18f, 0x41113564,
463 0x257b7834, 0x602a9c60, 0xdff8e8a3, 0x1f636c1b,
464 0x0e12b4c2, 0x02e1329e, 0xaf664fd1, 0xcad18115,
465 0x6b2395e0, 0x333e92e1, 0x3b240b62, 0xeebeb922,
466 0x85b2a20e, 0xe6ba0d99, 0xde720c8c, 0x2da2f728,
467 0xd0127845, 0x95b794fd, 0x647d0862, 0xe7ccf5f0,
468 0x5449a36f, 0x877d48fa, 0xc39dfd27, 0xf33e8d1e,
469 0x0a476341, 0x992eff74, 0x3a6f6eab, 0xf4f8fd37,
470 0xa812dc60, 0xa1ebddf8, 0x991be14c, 0xdb6e6b0d,
471 0xc67b5510, 0x6d672c37, 0x2765d43b, 0xdcd0e804,
472 0xf1290dc7, 0xcc00ffa3, 0xb5390f92, 0x690fed0b,
473 0x667b9ffb, 0xcedb7d9c, 0xa091cf0b, 0xd9155ea3,
474 0xbb132f88, 0x515bad24, 0x7b9479bf, 0x763bd6eb,
475 0x37392eb3, 0xcc115979, 0x8026e297, 0xf42e312d,
476 0x6842ada7, 0xc66a2b3b, 0x12754ccc, 0x782ef11c,
477 0x6a124237, 0xb79251e7, 0x06a1bbe6, 0x4bfb6350,
478 0x1a6b1018, 0x11caedfa, 0x3d25bdd8, 0xe2e1c3c9,
479 0x44421659, 0x0a121386, 0xd90cec6e, 0xd5abea2a,
480 0x64af674e, 0xda86a85f, 0xbebfe988, 0x64e4c3fe,
481 0x9dbc8057, 0xf0f7c086, 0x60787bf8, 0x6003604d,
482 0xd1fd8346, 0xf6381fb0, 0x7745ae04, 0xd736fccc,
483 0x83426b33, 0xf01eab71, 0xb0804187, 0x3c005e5f,
484 0x77a057be, 0xbde8ae24, 0x55464299, 0xbf582e61,
485 0x4e58f48f, 0xf2ddfda2, 0xf474ef38, 0x8789bdc2,
486 0x5366f9c3, 0xc8b38e74, 0xb475f255, 0x46fcd9b9,
487 0x7aeb2661, 0x8b1ddf84, 0x846a0e79, 0x915f95e2,
488 0x466e598e, 0x20b45770, 0x8cd55591, 0xc902de4c,
489 0xb90bace1, 0xbb8205d0, 0x11a86248, 0x7574a99e,
490 0xb77f19b6, 0xe0a9dc09, 0x662d09a1, 0xc4324633,
491 0xe85a1f02, 0x09f0be8c, 0x4a99a025, 0x1d6efe10,
492 0x1ab93d1d, 0x0ba5a4df, 0xa186f20f, 0x2868f169,
493 0xdcb7da83, 0x573906fe, 0xa1e2ce9b, 0x4fcd7f52,
494 0x50115e01, 0xa70683fa, 0xa002b5c4, 0x0de6d027,
495 0x9af88c27, 0x773f8641, 0xc3604c06, 0x61a806b5,
496 0xf0177a28, 0xc0f586e0, 0x006058aa, 0x30dc7d62,
497 0x11e69ed7, 0x2338ea63, 0x53c2dd94, 0xc2c21634,
498 0xbbcbee56, 0x90bcb6de, 0xebfc7da1, 0xce591d76,
499 0x6f05e409, 0x4b7c0188, 0x39720a3d, 0x7c927c24,
500 0x86e3725f, 0x724d9db9, 0x1ac15bb4, 0xd39eb8fc,
501 0xed545578, 0x08fca5b5, 0xd83d7cd3, 0x4dad0fc4,
502 0x1e50ef5e, 0xb161e6f8, 0xa28514d9, 0x6c51133c,
503 0x6fd5c7e7, 0x56e14ec4, 0x362abfce, 0xddc6c837,
504 0xd79a3234, 0x92638212, 0x670efa8e, 0x406000e0,
505 0x3a39ce37, 0xd3faf5cf, 0xabc27737, 0x5ac52d1b,
506 0x5cb0679e, 0x4fa33742, 0xd3822740, 0x99bc9bbe,
507 0xd5118e9d, 0xbf0f7315, 0xd62d1c7e, 0xc700c47b,
508 0xb78c1b6b, 0x21a19045, 0xb26eb1be, 0x6a366eb4,
509 0x5748ab2f, 0xbc946e79, 0xc6a376d2, 0x6549c2c8,
510 0x530ff8ee, 0x468dde7d, 0xd5730a1d, 0x4cd04dc6,
511 0x2939bbdb, 0xa9ba4650, 0xac9526e8, 0xbe5ee304,
512 0xa1fad5f0, 0x6a2d519a, 0x63ef8ce2, 0x9a86ee22,
513 0xc089c2b8, 0x43242ef6, 0xa51e03aa, 0x9cf2d0a4,
514 0x83c061ba, 0x9be96a4d, 0x8fe51550, 0xba645bd6,
515 0x2826a2f9, 0xa73a3ae1, 0x4ba99586, 0xef5562e9,
516 0xc72fefd3, 0xf752f7da, 0x3f046f69, 0x77fa0a59,
517 0x80e4a915, 0x87b08601, 0x9b09e6ad, 0x3b3ee593,
518 0xe990fd5a, 0x9e34d797, 0x2cf0b7d9, 0x022b8b51,
519 0x96d5ac3a, 0x017da67d, 0xd1cf3ed6, 0x7c7d2d28,
520 0x1f9f25cf, 0xadf2b89b, 0x5ad6b472, 0x5a88f54c,
521 0xe029ac71, 0xe019a5e6, 0x47b0acfd, 0xed93fa9b,
522 0xe8d3c48d, 0x283b57cc, 0xf8d56629, 0x79132e28,
523 0x785f0191, 0xed756055, 0xf7960e44, 0xe3d35e8c,
524 0x15056dd4, 0x88f46dba, 0x03a16125, 0x0564f0bd,
525 0xc3eb9e15, 0x3c9057a2, 0x97271aec, 0xa93a072a,
526 0x1b3f6d9b, 0x1e6321f5, 0xf59c66fb, 0x26dcf319,
527 0x7533d928, 0xb155fdf5, 0x03563482, 0x8aba3cbb,
528 0x28517711, 0xc20ad9f8, 0xabcc5167, 0xccad925f,
529 0x4de81751, 0x3830dc8e, 0x379d5862, 0x9320f991,
530 0xea7a90c2, 0xfb3e7bce, 0x5121ce64, 0x774fbe32,
531 0xa8b6e37e, 0xc3293d46, 0x48de5369, 0x6413e680,
532 0xa2ae0810, 0xdd6db224, 0x69852dfd, 0x09072166,
533 0xb39a460a, 0x6445c0dd, 0x586cdecf, 0x1c20c8ae,
534 0x5bbef7dd, 0x1b588d40, 0xccd2017f, 0x6bb4e3bb,
535 0xdda26a7e, 0x3a59ff45, 0x3e350a44, 0xbcb4cdd5,
536 0x72eacea8, 0xfa6484bb, 0x8d6612ae, 0xbf3c6f47,
537 0xd29be463, 0x542f5d9e, 0xaec2771b, 0xf64e6370,
538 0x740e0d8d, 0xe75b1357, 0xf8721671, 0xaf537d5d,
539 0x4040cb08, 0x4eb4e2cc, 0x34d2466a, 0x0115af84,
540 0xe1b00428, 0x95983a1d, 0x06b89fb4, 0xce6ea048,
541 0x6f3f3b82, 0x3520ab82, 0x011a1d4b, 0x277227f8,
542 0x611560b1, 0xe7933fdc, 0xbb3a792b, 0x344525bd,
543 0xa08839e1, 0x51ce794b, 0x2f32c9b7, 0xa01fbac9,
544 0xe01cc87e, 0xbcc7d1f6, 0xcf0111c3, 0xa1e8aac7,
545 0x1a908749, 0xd44fbd9a, 0xd0dadecb, 0xd50ada38,
546 0x0339c32a, 0xc6913667, 0x8df9317c, 0xe0b12b4f,
547 0xf79e59b7, 0x43f5bb3a, 0xf2d519ff, 0x27d9459c,
548 0xbf97222c, 0x15e6fc2a, 0x0f91fc71, 0x9b941525,
549 0xfae59361, 0xceb69ceb, 0xc2a86459, 0x12baa8d1,
550 0xb6c1075e, 0xe3056a0c, 0x10d25065, 0xcb03a442,
551 0xe0ec6e0e, 0x1698db3b, 0x4c98a0be, 0x3278e964,
552 0x9f1f9532, 0xe0d392df, 0xd3a0342b, 0x8971f21e,
553 0x1b0a7441, 0x4ba3348c, 0xc5be7120, 0xc37632d8,
554 0xdf359f8d, 0x9b992f2e, 0xe60b6f47, 0x0fe3f11d,
555 0xe54cda54, 0x1edad891, 0xce6279cf, 0xcd3e7e6f,
556 0x1618b166, 0xfd2c1d05, 0x848fd2c5, 0xf6fb2299,
557 0xf523f357, 0xa6327623, 0x93a83531, 0x56cccd02,
558 0xacf08162, 0x5a75ebb5, 0x6e163697, 0x88d273cc,
559 0xde966292, 0x81b949d0, 0x4c50901b, 0x71c65614,
560 0xe6c6c7bd, 0x327a140a, 0x45e1d006, 0xc3f27b9a,
561 0xc9aa53fd, 0x62a80f00, 0xbb25bfe2, 0x35bdd2f6,
562 0x71126905, 0xb2040222, 0xb6cbcf7c, 0xcd769c2b,
563 0x53113ec0, 0x1640e3d3, 0x38abbd60, 0x2547adf0,
564 0xba38209c, 0xf746ce76, 0x77afa1c5, 0x20756060,
565 0x85cbfe4e, 0x8ae88dd8, 0x7aaaf9b0, 0x4cf9aa7e,
566 0x1948c25c, 0x02fb8a8c, 0x01c36ae4, 0xd6ebe1f9,
567 0x90d4f869, 0xa65cdea0, 0x3f09252d, 0xc208e69f,
568 0xb74e6132, 0xce77e25b, 0x578fdfe3, 0x3ac372e6
571 #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]
572 #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 static int blowfishEncrypt(struct blowfishParam* bp, uint32_t* dst, const uint32_t* src)
576 #if WORDS_BIGENDIAN
577 register uint32_t xl = src[0], xr = src[1];
578 #else
579 register uint32_t xl = swapu32(src[0]), xr = swapu32(src[1]);
580 #endif
581 register uint32_t* p = bp->p;
582 register uint32_t* s = bp->s;
584 EROUND(xl, xr); EROUND(xr, xl);
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);
593 #if WORDS_BIGENDIAN
594 dst[1] = xl ^ *(p++);
595 dst[0] = xr ^ *(p++);
596 #else
597 dst[1] = swapu32(xl ^ *(p++));
598 dst[0] = swapu32(xr ^ *(p++));
599 #endif
601 return 0;
604 static int blowfishDecrypt(struct blowfishParam* bp, uint32_t* dst, const uint32_t* src)
606 #if WORDS_BIGENDIAN
607 register uint32_t xl = src[0], xr = src[1];
608 #else
609 register uint32_t xl = swapu32(src[0]), xr = swapu32(src[1]);
610 #endif
611 register uint32_t* p = bp->p+BLOWFISHPSIZE-1;
612 register uint32_t* s = bp->s;
614 DROUND(xl, xr); DROUND(xr, xl);
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);
623 #if WORDS_BIGENDIAN
624 dst[1] = xl ^ *(p--);
625 dst[0] = xr ^ *(p--);
626 #else
627 dst[1] = swapu32(xl ^ *(p--));
628 dst[0] = swapu32(xr ^ *(p--));
629 #endif
631 return 0;
634 static int blowfishSetup(struct blowfishParam* bp, const unsigned char* key, size_t keybits, cipherOperation op)
636 if ((op != ENCRYPT) && (op != DECRYPT))
637 return -1;
639 if (((keybits & 7) == 0) && (keybits >= 32) && (keybits <= 448))
641 register uint32_t* p = bp->p;
642 register uint32_t* s = bp->s;
643 register unsigned int i, j, k;
645 uint32_t tmp, work[2];
647 memcpy(s, _bf_s, 1024 * sizeof(uint32_t));
649 for (i = 0, k = 0; i < BLOWFISHPSIZE; i++)
651 tmp = 0;
652 for (j = 0; j < 4; j++)
654 tmp <<= 8;
655 tmp |= key[k++];
656 if (k >= (keybits >> 3))
657 k = 0;
659 p[i] = _bf_p[i] ^ tmp;
662 work[0] = work[1] = 0;
664 for (i = 0; i < BLOWFISHPSIZE; i += 2, p += 2)
666 blowfishEncrypt(bp, work, work);
667 #if WORDS_BIGENDIAN
668 p[0] = work[0];
669 p[1] = work[1];
670 #else
671 p[0] = swapu32(work[0]);
672 p[1] = swapu32(work[1]);
673 #endif
676 for (i = 0; i < 1024; i += 2, s += 2)
678 blowfishEncrypt(bp, work, work);
679 #if WORDS_BIGENDIAN
680 s[0] = work[0];
681 s[1] = work[1];
682 #else
683 s[0] = swapu32(work[0]);
684 s[1] = swapu32(work[1]);
685 #endif
688 /* clear fdback/iv */
689 bp->fdback[0] = 0;
690 bp->fdback[1] = 0;
692 return 0;
694 return -1;
697 static int blowfishSetIV(struct blowfishParam* bp, const unsigned char* iv)
699 if (iv)
700 memcpy(bp->fdback, iv, 8);
701 else
702 memset(bp->fdback, 0, 8);
704 return 0;
707 #define BLOWFISH_BLOCKSIZE 8
708 static int blowfishDecryptCBC(struct blowfishParam* bp, uint32_t* dst, const uint32_t* src, unsigned int nblocks)
710 register const unsigned int blockwords = BLOWFISH_BLOCKSIZE >> 2;
711 register uint32_t* fdback = bp->fdback;
712 register uint32_t* buf = (uint32_t*) malloc(blockwords * sizeof(uint32_t));
714 if (buf)
716 while (nblocks > 0)
718 register uint32_t tmp;
719 register unsigned int i;
721 blowfishDecrypt(bp, buf, src);
723 for (i = 0; i < blockwords; i++)
725 tmp = src[i];
726 dst[i] = buf[i] ^ fdback[i];
727 fdback[i] = tmp;
730 dst += blockwords;
731 src += blockwords;
733 nblocks--;
735 free(buf);
736 return 0;
739 return -1;
742 static bool bf_cbc_decrypt(const unsigned char* key, size_t keylen,
743 unsigned char* data, size_t datalen,
744 const unsigned char* iv)
746 struct blowfishParam param;
747 unsigned char *cipher;
748 unsigned int nblocks;
750 if (datalen % BLOWFISH_BLOCKSIZE)
751 return false;
753 if (blowfishSetup(&param, key, keylen * 8, ENCRYPT))
754 return false;
755 if (blowfishSetIV(&param, iv))
756 return false;
758 cipher = malloc(datalen);
759 memcpy(cipher, data, datalen);
761 nblocks = datalen / BLOWFISH_BLOCKSIZE;
762 if (blowfishDecryptCBC(&param, (uint32_t*)data, (uint32_t*)cipher,
763 nblocks))
765 free(cipher);
766 return false;
769 free(cipher);
770 return true;
773 static inline uint32_t swap(uint32_t val)
775 return ((val & 0xFF) << 24)
776 | ((val & 0xFF00) << 8)
777 | ((val & 0xFF0000) >> 8)
778 | ((val & 0xFF000000) >> 24);
781 static const char null_key_v1[] = "CTL:N0MAD|PDE0.SIGN.";
782 static const char null_key_v2[] = "CTL:N0MAD|PDE0.DPMP.";
783 static const char null_key_v3[] = "CTL:N0MAD|PDE0.DPFP.";
784 static const char null_key_v4[] = "CTL:Z3N07|PDE0.DPMP.";
786 static const char tl_zvm_key[] = "1sN0TM3D az u~may th1nk*"
787 "Creative Zen Vision:M";
788 static const char tl_zvm60_key[] = "1sN0TM3D az u~may th1nk*"
789 "Creative Zen Vision:M (D"
790 "VP-HD0004)";
791 static const char tl_zen_key[] = "1sN0TM3D az u~may th1nk*"
792 "Creative ZEN";
793 static const char tl_zenxf_key[] = "1sN0TM3D az u~may th1nk*"
794 "Creative ZEN X-Fi";
795 static const char tl_zenmo_key[] = "1sN0TM3D az u~may th1nk*"
796 "Creative ZEN Mozaic";
797 static const char tl_zv_key[] = "1sN0TM3D az u~may th1nk*"
798 "Creative Zen Vision";
799 static const char tl_zvw_key[] = "1sN0TM3D az u~may th1nk*"
800 "Creative ZEN Vision W";
801 static const char tl_zm_key[] = "1sN0TM3D az u~may th1nk*"
802 "Creative Zen Micro";
803 static const char tl_zmp_key[] = "1sN0TM3D az u~may th1nk*"
804 "Creative Zen MicroPhoto";
805 static const char tl_zs_key[] = "1sN0TM3D az u~may th1nk*"
806 "Creative Zen Sleek";
807 static const char tl_zsp_key[] = "1sN0TM3D az u~may th1nk*"
808 "Creative Zen Sleek Photo";
809 static const char tl_zt_key[] = "1sN0TM3D az u~may th1nk*"
810 "Creative Zen Touch";
811 static const char tl_zx_key[] = "1sN0TM3D az u~may th1nk*"
812 "NOMAD Jukebox Zen Xtra";
813 static const char tl_zenv_key[] = "1sN0TM3D az u~may th1nk*"
814 "Creative ZEN V";
815 static const char tl_zenvp_key[] = "1sN0TM3D az u~may th1nk*"
816 "Creative ZEN V Plus";
817 static const char tl_zenvv_key[] = "1sN0TM3D az u~may th1nk*"
818 "Creative ZEN V (Video)";
819 struct player_info_t
821 const char* name;
822 const char* null_key; /* HMAC-SHA1 key */
823 const char* tl_key; /* BlowFish key */
824 bool big_endian;
827 static struct player_info_t players[] = {
828 {"Zen Vision:M", null_key_v2, tl_zvm_key, false},
829 {"Zen Vision:M 60GB", null_key_v2, tl_zvm60_key, false},
830 {"ZEN", null_key_v4, tl_zen_key, false},
831 {"ZEN X-Fi", null_key_v4, tl_zenxf_key, false},
832 {"ZEN Mozaic", null_key_v4, tl_zenmo_key, false},
833 {"Zen Vision", null_key_v2, tl_zv_key, false},
834 {"Zen Vision W", null_key_v2, tl_zvw_key, false},
835 {"Zen Micro", null_key_v1, tl_zm_key, true},
836 {"Zen MicroPhoto", null_key_v1, tl_zmp_key, true},
837 {"Zen Sleek", null_key_v1, tl_zs_key, true},
838 {"Zen SleekPhoto", null_key_v1, tl_zsp_key, true},
839 {"Zen Touch", null_key_v1, tl_zt_key, true},
840 {"Zen Xtra", null_key_v1, tl_zx_key, true},
841 {"Zen V", null_key_v3, tl_zenv_key, false},
842 {"Zen V Plus", null_key_v3, tl_zenvp_key, false},
843 {"Zen V Video", null_key_v3, tl_zenvv_key, false},
844 {NULL, NULL, NULL, false}
847 void log_message(const char* format, ...);
849 int mkboot(const char* infile, const char* bootfile, const char* outfile, struct player_info_t *player)
851 FILE *infd, *bootfd, *outfd;
852 unsigned char *buffer, *out_buffer, enc_data[40], hash_key[20];
853 char *err_msg;
854 const char *fw_key;
855 uint32_t i, fw_offset, fw_size, data_ptr, data_size, ciff_size, cenc_size, iv[2];
857 /* TODO */
858 if(player->big_endian)
860 log_message("[ERR] Big-endian players are currently unsupported\n");
861 return -255;
864 infd = fopen(infile, "rb");
865 if(infd == NULL)
867 log_message("[ERR] Could not open %s\n", infile);
868 return -1;
871 buffer = malloc(filesize(infd));
872 if(buffer == NULL)
874 log_message("[ERR] Could not allocate %d unsigned chars\n", filesize(infd));
875 fclose(infd);
876 return -2;
879 if(fread(buffer, filesize(infd), 1, infd) != 1)
881 log_message("[ERR] Short read\n");
882 fclose(infd);
883 free(buffer);
884 return -3;
887 fclose(infd);
889 /* Rudimentary Win32 PE reading */
890 if(memcmp(&buffer[0], "MZ", 2) != 0 &&
891 memcmp(&buffer[0x118], "PE", 2) != 0)
893 log_message("[ERR] Input file isn't an executable\n");
894 free(buffer);
895 return -4;
898 data_ptr = 0, data_size = 0;
899 for(i=0x210; i < 0x1000; i+=0x28)
901 if(strcmp((char*)&buffer[i], ".data") == 0)
903 data_ptr = le2int(&buffer[i+0x14]);
904 data_size = le2int(&buffer[i+0x10]);
905 break;
909 if(data_ptr == 0 || data_size == 0)
911 log_message("[ERR] Couldn't find .data section\n");
912 free(buffer);
913 return -5;
916 log_message("[INFO] .data section is at 0x%x with size 0x%x\n", data_ptr, data_size);
918 fw_offset = find_firmware_offset(&buffer[data_ptr], data_size);
919 if(fw_offset == 0)
921 log_message("[ERR] Couldn't find firmware offset\n");
922 free(buffer);
923 return -6;
925 fw_size = le2int(&buffer[data_ptr+fw_offset]);
926 log_message("[INFO] Firmware offset is at 0x%x with size 0x%x\n", data_ptr+fw_offset, fw_size);
928 fw_key = find_firmware_key(&buffer[0], filesize(infd));
929 if(fw_key == NULL)
931 log_message("[ERR] Couldn't find firmware key\n");
932 free(buffer);
933 return -7;
935 log_message("[INFO] Firmware key is %s\n", fw_key);
937 log_message("[INFO] Descrambling firmware... ");
938 if(!crypt_firmware(fw_key, &buffer[data_ptr+fw_offset+4], fw_size))
940 log_message("Fail!\n");
941 free(buffer);
942 return -8;
944 else
945 log_message("Done!\n");
947 out_buffer = malloc(fw_size*2);
948 if(out_buffer == NULL)
950 log_message("[ERR] Couldn't allocate %d unsigned chars", fw_size*2);
951 free(buffer);
952 return -9;
955 memset(out_buffer, 0, fw_size*2);
957 err_msg = NULL;
958 log_message("[INFO] Decompressing firmware... ");
959 if(!inflate_to_buffer(&buffer[data_ptr+fw_offset+4], fw_size, out_buffer, fw_size*2, &err_msg))
961 log_message("Fail!\n[ERR] ZLib error: %s\n", err_msg);
962 free(buffer);
963 free(out_buffer);
964 return -10;
966 else
968 log_message("Done!\n");
969 free(buffer);
972 if(memcmp(out_buffer, "FFIC", 4) != 0)
974 log_message("[ERR] CIFF header doesn't match\n");
975 free(out_buffer);
976 return -11;
979 ciff_size = le2int(&out_buffer[4])+8+28; /* CIFF block + NULL block*/
981 bootfd = fopen(bootfile, "rb");
982 if(bootfd == NULL)
984 log_message("[ERR] Could not open %s\n", bootfile);
985 free(out_buffer);
986 return -12;
989 out_buffer = realloc(out_buffer, ciff_size+filesize(bootfd));
990 if(out_buffer == NULL)
992 log_message("[ERR] Cannot allocate %d unsigned chars\n", ciff_size+40+filesize(bootfd));
993 fclose(bootfd);
994 return -13;
997 log_message("[INFO] Locating encoded block... ");
999 i = 8;
1000 while(memcmp(&out_buffer[i], " LT©", 4) != 0 && i < ciff_size)
1002 if(memcmp(&out_buffer[i], "FNIC", 4) == 0)
1003 i += 4+4+96;
1004 else if(memcmp(&out_buffer[i], "ATAD", 4) == 0)
1006 i += 4;
1007 i += le2int(&out_buffer[i]);
1008 i += 4;
1010 else
1012 log_message("Fail!\n[ERR] Unknown block\n");
1013 fclose(bootfd);
1014 free(out_buffer);
1015 return -14;
1019 if(i > ciff_size || memcmp(&out_buffer[i], " LT©", 4) != 0)
1021 log_message("Fail!\n[ERR] Couldn't find encoded block\n");
1022 fclose(bootfd);
1023 free(out_buffer);
1024 return -15;
1027 log_message("Done!\n");
1029 outfd = fopen(outfile, "wb+");
1030 if(outfd == NULL)
1032 log_message("[ERR] Could not open %s\n", outfile);
1033 fclose(bootfd);
1034 free(out_buffer);
1035 return -16;
1038 if(fwrite(&out_buffer[0], i, 1, outfd) != 1)
1040 log_message("[ERR] Short write\n");
1041 fclose(bootfd);
1042 fclose(outfd);
1043 free(out_buffer);
1044 return -17;
1047 log_message("[INFO] Decrypting encoded block... ");
1049 iv[0] = 0;
1050 iv[1] = swap(le2int(&out_buffer[i+4]));
1051 if(bf_cbc_decrypt((unsigned char*)player->tl_key, strlen(player->tl_key)+1, &out_buffer[i+8],
1052 le2int(&out_buffer[i+4]), (const unsigned char*)&iv)
1053 == false)
1055 log_message("Fail!\n[ERR] Couldn't decrypt encoded block\n");
1056 fclose(bootfd);
1057 fclose(outfd);
1058 free(out_buffer);
1059 return -18;
1062 log_message("Done!\n");
1064 cenc_size = le2int(&out_buffer[i+8]);
1066 if(cenc_size > le2int(&out_buffer[i+4])*3)
1068 log_message("[ERR] Decrypted length of encoded block is unexpectedly large: 0x%08x\n", cenc_size);
1069 fclose(bootfd);
1070 fclose(outfd);
1071 free(out_buffer);
1072 return -19;
1075 buffer = malloc(cenc_size);
1076 if(buffer == NULL)
1078 log_message("[ERR] Couldn't allocate %d unsigned chars\n", cenc_size);
1079 fclose(bootfd);
1080 fclose(outfd);
1081 free(out_buffer);
1082 return -20;
1085 memset(buffer, 0, cenc_size);
1087 log_message("[INFO] Decompressing encoded block... ");
1089 if(!cenc_decode(&out_buffer[i+12], le2int(&out_buffer[i+4])-4, &buffer[0], cenc_size))
1091 log_message("Fail!\n[ERR] Couldn't decompress the encoded block\n");
1092 fclose(bootfd);
1093 fclose(outfd);
1094 free(out_buffer);
1095 free(buffer);
1096 return -21;
1099 log_message("Done!\n");
1101 log_message("[INFO] Renaming encoded block to Hcreativeos.jrm... ");
1103 memcpy(&enc_data, "ATAD", 4);
1104 int2le(cenc_size+32, &enc_data[4]);
1105 memset(&enc_data[8], 0, 32);
1106 memcpy(&enc_data[8], "H\0c\0r\0e\0a\0t\0i\0v\0e\0o\0s\0.\0j\0r\0m", 30);
1107 if(fwrite(enc_data, 40, 1, outfd) != 1)
1109 log_message("Fail!\n[ERR] Short write\n");
1110 fclose(bootfd);
1111 fclose(outfd);
1112 free(out_buffer);
1113 free(buffer);
1114 return -22;
1117 if(fwrite(&buffer[0], cenc_size, 1, outfd) != 1)
1119 log_message("Fail!\n[ERR] Short write\n");
1120 fclose(bootfd);
1121 fclose(outfd);
1122 free(out_buffer);
1123 free(buffer);
1124 return -23;
1127 free(buffer);
1128 log_message("Done!\n[INFO] Adding Hjukebox2.jrm... ");
1130 memcpy(&enc_data, "ATAD", 4);
1131 int2le(filesize(bootfd)+32, &enc_data[4]);
1132 memset(&enc_data[8], 0, 32);
1133 memcpy(&enc_data[8], "H\0j\0u\0k\0e\0b\0o\0x\0""2\0.\0j\0r\0m", 26);
1134 if(fwrite(enc_data, 40, 1, outfd) != 1)
1136 log_message("Fail!\n[ERR] Short write\n");
1137 fclose(bootfd);
1138 fclose(outfd);
1139 free(out_buffer);
1140 return -24;
1143 if(fread(&out_buffer[ciff_size], filesize(bootfd), 1, bootfd) != 1)
1145 log_message("Fail!\n[ERR] Short read\n");
1146 fclose(bootfd);
1147 fclose(outfd);
1148 free(out_buffer);
1149 return -25;
1152 if(memcmp(&out_buffer[ciff_size], "EDOC", 4) != 0)
1154 log_message("Fail!\n[ERR] Faulty bootloader\n");
1155 free(out_buffer);
1156 fclose(bootfd);
1157 fclose(outfd);
1158 return -26;
1161 if(fwrite(&out_buffer[ciff_size], filesize(bootfd), 1, outfd) != 1)
1163 log_message("Fail!\n[ERR] Short write\n");
1164 fclose(bootfd);
1165 fclose(outfd);
1166 free(out_buffer);
1167 return -27;
1170 fclose(bootfd);
1171 log_message("Done!\n");
1173 if(fwrite(&out_buffer[i+8+le2int(&out_buffer[i+4])], ciff_size-i-8-le2int(&out_buffer[i+4]), 1, outfd) != 1)
1175 log_message("[ERR] Short write\n");
1176 fclose(bootfd);
1177 fclose(outfd);
1178 free(out_buffer);
1179 return -28;
1182 fseek(outfd, 4, SEEK_SET);
1183 int2le(filesize(outfd)-8-28, enc_data);
1184 if(fwrite(enc_data, 4, 1, outfd) != 1)
1186 log_message("[ERR] Short write\n");
1187 fclose(outfd);
1188 free(out_buffer);
1189 return -29;
1192 free(out_buffer);
1193 fflush(outfd);
1195 log_message("[INFO] Updating checksum... ");
1197 buffer = malloc(filesize(outfd)-28);
1198 if(buffer == NULL)
1200 log_message("Fail!\n[ERR] Couldn't allocate %d unsigned chars\n", filesize(outfd)-28);
1201 fclose(outfd);
1202 return -30;
1205 fseek(outfd, 0, SEEK_SET);
1206 if(fread(buffer, filesize(outfd)-28, 1, outfd) != 1)
1208 log_message("Fail!\n[ERR] Short read\n");
1209 fclose(outfd);
1210 free(buffer);
1211 return -31;
1214 hmac_sha1((unsigned char*)player->null_key, strlen(player->null_key), &buffer[0], filesize(outfd)-28, &hash_key);
1216 fseek(outfd, filesize(outfd)-20, SEEK_SET);
1217 if(fwrite(hash_key, 20, 1, outfd) != 1)
1219 log_message("Fail!\n[ERR] Short write\n");
1220 fclose(outfd);
1221 free(buffer);
1222 return -32;
1225 fclose(outfd);
1227 log_message("Done!\n");
1228 return 0;
1231 #ifdef STANDALONE
1232 static void usage(void)
1234 int i;
1236 fprintf(stdout, "Usage: mkzenboot <firmware file> <boot file> <output file> <player>\n");
1237 fprintf(stdout, "Players:\n");
1238 for (i = 0; players[i].name != NULL; i++)
1239 fprintf(stdout, " * \"%s\"\n", players[i].name);
1241 exit(1);
1244 void log_message(const char* format, ...)
1246 va_list ap;
1248 va_start(ap, format);
1250 vfprintf(stderr, format, ap);
1252 va_end(ap);
1255 int main(int argc, char *argv[])
1257 char *infile, *bootfile, *outfile;
1258 int i;
1259 struct player_info_t *player = NULL;
1261 if(argc < 5)
1262 usage();
1264 infile = argv[1];
1265 bootfile = argv[2];
1266 outfile = argv[3];
1268 for (i = 0; players[i].name != NULL; i++)
1270 if(!strcasecmp(players[i].name, argv[4]))
1271 player = &players[i];
1274 if(player == NULL)
1276 fprintf(stderr, "[ERR] %s isn't listed as a player!\n", argv[4]);
1277 exit(1);
1280 return mkboot(infile, bootfile, outfile, player);
1282 #endif