~ubuntu-branches/ubuntu/oneiric/ghc/oneiric

« back to all changes in this revision

Viewing changes to debian/patches/linker-partially-stripped-objects

  • Committer: Bazaar Package Importer
  • Author(s): Iain Lane
  • Date: 2011-08-10 11:50:56 UTC
  • Revision ID: james.westby@ubuntu.com-20110810115056-10omvh0gszquj5cn
Tags: 7.0.3-1ubuntu3
Cherry-pick upstream commit cfbf0eb to support partially stripped object
files in the GHCi linker. Fixes loading the ghc package in GHCi and
associated compilation failures. Patch by Duncan Coutts
<duncan@well-typed.com>. (LP: #820847)

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
commit cfbf0eb134efd1c5d9a589f6ae2139d7fad60581
 
2
Author: Duncan Coutts <duncan@well-typed.com>
 
3
Date:   Thu May 12 16:25:41 2011 +0100
 
4
 
 
5
    Make the GHCi linker handle partially stripped object files (#5004)
 
6
 
 
7
    When you use 'strip --strip-unneeded' on a ELF format .o or .a file, if
 
8
    the object file has no global/exported symbols then 'strip' ends up
 
9
    removing the symbol table entirely. Previously the GHCi linker assumed
 
10
    there would always be exactly one symbol table and exactly one string
 
11
    table. In fact, in ELF object files there is no such limitation, instead
 
12
    each section points to the other sections it needs, in particular
 
13
    relocation sections have a link to the symbol table section they use and
 
14
    symbol table sections have a link to the corresponding string table.
 
15
    So instead of assuming there will always be a global symbol and string
 
16
    table, all we have to do is validate and follow these links. Then, when
 
17
    we encounter an empty object file that has no symbols then we handle it
 
18
    correctly, because since it's empty we never process any relocations and
 
19
    so never have to follow any links to non-existant symbol tables.
 
20
 
 
21
    Also, in the case where an object is fully stripped, we can now detect
 
22
    this more reliably and emit a more helpful error message, e.g:
 
23
 
 
24
    libHSghc-7.1.20110509.a(DsMeta.o): relocation section #2 has no symbol table
 
25
    This object file has probably been fully striped. Such files cannot be linked.
 
26
 
 
27
Index: ghc-7.0.3/rts/Linker.c
 
28
===================================================================
 
29
--- ghc-7.0.3.orig/rts/Linker.c 2011-08-10 11:49:12.285949093 +0100
 
30
+++ ghc-7.0.3/rts/Linker.c      2011-08-10 11:48:59.658456201 +0100
 
31
@@ -2208,6 +2208,7 @@
 
32
             //  stgFree(oc->image);
 
33
             // #endif
 
34
             stgFree(oc->fileName);
 
35
+            stgFree(oc->archiveMemberName);
 
36
             stgFree(oc->symbols);
 
37
             stgFree(oc->sections);
 
38
             stgFree(oc);
 
39
@@ -3540,31 +3541,6 @@
 
40
  * Generic ELF functions
 
41
  */
 
42
 
 
43
-static char *
 
44
-findElfSection ( void* objImage, Elf_Word sh_type )
 
45
-{
 
46
-   char* ehdrC = (char*)objImage;
 
47
-   Elf_Ehdr* ehdr = (Elf_Ehdr*)ehdrC;
 
48
-   Elf_Shdr* shdr = (Elf_Shdr*)(ehdrC + ehdr->e_shoff);
 
49
-   char* sh_strtab = ehdrC + shdr[ehdr->e_shstrndx].sh_offset;
 
50
-   char* ptr = NULL;
 
51
-   int i;
 
52
-
 
53
-   for (i = 0; i < ehdr->e_shnum; i++) {
 
54
-      if (shdr[i].sh_type == sh_type
 
55
-          /* Ignore the section header's string table. */
 
56
-          && i != ehdr->e_shstrndx
 
57
-          /* Ignore string tables named .stabstr, as they contain
 
58
-             debugging info. */
 
59
-          && 0 != memcmp(".stabstr", sh_strtab + shdr[i].sh_name, 8)
 
60
-         ) {
 
61
-         ptr = ehdrC + shdr[i].sh_offset;
 
62
-         break;
 
63
-      }
 
64
-   }
 
65
-   return ptr;
 
66
-}
 
67
-
 
68
 static int
 
69
 ocVerifyImage_ELF ( ObjectCode* oc )
 
70
 {
 
71
@@ -3572,7 +3548,6 @@
 
72
    Elf_Sym*  stab;
 
73
    int i, j, nent, nstrtab, nsymtabs;
 
74
    char* sh_strtab;
 
75
-   char* strtab;
 
76
 
 
77
    char*     ehdrC = (char*)(oc->image);
 
78
    Elf_Ehdr* ehdr  = (Elf_Ehdr*)ehdrC;
 
79
@@ -3654,20 +3629,64 @@
 
80
                ehdrC + shdr[i].sh_offset,
 
81
                       ehdrC + shdr[i].sh_offset + shdr[i].sh_size - 1));
 
82
 
 
83
-      if (shdr[i].sh_type == SHT_REL) {
 
84
-          IF_DEBUG(linker,debugBelch("Rel  " ));
 
85
-      } else if (shdr[i].sh_type == SHT_RELA) {
 
86
-          IF_DEBUG(linker,debugBelch("RelA " ));
 
87
-      } else {
 
88
-          IF_DEBUG(linker,debugBelch("     "));
 
89
+#define SECTION_INDEX_VALID(ndx) (ndx > SHN_UNDEF && ndx < ehdr->e_shnum)
 
90
+
 
91
+      switch (shdr[i].sh_type) {
 
92
+
 
93
+        case SHT_REL:
 
94
+        case SHT_RELA:
 
95
+          IF_DEBUG(linker,debugBelch( shdr[i].sh_type == SHT_REL ? "Rel  " : "RelA "));
 
96
+
 
97
+          if (!SECTION_INDEX_VALID(shdr[i].sh_link)) {
 
98
+            if (shdr[i].sh_link == SHN_UNDEF)
 
99
+              errorBelch("\n%s: relocation section #%d has no symbol table\n"
 
100
+                         "This object file has probably been fully striped. "
 
101
+                         "Such files cannot be linked.\n",
 
102
+                         oc->archiveMemberName ? oc->archiveMemberName : oc->fileName, i);
 
103
+            else
 
104
+              errorBelch("\n%s: relocation section #%d has an invalid link field (%d)\n",
 
105
+                         oc->archiveMemberName ? oc->archiveMemberName : oc->fileName,
 
106
+                         i, shdr[i].sh_link);
 
107
+            return 0;
 
108
+          }
 
109
+          if (shdr[shdr[i].sh_link].sh_type != SHT_SYMTAB) {
 
110
+            errorBelch("\n%s: relocation section #%d does not link to a symbol table\n",
 
111
+                       oc->archiveMemberName ? oc->archiveMemberName : oc->fileName, i);
 
112
+            return 0;
 
113
+          }
 
114
+          if (!SECTION_INDEX_VALID(shdr[i].sh_info)) {
 
115
+            errorBelch("\n%s: relocation section #%d has an invalid info field (%d)\n",
 
116
+                       oc->archiveMemberName ? oc->archiveMemberName : oc->fileName,
 
117
+                       i, shdr[i].sh_info);
 
118
+            return 0;
 
119
+          }
 
120
+
 
121
+          break;
 
122
+        case SHT_SYMTAB:
 
123
+          IF_DEBUG(linker,debugBelch("Sym  "));
 
124
+
 
125
+          if (!SECTION_INDEX_VALID(shdr[i].sh_link)) {
 
126
+            errorBelch("\n%s: symbol table section #%d has an invalid link field (%d)\n",
 
127
+                       oc->archiveMemberName ? oc->archiveMemberName : oc->fileName,
 
128
+                       i, shdr[i].sh_link);
 
129
+            return 0;
 
130
+          }
 
131
+          if (shdr[shdr[i].sh_link].sh_type != SHT_STRTAB) {
 
132
+            errorBelch("\n%s: symbol table section #%d does not link to a string table\n",
 
133
+                       oc->archiveMemberName ? oc->archiveMemberName : oc->fileName, i);
 
134
+
 
135
+            return 0;
 
136
+          }
 
137
+          break;
 
138
+        case SHT_STRTAB: IF_DEBUG(linker,debugBelch("Str  ")); break;
 
139
+        default:         IF_DEBUG(linker,debugBelch("     ")); break;
 
140
       }
 
141
       if (sh_strtab) {
 
142
           IF_DEBUG(linker,debugBelch("sname=%s\n", sh_strtab + shdr[i].sh_name ));
 
143
       }
 
144
    }
 
145
 
 
146
-   IF_DEBUG(linker,debugBelch( "\nString tables" ));
 
147
-   strtab = NULL;
 
148
+   IF_DEBUG(linker,debugBelch( "\nString tables\n" ));
 
149
    nstrtab = 0;
 
150
    for (i = 0; i < ehdr->e_shnum; i++) {
 
151
       if (shdr[i].sh_type == SHT_STRTAB
 
152
@@ -3677,18 +3696,16 @@
 
153
              debugging info. */
 
154
           && 0 != memcmp(".stabstr", sh_strtab + shdr[i].sh_name, 8)
 
155
          ) {
 
156
-         IF_DEBUG(linker,debugBelch("   section %d is a normal string table", i ));
 
157
-         strtab = ehdrC + shdr[i].sh_offset;
 
158
+         IF_DEBUG(linker,debugBelch("   section %d is a normal string table\n", i ));
 
159
          nstrtab++;
 
160
       }
 
161
    }
 
162
-   if (nstrtab != 1) {
 
163
-      errorBelch("%s: no string tables, or too many", oc->fileName);
 
164
-      return 0;
 
165
+   if (nstrtab == 0) {
 
166
+      IF_DEBUG(linker,debugBelch("   no normal string tables (potentially, but not necessarily a problem)\n"));
 
167
    }
 
168
 
 
169
    nsymtabs = 0;
 
170
-   IF_DEBUG(linker,debugBelch( "\nSymbol tables" ));
 
171
+   IF_DEBUG(linker,debugBelch( "Symbol tables\n" ));
 
172
    for (i = 0; i < ehdr->e_shnum; i++) {
 
173
       if (shdr[i].sh_type != SHT_SYMTAB) continue;
 
174
       IF_DEBUG(linker,debugBelch( "section %d is a symbol table\n", i ));
 
175
@@ -3730,13 +3747,17 @@
 
176
          }
 
177
          IF_DEBUG(linker,debugBelch("  " ));
 
178
 
 
179
-         IF_DEBUG(linker,debugBelch("name=%s\n", strtab + stab[j].st_name ));
 
180
+         IF_DEBUG(linker,debugBelch("name=%s\n",
 
181
+                        ehdrC + shdr[shdr[i].sh_link].sh_offset
 
182
+                              + stab[j].st_name ));
 
183
       }
 
184
    }
 
