1 /* i386-darwin.macho-main.c -- loader stub for Mach-o i386
2 
3    This file is part of the UPX executable compressor.
4 
5    Copyright (C) 1996-2020 Markus Franz Xaver Johannes Oberhumer
6    Copyright (C) 1996-2020 Laszlo Molnar
7    Copyright (C) 2000-2020 John F. Reiser
8    All Rights Reserved.
9 
10    UPX and the UCL library are free software; you can redistribute them
11    and/or modify them under the terms of the GNU General Public License as
12    published by the Free Software Foundation; either version 2 of
13    the License, or (at your option) any later version.
14 
15    This program is distributed in the hope that it will be useful,
16    but WITHOUT ANY WARRANTY; without even the implied warranty of
17    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
18    GNU General Public License for more details.
19 
20    You should have received a copy of the GNU General Public License
21    along with this program; see the file COPYING.
22    If not, write to the Free Software Foundation, Inc.,
23    59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
24 
25    Markus F.X.J. Oberhumer              Laszlo Molnar
26    <markus@oberhumer.com>               <ezerotven+github@gmail.com>
27 
28    John F. Reiser
29    <jreiser@users.sourceforge.net>
30  */
31 
32 
33 #define __WORDSIZE 32
34 #include "include/darwin.h"
35 
36 #ifndef DEBUG  /*{*/
37 #define DEBUG 0
38 #endif  /*}*/
39 
40 /*************************************************************************
41 // configuration section
42 **************************************************************************/
43 
44 // In order to make it much easier to move this code at runtime and execute
45 // it at an address different from it load address:  there must be no
46 // static data, and no string constants.
47 
48 #if !DEBUG  /*{*/
49 #define DPRINTF(a ...) /* empty: no debug drivel */
50 #else  /*}{ DEBUG */
51 #define DPRINTF(fmt, args...) ({ \
52     char const *r_fmt; \
53     asm("call 0f; .asciz \"" fmt "\"; 0: pop %0" \
54 /*out*/ : "=r"(r_fmt) ); \
55     dprintf(r_fmt, args); \
56 })
57 
58 #define va_arg      __builtin_va_arg
59 #define va_end      __builtin_va_end
60 #define va_list     __builtin_va_list
61 #define va_start    __builtin_va_start
62 
63 static int
unsimal(unsigned x,char * ptr,int n)64 unsimal(unsigned x, char *ptr, int n)
65 {
66     if (10<=x) {
67         unsigned const q = x / 10;
68         x -= 10 * q;
69         n = unsimal(q, ptr, n);
70     }
71     ptr[n] = '0' + x;
72     return 1+ n;
73 }
74 
75 static int
decimal(int x,char * ptr,int n)76 decimal(int x, char *ptr, int n)
77 {
78     if (x < 0) {
79         x = -x;
80         ptr[n++] = '-';
81     }
82     return unsimal(x, ptr, n);
83 }
84 
85 static int
heximal(unsigned long x,char * ptr,int n)86 heximal(unsigned long x, char *ptr, int n)
87 {
88     unsigned j = -1+ 2*sizeof(unsigned long);
89     unsigned long m = 0xful << (4 * j);
90     for (; j; --j, m >>= 4) { // omit leading 0 digits
91         if (m & x) break;
92     }
93     for (; m; --j, m >>= 4) {
94         unsigned d = 0xf & (x >> (4 * j));
95         ptr[n++] = ((10<=d) ? ('a' - 10) : '0') + d;
96     }
97     return n;
98 }
99 
100 static int
dprintf(char const * fmt,...)101 dprintf(char const *fmt, ...)
102 {
103     int n= 0;
104     char const *literal = 0;  // NULL
105     char buf[24];  // ~0ull == 18446744073709551615 ==> 20 chars
106     va_list va; va_start(va, fmt);
107     for (;;) {
108         char c = *fmt++;
109         if (!c) { // end of fmt
110             if (literal) {
111                 goto finish;
112             }
113             break;  // goto done
114         }
115         if ('%'!=c) {
116             if (!literal) {
117                 literal = fmt;  // 1 beyond start of literal
118             }
119             continue;
120         }
121         // '%' == c
122         if (literal) {
123 finish:
124             n += write(2, -1+ literal, fmt - literal);
125             literal = 0;  // NULL
126             if (!c) { // fmt already ended
127                break;  // goto done
128             }
129         }
130         switch (c= *fmt++) { // deficiency: does not handle _long_
131         default: { // un-implemented conversion
132             n+= write(2, -1+ fmt, 1);
133         } break;
134         case 0: { // fmt ends with "%\0" ==> ignore
135             goto done;
136         } break;
137         case 'u': {
138             n+= write(2, buf, unsimal(va_arg(va, unsigned), buf, 0));
139         } break;
140         case 'd': {
141             n+= write(2, buf, decimal(va_arg(va, int), buf, 0));
142         } break;
143         case 'p': {
144             buf[0] = '0';
145             buf[1] = 'x';
146             n+= write(2, buf, heximal((unsigned long)va_arg(va, void *), buf, 2));
147         } break;
148         case 'x': {
149             buf[0] = '0';
150             buf[1] = 'x';
151             n+= write(2, buf, heximal(va_arg(va, unsigned int), buf, 2));
152         } break;
153         case 's': {
154             char *s0= (char *)va_arg(va, unsigned char *), *s= s0;
155             if (s) while (*s) ++s;
156             n+= write(2, s0, s - s0);
157         } break;
158         } // 'switch'
159     }
160 done:
161     va_end(va);
162     return n;
163 }
164 #endif  /*}*/
165 
166 extern int spin(int);
167 
168 /*************************************************************************
169 // "file" util
170 **************************************************************************/
171 
172 typedef struct {
173     size_t size;  // must be first to match size[0] uncompressed size
174     void *buf;
175 } Extent;
176 
177 static void
xread(Extent * x,void * buf,size_t count)178 xread(Extent *x, void *buf, size_t count)
179 {
180     unsigned char *p=x->buf, *q=buf;
181     size_t j;
182     DPRINTF("xread %%p(%%x %%p) %%p %%x\\n",
183             x, x->size, x->buf, buf, count);
184     if (x->size < count) {
185         DPRINTF("xreadfail %%p(%%x %%p) %%p %%x\\n",
186                 x, x->size, x->buf, buf, count);
187         exit(127);
188     }
189     for (j = count; 0!=j--; ++p, ++q) {
190         *q = *p;
191     }
192     x->buf  += count;
193     x->size -= count;
194 }
195 
196 
197 /*************************************************************************
198 // util
199 **************************************************************************/
200 
201 #if 1  //{  save space
202 #define ERR_LAB error: exit(127);
203 #define err_exit(a) goto error
204 #else  //}{  save debugging time
205 #define ERR_LAB /*empty*/
206 
207 static void
err_exit(int a)208 err_exit(int a)
209 {
210     DPRINTF((STR_exit(), a));
211     (void)a;  // debugging convenience
212     exit(127);
213 }
214 #endif  //}
215 
216 
217 /*************************************************************************
218 // UPX & NRV stuff
219 **************************************************************************/
220 
221 struct l_info { // 12-byte trailer for loader (after macho headers)
222     unsigned l_checksum;
223     unsigned l_magic;  // UPX_MAGIC_LE32
224     unsigned short l_lsize;
225     unsigned char l_version;
226     unsigned char l_format;
227 };
228 struct p_info { // 12-byte packed program header
229     unsigned p_progid;
230     unsigned p_filesize;
231     unsigned p_blocksize;
232 };
233 
234 struct b_info { // 12-byte header before each compressed block
235     unsigned sz_unc;  // uncompressed_size
236     unsigned sz_cpr;  //   compressed_size
237     unsigned char b_method;  // compression algorithm
238     unsigned char b_ftid;  // filter id
239     unsigned char b_cto8;  // filter parameter
240     unsigned char b_unused;
241 };
242 
243 typedef void f_unfilter(
244     nrv_byte *,  // also addvalue
245     nrv_uint,
246     unsigned cto8, // junk in high 24 bits
247     unsigned ftid
248 );
249 typedef int f_expand(
250     const nrv_byte *, nrv_uint,
251           nrv_byte *, nrv_uint *, unsigned );
252 
253 static void
unpackExtent(Extent * const xi,Extent * const xo,f_expand * const f_decompress,f_unfilter * f_unf)254 unpackExtent(
255     Extent *const xi,  // input
256     Extent *const xo,  // output
257     f_expand *const f_decompress,
258     f_unfilter *f_unf
259 )
260 {
261     DPRINTF("unpackExtent in=%%p(%%x %%p)  out=%%p(%%x %%p)  %%p %%p\\n",
262         xi, xi->size, xi->buf, xo, xo->size, xo->buf, f_decompress, f_unf);
263     while (xo->size) {
264         struct b_info h;
265         //   Note: if h.sz_unc == h.sz_cpr then the block was not
266         //   compressible and is stored in its uncompressed form.
267 
268         // Read and check block sizes.
269         xread(xi, (unsigned char *)&h, sizeof(h));
270         DPRINTF("  sz_unc=%%x  sz_cpr=%%x  param=%%x\\n",
271             h.sz_unc, h.sz_cpr, *(int *)&h.b_method);
272         if (h.sz_unc == 0) {                     // uncompressed size 0 -> EOF
273             if (h.sz_cpr != UPX_MAGIC_LE32)      // h.sz_cpr must be h->magic
274                 err_exit(2);
275             if (xi->size != 0)                 // all bytes must be written
276                 err_exit(3);
277             break;
278         }
279         if (h.sz_cpr <= 0) {
280             err_exit(4);
281 ERR_LAB
282         }
283         if (h.sz_cpr > h.sz_unc
284         ||  h.sz_unc > xo->size ) {
285             DPRINTF("sz_cpr=%%x  sz_unc=%%x  xo->size=%%x\\n",
286                         h.sz_cpr, h.sz_unc, xo->size);
287             err_exit(5);
288         }
289         // Now we have:
290         //   assert(h.sz_cpr <= h.sz_unc);
291         //   assert(h.sz_unc > 0 && h.sz_unc <= blocksize);
292         //   assert(h.sz_cpr > 0 && h.sz_cpr <= blocksize);
293 
294         if (h.sz_cpr < h.sz_unc) { // Decompress block
295             nrv_uint out_len = h.sz_unc;  // EOF for lzma
296             int const j = (*f_decompress)(xi->buf, h.sz_cpr,
297                 xo->buf, &out_len, h.b_method);
298             if (j != 0 || out_len != (nrv_uint)h.sz_unc)
299                 err_exit(7);
300             DPRINTF("  b_ftid=%%x  f_unf=%%p\\n", h.b_ftid, f_unf);
301             if (h.b_ftid!=0 && f_unf) {  // have filter
302                 DPRINTF(" unfiltering f_unf=%%p  buf=%%p  len=%%x  cto=%%x  ftid=%%x\\n",
303                         f_unf, xo->buf, out_len, h.b_cto8, h.b_ftid);
304                 (*f_unf)(xo->buf, out_len, h.b_cto8, h.b_ftid);
305             }
306             xi->buf  += h.sz_cpr;
307             xi->size -= h.sz_cpr;
308         }
309         else { // copy literal block
310             xread(xi, xo->buf, h.sz_cpr);
311         }
312         xo->buf  += h.sz_unc;
313         xo->size -= h.sz_unc;
314     }
315 }
316 
317 static void
upx_bzero(unsigned char * p,size_t len)318 upx_bzero(unsigned char *p, size_t len)
319 {
320     if (len) do {
321         *p++= 0;
322     } while (--len);
323 }
324 #define bzero upx_bzero
325 
326 
327 // The PF_* and PROT_* bits are {1,2,4}; the conversion table fits in 32 bits.
328 #define REP8(x) \
329     ((x)|((x)<<4)|((x)<<8)|((x)<<12)|((x)<<16)|((x)<<20)|((x)<<24)|((x)<<28))
330 #define EXP8(y) \
331     ((1&(y)) ? 0xf0f0f0f0 : (2&(y)) ? 0xff00ff00 : (4&(y)) ? 0xffff0000 : 0)
332 #define PF_TO_PROT(pf) \
333     ((PROT_READ|PROT_WRITE|PROT_EXEC) & ( \
334         ( (REP8(PROT_EXEC ) & EXP8(PF_X)) \
335          |(REP8(PROT_READ ) & EXP8(PF_R)) \
336          |(REP8(PROT_WRITE) & EXP8(PF_W)) \
337         ) >> ((pf & (PF_R|PF_W|PF_X))<<2) ))
338 
339 typedef size_t Addr;
340 
341 typedef struct {
342     unsigned magic;
343     unsigned nfat_arch;
344 } Fat_header;
345 typedef struct {
346     unsigned cputype;
347     unsigned cpusubtype;
348     unsigned offset;
349     unsigned size;
350     unsigned align;  /* shift count (log base 2) */
351 } Fat_arch;
352     enum e8 {
353         FAT_MAGIC = 0xcafebabe,
354         FAT_CIGAM = 0xbebafeca
355     };
356     enum e9 {
357         CPU_TYPE_I386      =          7,
358         CPU_TYPE_AMD64     = 0x01000007,
359         CPU_TYPE_ARM       =         12,
360         CPU_TYPE_POWERPC   = 0x00000012,
361         CPU_TYPE_POWERPC64 = 0x01000012
362     };
363 
364 typedef struct {
365     unsigned magic;
366     unsigned cputype;
367     unsigned cpysubtype;
368     unsigned filetype;
369     unsigned ncmds;
370     unsigned sizeofcmds;
371     unsigned flags;
372 } Mach_header;
373         enum e0 {
374             MH_MAGIC   =   0xfeedface,
375             MH_MAGIC64 = 1+0xfeedface
376         };
377         enum e2 {
378             MH_EXECUTE = 2
379         };
380         enum e3 {
381             MH_NOUNDEFS = 1
382         };
383 
384 typedef struct {
385     unsigned cmd;
386     unsigned cmdsize;
387 } Mach_load_command;
388         enum e4 {
389             LC_SEGMENT       = 0x1,
390             LC_SEGMENT_64    = 0x19,
391             LC_THREAD        = 0x4,
392             LC_UNIXTHREAD    = 0x5,
393             LC_LOAD_DYLINKER = 0xe
394         };
395 
396 typedef struct {
397     unsigned cmd;
398     unsigned cmdsize;
399     char segname[16];
400     Addr vmaddr;
401     Addr vmsize;
402     unsigned fileoff;
403     unsigned filesize;
404     unsigned maxprot;
405     unsigned initprot;
406     unsigned nsects;
407     unsigned flags;
408 } Mach_segment_command;
409         enum e5 {
410             VM_PROT_NONE = 0,
411             VM_PROT_READ = 1,
412             VM_PROT_WRITE = 2,
413             VM_PROT_EXECUTE = 4
414         };
415 
416 typedef struct {
417     char sectname[16];
418     char segname[16];
419     Addr addr;   /* memory address */
420     Addr size;   /* size in bytes */
421     unsigned offset; /* file offset */
422     unsigned align;  /* power of 2 */
423     unsigned reloff; /* file offset of relocation entries */
424     unsigned nreloc; /* number of relocation entries */
425     unsigned flags;  /* section type and attributes */
426     unsigned reserved1;  /* for offset or index */
427     unsigned reserved2;  /* for count or sizeof */
428 } Mach_section_command;
429 
430 typedef struct {
431     unsigned eax, ebx, ecx, edx;
432     unsigned edi, esi, ebp;
433     unsigned esp, ss;
434     unsigned eflags;
435     unsigned eip, cs;
436     unsigned ds, es, fs, gs;
437 } Mach_i386_thread_state;
438 
439 typedef struct {
440     unsigned cmd;            /* LC_THREAD or  LC_UNIXTHREAD */
441     unsigned cmdsize;        /* total size of this command */
442     unsigned flavor;
443     unsigned count;          /* sizeof(following_thread_state)/4 */
444     Mach_i386_thread_state state;
445 } Mach_thread_command;
446         enum e6 {
447             i386_THREAD_STATE = 1
448         };
449         enum e7 {
450             i386_THREAD_STATE_COUNT = sizeof(Mach_i386_thread_state)/4
451         };
452 
453 typedef union {
454     unsigned long offset;  /* from start of load command to string */
455     char *ptr;
456 } Mach_lc_str;
457 
458 #define MAP_FIXED     0x10
459 #define MAP_PRIVATE   0x02
460 #define MAP_ANON    0x1000
461 #define PROT_READ      1
462 #define PROT_WRITE     2
463 #define PROT_EXEC      4
464 #define MAP_ANON_FD    -1
465 
466 // We have off_t_upx_stub as 32 bits, but syscalls consider off_t as 64 bits.
467 // Make the top 32 bits explicit, and pass a 0.
468 extern void *mmap(void *, size_t, unsigned, unsigned, int, off_t_upx_stub, unsigned);
469 extern ssize_t pread(int, void *, size_t, off_t_upx_stub, unsigned);
470 extern void bswap(void *, unsigned);
471 
472 enum {
473         MH_DYLINKER= 7,     /* /usr/bin/dyld */
474         MH_PIE      = 0x200000   // ASLR
475 
476 };
477 
478 // Find convex hull of PT_LOAD (the minimal interval which covers all PT_LOAD),
479 // and mmap that much, to be sure that a kernel using exec-shield-randomize
480 // won't place the first piece in a way that leaves no room for the rest.
481 static Addr // returns relocation constant
xfind_pages(Mach_header const * const mhdr,Mach_segment_command const * sc,int const ncmds,Addr addr)482 xfind_pages(
483     Mach_header const *const mhdr,
484     Mach_segment_command const *sc,
485     int const ncmds,
486     Addr addr
487 )
488 {
489     Addr lo= ~(Addr)0, hi= 0;
490     int j;
491     unsigned mflags = ((mhdr->filetype == MH_DYLINKER || mhdr->flags & MH_PIE) ? 0 : MAP_FIXED);
492     mflags += MAP_PRIVATE | MAP_ANON;  // '+' can optimize better than '|'
493     DPRINTF("xfind_pages  mhdr=%%p  sc=%%p  ncmds=%%d  addr=%%p  mflags=%%x\\n",
494         mhdr, sc, ncmds, addr, mflags);
495     for (j=0; j < ncmds; ++j,
496         (sc = (Mach_segment_command const *)((sc->cmdsize>>2) + (unsigned const *)sc))
497     ) if (LC_SEGMENT==sc->cmd) {
498         DPRINTF("  #%%d  cmd=%%x  cmdsize=%%x  vmaddr=%%p  vmsize==%%p  lo=%%p  mflags=%%x\\n",
499             j, sc->cmd, sc->cmdsize, sc->vmaddr, sc->vmsize, lo, mflags);
500         if (sc->vmsize  // theoretically occupies address space
501         &&  !(sc->vmaddr==0 && (MAP_FIXED & mflags))  // but ignore PAGEZERO when MAP_FIXED
502         ) {
503             if (mhdr->filetype == MH_DYLINKER  // /usr/lib/dyld
504             &&  0==(1+ lo)  // 1st LC_SEGMENT
505             &&  sc->vmaddr != 0  // non-floating address
506             ) {
507                 // "pre-linked" dyld on MacOS 10.11.x El Capitan
508                 mflags |= MAP_FIXED;
509             }
510             if (lo > sc->vmaddr) {
511                 lo = sc->vmaddr;
512             }
513             if (hi < (sc->vmsize + sc->vmaddr)) {
514                 hi =  sc->vmsize + sc->vmaddr;
515             }
516         }
517     }
518     lo -= ~PAGE_MASK & lo;  // round down to page boundary
519     hi  =  PAGE_MASK & (hi - lo - PAGE_MASK -1);  // page length
520     DPRINTF("  addr=%%p  lo=%%p  len=%%p  mflags=%%x\\n", addr, lo, hi, mflags);
521     if (MAP_FIXED & mflags) {
522         addr = lo;
523         int rv = munmap((void *)addr, hi);
524         if (rv) {
525             DPRINTF("munmap addr=%%p len=%%p, rv=%%x\\n", addr, hi, rv);
526         }
527     }
528     addr = (Addr)mmap((void *)addr, hi, VM_PROT_NONE, mflags, MAP_ANON_FD, 0, 0);
529     DPRINTF("  addr=%%p\\n", addr);
530     if (~PAGE_MASK & addr) {
531         //err_exit(6);
532     }
533     return (Addr)(addr - lo);
534 }
535 Addr  // entry: &hatch if main; Mach_thread_state->eip if dyld
do_xmap(Mach_header * const mhdr,off_t_upx_stub const fat_offset,Extent * const xi,int const fdi,Mach_header ** mhdrpp,f_expand * const f_exp,f_unfilter * const f_unf)536 do_xmap(
537     Mach_header *const mhdr,
538     off_t_upx_stub const fat_offset,
539     Extent *const xi,
540     int const fdi,
541     Mach_header **mhdrpp,
542     f_expand *const f_exp,
543     f_unfilter *const f_unf
544 )
545 {
546     DPRINTF("do_xmap  fdi=%%x  mhdr=%%p  *mhdrpp=%%p  xi=%%p(%%x %%p) f_unf=%%p\\n",
547         fdi, mhdr, (mhdrpp ? *mhdrpp : 0), xi, (xi? xi->size: 0), (xi? xi->buf: 0), f_unf);
548 
549     Addr rv = 0;
550     Mach_segment_command *sc = (Mach_segment_command *)(1+ mhdr);
551     Addr const reloc = xfind_pages(mhdr, sc, mhdr->ncmds, 0);
552     DPRINTF("do_xmap reloc=%%p\\n", reloc);
553     unsigned j;
554     for ( j=0; j < mhdr->ncmds; ++j,
555         (sc = (Mach_segment_command *)((sc->cmdsize>>2) + (unsigned *)sc))
556     ) {
557         DPRINTF("  #%%d  cmd=%%x  cmdsize=%%x  vmsize=%%x\\n",
558                 j, sc->cmd, sc->cmdsize, sc->vmsize);
559         if (LC_SEGMENT==sc->cmd && !sc->vmsize) {
560             // Typical __DWARF info segment for 'rust'
561             struct b_info h;
562             xread(xi, (unsigned char *)&h, sizeof(h));
563             DPRINTF("    0==.vmsize; skipping %%x\\n", h.sz_cpr);
564             xi->buf += h.sz_cpr;
565         }
566         if (LC_SEGMENT==sc->cmd && sc->vmsize) {
567             Extent xo;
568             size_t mlen = xo.size = sc->filesize;
569                           xo.buf  = (void *)(reloc + sc->vmaddr);
570             Addr  addr = (Addr)xo.buf;
571             Addr haddr = sc->vmsize + addr;
572             size_t frag = addr &~ PAGE_MASK;
573             addr -= frag;
574             mlen += frag;
575 
576             DPRINTF("    mlen=%%p  frag=%%p  addr=%%p\\n", mlen, frag, addr);
577             if (0!=mlen) { // In particular, omitted for __PAGEZERO
578                 size_t const mlen3 = mlen
579     #if defined(__x86_64__)  //{
580                     // Decompressor can overrun the destination by 3 bytes.  [x86 only]
581                     + (xi ? 3 : 0)
582     #endif  //}
583                     ;
584                 unsigned const prot = VM_PROT_READ | VM_PROT_WRITE;
585                 // MAP_FIXED: xfind_pages() reserved them, so use them!
586                 unsigned const flags = MAP_FIXED | MAP_PRIVATE |
587                                 ((xi || 0==sc->filesize) ? MAP_ANON    : 0);
588                 int const fdm = ((xi || 0==sc->filesize) ? MAP_ANON_FD : fdi);
589                 off_t_upx_stub const offset = sc->fileoff + fat_offset;
590 
591                 DPRINTF("mmap  addr=%%p  len=%%p  prot=%%x  flags=%%x  fd=%%d  off=%%p  reloc=%%p\\n",
592                     addr, mlen3, prot, flags, fdm, offset, reloc);
593                 {
594                     Addr maddr = (Addr)mmap((void *)addr, mlen3, prot, flags, fdm, offset, 0);
595                     DPRINTF("maddr=%%p\\n", maddr);
596                     if (maddr != addr) {
597                         err_exit(8);
598                     }
599                     addr = maddr;
600                 }
601                 if (mhdrpp && !*mhdrpp) { // MH_DYLINKER
602                     *mhdrpp = (Mach_header*)addr;
603                 }
604             }
605             if (xi && 0!=sc->filesize) {
606                 if (0==sc->fileoff /*&& 0!=mhdrpp*/) {
607                     *mhdrpp = (Mach_header *)(void *)addr;
608                 }
609                 unpackExtent(xi, &xo, f_exp, f_unf);
610             }
611             DPRINTF("xi=%%p  mlen=%%p  fileoff=%%p  nsects=%%d\\n",
612                 xi, mlen, sc->fileoff, sc->nsects);
613             if (xi && mlen && !sc->fileoff && sc->nsects) {
614                 // main target __TEXT segment at beginning of file with sections (__text)
615                 // Use upto 2 words of header padding for the escape hatch.
616                 // fold.S could do this easier, except PROT_WRITE is missing then.
617                 union {
618                     unsigned char  *p0;
619                     unsigned short *p1;
620                     unsigned int   *p2;
621                     unsigned long  *p3;
622                 } u;
623                 u.p0 = (unsigned char *)addr;
624                 Mach_segment_command *segp = (Mach_segment_command *)((((char *)sc - (char *)mhdr)>>2) + u.p2);
625                 Mach_section_command *const secp = (Mach_section_command *)(1+ segp);
626                 unsigned *hatch= -2+ (secp->offset>>2) + u.p2;
627                 DPRINTF("hatch=%%p  segp=%%p  secp=%%p  secp->offset=%%p  mhdr=%%p\\n", hatch, segp, secp, secp->offset, addr);
628     #if defined(__aarch64__)  //{
629                 hatch[0] = 0xd4000001;  // svc #0  // syscall
630                 hatch[1] = 0xd65f03c0;  // ret
631     #elif defined(__arm__)  //}{
632                 hatch[0] = 0xef000000;  // svc 0x0  // syscall
633                 hatch[1] = 0xe12fff1e;  // bx lr
634     #elif defined(__x86_64__)  //}{
635                 hatch[0] = 0xc3050f90;  // nop; syscall; ret
636     #elif defined(__i386__)  //}{
637                 hatch[0] = 0xc3050f90;  // nop; syscall; ret
638     #endif  //}
639                 rv = (Addr)hatch;
640             }
641             /*bzero(addr, frag);*/  // fragment at lo end
642             frag = (-mlen) &~ PAGE_MASK;  // distance to next page boundary
643             bzero((void *)(mlen+addr), frag);  // fragment at hi end
644             if (0!=mlen && 0!=mprotect((void *)addr, mlen, sc->initprot)) {
645                 err_exit(10);
646     ERR_LAB
647             }
648             addr += mlen + frag;  /* page boundary on hi end */
649             if (
650     #if SIMULATE_ON_LINUX_EABI4  /*{*/
651                 0!=addr &&
652     #endif  /*}*/
653                             addr < haddr) { // need pages for .bss
654                 if (0!=addr && addr != (Addr)mmap((void *)addr, haddr - addr, sc->initprot,
655                         MAP_FIXED | MAP_PRIVATE | MAP_ANON, MAP_ANON_FD, 0, 0) ) {
656                     err_exit(9);
657                 }
658             }
659             else if (xi) { // cleanup if decompressor overrun crosses page boundary
660                 mlen = ~PAGE_MASK & (3+ mlen);
661                 if (mlen<=3) { // page fragment was overrun buffer only
662                     DPRINTF("munmap  %%x  %%x\\n", addr, mlen);
663                     munmap((char *)addr, mlen);
664                 }
665             }
666         }
667         else if (!xi  // dyld
668         && (LC_UNIXTHREAD==sc->cmd || LC_THREAD==sc->cmd)) {
669             Mach_thread_command *const thrc = (Mach_thread_command *)sc;
670             DPRINTF("thread_command= %%p\\n", sc);
671             if (1
672             // FIXME  THREAD_STATE      ==thrc->flavor
673             //    &&  THREAD_STATE_COUNT==thrc->count
674             ) {
675                 DPRINTF("thread_state= %%p  flavor=%%d  count=%%x  reloc=%%p\\n",
676                     &thrc->state, thrc->flavor, thrc->count, reloc);
677     #if defined(__aarch64__)  //{
678                 rv = reloc + thrc->state.pc;
679     #elif defined(__arm__)  //}{
680                 rv = reloc + thrc->state.pc;
681     #elif defined(__x86_64__)  //}{
682                 rv = reloc + thrc->state.rip;
683     #elif defined(__i386__)  //}{
684                 rv = reloc + thrc->state.eip;
685     #else  //}{
686         #error do_xmap rv $ARCH
687     #endif  //}
688             }
689         }
690     }
691     DPRINTF("do_xmap= %%p\\n", rv);
692     return rv;
693 }
694 
695 /*************************************************************************
696 // upx_main - called by our entry code
697 //
698 **************************************************************************/
699 
700 Addr
upx_main(Mach_header ** const mhdrpp,f_unfilter * const f_unf,f_expand * const f_decompress,Mach_header * const mhdr,size_t const sz_mhdr,size_t volatile sz_compressed,struct l_info const * const li)701 upx_main(
702     Mach_header **const mhdrpp,  // Out: *mhdrpp= &real Mach_header
703     f_unfilter *const f_unf,
704     f_expand *const f_decompress,
705     Mach_header *const mhdr,  // temp char[sz_mhdr] for decompressing
706     size_t const sz_mhdr,
707     size_t volatile sz_compressed,  // total length
708     struct l_info const *const li
709 )
710 {
711     Addr entry;
712     off_t_upx_stub fat_offset = 0;
713     Extent xi, xo, xi0;
714     xi.buf  = CONST_CAST(unsigned char *, 1+ (struct p_info const *)(1+ li));  // &b_info
715     xi.size = sz_compressed - (sizeof(struct l_info) + sizeof(struct p_info));
716     xo.buf  = (unsigned char *)mhdr;
717     xo.size = ((struct b_info const *)(void const *)xi.buf)->sz_unc;
718     xi0 = xi;
719 
720     DPRINTF("upx_main szc=%%x  f_dec=%%p  f_unf=%%p  "
721     "  xo=%%p(%%x %%p)  xi=%%p(%%x %%p)  mhdrpp=%%p\\n",
722         sz_compressed, f_decompress, f_unf,
723         &xo, xo.size, xo.buf,
724         &xi, xi.size, xi.buf, mhdrpp);
725 
726     // Uncompress Macho headers
727     unpackExtent(&xi, &xo, f_decompress, 0);  // never filtered?
728 
729     entry = do_xmap(mhdr, fat_offset, &xi0, MAP_ANON_FD, mhdrpp, f_decompress, f_unf);
730 
731   { // Map dyld dynamic loader
732     Mach_load_command const *lc = (Mach_load_command const *)(1+ mhdr);
733     unsigned j;
734 
735     for (j=0; j < mhdr->ncmds; ++j,
736         (lc = (Mach_load_command const *)(lc->cmdsize + (void const *)lc))
737     ) if (LC_LOAD_DYLINKER==lc->cmd) {
738         char const *const dyld_name = ((Mach_lc_str const *)(1+ lc))->offset +
739             (char const *)lc;
740         int const fdi = open(dyld_name, O_RDONLY, 0);
741         if (0 > fdi) {
742             err_exit(18);
743         }
744 fat:
745         if ((ssize_t)sz_mhdr!=pread(fdi, (void *)mhdr, sz_mhdr, fat_offset, 0)) {
746 ERR_LAB
747             err_exit(19);
748         }
749         switch (mhdr->magic) {
750         case MH_MAGIC: break;
751         case MH_MAGIC64: break;
752         case FAT_CIGAM:
753         case FAT_MAGIC: {
754             // stupid Apple: waste code and a page fault on EVERY execve
755             Fat_header *const fh = (Fat_header *)mhdr;
756             Fat_arch *fa = (Fat_arch *)(1+ fh);
757             bswap(fh, sizeof(*fh) + (fh->nfat_arch>>24)*sizeof(*fa));
758             for (j= 0; j < fh->nfat_arch; ++j, ++fa) {
759                 if (CPU_TYPE_I386==fa->cputype) {
760                     fat_offset= fa->offset;
761                     goto fat;
762                 }
763             }
764         } break;
765         } // switch
766         entry = do_xmap(mhdr, fat_offset, 0, fdi, 0, 0, 0);
767         close(fdi);
768         break;
769     }
770   }
771 
772     return entry;
773 }
774 
775 /* vim:set ts=4 sw=4 et: */
776