1 #include "Rts.h"
2 
3 #if defined(linux_HOST_OS) || defined(solaris2_HOST_OS) \
4 || defined(linux_android_HOST_OS) \
5 || defined(freebsd_HOST_OS) || defined(kfreebsdgnu_HOST_OS) \
6 || defined(dragonfly_HOST_OS) || defined(netbsd_HOST_OS) \
7 || defined(openbsd_HOST_OS) || defined(gnu_HOST_OS)
8 
9 // It is essential that this is included before any <elf.h> is included. <elf.h>
10 // defines R_XXX relocations, which would interfere with the COMPAT_R_XXX
11 // relocations we generate.  E.g. COMPAT_ ## R_ARM_ARM32 would end up as
12 // const unsigned COMPAT_3 = 0x03; instead of
13 // const unsigned COMPAT_R_ARM_ARM32 = 0x03;
14 #include "elf_compat.h"
15 
16 #include "RtsUtils.h"
17 #include "RtsSymbolInfo.h"
18 #include "linker/Elf.h"
19 #include "linker/CacheFlush.h"
20 #include "linker/M32Alloc.h"
21 #include "linker/SymbolExtras.h"
22 #include "sm/OSMem.h"
23 #include "GetEnv.h"
24 #include "linker/util.h"
25 #include "linker/elf_util.h"
26 
27 #include <stdlib.h>
28 #include <unistd.h>
29 #include <string.h>
30 #if defined(HAVE_SYS_STAT_H)
31 #include <sys/stat.h>
32 #endif
33 #if defined(HAVE_SYS_TYPES_H)
34 #include <sys/types.h>
35 #endif
36 #if defined(HAVE_FCNTL_H)
37 #include <fcntl.h>
38 #endif
39 #if defined(dragonfly_HOST_OS)
40 #include <sys/tls.h>
41 #endif
42 
43 /* on x86_64 we have a problem with relocating symbol references in
44  * code that was compiled without -fPIC.  By default, the small memory
45  * model is used, which assumes that symbol references can fit in a
46  * 32-bit slot.  The system dynamic linker makes this work for
47  * references to shared libraries by either (a) allocating a jump
48  * table slot for code references, or (b) moving the symbol at load
49  * time (and copying its contents, if necessary) for data references.
50  *
51  * We unfortunately can't tell whether symbol references are to code
52  * or data.  So for now we assume they are code (the vast majority
53  * are), and allocate jump-table slots.  Unfortunately this will
54  * SILENTLY generate crashing code for data references.  This hack is
55  * enabled by X86_64_ELF_NONPIC_HACK.
56  *
57  * One workaround is to use shared Haskell libraries. This is the case
58  * when dynamically-linked GHCi is used.
59  *
60  * Another workaround is to keep the static libraries but compile them
61  * with -fPIC -fexternal-dynamic-refs, because that will generate PIC
62  * references to data which can be relocated. This is the case when
63  * +RTS -xp is passed.
64  *
65  * See bug #781
66  * See thread http://www.haskell.org/pipermail/cvs-ghc/2007-September/038458.html
67  *
68  * Naming Scheme for Symbol Macros
69  *
70  * SymI_*: symbol is internal to the RTS. It resides in an object
71  *         file/library that is statically.
72  * SymE_*: symbol is external to the RTS library. It might be linked
73  *         dynamically.
74  *
75  * Sym*_HasProto  : the symbol prototype is imported in an include file
76  *                  or defined explicitly
77  * Sym*_NeedsProto: the symbol is undefined and we add a dummy
78  *                  default proto extern void sym(void);
79  */
80 #define X86_64_ELF_NONPIC_HACK (!RtsFlags.MiscFlags.linkerAlwaysPic)
81 
82 #if defined(sparc_HOST_ARCH)
83 #  define ELF_TARGET_SPARC  /* Used inside <elf.h> */
84 #elif defined(i386_HOST_ARCH)
85 #  define ELF_TARGET_386    /* Used inside <elf.h> */
86 #elif defined(x86_64_HOST_ARCH)
87 #  define ELF_TARGET_X64_64
88 #  define ELF_TARGET_AMD64 /* Used inside <elf.h> on Solaris 11 */
89 #endif
90 
91 #if !defined(openbsd_HOST_OS)
92 #  include <elf.h>
93 #else
94 /* openbsd elf has things in different places, with diff names */
95 #  include <elf_abi.h>
96 #endif
97 
98 #if defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)
99 #  define NEED_GOT
100 #  define NEED_PLT
101 #  include "elf_got.h"
102 #  include "elf_plt.h"
103 #  include "elf_reloc.h"
104 #endif
105 
106 /*
107 
108    Note [Many ELF Sections]
109 
110    The normal section number fields in ELF are limited to 16 bits, which runs
111    out of bits when you try to cram in more sections than that.
112 
113    To solve this, the fields e_shnum and e_shstrndx in the ELF header have an
114    escape value (different for each case), and the actual section number is
115    stashed into unused fields in the first section header.
116 
117    For symbols, there seems to have been no place in the actual symbol table
118    for the extra bits, so the indexes have been moved into an auxiliary
119    section instead.
120    For symbols in sections beyond 0xff00, the symbol's st_shndx will be an
121    escape value (SHN_XINDEX), and the actual 32-bit section number for symbol N
122    is stored at index N in the SHT_SYMTAB_SHNDX table.
123 
124    These extensions seem to be undocumented in version 4.1 of the ABI and only
125    appear in the drafts for the "next" version:
126       https://refspecs.linuxfoundation.org/elf/gabi4+/contents.html
127 
128 */
129 
elf_shnum(Elf_Ehdr * ehdr)130 static Elf_Word elf_shnum(Elf_Ehdr* ehdr)
131 {
132    Elf_Shdr* shdr = (Elf_Shdr*) ((char*)ehdr + ehdr->e_shoff);
133    Elf_Half shnum = ehdr->e_shnum;
134    return shnum != SHN_UNDEF ? shnum : shdr[0].sh_size;
135 }
136 
elf_shstrndx(Elf_Ehdr * ehdr)137 static Elf_Word elf_shstrndx(Elf_Ehdr* ehdr)
138 {
139    Elf_Half shstrndx = ehdr->e_shstrndx;
140 #if defined(SHN_XINDEX)
141    Elf_Shdr* shdr = (Elf_Shdr*) ((char*)ehdr + ehdr->e_shoff);
142    return shstrndx != SHN_XINDEX ? shstrndx : shdr[0].sh_link;
143 #else
144    // some OSes do not support SHN_XINDEX yet, let's revert to
145    // old way
146    return shstrndx;
147 #endif
148 }
149 
150 #if defined(SHN_XINDEX)
151 static Elf_Word*
get_shndx_table(Elf_Ehdr * ehdr)152 get_shndx_table(Elf_Ehdr* ehdr)
153 {
154    Elf_Word  i;
155    char*     ehdrC    = (char*)ehdr;
156    Elf_Shdr* shdr     = (Elf_Shdr*) (ehdrC + ehdr->e_shoff);
157    const Elf_Word shnum = elf_shnum(ehdr);
158 
159    for (i = 0; i < shnum; i++) {
160      if (shdr[i].sh_type == SHT_SYMTAB_SHNDX) {
161        return (Elf32_Word*)(ehdrC + shdr[i].sh_offset);
162      }
163    }
164    return NULL;
165 }
166 #endif
167 
168 /*
169  * ocInit and ocDeinit
170  */
171 
172 void
ocInit_ELF(ObjectCode * oc)173 ocInit_ELF(ObjectCode * oc)
174 {
175     ocDeinit_ELF(oc);
176 
177     oc->info = (struct ObjectCodeFormatInfo*)stgCallocBytes(
178             1, sizeof *oc->info,
179             "ocInit_Elf(ObjectCodeFormatInfo)");
180     // TODO: fill info
181     oc->info->elfHeader = (Elf_Ehdr *)oc->image;
182     oc->info->programHeader = (Elf_Phdr *) ((uint8_t*)oc->image
183                                             + oc->info->elfHeader->e_phoff);
184     oc->info->sectionHeader = (Elf_Shdr *) ((uint8_t*)oc->image
185                                             + oc->info->elfHeader->e_shoff);
186     oc->info->sectionHeaderStrtab = (char*)((uint8_t*)oc->image +
187             oc->info->sectionHeader[oc->info->elfHeader->e_shstrndx].sh_offset);
188 
189     oc->n_sections = elf_shnum(oc->info->elfHeader);
190 
191     /* get the symbol table(s) */
192     for(int i=0; i < oc->n_sections; i++) {
193         if(SHT_REL  == oc->info->sectionHeader[i].sh_type) {
194             ElfRelocationTable *relTab = (ElfRelocationTable *)stgCallocBytes(
195                     1, sizeof(ElfRelocationTable),
196                     "ocInit_Elf(ElfRelocationTable");
197             relTab->index = i;
198 
199             relTab->relocations =
200                 (Elf_Rel*) ((uint8_t*)oc->info->elfHeader
201                                     + oc->info->sectionHeader[i].sh_offset);
202             relTab->n_relocations = oc->info->sectionHeader[i].sh_size
203                                     / sizeof(Elf_Rel);
204             relTab->targetSectionIndex = oc->info->sectionHeader[i].sh_info;
205 
206             relTab->sectionHeader      = &oc->info->sectionHeader[i];
207 
208             if(oc->info->relTable == NULL) {
209                 oc->info->relTable = relTab;
210             } else {
211                 ElfRelocationTable * tail = oc->info->relTable;
212                 while(tail->next != NULL) tail = tail->next;
213                 tail->next = relTab;
214             }
215 
216         } else if(SHT_RELA == oc->info->sectionHeader[i].sh_type) {
217             ElfRelocationATable *relTab = (ElfRelocationATable *)stgCallocBytes(
218                     1, sizeof(ElfRelocationATable),
219                     "ocInit_Elf(ElfRelocationTable");
220             relTab->index = i;
221 
222             relTab->relocations =
223                 (Elf_Rela*) ((uint8_t*)oc->info->elfHeader
224                                      + oc->info->sectionHeader[i].sh_offset);
225             relTab->n_relocations = oc->info->sectionHeader[i].sh_size
226                                     / sizeof(Elf_Rela);
227             relTab->targetSectionIndex = oc->info->sectionHeader[i].sh_info;
228 
229             relTab->sectionHeader      = &oc->info->sectionHeader[i];
230 
231             if(oc->info->relaTable == NULL) {
232                 oc->info->relaTable = relTab;
233             } else {
234                 ElfRelocationATable * tail = oc->info->relaTable;
235                 while(tail->next != NULL) tail = tail->next;
236                 tail->next = relTab;
237             }
238 
239         } else if(SHT_SYMTAB == oc->info->sectionHeader[i].sh_type) {
240 
241             ElfSymbolTable *symTab = (ElfSymbolTable *)stgCallocBytes(
242                     1, sizeof(ElfSymbolTable),
243                     "ocInit_Elf(ElfSymbolTable");
244 
245             symTab->index = i; /* store the original index, so we can later
246                                 * find or assert that we are dealing with the
247                                 * correct symbol table */
248 
249             Elf_Sym *stab = (Elf_Sym*)((uint8_t*)oc->info->elfHeader
250                                        + oc->info->sectionHeader[i].sh_offset);
251             symTab->n_symbols = oc->info->sectionHeader[i].sh_size
252                                 / sizeof(Elf_Sym);
253             symTab->symbols = (ElfSymbol *)stgCallocBytes(
254                     symTab->n_symbols, sizeof(ElfSymbol),
255                     "ocInit_Elf(ElfSymbol)");
256 
257             /* get the strings table */
258             size_t lnkIdx = oc->info->sectionHeader[i].sh_link;
259             symTab->names = (char*)(uint8_t*)oc->info->elfHeader
260                             + oc->info->sectionHeader[lnkIdx].sh_offset;
261 
262             /* build the ElfSymbols from the symbols */
263             for(size_t j=0; j < symTab->n_symbols; j++) {
264 
265                 symTab->symbols[j].name = stab[j].st_name == 0
266                                           ? "(noname)"
267                                           : symTab->names + stab[j].st_name;
268                 symTab->symbols[j].elf_sym = &stab[j];
269                 /* we don't have an address for this symbol yet; this will be
270                  * populated during ocGetNames. hence addr = NULL.
271                  */
272                 symTab->symbols[j].addr  = NULL;
273                 symTab->symbols[j].got_addr = NULL;
274             }
275 
276             /* append the ElfSymbolTable */
277             if(oc->info->symbolTables == NULL) {
278                 oc->info->symbolTables = symTab;
279             } else {
280                 ElfSymbolTable * tail = oc->info->symbolTables;
281                 while(tail->next != NULL) tail = tail->next;
282                 tail->next = symTab;
283             }
284         }
285     }
286 }
287 
288 void
ocDeinit_ELF(ObjectCode * oc)289 ocDeinit_ELF(ObjectCode * oc)
290 {
291     /* free all ElfSymbolTables, and their associated
292      * ElfSymbols
293      */
294     if(oc->info != NULL) {
295 #if defined(NEED_GOT)
296         freeGot(oc);
297 #endif
298         ElfSymbolTable * last = oc->info->symbolTables;
299 
300         while(last != NULL) {
301             ElfSymbolTable * t = last;
302             last = last->next;
303             stgFree(t->symbols);
304             stgFree(t);
305         }
306 
307         {
308             ElfRelocationTable *last = oc->info->relTable;
309             while (last != NULL) {
310                 ElfRelocationTable *t = last;
311                 last = last->next;
312                 stgFree(t);
313             }
314         }
315 
316         {
317             ElfRelocationATable *last = oc->info->relaTable;
318             while (last != NULL) {
319                 ElfRelocationATable *t = last;
320                 last = last->next;
321                 stgFree(t);
322             }
323         }
324 
325         stgFree(oc->info);
326         oc->info = NULL;
327     }
328 }
329 
330 /*
331  * Generic ELF functions
332  */
333 
334 int
ocVerifyImage_ELF(ObjectCode * oc)335 ocVerifyImage_ELF ( ObjectCode* oc )
336 {
337    Elf_Shdr* shdr;
338    Elf_Sym*  stab;
339    int j, nent, nstrtab, nsymtabs;
340    Elf_Word i, shnum, shstrndx;
341    char* sh_strtab;
342 
343    char*     ehdrC = (char*)(oc->image);
344    Elf_Ehdr* ehdr  = (Elf_Ehdr*)ehdrC;
345 
346    if (ehdr->e_ident[EI_MAG0] != ELFMAG0 ||
347        ehdr->e_ident[EI_MAG1] != ELFMAG1 ||
348        ehdr->e_ident[EI_MAG2] != ELFMAG2 ||
349        ehdr->e_ident[EI_MAG3] != ELFMAG3) {
350       errorBelch("%s: not an ELF object", oc->fileName);
351       return 0;
352    }
353 
354    if (ehdr->e_ident[EI_CLASS] != ELFCLASS) {
355       errorBelch("%s: unsupported ELF format", oc->fileName);
356       return 0;
357    }
358 
359    if (ehdr->e_ident[EI_DATA] == ELFDATA2LSB) {
360        IF_DEBUG(linker,debugBelch( "Is little-endian\n" ));
361    } else
362    if (ehdr->e_ident[EI_DATA] == ELFDATA2MSB) {
363        IF_DEBUG(linker,debugBelch( "Is big-endian\n" ));
364    } else {
365        errorBelch("%s: unknown endianness", oc->fileName);
366        return 0;
367    }
368 
369    if (ehdr->e_type != ET_REL) {
370       errorBelch("%s: not a relocatable object (.o) file", oc->fileName);
371       return 0;
372    }
373    IF_DEBUG(linker, debugBelch( "Is a relocatable object (.o) file\n" ));
374 
375    IF_DEBUG(linker,debugBelch( "Architecture is " ));
376    switch (ehdr->e_machine) {
377 #if defined(EM_ARM)
378       case EM_ARM:   IF_DEBUG(linker,debugBelch( "arm" )); break;
379 #endif
380       case EM_386:   IF_DEBUG(linker,debugBelch( "x86" )); break;
381 #if defined(EM_SPARC32PLUS)
382       case EM_SPARC32PLUS:
383 #endif
384       case EM_SPARC: IF_DEBUG(linker,debugBelch( "sparc" )); break;
385 #if defined(EM_IA_64)
386       case EM_IA_64: IF_DEBUG(linker,debugBelch( "ia64" )); break;
387 #endif
388       case EM_PPC:   IF_DEBUG(linker,debugBelch( "powerpc32" )); break;
389 #if defined(EM_PPC64)
390       case EM_PPC64: IF_DEBUG(linker,debugBelch( "powerpc64" ));
391           errorBelch("%s: RTS linker not implemented on PowerPC 64-bit",
392                      oc->fileName);
393           return 0;
394 #endif
395 #if defined(EM_S390)
396       case EM_S390:  IF_DEBUG(linker,debugBelch( "s390" ));
397           errorBelch("%s: RTS linker not implemented on s390",
398                      oc->fileName);
399           return 0;
400 #endif
401 #if defined(EM_X86_64)
402       case EM_X86_64: IF_DEBUG(linker,debugBelch( "x86_64" )); break;
403 #elif defined(EM_AMD64)
404       case EM_AMD64: IF_DEBUG(linker,debugBelch( "amd64" )); break;
405 #endif
406 #if defined(EM_AARCH64)
407       case EM_AARCH64: IF_DEBUG(linker,debugBelch( "aarch64" )); break;
408 #endif
409        default:       IF_DEBUG(linker,debugBelch( "unknown" ));
410                      errorBelch("%s: unknown architecture (e_machine == %d)"
411                                 , oc->fileName, ehdr->e_machine);
412                      return 0;
413    }
414 
415    shnum = elf_shnum(ehdr);
416    IF_DEBUG(linker,debugBelch(
417              "\nSection header table: start %ld, n_entries %d, ent_size %d\n",
418              (long)ehdr->e_shoff, shnum, ehdr->e_shentsize  ));
419 
420    ASSERT(ehdr->e_shentsize == sizeof(Elf_Shdr));
421 
422    shdr = (Elf_Shdr*) (ehdrC + ehdr->e_shoff);
423 
424    shstrndx = elf_shstrndx(ehdr);
425    if (shstrndx == SHN_UNDEF) {
426       errorBelch("%s: no section header string table", oc->fileName);
427       return 0;
428    } else {
429       IF_DEBUG(linker,debugBelch( "Section header string table is section %d\n",
430                           shstrndx));
431       sh_strtab = ehdrC + shdr[shstrndx].sh_offset;
432    }
433 
434    for (i = 0; i < shnum; i++) {
435       IF_DEBUG(linker,debugBelch("%2d:  ", i ));
436       IF_DEBUG(linker,debugBelch("type=%2d  ", (int)shdr[i].sh_type ));
437       IF_DEBUG(linker,debugBelch("size=%4d  ", (int)shdr[i].sh_size ));
438       IF_DEBUG(linker,debugBelch("offs=%4d  ", (int)shdr[i].sh_offset ));
439       IF_DEBUG(linker,debugBelch("  (%p .. %p)  ",
440                ehdrC + shdr[i].sh_offset,
441                       ehdrC + shdr[i].sh_offset + shdr[i].sh_size - 1));
442 
443 #define SECTION_INDEX_VALID(ndx) (ndx > SHN_UNDEF && ndx < shnum)
444 
445       switch (shdr[i].sh_type) {
446 
447         case SHT_REL:
448         case SHT_RELA:
449           IF_DEBUG(linker,debugBelch( shdr[i].sh_type == SHT_REL ? "Rel  " : "RelA "));
450 
451           if (!SECTION_INDEX_VALID(shdr[i].sh_link)) {
452             if (shdr[i].sh_link == SHN_UNDEF)
453               errorBelch("\n%s: relocation section #%d has no symbol table\n"
454                          "This object file has probably been fully stripped. "
455                          "Such files cannot be linked.\n",
456                          oc->archiveMemberName ? oc->archiveMemberName : oc->fileName, i);
457             else
458               errorBelch("\n%s: relocation section #%d has an invalid link field (%d)\n",
459                          oc->archiveMemberName ? oc->archiveMemberName : oc->fileName,
460                          i, shdr[i].sh_link);
461             return 0;
462           }
463           if (shdr[shdr[i].sh_link].sh_type != SHT_SYMTAB) {
464             errorBelch("\n%s: relocation section #%d does not link to a symbol table\n",
465                        oc->archiveMemberName ? oc->archiveMemberName : oc->fileName, i);
466             return 0;
467           }
468           if (!SECTION_INDEX_VALID(shdr[i].sh_info)) {
469             errorBelch("\n%s: relocation section #%d has an invalid info field (%d)\n",
470                        oc->archiveMemberName ? oc->archiveMemberName : oc->fileName,
471                        i, shdr[i].sh_info);
472             return 0;
473           }
474 
475           break;
476         case SHT_SYMTAB:
477           IF_DEBUG(linker,debugBelch("Sym  "));
478 
479           if (!SECTION_INDEX_VALID(shdr[i].sh_link)) {
480             errorBelch("\n%s: symbol table section #%d has an invalid link field (%d)\n",
481                        oc->archiveMemberName ? oc->archiveMemberName : oc->fileName,
482                        i, shdr[i].sh_link);
483             return 0;
484           }
485           if (shdr[shdr[i].sh_link].sh_type != SHT_STRTAB) {
486             errorBelch("\n%s: symbol table section #%d does not link to a string table\n",
487                        oc->archiveMemberName ? oc->archiveMemberName : oc->fileName, i);
488 
489             return 0;
490           }
491           break;
492         case SHT_STRTAB: IF_DEBUG(linker,debugBelch("Str  ")); break;
493         default:         IF_DEBUG(linker,debugBelch("     ")); break;
494       }
495       if (sh_strtab) {
496           IF_DEBUG(linker,debugBelch("sname=%s\n", sh_strtab + shdr[i].sh_name ));
497       }
498    }
499 
500    IF_DEBUG(linker,debugBelch( "\nString tables\n" ));
501    nstrtab = 0;
502    for (i = 0; i < shnum; i++) {
503       if (shdr[i].sh_type == SHT_STRTAB
504           /* Ignore the section header's string table. */
505           && i != shstrndx
506           /* Ignore string tables named .stabstr, as they contain
507              debugging info. */
508           && 0 != memcmp(".stabstr", sh_strtab + shdr[i].sh_name, 8)
509          ) {
510          IF_DEBUG(linker,debugBelch("   section %d is a normal string table\n", i ));
511          nstrtab++;
512       }
513    }
514    if (nstrtab == 0) {
515       IF_DEBUG(linker,debugBelch("   no normal string tables (potentially, but not necessarily a problem)\n"));
516    }
517 #if defined(SHN_XINDEX)
518    Elf_Word* shndxTable = get_shndx_table(ehdr);
519 #endif
520    nsymtabs = 0;
521    IF_DEBUG(linker,debugBelch( "Symbol tables\n" ));
522    for (i = 0; i < shnum; i++) {
523       if (shdr[i].sh_type != SHT_SYMTAB) continue;
524       IF_DEBUG(linker,debugBelch( "section %d is a symbol table\n", i ));
525       nsymtabs++;
526       stab = (Elf_Sym*) (ehdrC + shdr[i].sh_offset);
527       nent = shdr[i].sh_size / sizeof(Elf_Sym);
528       IF_DEBUG(linker,debugBelch( "   number of entries is apparently %d (%ld rem)\n",
529                nent,
530                (long)shdr[i].sh_size % sizeof(Elf_Sym)
531              ));
532       if (0 != shdr[i].sh_size % sizeof(Elf_Sym)) {
533          errorBelch("%s: non-integral number of symbol table entries", oc->fileName);
534          return 0;
535       }
536       for (j = 0; j < nent; j++) {
537          Elf_Word secno = stab[j].st_shndx;
538 #if defined(SHN_XINDEX)
539          /* See Note [Many ELF Sections] */
540          if (secno == SHN_XINDEX) {
541             ASSERT(shndxTable);
542             secno = shndxTable[j];
543          }
544 #endif
545          IF_DEBUG(linker,debugBelch("   %2d  ", j ));
546          IF_DEBUG(linker,debugBelch("  sec=%-5d  size=%-3d  val=%5p  ",
547                              (int)secno,
548                              (int)stab[j].st_size,
549                              (char*)stab[j].st_value ));
550 
551          IF_DEBUG(linker,debugBelch("type=" ));
552          switch (ELF_ST_TYPE(stab[j].st_info)) {
553             case STT_NOTYPE:  IF_DEBUG(linker,debugBelch("notype " )); break;
554             case STT_OBJECT:  IF_DEBUG(linker,debugBelch("object " )); break;
555             case STT_FUNC  :  IF_DEBUG(linker,debugBelch("func   " )); break;
556             case STT_SECTION: IF_DEBUG(linker,debugBelch("section" )); break;
557             case STT_FILE:    IF_DEBUG(linker,debugBelch("file   " )); break;
558             default:          IF_DEBUG(linker,debugBelch("?      " )); break;
559          }
560          IF_DEBUG(linker,debugBelch("  " ));
561 
562          IF_DEBUG(linker,debugBelch("bind=" ));
563          switch (ELF_ST_BIND(stab[j].st_info)) {
564             case STB_LOCAL :  IF_DEBUG(linker,debugBelch("local " )); break;
565             case STB_GLOBAL:  IF_DEBUG(linker,debugBelch("global" )); break;
566             case STB_WEAK  :  IF_DEBUG(linker,debugBelch("weak  " )); break;
567             default:          IF_DEBUG(linker,debugBelch("?     " )); break;
568          }
569          IF_DEBUG(linker,debugBelch("  " ));
570 
571          IF_DEBUG(linker,debugBelch("other=%2x ", stab[j].st_other ));
572          IF_DEBUG(linker,debugBelch("name=%s [%x]\n",
573                         ehdrC + shdr[shdr[i].sh_link].sh_offset
574                               + stab[j].st_name, stab[j].st_name ));
575       }
576    }
577 
578    if (nsymtabs == 0) {
579      // Not having a symbol table is not in principle a problem.
580      // When an object file has no symbols then the 'strip' program
581      // typically will remove the symbol table entirely.
582      IF_DEBUG(linker,debugBelch("   no symbol tables (potentially, but not necessarily a problem)\n"));
583    }
584 
585    return 1;
586 }
587 
588 /* Figure out what kind of section it is.  Logic derived from
589    Figure 1.14 ("Special Sections") of the ELF document
590    ("Portable Formats Specification, Version 1.1"). */
getSectionKind_ELF(Elf_Shdr * hdr,int * is_bss)591 static SectionKind getSectionKind_ELF( Elf_Shdr *hdr, int *is_bss )
592 {
593     *is_bss = false;
594 
595     if (hdr->sh_type == SHT_PROGBITS
596         && (hdr->sh_flags & SHF_ALLOC) && (hdr->sh_flags & SHF_EXECINSTR)) {
597         /* .text-style section */
598         return SECTIONKIND_CODE_OR_RODATA;
599     }
600 
601     if (hdr->sh_type == SHT_PROGBITS
602             && (hdr->sh_flags & SHF_ALLOC) && (hdr->sh_flags & SHF_WRITE)) {
603             /* .data-style section */
604             return SECTIONKIND_RWDATA;
605     }
606 
607     if (hdr->sh_type == SHT_PROGBITS
608         && (hdr->sh_flags & SHF_ALLOC) && !(hdr->sh_flags & SHF_WRITE)) {
609         /* .rodata-style section */
610         return SECTIONKIND_CODE_OR_RODATA;
611     }
612 #if defined(SHT_INIT_ARRAY)
613     if (hdr->sh_type == SHT_INIT_ARRAY
614         && (hdr->sh_flags & SHF_ALLOC) && (hdr->sh_flags & SHF_WRITE)) {
615        /* .init_array section */
616         return SECTIONKIND_INIT_ARRAY;
617     }
618 #endif /* not SHT_INIT_ARRAY */
619     if (hdr->sh_type == SHT_NOBITS
620         && (hdr->sh_flags & SHF_ALLOC) && (hdr->sh_flags & SHF_WRITE)) {
621         /* .bss-style section */
622         *is_bss = true;
623         return SECTIONKIND_RWDATA;
624     }
625 
626     return SECTIONKIND_OTHER;
627 }
628 
629 #if !defined(NEED_PLT)
630 
631 static void *
mapObjectFileSection(int fd,Elf_Word offset,Elf_Word size,void ** mapped_start,StgWord * mapped_size,StgWord * mapped_offset)632 mapObjectFileSection (int fd, Elf_Word offset, Elf_Word size,
633                       void **mapped_start, StgWord *mapped_size,
634                       StgWord *mapped_offset)
635 {
636     void *p;
637     size_t pageOffset, pageSize;
638 
639     pageOffset = roundDownToPage(offset);
640     pageSize = roundUpToPage(offset-pageOffset+size);
641     p = mmapForLinker(pageSize, PROT_READ | PROT_WRITE, 0, fd, pageOffset);
642     if (p == NULL) return NULL;
643     *mapped_size = pageSize;
644     *mapped_offset = pageOffset;
645     *mapped_start = p;
646     return (void*)((StgWord)p + offset - pageOffset);
647 }
648 #endif
649 
650 int
ocGetNames_ELF(ObjectCode * oc)651 ocGetNames_ELF ( ObjectCode* oc )
652 {
653    Elf_Word i;
654    int result, fd = -1;
655 
656    char*     ehdrC    = (char*)(oc->image);
657    Elf_Ehdr* ehdr     = (Elf_Ehdr*)ehdrC;
658 
659    Elf_Shdr* shdr     = (Elf_Shdr*) (ehdrC + ehdr->e_shoff);
660    Section * sections;
661 #if defined(SHN_XINDEX)
662    Elf_Word* shndxTable = get_shndx_table(ehdr);
663 #endif
664    const Elf_Word shnum = elf_shnum(ehdr);
665 
666    ASSERT(symhash != NULL);
667 
668    sections = (Section*)stgCallocBytes(sizeof(Section), shnum,
669                                        "ocGetNames_ELF(sections)");
670    oc->sections = sections;
671    oc->n_sections = shnum;
672 
673    if (oc->imageMapped) {
674 #if defined(openbsd_HOST_OS)
675        fd = open(oc->fileName, O_RDONLY, S_IRUSR);
676 #else
677        fd = open(oc->fileName, O_RDONLY);
678 #endif
679        if (fd == -1) {
680            errorBelch("loadObj: can't open %" PATH_FMT, oc->fileName);
681            return 0;
682        }
683    }
684 
685    for (i = 0; i < shnum; i++) {
686       int         is_bss = false;
687       SectionKind kind   = getSectionKind_ELF(&shdr[i], &is_bss);
688       SectionAlloc alloc = SECTION_NOMEM;
689       void *start = NULL, *mapped_start = NULL;
690       StgWord mapped_size = 0, mapped_offset = 0;
691       StgWord size = shdr[i].sh_size;
692       StgWord offset = shdr[i].sh_offset;
693       StgWord align = shdr[i].sh_addralign;
694 
695       if (is_bss && size > 0) {
696          /* This is a non-empty .bss section.  Allocate zeroed space for
697             it, and set its .sh_offset field such that
698             ehdrC + .sh_offset == addr_of_zeroed_space.  */
699 #if defined(NEED_GOT) || RTS_LINKER_USE_MMAP
700           if (USE_CONTIGUOUS_MMAP || RtsFlags.MiscFlags.linkerAlwaysPic) {
701               /* The space for bss sections is already preallocated */
702               CHECK(oc->bssBegin != NULL);
703               alloc = SECTION_NOMEM;
704               CHECK(oc->image != 0x0);
705               start =
706                 oc->image + roundUpToAlign(oc->bssBegin - oc->image, align);
707               oc->bssBegin = (char*)start + size;
708               CHECK(oc->bssBegin <= oc->bssEnd);
709           } else {
710               /* Use mmapForLinker to allocate .bss, otherwise the malloced
711                * address might be out of range for sections that are mmaped.
712                */
713               alloc = SECTION_MMAP;
714               start = mmapAnonForLinker(size);
715               if (start == NULL) {
716                 barf("failed to mmap memory for bss. "
717                      "errno = %d", errno);
718               }
719               mapped_start = start;
720               mapped_offset = 0;
721               mapped_size = roundUpToPage(size);
722           }
723           CHECK(start != 0x0);
724 #else
725           alloc = SECTION_MALLOC;
726           start = stgCallocBytes(1, size, "ocGetNames_ELF(BSS)");
727           mapped_start = start;
728 #endif
729          /*
730          debugBelch("BSS section at 0x%x, size %d\n",
731                          zspace, shdr[i].sh_size);
732          */
733           addSection(&sections[i], kind, alloc, start, size,
734                      mapped_offset, mapped_start, mapped_size);
735 
736           oc->sections[i].info->nstubs = 0;
737           oc->sections[i].info->stub_offset = NULL;
738           oc->sections[i].info->stub_size = 0;
739           oc->sections[i].info->stubs = NULL;
740       } else if (kind != SECTIONKIND_OTHER && size > 0) {
741 
742 #if defined(NEED_PLT)
743           /* To support stubs next to sections, we will use the following
744            * layout:
745            *
746            * .--------------.
747            * | Section data |
748            * |--------------|
749            * | Stub space   |
750            * '--------------'
751            *
752            * This ensures that the plt stubs are in range for the section data,
753            * Unless the section data exceeds the size for relative jump, in
754            * which case I wouldn't know how to solve this, without starting to
755            * break up the section itself.
756            */
757 
758           unsigned nstubs = numberOfStubsForSection(oc, i);
759           unsigned stub_space = STUB_SIZE * nstubs;
760 
761           void * mem = mmapAnonForLinker(size+stub_space);
762 
763           if( mem == NULL ) {
764               barf("failed to mmap allocated memory to load section %d. "
765                    "errno = %d", i, errno);
766           }
767 
768           /* copy only the image part over; we don't want to copy data
769            * into the stub part.
770            */
771           memcpy( mem, oc->image + offset, size );
772 
773           alloc = SECTION_MMAP;
774 
775           mapped_offset = 0;
776           mapped_size = roundUpToPage(size+stub_space);
777           start = mem;
778           mapped_start = mem;
779 #else
780           if (USE_CONTIGUOUS_MMAP || RtsFlags.MiscFlags.linkerAlwaysPic) {
781               // already mapped.
782               start = oc->image + offset;
783               alloc = SECTION_NOMEM;
784           }
785           // use the m32 allocator if either the image is not mapped
786           // (i.e. we cannot map the secions separately), or if the section
787           // size is small.
788           else if (!oc->imageMapped || size < getPageSize() / 3) {
789               bool executable = kind == SECTIONKIND_CODE_OR_RODATA;
790               m32_allocator *allocator = executable ? oc->rx_m32 : oc->rw_m32;
791               // align on 16 bytes. The reason being that llvm will emit see
792               // paddq statements for x86_64 under optimisation and load from
793               // RODATA sections. Specifically .rodata.cst16. However we don't
794               // handle the cst part in any way what so ever, so 16 seems
795               // better than 8.
796               start = m32_alloc(allocator, size, 16);
797               if (start == NULL) goto fail;
798               memcpy(start, oc->image + offset, size);
799               alloc = SECTION_M32;
800           } else {
801               start = mapObjectFileSection(fd, offset, size,
802                                            &mapped_start, &mapped_size,
803                                            &mapped_offset);
804               if (start == NULL) goto fail;
805               alloc = SECTION_MMAP;
806           }
807 #endif
808           addSection(&sections[i], kind, alloc, start, size,
809                      mapped_offset, mapped_start, mapped_size);
810 
811 #if defined(NEED_PLT)
812           oc->sections[i].info->nstubs = 0;
813           oc->sections[i].info->stub_offset = (uint8_t*)mem + size;
814           oc->sections[i].info->stub_size = stub_space;
815           oc->sections[i].info->stubs = NULL;
816 #else
817           oc->sections[i].info->nstubs = 0;
818           oc->sections[i].info->stub_offset = NULL;
819           oc->sections[i].info->stub_size = 0;
820           oc->sections[i].info->stubs = NULL;
821 #endif
822 
823           addProddableBlock(oc, start, size);
824       } else {
825           addSection(&oc->sections[i], kind, alloc, oc->image+offset, size,
826                      0, 0, 0);
827           oc->sections[i].info->nstubs = 0;
828           oc->sections[i].info->stub_offset = NULL;
829           oc->sections[i].info->stub_size = 0;
830           oc->sections[i].info->stubs = NULL;
831       }
832       oc->sections[i].info->name          = oc->info->sectionHeaderStrtab
833                                             + shdr[i].sh_name;
834       oc->sections[i].info->sectionHeader = &shdr[i];
835 
836 
837 
838 
839       if (shdr[i].sh_type != SHT_SYMTAB) continue;
840 
841       /* copy stuff into this module's object symbol table */
842 
843       oc->n_symbols = 0;
844       for(ElfSymbolTable *symTab = oc->info->symbolTables;
845           symTab != NULL; symTab = symTab->next) {
846           oc->n_symbols += symTab->n_symbols;
847       }
848 
849       oc->symbols = stgCallocBytes(oc->n_symbols, sizeof(Symbol_t),
850                                    "ocGetNames_ELF(oc->symbols)");
851       // Note calloc: if we fail partway through initializing symbols, we need
852       // to undo the additions to the symbol table so far. We know which ones
853       // have been added by whether the entry is NULL or not.
854 
855       unsigned curSymbol = 0;
856 
857       unsigned long common_size = 0;
858       unsigned long common_used = 0;
859       for(ElfSymbolTable *symTab = oc->info->symbolTables;
860            symTab != NULL; symTab = symTab->next) {
861            for (size_t j = 0; j < symTab->n_symbols; j++) {
862                ElfSymbol *symbol = &symTab->symbols[j];
863                if (SHN_COMMON == symTab->symbols[j].elf_sym->st_shndx) {
864                    common_size += symbol->elf_sym->st_size;
865                }
866            }
867       }
868       void * common_mem = NULL;
869       if(common_size > 0) {
870           common_mem = mmapAnonForLinker(common_size);
871           if (common_mem == NULL) {
872             barf("ocGetNames_ELF: Failed to allocate memory for SHN_COMMONs");
873           }
874       }
875 
876       //TODO: we ignore local symbols anyway right? So we can use the
877       //      shdr[i].sh_info to get the index of the first non-local symbol
878       // ie we should use j = shdr[i].sh_info
879        for(ElfSymbolTable *symTab = oc->info->symbolTables;
880            symTab != NULL; symTab = symTab->next) {
881            for (size_t j = 0; j < symTab->n_symbols; j++) {
882 
883                char isLocal = false; /* avoids uninit-var warning */
884                HsBool isWeak = HS_BOOL_FALSE;
885                SymbolName *nm = symTab->symbols[j].name;
886                unsigned short shndx = symTab->symbols[j].elf_sym->st_shndx;
887 
888                ElfSymbol *symbol = &symTab->symbols[j];
889 
890                Elf_Word secno;
891 
892 
893                /* See Note [Many ELF Sections] */
894                /* Note that future checks for special SHN_* numbers should check
895                 * the shndx variable, not the section number in secno. Sections
896                 * with the real number in the SHN_LORESERVE..HIRESERVE range
897                 * will have shndx SHN_XINDEX and a secno with one of the
898                 * reserved values. */
899                secno = shndx;
900 #if defined(SHN_XINDEX)
901                if (shndx == SHN_XINDEX) {
902                   ASSERT(shndxTable);
903                   secno = shndxTable[j];
904                }
905 #endif
906                /* Figure out if we want to add it; if so, set ad to its
907                   address.  Otherwise leave ad == NULL. */
908 
909                if (shndx == SHN_COMMON) {
910                    isLocal = false;
911                    ASSERT(common_used < common_size);
912                    ASSERT(common_mem);
913                    symbol->addr = (void*)((uintptr_t)common_mem + common_used);
914                    common_used += symbol->elf_sym->st_size;
915                    ASSERT(common_used <= common_size);
916 
917                    IF_DEBUG(linker,
918                             debugBelch("COMMON symbol, size %ld name %s allocated at %p\n",
919                                        symbol->elf_sym->st_size, nm, symbol->addr));
920 
921                    /* Pointless to do addProddableBlock() for this area,
922                       since the linker should never poke around in it. */
923                } else if ((ELF_ST_BIND(symbol->elf_sym->st_info) == STB_GLOBAL
924                            || ELF_ST_BIND(symbol->elf_sym->st_info) == STB_LOCAL
925                            || ELF_ST_BIND(symbol->elf_sym->st_info) == STB_WEAK
926                                                                   )
927                           /* and not an undefined symbol */
928                           && shndx != SHN_UNDEF
929                           /* and not in a "special section" */
930                           && (shndx < SHN_LORESERVE
931 #if defined(SHN_XINDEX)
932                                   || shndx == SHN_XINDEX
933 #endif
934                           )
935                           &&
936                           /* and it's a not a section or string table or
937                            * anything silly */
938                           (ELF_ST_TYPE(symbol->elf_sym->st_info) == STT_FUNC
939                           || ELF_ST_TYPE(symbol->elf_sym->st_info) == STT_OBJECT
940                           || ELF_ST_TYPE(symbol->elf_sym->st_info) == STT_NOTYPE
941                           )
942                        ) {
943                    /* Section 0 is the undefined section, hence > and not >=. */
944                    ASSERT(secno > 0 && secno < shnum);
945                    /*
946                    if (shdr[secno].sh_type == SHT_NOBITS) {
947                       debugBelch("   BSS symbol, size %d off %d name %s\n",
948                                       stab[j].st_size, stab[j].st_value, nm);
949                    }
950                    */
951                    symbol->addr = (SymbolAddr*)(
952                            (intptr_t) oc->sections[secno].start +
953                            (intptr_t) symbol->elf_sym->st_value);
954                    ASSERT(symbol->addr != 0x0);
955                    if (ELF_ST_BIND(symbol->elf_sym->st_info) == STB_LOCAL) {
956                        isLocal = true;
957                        isWeak = false;
958                    } else { /* STB_GLOBAL or STB_WEAK */
959                        IF_DEBUG(linker,
960                                 debugBelch("addOTabName(GLOB): %10p  %s %s\n",
961                                            symbol->addr, oc->fileName, nm));
962                        isLocal = false;
963                        isWeak = ELF_ST_BIND(symbol->elf_sym->st_info)
964                                 == STB_WEAK;
965                    }
966                }
967 
968                /* And the decision is ... */
969 
970                if (symbol->addr != NULL) {
971                    ASSERT(nm != NULL);
972                    /* Acquire! */
973                    if (!isLocal) {
974 
975                        if (isWeak == HS_BOOL_TRUE) {
976                            setWeakSymbol(oc, nm);
977                        }
978                        if (!ghciInsertSymbolTable(oc->fileName, symhash,
979                                                   nm, symbol->addr, isWeak, oc)
980                            ) {
981                            goto fail;
982                        }
983                        oc->symbols[curSymbol++].name = nm;
984                        oc->symbols[curSymbol].addr = symbol->addr;
985                    }
986                } else {
987                    /* Skip. */
988                    IF_DEBUG(linker,
989                             debugBelch("skipping `%s'\n",
990                                                nm)
991                    );
992 
993                    /*
994                    debugBelch(
995                       "skipping   bind = %d,  type = %d,  secno = %d   `%s'\n",
996                       (int)ELF_ST_BIND(stab[j].st_info),
997                       (int)ELF_ST_TYPE(stab[j].st_info),
998                       (int)secno,
999                       nm
1000                    );
1001                    */
1002                }
1003            }
1004       }
1005    }
1006 
1007 #if defined(NEED_GOT)
1008    if(makeGot( oc ))
1009        errorBelch("Failed to create GOT for %s",
1010                   oc->archiveMemberName
1011                   ? oc->archiveMemberName
1012                   : oc->fileName);
1013 #endif
1014    result = 1;
1015    goto end;
1016 
1017 fail:
1018    result = 0;
1019    goto end;
1020 
1021 end:
1022    if (fd >= 0) close(fd);
1023    return result;
1024 }
1025 
1026 // the aarch64 linker uses relocacteObjectCodeAarch64,
1027 // see elf_reloc_aarch64.{h,c}
1028 #if !defined(aarch64_HOST_ARCH)
1029 
1030 /* Do ELF relocations which lack an explicit addend.  All x86-linux
1031    and arm-linux relocations appear to be of this form. */
1032 static int
do_Elf_Rel_relocations(ObjectCode * oc,char * ehdrC,Elf_Shdr * shdr,int shnum)1033 do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC,
1034                          Elf_Shdr* shdr, int shnum )
1035 {
1036    int j;
1037 
1038    Elf_Word* targ;
1039    Elf_Rel*  rtab = (Elf_Rel*) (ehdrC + shdr[shnum].sh_offset);
1040 
1041    int         nent = shdr[shnum].sh_size / sizeof(Elf_Rel);
1042    int target_shndx = shdr[shnum].sh_info;
1043    int symtab_shndx = shdr[shnum].sh_link;
1044 
1045    ElfSymbolTable *stab = NULL;
1046    for(ElfSymbolTable * st = oc->info->symbolTables;
1047        st != NULL; st = st->next) {
1048        if((int)st->index == symtab_shndx) {
1049            stab = st;
1050            break;
1051        }
1052    }
1053    ASSERT(stab != NULL);
1054 
1055    targ  = (Elf_Word*)oc->sections[target_shndx].start;
1056    IF_DEBUG(linker,debugBelch(
1057                 "relocations for section %d using symtab %d\n",
1058                 target_shndx, symtab_shndx));
1059 
1060    /* Skip sections that we're not interested in. */
1061    if (oc->sections[target_shndx].kind == SECTIONKIND_OTHER) {
1062        IF_DEBUG(linker,debugBelch( "skipping (target section not loaded)"));
1063        return 1;
1064    }
1065 
1066    /* The following nomenclature is used for the operation:
1067     * - S -- (when used on its own) is the address of the symbol.
1068     * - A -- is the addend for the relocation.
1069     * - P -- is the address of the place being relocated (derived from r_offset).
1070     * - Pa - is the adjusted address of the place being relocated, defined as (P & 0xFFFFFFFC).
1071     * - T -- is 1 if the target symbol S has type STT_FUNC and the symbol addresses a Thumb instruction; it is 0 otherwise.
1072     * - B(S) is the addressing origin of the output segment defining the symbol S. The origin is not required to be the
1073     *        base address of the segment. This value must always be word-aligned.
1074     * - GOT_ORG is the addressing origin of the Global Offset Table (the indirection table for imported data addresses).
1075     *        This value must always be word-aligned.  See §4.6.1.8, Proxy generating relocations.
1076     * - GOT(S) is the address of the GOT entry for the symbol S.
1077     *
1078     * See the ELF for "ARM Specification" for details:
1079     * https://developer.arm.com/architectures/system-architectures/software-standards/abi
1080     */
1081 
1082    for (j = 0; j < nent; j++) {
1083        Elf_Addr offset = rtab[j].r_offset;
1084        Elf_Addr info   = rtab[j].r_info;
1085 
1086        Elf_Addr  P  = ((Elf_Addr)targ) + offset;
1087        Elf_Word* pP = (Elf_Word*)P;
1088 #if defined(i386_HOST_ARCH) || defined(DEBUG)
1089        Elf_Addr  A  = *pP;
1090 #endif
1091        Elf_Addr  S;
1092        void*     S_tmp;
1093 #if defined(i386_HOST_ARCH)
1094        Elf_Addr  value;
1095 #endif
1096 #if defined(arm_HOST_ARCH)
1097        int is_target_thm=0, T=0;
1098 #endif
1099 
1100        ElfSymbol * symbol = NULL;
1101 
1102        IF_DEBUG(linker,debugBelch( "Rel entry %3d is raw(%6p %6p): ",
1103                                    j, (void*)offset, (void*)info ));
1104        if (!info) {
1105            IF_DEBUG(linker,debugBelch( " ZERO" ));
1106            S = 0;
1107        } else {
1108            symbol = &stab->symbols[ELF_R_SYM(info)];
1109            /* First see if it is a local symbol. */
1110            if (ELF_ST_BIND(symbol->elf_sym->st_info) == STB_LOCAL || strncmp(symbol->name, "_GLOBAL_OFFSET_TABLE_", 21) == 0) {
1111                S = (Elf_Addr)symbol->addr;
1112            } else {
1113                S_tmp = lookupDependentSymbol( symbol->name, oc );
1114                S = (Elf_Addr)S_tmp;
1115            }
1116            if (!S) {
1117                errorBelch("%s: unknown symbol `%s'",
1118                           oc->fileName, symbol->name);
1119                return 0;
1120            }
1121            IF_DEBUG(linker,debugBelch( "`%s' resolves to %p\n", symbol->name,
1122                                        (void*)S ));
1123 
1124 #if defined(arm_HOST_ARCH)
1125            /*
1126             * 4.5.3 Symbol Values
1127             *
1128             * In addition to the normal rules for symbol values the following
1129             * rules shall also apply to symbols of type STT_FUNC:
1130             * - If the symbol addresses an ARM instruction, its value is the
1131             *   address of the instruction (in a relocatable object, the
1132             *   offset of the instruction from the start of the section
1133             *   containing it).
1134             * - If the symbol addresses a Thumb instruction, its value is the
1135             *   address of the instruction with bit zero set (in a relocatable
1136             *   object, the section offset with bit zero set).
1137             * - For the purposes of relocation the value used shall be the
1138             *   address of the instruction (st_value & ~1).
1139             *
1140             *  Note: This allows a linker to distinguish ARM and Thumb code
1141             *        symbols without having to refer to the map. An ARM symbol
1142             *        will always have an even value, while a Thumb symbol will
1143             *        always have an odd value. However, a linker should strip
1144             *        the discriminating bit from the value before using it for
1145             *        relocation.
1146             *
1147             * (source: ELF for the ARM Architecture
1148             *          ARM IHI 0044F, current through ABI release 2.10
1149             *          24th November 2015)
1150             */
1151            if(ELF_ST_TYPE(symbol->elf_sym->st_info) == STT_FUNC) {
1152                is_target_thm = S & 0x1;
1153                T = is_target_thm;
1154                S &= ~1;
1155            }
1156 #endif
1157        }
1158 
1159        int reloc_type = ELF_R_TYPE(info);
1160        IF_DEBUG(linker,debugBelch("Reloc: P = %p   S = %p   A = %p   type=%d\n",
1161                                   (void*)P, (void*)S, (void*)A, reloc_type ));
1162        checkProddableBlock ( oc, pP, sizeof(Elf_Word) );
1163 
1164 #if defined(i386_HOST_ARCH)
1165        value = S + A;
1166 #endif
1167 
1168        switch (reloc_type) {
1169 #        if defined(i386_HOST_ARCH)
1170        case COMPAT_R_386_NONE:                  break;
1171        case COMPAT_R_386_32:   *pP = value;     break;
1172        case COMPAT_R_386_PC32: *pP = value - P; break;
1173 #        endif
1174 
1175 #        if defined(arm_HOST_ARCH)
1176        case COMPAT_R_ARM_ABS32:     /* (S + A) | T */
1177            // Specified by Linux ARM ABI to be equivalent to ABS32
1178        case COMPAT_R_ARM_TARGET1:
1179            *(Elf32_Word *)P += S;
1180            *(Elf32_Word *)P |= T;
1181            break;
1182 
1183        case COMPAT_R_ARM_REL32:     /* ((S + A) | T) – P */
1184            *(Elf32_Word *)P += S;
1185            *(Elf32_Word *)P |= T;
1186            *(Elf32_Word *)P -= P;
1187            break;
1188 
1189        case COMPAT_R_ARM_BASE_PREL: /* B(S) + A – P */
1190        {
1191            int32_t A = *pP;
1192            // bfd used to encode sb (B(S)) as 0.
1193            *(uint32_t *)P += 0 + A - P;
1194            break;
1195        }
1196 
1197        case COMPAT_R_ARM_GOT_BREL: /* GOT(S) + A – GOT_ORG */
1198        {
1199            int32_t A = *pP;
1200            void* GOT_S = symbol->got_addr;
1201            *(uint32_t *)P = (uint32_t) GOT_S + A - (uint32_t) oc->info->got_start;
1202            break;
1203        }
1204 
1205        case COMPAT_R_ARM_CALL:
1206        case COMPAT_R_ARM_JUMP24:
1207        {
1208            // N.B. LLVM's LLD linker's relocation implementation is a fantastic
1209            // resource
1210            StgWord32 *word = (StgWord32 *)P;
1211            StgInt32 imm = (*word & ((1<<24)-1)) << 2;
1212 
1213            const StgBool is_blx = (*word & 0xf0000000) == 0xf0000000;
1214            const StgWord32 hBit = is_blx ? ((*word >> 24) & 1) : 0;
1215            imm |= hBit << 1;
1216 
1217            // Sign extend to 32 bits
1218            // I would have thought this would be 24 bits but LLD uses 26 here.
1219            // Hmm.
1220            int32_t A = signExtend32(26, imm);
1221 
1222            S = S + A; A = 0;
1223 
1224            StgWord32 result = ((S + A) | T) - P;
1225 
1226            const StgBool overflow = !isInt(26, (StgInt32) result);
1227            // Handle overflow and Thumb interworking
1228            const StgBool needs_veneer =
1229                (is_target_thm && ELF_R_TYPE(info) == COMPAT_R_ARM_JUMP24)
1230                || overflow;
1231 
1232            if(needs_veneer) { /* overflow or thum interworking */
1233                // Note [PC bias]
1234                // From the ELF for the ARM Architecture documentation:
1235                // > 4.6.1.1 Addends and PC-bias compensation
1236                // > A binary file may use REL or RELA relocations or a mixture
1237                // > of the two (but multiple relocations for the same address
1238                // > must use only one type).
1239                // > If the relocation is pc-relative then compensation for the
1240                // > PC bias (the PC value is 8 bytes ahead of the executing
1241                // > instruction in ARM state and 4 bytes in Thumb state) must
1242                // > be encoded in the relocation by the object producer.
1243                int32_t bias = 8;
1244 
1245                S += bias;
1246                /* try to locate an existing stub for this target */
1247                if(findStub(&oc->sections[target_shndx], (void**)&S, 0)) {
1248                    /* didn't find any. Need to create one */
1249                    if(makeStub(&oc->sections[target_shndx], (void**)&S, 0)) {
1250                        errorBelch("Unable to create veneer for ARM_CALL\n");
1251                        return 0;
1252                    }
1253                }
1254                S -= bias;
1255 
1256                result = ((S + A) | T) - P;
1257                result &= ~1; // Clear thumb indicator bit
1258 
1259                ASSERT(isInt(26, result)); /* X in range */
1260            }
1261 
1262            // Update the branch target
1263            const StgWord32 imm24 = (result & 0x03fffffc) >> 2;
1264            *word = (*word & ~0x00ffffff)
1265                  | (imm24 & 0x00ffffff);
1266 
1267            // Change the relocated branch into a BLX if necessary
1268            const StgBool switch_mode =
1269                is_target_thm && (reloc_type == COMPAT_R_ARM_CALL);
1270            if (!needs_veneer && switch_mode) {
1271                const StgWord32 hBit = (result & 0x2) >> 1;
1272                // Change instruction to BLX
1273                *word = (*word & ~0xFF000000) | ((0xfa | hBit) << 24);
1274                IF_DEBUG(linker, debugBelch("Changed BL to BLX at %p\n", word));
1275            }
1276            break;
1277        }
1278 
1279        case COMPAT_R_ARM_MOVT_ABS:
1280        case COMPAT_R_ARM_MOVW_ABS_NC:
1281        {
1282            StgWord32 *word = (StgWord32 *)P;
1283            StgWord32 imm12 = *word & 0xfff;
1284            StgWord32 imm4 = (*word >> 16) & 0xf;
1285            StgInt32 offset = imm4 << 12 | imm12;
1286            StgWord32 result = (S + offset) | T;
1287 
1288            if (reloc_type == COMPAT_R_ARM_MOVT_ABS)
1289                result = (result & 0xffff0000) >> 16;
1290 
1291            StgWord32 result12 = result & 0xfff;
1292            StgWord32 result4 = (result >> 12) & 0xf;
1293            *word = (*word & ~0xf0fff) | (result4 << 16) | result12;
1294            break;
1295        }
1296 
1297        case COMPAT_R_ARM_THM_CALL:
1298        case COMPAT_R_ARM_THM_JUMP24:
1299        {
1300            StgWord16 *upper = (StgWord16 *)P;
1301            StgWord16 *lower = (StgWord16 *)(P + 2);
1302 
1303            int overflow;
1304            int to_thm = (*lower >> 12) & 1;
1305            int sign = (*upper >> 10) & 1;
1306            int j1, j2, i1, i2;
1307 
1308            // Decode immediate value
1309            j1 = (*lower >> 13) & 1; i1 = ~(j1 ^ sign) & 1;
1310            j2 = (*lower >> 11) & 1; i2 = ~(j2 ^ sign) & 1;
1311 
1312            StgInt32 A = (sign << 24)
1313                         | (i1 << 23)
1314                         | (i2 << 22)
1315                         | ((*upper & 0x03ff) << 12)
1316                         | ((*lower & 0x07ff) << 1);
1317 
1318             // Sign extend 25 to 32 bits
1319            if (A & 0x01000000)
1320                A -= 0x02000000;
1321 
1322            S = S + A; A = 0;
1323 
1324            offset = ((S + A) | T) - P;
1325            overflow = offset <= (StgWord32)0xff000000
1326                    || offset >= (StgWord32)0x01000000;
1327 
1328            if ((!is_target_thm && ELF_R_TYPE(info) == COMPAT_R_ARM_THM_JUMP24)
1329                || overflow) {
1330                // Generate veneer
1331 
1332                // see [PC bias] above.
1333                int32_t bias = 4;
1334                S += bias;
1335                // set the Thumb indicator to S, the final address should
1336                // carry the correct thumb indicator.
1337                S |= T;
1338                /* try to locate an existing stub for this target */
1339                if(findStub(&oc->sections[target_shndx], (void**)&S, 1)) {
1340                    /* didn't find any. Need to create one */
1341                    if(makeStub(&oc->sections[target_shndx], (void**)&S, 1)) {
1342                        errorBelch("Unable to create veneer for ARM_THM_CALL\n");
1343                        return 0;
1344                    }
1345                }
1346                S -= bias;
1347 
1348                offset = ((S + A) | T) - P;
1349 
1350                sign = offset >> 31;
1351                to_thm = 1;
1352            } else if (!is_target_thm
1353                       && ELF_R_TYPE(info) == COMPAT_R_ARM_THM_CALL) {
1354                offset &= ~0x3;
1355                to_thm = 0;
1356            }
1357 
1358            // Reencode instruction
1359            i1 = ~(offset >> 23) & 1; j1 = sign ^ i1;
1360            i2 = ~(offset >> 22) & 1; j2 = sign ^ i2;
1361            *upper = ( (*upper & 0xf800)
1362                   | (sign << 10)
1363                   | ((offset >> 12) & 0x03ff) );
1364            *lower = ( (*lower & 0xd000)
1365                   | (j1 << 13)
1366                   | (to_thm << 12)
1367                   | (j2 << 11)
1368                   | ((offset >> 1) & 0x07ff) );
1369            break;
1370        }
1371 
1372        case COMPAT_R_ARM_THM_MOVT_ABS:
1373        case COMPAT_R_ARM_THM_MOVW_ABS_NC:
1374        {
1375            StgWord16 *upper = (StgWord16 *)P;
1376            StgWord16 *lower = (StgWord16 *)(P + 2);
1377            StgInt32 offset = ((*upper & 0x000f) << 12)
1378                            | ((*upper & 0x0400) << 1)
1379                            | ((*lower & 0x7000) >> 4)
1380                            | (*lower & 0x00ff);
1381 
1382            offset = (offset ^ 0x8000) - 0x8000; // Sign extend
1383            offset += S;
1384            if (ELF_R_TYPE(info) == COMPAT_R_ARM_THM_MOVW_ABS_NC)
1385                offset |= T;
1386            else if (ELF_R_TYPE(info) == COMPAT_R_ARM_THM_MOVT_ABS)
1387                offset >>= 16;
1388 
1389            *upper = ( (*upper & 0xfbf0)
1390                   | ((offset & 0xf000) >> 12)
1391                   | ((offset & 0x0800) >> 1) );
1392            *lower = ( (*lower & 0x8f00)
1393                   | ((offset & 0x0700) << 4)
1394                   | (offset & 0x00ff) );
1395            break;
1396        }
1397 
1398        case COMPAT_R_ARM_THM_JUMP8:
1399        {
1400            StgWord16 *word = (StgWord16 *)P;
1401            StgWord offset = *word & 0x01fe;
1402            offset += S - P;
1403            if (!is_target_thm) {
1404                errorBelch("%s: Thumb to ARM transition with JUMP8 relocation "
1405                           "not supported\n",
1406                           oc->fileName);
1407                return 0;
1408            }
1409 
1410            *word = (*word & ~0x01fe)
1411                  | (offset & 0x01fe);
1412            break;
1413        }
1414 
1415        case COMPAT_R_ARM_THM_JUMP11:
1416        {
1417            StgWord16 *word = (StgWord16 *)P;
1418            StgWord offset = *word & 0x0ffe;
1419            offset += S - P;
1420            if (!is_target_thm) {
1421                errorBelch("%s: Thumb to ARM transition with JUMP11 relocation "
1422                           "not supported\n",
1423                           oc->fileName);
1424                return 0;
1425            }
1426 
1427            *word = (*word & ~0x0ffe)
1428                  | (offset & 0x0ffe);
1429            break;
1430        }
1431        case COMPAT_R_ARM_GOT_PREL: {
1432               int32_t A = *pP;
1433               void* GOT_S = symbol->got_addr;
1434               ASSERT(GOT_S);
1435               *(uint32_t *)P = (uint32_t) GOT_S + A - P;
1436               break;
1437        }
1438 #        endif // arm_HOST_ARCH
1439 
1440        default:
1441            errorBelch("%s: unhandled ELF relocation(Rel) type %" FMT_Word "\n",
1442                       oc->fileName, (W_)ELF_R_TYPE(info));
1443            return 0;
1444        }
1445 
1446    }
1447    return 1;
1448 }
1449 
1450 /* Do ELF relocations for which explicit addends are supplied.
1451    sparc-solaris relocations appear to be of this form. */
1452 static int
do_Elf_Rela_relocations(ObjectCode * oc,char * ehdrC,Elf_Shdr * shdr,int shnum)1453 do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC,
1454                           Elf_Shdr* shdr, int shnum )
1455 {
1456    int j;
1457    SymbolName* symbol = NULL;
1458    Elf_Rela* rtab = (Elf_Rela*) (ehdrC + shdr[shnum].sh_offset);
1459    Elf_Sym*  stab;
1460    char*     strtab;
1461    int         nent = shdr[shnum].sh_size / sizeof(Elf_Rela);
1462    int symtab_shndx = shdr[shnum].sh_link;
1463    int strtab_shndx = shdr[symtab_shndx].sh_link;
1464    int target_shndx = shdr[shnum].sh_info;
1465 #if defined(SHN_XINDEX)
1466    Elf_Word* shndx_table = get_shndx_table((Elf_Ehdr*)ehdrC);
1467 #endif
1468 #if defined(DEBUG) || defined(sparc_HOST_ARCH) || defined(powerpc_HOST_ARCH) \
1469     || defined(x86_64_HOST_ARCH)
1470    /* This #if def only serves to avoid unused-var warnings. */
1471    Elf_Addr targ = (Elf_Addr) oc->sections[target_shndx].start;
1472 #endif
1473 
1474    stab  = (Elf_Sym*) (ehdrC + shdr[ symtab_shndx ].sh_offset);
1475    strtab= (char*)    (ehdrC + shdr[ strtab_shndx ].sh_offset);
1476 
1477    IF_DEBUG(linker,debugBelch( "relocations for section %d using symtab %d\n",
1478                           target_shndx, symtab_shndx ));
1479 
1480    /* Skip sections that we're not interested in. */
1481    if (oc->sections[target_shndx].kind == SECTIONKIND_OTHER) {
1482            IF_DEBUG(linker,debugBelch( "skipping (target section not loaded)"));
1483            return 1;
1484    }
1485 
1486    for (j = 0; j < nent; j++) {
1487 #if defined(DEBUG) || defined(sparc_HOST_ARCH) || defined(powerpc_HOST_ARCH) \
1488     || defined(x86_64_HOST_ARCH)
1489       /* This #if def only serves to avoid unused-var warnings. */
1490       Elf_Addr  offset = rtab[j].r_offset;
1491       Elf_Addr  P      = targ + offset;
1492       Elf_Addr  A      = rtab[j].r_addend;
1493 #endif
1494 #if defined(sparc_HOST_ARCH) || defined(powerpc_HOST_ARCH) \
1495     || defined(x86_64_HOST_ARCH)
1496       Elf_Addr  value;
1497 #endif
1498       Elf_Addr  info   = rtab[j].r_info;
1499       Elf_Addr  S;
1500       void*     S_tmp;
1501 #     if defined(sparc_HOST_ARCH)
1502       Elf_Word* pP = (Elf_Word*)P;
1503       Elf_Word  w1, w2;
1504 #     elif defined(powerpc_HOST_ARCH)
1505       Elf_Sword delta;
1506 #     endif
1507 
1508       IF_DEBUG(linker,debugBelch( "Rel entry %3d is raw(%6p %6p %6p)   ",
1509                              j, (void*)offset, (void*)info,
1510                                 (void*)A ));
1511       if (!info) {
1512          IF_DEBUG(linker,debugBelch( " ZERO" ));
1513          S = 0;
1514       } else {
1515          Elf_Sym sym = stab[ELF_R_SYM(info)];
1516          /* First see if it is a local symbol. */
1517          if (ELF_ST_BIND(sym.st_info) == STB_LOCAL) {
1518             /* Yes, so we can get the address directly from the ELF symbol
1519                table. */
1520             symbol = sym.st_name==0 ? "(noname)" : strtab+sym.st_name;
1521             /* See Note [Many ELF Sections] */
1522             Elf_Word secno = sym.st_shndx;
1523 #if defined(SHN_XINDEX)
1524             if (secno == SHN_XINDEX) {
1525               secno = shndx_table[ELF_R_SYM(info)];
1526             }
1527 #endif
1528             S = (Elf_Addr)oc->sections[secno].start
1529                 + stab[ELF_R_SYM(info)].st_value;
1530          } else {
1531             /* No, so look up the name in our global table. */
1532             symbol = strtab + sym.st_name;
1533             S_tmp = lookupDependentSymbol( symbol, oc );
1534             S = (Elf_Addr)S_tmp;
1535          }
1536          if (!S) {
1537            errorBelch("%s: unknown symbol `%s'", oc->fileName, symbol);
1538            return 0;
1539          }
1540          IF_DEBUG(linker,debugBelch("`%s' resolves to %p\n", symbol, (void*)S));
1541       }
1542 
1543 #if defined(DEBUG) || defined(sparc_HOST_ARCH) || defined(powerpc_HOST_ARCH) \
1544     || defined(x86_64_HOST_ARCH)
1545       IF_DEBUG(linker,debugBelch("Reloc: P = %p   S = %p   A = %p\n",
1546                                         (void*)P, (void*)S, (void*)A ));
1547       checkProddableBlock(oc, (void*)P, sizeof(Elf_Word));
1548 #endif
1549 
1550 #if defined(sparc_HOST_ARCH) || defined(powerpc_HOST_ARCH) \
1551     || defined(x86_64_HOST_ARCH)
1552       value = S + A;
1553 #endif
1554 
1555       switch (ELF_R_TYPE(info)) {
1556 #        if defined(sparc_HOST_ARCH)
1557          case R_SPARC_WDISP30:
1558             w1 = *pP & 0xC0000000;
1559             w2 = (Elf_Word)((value - P) >> 2);
1560             ASSERT((w2 & 0xC0000000) == 0);
1561             w1 |= w2;
1562             *pP = w1;
1563             break;
1564          case R_SPARC_HI22:
1565             w1 = *pP & 0xFFC00000;
1566             w2 = (Elf_Word)(value >> 10);
1567             ASSERT((w2 & 0xFFC00000) == 0);
1568             w1 |= w2;
1569             *pP = w1;
1570             break;
1571          case R_SPARC_LO10:
1572             w1 = *pP & ~0x3FF;
1573             w2 = (Elf_Word)(value & 0x3FF);
1574             ASSERT((w2 & ~0x3FF) == 0);
1575             w1 |= w2;
1576             *pP = w1;
1577             break;
1578 
1579          /* According to the Sun documentation:
1580             R_SPARC_UA32
1581             This relocation type resembles R_SPARC_32, except it refers to an
1582             unaligned word. That is, the word to be relocated must be treated
1583             as four separate bytes with arbitrary alignment, not as a word
1584             aligned according to the architecture requirements.
1585          */
1586          case R_SPARC_UA32:
1587             w2  = (Elf_Word)value;
1588 
1589             // SPARC doesn't do misaligned writes of 32 bit words,
1590             //       so we have to do this one byte-at-a-time.
1591             char *pPc   = (char*)pP;
1592             pPc[0]      = (char) ((Elf_Word)(w2 & 0xff000000) >> 24);
1593             pPc[1]      = (char) ((Elf_Word)(w2 & 0x00ff0000) >> 16);
1594             pPc[2]      = (char) ((Elf_Word)(w2 & 0x0000ff00) >> 8);
1595             pPc[3]      = (char) ((Elf_Word)(w2 & 0x000000ff));
1596             break;
1597 
1598          case R_SPARC_32:
1599             w2 = (Elf_Word)value;
1600             *pP = w2;
1601             break;
1602 #        elif defined(powerpc_HOST_ARCH)
1603          case R_PPC_ADDR16_LO:
1604             *(Elf32_Half*) P = value;
1605             break;
1606 
1607          case R_PPC_ADDR16_HI:
1608             *(Elf32_Half*) P = value >> 16;
1609             break;
1610 
1611          case R_PPC_ADDR16_HA:
1612             *(Elf32_Half*) P = (value + 0x8000) >> 16;
1613             break;
1614 
1615          case R_PPC_ADDR32:
1616             *(Elf32_Word *) P = value;
1617             break;
1618 
1619          case R_PPC_REL32:
1620             *(Elf32_Word *) P = value - P;
1621             break;
1622 
1623          case R_PPC_PLTREL24:
1624             value -= 0x8000; /* See Note [.LCTOC1 in PPC PIC code] */
1625             FALLTHROUGH;
1626          case R_PPC_REL24:
1627             delta = value - P;
1628 
1629             if( delta << 6 >> 6 != delta )
1630             {
1631                value = (Elf_Addr)(&makeSymbolExtra( oc, ELF_R_SYM(info), value )
1632                                         ->jumpIsland);
1633                delta = value - P;
1634 
1635                if( value == 0 || delta << 6 >> 6 != delta )
1636                {
1637                   barf( "Unable to make SymbolExtra for #%d",
1638                         ELF_R_SYM(info) );
1639                   return 0;
1640                }
1641             }
1642 
1643             *(Elf_Word *) P = (*(Elf_Word *) P & 0xfc000003)
1644                                           | (delta & 0x3fffffc);
1645             break;
1646 
1647          case R_PPC_REL16_LO:
1648             *(Elf32_Half*) P = value - P;
1649             break;
1650 
1651          case R_PPC_REL16_HI:
1652             *(Elf32_Half*) P = (value - P) >> 16;
1653             break;
1654 
1655          case R_PPC_REL16_HA:
1656             *(Elf32_Half*) P = (value + 0x8000 - P) >> 16;
1657             break;
1658 #        endif
1659 
1660 #if defined(x86_64_HOST_ARCH)
1661       case COMPAT_R_X86_64_NONE:
1662           break;
1663 
1664       case COMPAT_R_X86_64_64:
1665       {
1666           Elf64_Xword payload = value;
1667           memcpy((void*)P, &payload, sizeof(payload));
1668           break;
1669       }
1670 
1671       case COMPAT_R_X86_64_PC32:
1672       {
1673           StgInt64 off = value - P;
1674           if (off != (Elf64_Sword)off && X86_64_ELF_NONPIC_HACK) {
1675               StgInt64 pltAddress =
1676                   (StgInt64) &makeSymbolExtra(oc, ELF_R_SYM(info), S)
1677                                             -> jumpIsland;
1678               off = pltAddress + A - P;
1679           }
1680           if (off != (Elf64_Sword)off) {
1681               errorBelch(
1682                   "R_X86_64_PC32 relocation out of range: %s = %" PRIx64
1683                   "\nRecompile %s with -fPIC -fexternal-dynamic-refs.",
1684                   symbol, off, oc->fileName);
1685               return 0;
1686           }
1687           Elf64_Sword payload = off;
1688           memcpy((void*)P, &payload, sizeof(payload));
1689           break;
1690       }
1691 
1692       case COMPAT_R_X86_64_PC64:
1693       {
1694           Elf64_Sxword payload = value - P;
1695           memcpy((void*)P, &payload, sizeof(payload));
1696           break;
1697       }
1698 
1699       case COMPAT_R_X86_64_32:
1700       {
1701           if (value != (Elf64_Word)value && X86_64_ELF_NONPIC_HACK) {
1702               StgInt64 pltAddress =
1703                   (StgInt64) &makeSymbolExtra(oc, ELF_R_SYM(info), S)
1704                                             -> jumpIsland;
1705               value = pltAddress + A;
1706           }
1707           if (value != (Elf64_Word)value) {
1708               errorBelch(
1709                   "R_X86_64_32 relocation out of range: %s = %" PRIx64
1710                   "\nRecompile %s with -fPIC -fexternal-dynamic-refs.",
1711                   symbol, value, oc->fileName);
1712               return 0;
1713           }
1714           Elf64_Word payload = value;
1715           memcpy((void*)P, &payload, sizeof(payload));
1716           break;
1717       }
1718 
1719       case COMPAT_R_X86_64_32S:
1720       {
1721           if ((StgInt64)value != (Elf64_Sword)value && X86_64_ELF_NONPIC_HACK) {
1722               StgInt64 pltAddress =
1723                   (StgInt64) &makeSymbolExtra(oc, ELF_R_SYM(info), S)
1724                                             -> jumpIsland;
1725               value = pltAddress + A;
1726           }
1727           if ((StgInt64)value != (Elf64_Sword)value) {
1728               errorBelch(
1729                   "R_X86_64_32S relocation out of range: %s = %" PRIx64
1730                   "\nRecompile %s with -fPIC -fexternal-dynamic-refs.",
1731                   symbol, value, oc->fileName);
1732               return 0;
1733           }
1734           Elf64_Sword payload = value;
1735           memcpy((void*)P, &payload, sizeof(payload));
1736           break;
1737       }
1738       case COMPAT_R_X86_64_REX_GOTPCRELX:
1739       case COMPAT_R_X86_64_GOTPCRELX:
1740       case COMPAT_R_X86_64_GOTPCREL:
1741       {
1742           StgInt64 gotAddress = (StgInt64) &makeSymbolExtra(oc, ELF_R_SYM(info), S)->addr;
1743           StgInt64 off = gotAddress + A - P;
1744           if (off != (Elf64_Sword)off) {
1745               barf(
1746                   "COMPAT_R_X86_64_GOTPCREL relocation out of range: "
1747                   "%s = %" PRIx64 " in %s.",
1748                   symbol, off, oc->fileName);
1749           }
1750           Elf64_Sword payload = off;
1751           memcpy((void*)P, &payload, sizeof(payload));
1752           break;
1753       }
1754 #if defined(dragonfly_HOST_OS)
1755       case COMPAT_R_X86_64_GOTTPOFF:
1756       {
1757         /* determine the offset of S to the current thread's tls
1758            area
1759            XXX: Move this to the beginning of function */
1760           struct tls_info ti;
1761           get_tls_area(0, &ti, sizeof(ti));
1762           /* make entry in GOT that contains said offset */
1763           StgInt64 gotEntry = (StgInt64) &makeSymbolExtra(oc, ELF_R_SYM(info),
1764                                          (S - (Elf64_Addr)(ti.base)))->addr;
1765           StgInt64 off = gotEntry + A - P;
1766           if (off != (Elf64_Sword)off) {
1767               barf(
1768                   "COMPAT_R_X86_64_GOTTPOFF relocation out of range: "
1769                   "%s = %" PRIx64 " in %s.",
1770                   symbol, off, oc->fileName);
1771           }
1772           Elf64_Sword payload = off;
1773           memcpy((void*)P, &payload, sizeof(payload));
1774           break;
1775       }
1776 #endif
1777 
1778       case COMPAT_R_X86_64_PLT32:
1779       {
1780           StgInt64 off = value - P;
1781           if (off != (Elf64_Sword)off) {
1782               StgInt64 pltAddress = (StgInt64) &makeSymbolExtra(oc, ELF_R_SYM(info), S)
1783                                                     -> jumpIsland;
1784               off = pltAddress + A - P;
1785           }
1786           if (off != (Elf64_Sword)off) {
1787               barf(
1788                   "R_X86_64_PLT32 relocation out of range: "
1789                   "%s = %" PRIx64 " in %s.",
1790                   symbol, off, oc->fileName);
1791           }
1792           Elf64_Sword payload = off;
1793           memcpy((void*)P, &payload, sizeof(payload));
1794           break;
1795       }
1796 #endif
1797 
1798          default:
1799             barf("%s: unhandled ELF relocation(RelA) type %" FMT_Word "\n",
1800                   oc->fileName, (W_)ELF_R_TYPE(info));
1801             return 0;
1802       }
1803 
1804    }
1805    return 1;
1806 }
1807 #endif /* !aarch64_HOST_ARCH */
1808 
1809 
1810 static bool
ocMprotect_Elf(ObjectCode * oc)1811 ocMprotect_Elf( ObjectCode *oc )
1812 {
1813     for(int i=0; i < oc->n_sections; i++) {
1814         Section *section = &oc->sections[i];
1815         if(section->size == 0) continue;
1816         switch (section->kind) {
1817         case SECTIONKIND_CODE_OR_RODATA:
1818             if (section->alloc != SECTION_M32) {
1819                 // N.B. m32 handles protection of its allocations during
1820                 // flushing.
1821                 mmapForLinkerMarkExecutable(section->mapped_start, section->mapped_size);
1822             }
1823             break;
1824         default:
1825             break;
1826         }
1827     }
1828 
1829     return true;
1830 }
1831 
1832 int
ocResolve_ELF(ObjectCode * oc)1833 ocResolve_ELF ( ObjectCode* oc )
1834 {
1835    char*     ehdrC = (char*)(oc->image);
1836    Elf_Ehdr* ehdr  = (Elf_Ehdr*) ehdrC;
1837    Elf_Shdr* shdr  = (Elf_Shdr*) (ehdrC + ehdr->e_shoff);
1838    const Elf_Word shnum = elf_shnum(ehdr);
1839 
1840 #if defined(SHN_XINDEX)
1841     Elf_Word* shndxTable = get_shndx_table(ehdr);
1842 #endif
1843 
1844     /* resolve section symbols
1845      * these are special symbols that point to sections, and have no name.
1846      * Usually there should be one symbol for each text and data section.
1847      *
1848      * We need to resolve (assign addresses) to them, to be able to use them
1849      * during relocation.
1850      */
1851     for(ElfSymbolTable *symTab = oc->info->symbolTables;
1852         symTab != NULL; symTab = symTab->next) {
1853         for (size_t i = 0; i < symTab->n_symbols; i++) {
1854             ElfSymbol *symbol = &symTab->symbols[i];
1855             if(STT_SECTION == ELF_ST_TYPE(symbol->elf_sym->st_info)) {
1856                 /* NOTE: We assume that oc->sections corresponds to the
1857                  *       sections in the object file.  This is currently true,
1858                  *       and will stay true, unless we start to compress
1859                  *       oc->sections by not having an entry for sections we
1860                  *       are not interested in.
1861                  */
1862 
1863 
1864                 /* See Note [Many ELF Sections] */
1865                 /* Note that future checks for special SHN_* numbers should
1866                  * check the shndx variable, not the section number in secno.
1867                  * Sections with the real number in the SHN_LORESERVE..HIRESERVE
1868                  * range will have shndx SHN_XINDEX and a secno with one of the
1869                  * reserved values.
1870                  */
1871                 Elf_Word secno = symbol->elf_sym->st_shndx;
1872 #if defined(SHN_XINDEX)
1873                 if (secno == SHN_XINDEX) {
1874                     ASSERT(shndxTable);
1875                     secno = shndxTable[i];
1876                 }
1877 #endif
1878                 ASSERT(symbol->elf_sym->st_name == 0);
1879                 ASSERT(symbol->elf_sym->st_value == 0);
1880                 ASSERT(0x0 != oc->sections[ secno ].start);
1881                 symbol->addr = oc->sections[ secno ].start;
1882             }
1883         }
1884     }
1885 
1886 #if defined(NEED_GOT)
1887     if(fillGot( oc ))
1888         return 0;
1889     /* silence warnings */
1890     (void) shnum;
1891     (void) shdr;
1892 #endif /* NEED_GOT */
1893 
1894 #if defined(aarch64_HOST_ARCH)
1895     /* use new relocation design */
1896     if(relocateObjectCode( oc ))
1897         return 0;
1898 #else
1899     /* Process the relocation sections. */
1900     for (Elf_Word i = 0; i < shnum; i++) {
1901         if (shdr[i].sh_type == SHT_REL) {
1902           bool ok = do_Elf_Rel_relocations ( oc, ehdrC, shdr, i );
1903           if (!ok)
1904               return ok;
1905         }
1906         else
1907         if (shdr[i].sh_type == SHT_RELA) {
1908           bool ok = do_Elf_Rela_relocations ( oc, ehdrC, shdr, i );
1909           if (!ok)
1910               return ok;
1911         }
1912     }
1913 #endif
1914 
1915 #if defined(powerpc_HOST_ARCH)
1916     ocFlushInstructionCache( oc );
1917 #endif
1918 
1919     return ocMprotect_Elf(oc);
1920 }
1921 
ocRunInit_ELF(ObjectCode * oc)1922 int ocRunInit_ELF( ObjectCode *oc )
1923 {
1924    Elf_Word i;
1925    char*     ehdrC = (char*)(oc->image);
1926    Elf_Ehdr* ehdr  = (Elf_Ehdr*) ehdrC;
1927    Elf_Shdr* shdr  = (Elf_Shdr*) (ehdrC + ehdr->e_shoff);
1928    char* sh_strtab = ehdrC + shdr[elf_shstrndx(ehdr)].sh_offset;
1929    int argc, envc;
1930    char **argv, **envv;
1931 
1932    getProgArgv(&argc, &argv);
1933    getProgEnvv(&envc, &envv);
1934 
1935    // XXX Apparently in some archs .init may be something
1936    // special!  See DL_DT_INIT_ADDRESS macro in glibc
1937    // as well as ELF_FUNCTION_PTR_IS_SPECIAL.  We've not handled
1938    // it here, please file a bug report if it affects you.
1939    for (i = 0; i < elf_shnum(ehdr); i++) {
1940       init_t *init_start, *init_end, *init;
1941       int is_bss = false;
1942       SectionKind kind = getSectionKind_ELF(&shdr[i], &is_bss);
1943       if (kind == SECTIONKIND_CODE_OR_RODATA
1944        && 0 == memcmp(".init", sh_strtab + shdr[i].sh_name, 5)) {
1945           init_t init_f = (init_t)(oc->sections[i].start);
1946           init_f(argc, argv, envv);
1947       }
1948 
1949       if (kind == SECTIONKIND_INIT_ARRAY) {
1950           char *init_startC = oc->sections[i].start;
1951          init_start = (init_t*)init_startC;
1952          init_end = (init_t*)(init_startC + shdr[i].sh_size);
1953          for (init = init_start; init < init_end; init++) {
1954             ASSERT(0x0 != *init);
1955             (*init)(argc, argv, envv);
1956          }
1957       }
1958 
1959       // XXX could be more strict and assert that it's
1960       // SECTIONKIND_RWDATA; but allowing RODATA seems harmless enough.
1961       if ((kind == SECTIONKIND_RWDATA || kind == SECTIONKIND_CODE_OR_RODATA)
1962        && 0 == memcmp(".ctors", sh_strtab + shdr[i].sh_name, 6)) {
1963           char *init_startC = oc->sections[i].start;
1964          init_start = (init_t*)init_startC;
1965          init_end = (init_t*)(init_startC + shdr[i].sh_size);
1966          // ctors run in reverse
1967          for (init = init_end - 1; init >= init_start; init--) {
1968             (*init)(argc, argv, envv);
1969          }
1970       }
1971    }
1972 
1973    freeProgEnvv(envc, envv);
1974    return 1;
1975 }
1976 
1977 /*
1978  * PowerPC & X86_64 ELF specifics
1979  */
1980 
1981 #if defined(NEED_SYMBOL_EXTRAS)
1982 
ocAllocateExtras_ELF(ObjectCode * oc)1983 int ocAllocateExtras_ELF( ObjectCode *oc )
1984 {
1985   Elf_Ehdr *ehdr = (Elf_Ehdr *) oc->image;
1986   Elf_Shdr* shdr = (Elf_Shdr *) ( ((char *)oc->image) + ehdr->e_shoff );
1987   Elf_Shdr* symtab = NULL;
1988   Elf_Word shnum = elf_shnum(ehdr);
1989   int bssSize = 0;
1990 
1991   for (Elf_Word i = 0; i < shnum; ++i) {
1992     if(shdr[i].sh_type == SHT_SYMTAB) {
1993       symtab = &shdr[i];
1994     } else {
1995       int isBss = 0;
1996       getSectionKind_ELF(&shdr[i], &isBss);
1997       if (isBss && shdr[i].sh_size > 0) {
1998         bssSize += roundUpToAlign(shdr[i].sh_size, shdr[i].sh_addralign);
1999       }
2000     }
2001   }
2002 
2003   if (symtab == NULL)
2004   {
2005     // Not having a symbol table is not in principle a problem.
2006     // When an object file has no symbols then the 'strip' program
2007     // typically will remove the symbol table entirely.
2008     IF_DEBUG(linker, debugBelch( "The ELF file %s contains no symtab\n",
2009              oc->archiveMemberName ? oc->archiveMemberName : oc->fileName ));
2010     return 1;
2011   }
2012 
2013   if( symtab->sh_entsize != sizeof( Elf_Sym ) )
2014   {
2015     errorBelch( "The entry size (%d) of the symtab isn't %d\n",
2016       (int) symtab->sh_entsize, (int) sizeof( Elf_Sym ) );
2017 
2018     return 0;
2019   }
2020 
2021   return ocAllocateExtras(oc, symtab->sh_size / sizeof( Elf_Sym ), 0, bssSize);
2022 }
2023 
2024 #endif /* NEED_SYMBOL_EXTRAS */
2025 
2026 #endif /* elf */
2027