185
 
 
186
    if (nsymtabs == 0) {
 
187
-      errorBelch("%s: didn't find any symbol tables", oc->fileName);
 
188
-      return 0;
 
189
+     // Not having a symbol table is not in principle a problem.
 
190
+     // When an object file has no symbols then the 'strip' program
 
191
+     // typically will remove the symbol table entirely.
 
192
+     IF_DEBUG(linker,debugBelch("   no symbol tables (potentially, but not necessarily a problem)\n"));
 
193
    }
 
194
 
 
195
    return 1;
 
196
@@ -3783,16 +3804,11 @@
 
197
 
 
198
    char*     ehdrC    = (char*)(oc->image);
 
199
    Elf_Ehdr* ehdr     = (Elf_Ehdr*)ehdrC;
 
200
-   char*     strtab   = findElfSection ( ehdrC, SHT_STRTAB );
 
201
+   char*     strtab;
 
202
    Elf_Shdr* shdr     = (Elf_Shdr*) (ehdrC + ehdr->e_shoff);
 
203
 
 
204
    ASSERT(symhash != NULL);
 
205
 
 
206
-   if (!strtab) {
 
207
-      errorBelch("%s: no strtab", oc->fileName);
 
208
-      return 0;
 
209
-   }
 
210
-
 
211
    k = 0;
 
212
    for (i = 0; i < ehdr->e_shnum; i++) {
 
213
       /* Figure out what kind of section it is.  Logic derived from
 
214
@@ -3825,12 +3841,16 @@
 
215
 
 
216
       /* copy stuff into this module's object symbol table */
 
217
       stab = (Elf_Sym*) (ehdrC + shdr[i].sh_offset);
 
218
+      strtab = ehdrC + shdr[shdr[i].sh_link].sh_offset;
 
219
       nent = shdr[i].sh_size / sizeof(Elf_Sym);
 
220
 
 
221
       oc->n_symbols = nent;
 
222
       oc->symbols = stgMallocBytes(oc->n_symbols * sizeof(char*),
 
223
                                    "ocGetNames_ELF(oc->symbols)");
 
224
 
 
225
+      //TODO: we ignore local symbols anyway right? So we can use the
 
226
+      //      shdr[i].sh_info to get the index of the first non-local symbol
 
227
+      // ie we should use j = shdr[i].sh_info
 
228
       for (j = 0; j < nent; j++) {
 
229
 
 
230
          char  isLocal = FALSE; /* avoids uninit-var warning */
 
231
@@ -3928,21 +3948,24 @@
 
232
    relocations appear to be of this form. */
 
233
 static int
 
234
 do_Elf_Rel_relocations ( ObjectCode* oc, char* ehdrC,
 
235
-                         Elf_Shdr* shdr, int shnum,
 
236
-                         Elf_Sym*  stab, char* strtab )
 
237
+                         Elf_Shdr* shdr, int shnum )
 
238
 {
 
239
    int j;
 
240
    char *symbol;
 
241
    Elf_Word* targ;
 
242
    Elf_Rel*  rtab = (Elf_Rel*) (ehdrC + shdr[shnum].sh_offset);
 
243
+   Elf_Sym*  stab;
 
244
+   char*     strtab;
 
245
    int         nent = shdr[shnum].sh_size / sizeof(Elf_Rel);
 
246
    int target_shndx = shdr[shnum].sh_info;
 
247
    int symtab_shndx = shdr[shnum].sh_link;
 
248
+   int strtab_shndx = shdr[symtab_shndx].sh_link;
 
249
 
 
250
    stab  = (Elf_Sym*) (ehdrC + shdr[ symtab_shndx ].sh_offset);
 
251
+   strtab= (char*)    (ehdrC + shdr[ strtab_shndx ].sh_offset);
 
252
    targ  = (Elf_Word*)(ehdrC + shdr[ target_shndx ].sh_offset);
 
253
-   IF_DEBUG(linker,debugBelch( "relocations for section %d using symtab %d\n",
 
254
-                          target_shndx, symtab_shndx ));
 
255
+   IF_DEBUG(linker,debugBelch( "relocations for section %d using symtab %d and strtab %d\n",
 
256
+                          target_shndx, symtab_shndx, strtab_shndx ));
 
257
 
 
258
    /* Skip sections that we're not interested in. */
 
259
    {
 
260
@@ -4028,18 +4051,21 @@
 
261
    sparc-solaris relocations appear to be of this form. */
 
262
 static int
 
263
 do_Elf_Rela_relocations ( ObjectCode* oc, char* ehdrC,
 
264
-                          Elf_Shdr* shdr, int shnum,
 
265
-                          Elf_Sym*  stab, char* strtab )
 
266
+                          Elf_Shdr* shdr, int shnum )
 
267
 {
 
268
    int j;
 
269
    char *symbol = NULL;
 
270
    Elf_Addr targ;
 
271
    Elf_Rela* rtab = (Elf_Rela*) (ehdrC + shdr[shnum].sh_offset);
 
272
+   Elf_Sym*  stab;
 
273
+   char*     strtab;
 
274
    int         nent = shdr[shnum].sh_size / sizeof(Elf_Rela);
 
275
    int target_shndx = shdr[shnum].sh_info;
 
276
    int symtab_shndx = shdr[shnum].sh_link;
 
277
+   int strtab_shndx = shdr[symtab_shndx].sh_link;
 
278
 
 
279
    stab  = (Elf_Sym*) (ehdrC + shdr[ symtab_shndx ].sh_offset);
 
280
+   strtab= (char*)    (ehdrC + shdr[ strtab_shndx ].sh_offset);
 
281
    targ  = (Elf_Addr) (ehdrC + shdr[ target_shndx ].sh_offset);
 
282
    IF_DEBUG(linker,debugBelch( "relocations for section %d using symtab %d\n",
 
283
                           target_shndx, symtab_shndx ));
 
284
@@ -4308,35 +4334,20 @@
 
285
 static int
 
286
 ocResolve_ELF ( ObjectCode* oc )
 
287
 {
 
288
-   char *strtab;
 
289
    int   shnum, ok;
 
290
-   Elf_Sym*  stab  = NULL;
 
291
    char*     ehdrC = (char*)(oc->image);
 
292
    Elf_Ehdr* ehdr  = (Elf_Ehdr*) ehdrC;
 
293
    Elf_Shdr* shdr  = (Elf_Shdr*) (ehdrC + ehdr->e_shoff);
 
294
 
 
295
-   /* first find "the" symbol table */
 
296
-   stab = (Elf_Sym*) findElfSection ( ehdrC, SHT_SYMTAB );
 
297
-
 
298
-   /* also go find the string table */
 
299
-   strtab = findElfSection ( ehdrC, SHT_STRTAB );
 
300
-
 
301
-   if (stab == NULL || strtab == NULL) {
 
302
-      errorBelch("%s: can't find string or symbol table", oc->fileName);
 
303
-      return 0;
 
304
-   }
 
305
-
 
306
    /* Process the relocation sections. */
 
307
    for (shnum = 0; shnum < ehdr->e_shnum; shnum++) {
 
308
       if (shdr[shnum].sh_type == SHT_REL) {
 
309
-         ok = do_Elf_Rel_relocations ( oc, ehdrC, shdr,
 
310
-                                       shnum, stab, strtab );
 
311
+         ok = do_Elf_Rel_relocations ( oc, ehdrC, shdr, shnum );
 
312
          if (!ok) return ok;
 
313
       }
 
314
       else
 
315
       if (shdr[shnum].sh_type == SHT_RELA) {
 
316
-         ok = do_Elf_Rela_relocations ( oc, ehdrC, shdr,
 
317
-                                        shnum, stab, strtab );
 
318
+         ok = do_Elf_Rela_relocations ( oc, ehdrC, shdr, shnum );
 
319
          if (!ok) return ok;
 
320
       }
 
321
    }
 
322
@@ -4369,8 +4380,12 @@
 
323
 
 
324
   if( i == ehdr->e_shnum )
 
325
   {
 
326
-    errorBelch( "This ELF file contains no symtab" );
 
327
-    return 0;
 
328
+    // Not having a symbol table is not in principle a problem.
 
329
+    // When an object file has no symbols then the 'strip' program
 
330
+    // typically will remove the symbol table entirely.
 
331
+    IF_DEBUG(linker, debugBelch( "The ELF file %s contains no symtab\n",
 
332
+             oc->archiveMemberName ? oc->archiveMemberName : oc->fileName ));
 
333
+    return 1;
 
334
   }
 
335
 
 
336
   if( shdr[i].sh_entsize != sizeof( Elf_Sym ) )