OSDN Git Service

Support for Toshiba MeP and for complex relocations.
[pf3gnuchains/pf3gnuchains3x.git] / bfd / elf32-mep.c
1 /* MeP-specific support for 32-bit ELF.
2    Copyright (C) 2001, 2002, 2003, 2004, 2005, 2006
3    Free Software Foundation, Inc.
4
5    This file is part of BFD, the Binary File Descriptor library.
6
7    This program is free software; you can redistribute it and/or modify
8    it under the terms of the GNU General Public License as published by
9    the Free Software Foundation; either version 2 of the License, or
10    (at your option) any later version.
11
12    This program is distributed in the hope that it will be useful,
13    but WITHOUT ANY WARRANTY; without even the implied warranty of
14    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15    GNU General Public License for more details.
16
17    You should have received a copy of the GNU General Public License
18    along with this program; if not, write to the Free Software
19    Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.  */
20
21 #include "bfd.h"
22 #include "sysdep.h"
23 #include "libbfd.h"
24 #include "elf-bfd.h"
25 #include "elf/mep.h"
26 #include "libiberty.h"
27
28 /* Forward declarations.  */
29
30 /* Private relocation functions.  */
31 \f
32 #define MEPREL(type, size, bits, right, left, pcrel, overflow, mask) \
33   {(unsigned)type, right, size, bits, pcrel, left, overflow, mep_reloc, #type, FALSE, 0, mask, 0 }
34
35 #define N complain_overflow_dont
36 #define S complain_overflow_signed
37 #define U complain_overflow_unsigned
38
39 static bfd_reloc_status_type mep_reloc (bfd *, arelent *, struct bfd_symbol *,
40                                         void *, asection *, bfd *, char **);
41
42 static reloc_howto_type mep_elf_howto_table [] =
43 {
44   /* type, size, bits, leftshift, rightshift, pcrel, OD/OS/OU, mask.  */
45   MEPREL (R_MEP_NONE,     0,  0, 0, 0, 0, N, 0),
46   MEPREL (R_RELC,         0,  0, 0, 0, 0, N, 0),
47   /* MEPRELOC:HOWTO */
48     /* This section generated from bfd/mep-relocs.pl from include/elf/mep.h.  */
49   MEPREL (R_MEP_8,        0,  8, 0, 0, 0, U, 0xff),
50   MEPREL (R_MEP_16,       1, 16, 0, 0, 0, U, 0xffff),
51   MEPREL (R_MEP_32,       2, 32, 0, 0, 0, U, 0xffffffff),
52   MEPREL (R_MEP_PCREL8A2, 1,  8, 1, 1, 1, S, 0x00fe),
53   MEPREL (R_MEP_PCREL12A2,1, 12, 1, 1, 1, S, 0x0ffe),
54   MEPREL (R_MEP_PCREL17A2,2, 17, 0, 1, 1, S, 0x0000ffff),
55   MEPREL (R_MEP_PCREL24A2,2, 24, 0, 1, 1, S, 0x07f0ffff),
56   MEPREL (R_MEP_PCABS24A2,2, 24, 0, 1, 0, U, 0x07f0ffff),
57   MEPREL (R_MEP_LOW16,    2, 16, 0, 0, 0, N, 0x0000ffff),
58   MEPREL (R_MEP_HI16U,    2, 32, 0,16, 0, N, 0x0000ffff),
59   MEPREL (R_MEP_HI16S,    2, 32, 0,16, 0, N, 0x0000ffff),
60   MEPREL (R_MEP_GPREL,    2, 16, 0, 0, 0, S, 0x0000ffff),
61   MEPREL (R_MEP_TPREL,    2, 16, 0, 0, 0, S, 0x0000ffff),
62   MEPREL (R_MEP_TPREL7,   1,  7, 0, 0, 0, U, 0x007f),
63   MEPREL (R_MEP_TPREL7A2, 1,  7, 1, 1, 0, U, 0x007e),
64   MEPREL (R_MEP_TPREL7A4, 1,  7, 2, 2, 0, U, 0x007c),
65   MEPREL (R_MEP_UIMM24,   2, 24, 0, 0, 0, U, 0x00ffffff),
66   MEPREL (R_MEP_ADDR24A4, 2, 24, 0, 2, 0, U, 0x00fcffff),
67   MEPREL (R_MEP_GNU_VTINHERIT,1,  0,16,32, 0, N, 0x0000),
68   MEPREL (R_MEP_GNU_VTENTRY,1,  0,16,32, 0, N, 0x0000),
69   /* MEPRELOC:END */
70 };
71
72 #define VALID_MEP_RELOC(N) ((N) >= 0 \
73   && (N) < ARRAY_SIZE (mep_elf_howto_table)
74
75 #undef N
76 #undef S
77 #undef U
78
79 static bfd_reloc_status_type
80 mep_reloc
81     (bfd *               abfd ATTRIBUTE_UNUSED,
82      arelent *           reloc_entry ATTRIBUTE_UNUSED,
83      struct bfd_symbol * symbol ATTRIBUTE_UNUSED,
84      void *              data ATTRIBUTE_UNUSED,
85      asection *          input_section ATTRIBUTE_UNUSED,
86      bfd *               output_bfd ATTRIBUTE_UNUSED,
87      char **             error_message ATTRIBUTE_UNUSED)
88 {
89   return bfd_reloc_ok;
90 }
91
92 \f
93
94 #define BFD_RELOC_MEP_NONE BFD_RELOC_NONE
95 #if defined (__STDC__) || defined (ALMOST_STDC) || defined (HAVE_STRINGIZE)
96 #define MAP(n) case BFD_RELOC_MEP_##n: type = R_MEP_##n; break
97 #else
98 #define MAP(n) case BFD_RELOC_MEP_/**/n: type = R_MEP_/**/n; break
99 #endif
100
101 static reloc_howto_type *
102 mep_reloc_type_lookup
103     (bfd * abfd ATTRIBUTE_UNUSED,
104      bfd_reloc_code_real_type code)
105 {
106   unsigned int type = 0;
107
108   switch (code)
109     {
110     MAP(NONE);
111     case BFD_RELOC_8:
112       type = R_MEP_8;
113       break;
114     case BFD_RELOC_16:
115       type = R_MEP_16;
116       break;
117     case BFD_RELOC_32:
118       type = R_MEP_32;
119       break;
120     case BFD_RELOC_VTABLE_ENTRY:
121       type = R_MEP_GNU_VTENTRY;
122       break;
123     case BFD_RELOC_VTABLE_INHERIT:
124       type = R_MEP_GNU_VTINHERIT;
125       break;
126     case BFD_RELOC_RELC:
127       type = R_RELC;
128       break;
129
130     /* MEPRELOC:MAP */
131     /* This section generated from bfd/mep-relocs.pl from include/elf/mep.h.  */
132     MAP(8);
133     MAP(16);
134     MAP(32);
135     MAP(PCREL8A2);
136     MAP(PCREL12A2);
137     MAP(PCREL17A2);
138     MAP(PCREL24A2);
139     MAP(PCABS24A2);
140     MAP(LOW16);
141     MAP(HI16U);
142     MAP(HI16S);
143     MAP(GPREL);
144     MAP(TPREL);
145     MAP(TPREL7);
146     MAP(TPREL7A2);
147     MAP(TPREL7A4);
148     MAP(UIMM24);
149     MAP(ADDR24A4);
150     MAP(GNU_VTINHERIT);
151     MAP(GNU_VTENTRY);
152     /* MEPRELOC:END */
153
154     default:
155       /* Pacify gcc -Wall.  */
156       fprintf (stderr, "mep: no reloc for code %d\n", code);
157       return NULL;
158     }
159
160   if (mep_elf_howto_table[type].type != type)
161     {
162       fprintf (stderr, "MeP: howto %d has type %d\n", type, mep_elf_howto_table[type].type);
163       abort ();
164     }
165
166   return mep_elf_howto_table + type;
167 }
168
169 #undef MAP
170
171 \f
172 /* Perform a single relocation.  */
173
174 static struct bfd_link_info *mep_info;
175 static int warn_tp = 0, warn_sda = 0;
176
177 static bfd_vma
178 mep_lookup_global
179     (char *    name,
180      bfd_vma   ofs,
181      bfd_vma * cache,
182      int *     warn)
183 {
184   struct bfd_link_hash_entry *h;
185
186   if (*cache || *warn)
187     return *cache;
188
189   h = bfd_link_hash_lookup (mep_info->hash, name, FALSE, FALSE, TRUE);
190   if (h == 0 || h->type != bfd_link_hash_defined)
191     {
192       *warn = ofs + 1;
193       return 0;
194     }
195   *cache = (h->u.def.value
196           + h->u.def.section->output_section->vma
197           + h->u.def.section->output_offset);
198   return *cache;
199 }
200
201 static bfd_vma
202 mep_tpoff_base (bfd_vma ofs)
203 {
204   static bfd_vma cache = 0;
205   return mep_lookup_global ("__tpbase", ofs, &cache, &warn_tp);
206 }
207
208 static bfd_vma
209 mep_sdaoff_base (bfd_vma ofs)
210 {
211   static bfd_vma cache = 0;
212   return mep_lookup_global ("__sdabase", ofs, &cache, &warn_sda);
213 }
214
215 static bfd_reloc_status_type
216 mep_final_link_relocate
217     (reloc_howto_type *  howto,
218      bfd *               input_bfd,
219      asection *          input_section,
220      bfd_byte *          contents,
221      Elf_Internal_Rela * rel,
222      bfd_vma             relocation)
223 {
224   unsigned long u;
225   long s;
226   unsigned char *byte;
227   bfd_vma pc;
228   bfd_reloc_status_type r = bfd_reloc_ok;
229   int e2, e4;
230
231   if (bfd_big_endian (input_bfd))
232     {
233       e2 = 0;
234       e4 = 0;
235     }
236   else
237     {
238       e2 = 1;
239       e4 = 3;
240     }
241
242   pc = (input_section->output_section->vma
243         + input_section->output_offset
244         + rel->r_offset);
245
246   s = relocation + rel->r_addend;
247
248   byte = (unsigned char *)contents + rel->r_offset;
249
250   if (howto->type == R_MEP_PCREL24A2
251       && s == 0
252       && pc >= 0x800000)
253     {
254       /* This is an unreachable branch to an undefined weak function.
255          Silently ignore it, since the opcode can't do that but should
256          never be executed anyway.  */
257       return bfd_reloc_ok;
258     }
259
260   if (howto->pc_relative)
261     s -= pc;
262
263   u = (unsigned long) s;
264
265   switch (howto->type)
266     {
267     /* MEPRELOC:APPLY */
268     /* This section generated from bfd/mep-relocs.pl from include/elf/mep.h.  */
269     case R_MEP_8: /* 76543210 */
270       if (u > 255) r = bfd_reloc_overflow;
271       byte[0] = (u & 0xff);
272       break;
273     case R_MEP_16: /* fedcba9876543210 */
274       if (u > 65535) r = bfd_reloc_overflow;
275       byte[0^e2] = ((u >> 8) & 0xff);
276       byte[1^e2] = (u & 0xff);
277       break;
278     case R_MEP_32: /* vutsrqponmlkjihgfedcba9876543210 */
279       byte[0^e4] = ((u >> 24) & 0xff);
280       byte[1^e4] = ((u >> 16) & 0xff);
281       byte[2^e4] = ((u >> 8) & 0xff);
282       byte[3^e4] = (u & 0xff);
283       break;
284     case R_MEP_PCREL8A2: /* --------7654321- */
285       if (-128 > s || s > 127) r = bfd_reloc_overflow;
286       byte[1^e2] = (byte[1^e2] & 0x01) | (s & 0xfe);
287       break;
288     case R_MEP_PCREL12A2: /* ----ba987654321- */
289       if (-2048 > s || s > 2047) r = bfd_reloc_overflow;
290       byte[0^e2] = (byte[0^e2] & 0xf0) | ((s >> 8) & 0x0f);
291       byte[1^e2] = (byte[1^e2] & 0x01) | (s & 0xfe);
292       break;
293     case R_MEP_PCREL17A2: /* ----------------gfedcba987654321 */
294       if (-65536 > s || s > 65535) r = bfd_reloc_overflow;
295       byte[2^e2] = ((s >> 9) & 0xff);
296       byte[3^e2] = ((s >> 1) & 0xff);
297       break;
298     case R_MEP_PCREL24A2: /* -----7654321----nmlkjihgfedcba98 */
299       if (-8388608 > s || s > 8388607) r = bfd_reloc_overflow;
300       byte[0^e2] = (byte[0^e2] & 0xf8) | ((s >> 5) & 0x07);
301       byte[1^e2] = (byte[1^e2] & 0x0f) | ((s << 3) & 0xf0);
302       byte[2^e2] = ((s >> 16) & 0xff);
303       byte[3^e2] = ((s >> 8) & 0xff);
304       break;
305     case R_MEP_PCABS24A2: /* -----7654321----nmlkjihgfedcba98 */
306       if (u > 16777215) r = bfd_reloc_overflow;
307       byte[0^e2] = (byte[0^e2] & 0xf8) | ((u >> 5) & 0x07);
308       byte[1^e2] = (byte[1^e2] & 0x0f) | ((u << 3) & 0xf0);
309       byte[2^e2] = ((u >> 16) & 0xff);
310       byte[3^e2] = ((u >> 8) & 0xff);
311       break;
312     case R_MEP_LOW16: /* ----------------fedcba9876543210 */
313       byte[2^e2] = ((u >> 8) & 0xff);
314       byte[3^e2] = (u & 0xff);
315       break;
316     case R_MEP_HI16U: /* ----------------vutsrqponmlkjihg */
317       byte[2^e2] = ((u >> 24) & 0xff);
318       byte[3^e2] = ((u >> 16) & 0xff);
319       break;
320     case R_MEP_HI16S: /* ----------------vutsrqponmlkjihg */
321       byte[2^e2] = ((s >> 24) & 0xff);
322       byte[3^e2] = ((s >> 16) & 0xff);
323       break;
324     case R_MEP_GPREL: /* ----------------fedcba9876543210 */
325       s -= mep_sdaoff_base(rel->r_offset);
326       if (-32768 > s || s > 32767) r = bfd_reloc_overflow;
327       byte[2^e2] = ((s >> 8) & 0xff);
328       byte[3^e2] = (s & 0xff);
329       break;
330     case R_MEP_TPREL: /* ----------------fedcba9876543210 */
331       s -= mep_tpoff_base(rel->r_offset);
332       if (-32768 > s || s > 32767) r = bfd_reloc_overflow;
333       byte[2^e2] = ((s >> 8) & 0xff);
334       byte[3^e2] = (s & 0xff);
335       break;
336     case R_MEP_TPREL7: /* ---------6543210 */
337       u -= mep_tpoff_base(rel->r_offset);
338       if (u > 127) r = bfd_reloc_overflow;
339       byte[1^e2] = (byte[1^e2] & 0x80) | (u & 0x7f);
340       break;
341     case R_MEP_TPREL7A2: /* ---------654321- */
342       u -= mep_tpoff_base(rel->r_offset);
343       if (u > 127) r = bfd_reloc_overflow;
344       byte[1^e2] = (byte[1^e2] & 0x81) | (u & 0x7e);
345       break;
346     case R_MEP_TPREL7A4: /* ---------65432-- */
347       u -= mep_tpoff_base(rel->r_offset);
348       if (u > 127) r = bfd_reloc_overflow;
349       byte[1^e2] = (byte[1^e2] & 0x83) | (u & 0x7c);
350       break;
351     case R_MEP_UIMM24: /* --------76543210nmlkjihgfedcba98 */
352       if (u > 16777215) r = bfd_reloc_overflow;
353       byte[1^e2] = (u & 0xff);
354       byte[2^e2] = ((u >> 16) & 0xff);
355       byte[3^e2] = ((u >> 8) & 0xff);
356       break;
357     case R_MEP_ADDR24A4: /* --------765432--nmlkjihgfedcba98 */
358       if (u > 16777215) r = bfd_reloc_overflow;
359       byte[1^e2] = (byte[1^e2] & 0x03) | (u & 0xfc);
360       byte[2^e2] = ((u >> 16) & 0xff);
361       byte[3^e2] = ((u >> 8) & 0xff);
362       break;
363     case R_MEP_GNU_VTINHERIT: /* ---------------- */
364       break;
365     case R_MEP_GNU_VTENTRY: /* ---------------- */
366       break;
367     /* MEPRELOC:END */
368     default:
369       abort ();
370     }
371
372   return r;
373 }
374 \f
375 /* Set the howto pointer for a MEP ELF reloc.  */
376
377 static void
378 mep_info_to_howto_rela
379     (bfd *               abfd ATTRIBUTE_UNUSED,
380      arelent *           cache_ptr,
381      Elf_Internal_Rela * dst)
382 {
383   unsigned int r_type;
384
385   r_type = ELF32_R_TYPE (dst->r_info);
386   cache_ptr->howto = & mep_elf_howto_table [r_type];
387 }
388
389 /* Look through the relocs for a section during the first phase.
390    Since we don't do .gots or .plts, we just need to consider the
391    virtual table relocs for gc.  */
392
393 static bfd_boolean
394 mep_elf_check_relocs
395     (bfd *                     abfd,
396      struct bfd_link_info *    info,
397      asection *                sec,
398      const Elf_Internal_Rela * relocs)
399 {
400   Elf_Internal_Shdr *           symtab_hdr;
401   struct elf_link_hash_entry ** sym_hashes;
402   struct elf_link_hash_entry ** sym_hashes_end;
403   const Elf_Internal_Rela *     rel;
404   const Elf_Internal_Rela *     rel_end;
405
406   if (info->relocatable)
407     return TRUE;
408
409   symtab_hdr = &elf_tdata (abfd)->symtab_hdr;
410   sym_hashes = elf_sym_hashes (abfd);
411   sym_hashes_end = sym_hashes + symtab_hdr->sh_size / sizeof (Elf32_External_Sym);
412   if (!elf_bad_symtab (abfd))
413     sym_hashes_end -= symtab_hdr->sh_info;
414
415   rel_end = relocs + sec->reloc_count;
416   for (rel = relocs; rel < rel_end; rel++)
417     {
418       struct elf_link_hash_entry *h;
419       unsigned long r_symndx;
420
421       r_symndx = ELF32_R_SYM (rel->r_info);
422       if (r_symndx < symtab_hdr->sh_info)
423         h = NULL;
424       else
425         h = sym_hashes[r_symndx - symtab_hdr->sh_info];
426     }
427   return TRUE;
428 }
429
430 \f
431 /* Relocate a MEP ELF section.
432    There is some attempt to make this function usable for many architectures,
433    both USE_REL and USE_RELA ['twould be nice if such a critter existed],
434    if only to serve as a learning tool.
435
436    The RELOCATE_SECTION function is called by the new ELF backend linker
437    to handle the relocations for a section.
438
439    The relocs are always passed as Rela structures; if the section
440    actually uses Rel structures, the r_addend field will always be
441    zero.
442
443    This function is responsible for adjusting the section contents as
444    necessary, and (if using Rela relocs and generating a relocatable
445    output file) adjusting the reloc addend as necessary.
446
447    This function does not have to worry about setting the reloc
448    address or the reloc symbol index.
449
450    LOCAL_SYMS is a pointer to the swapped in local symbols.
451
452    LOCAL_SECTIONS is an array giving the section in the input file
453    corresponding to the st_shndx field of each local symbol.
454
455    The global hash table entry for the global symbols can be found
456    via elf_sym_hashes (input_bfd).
457
458    When generating relocatable output, this function must handle
459    STB_LOCAL/STT_SECTION symbols specially.  The output symbol is
460    going to be the section symbol corresponding to the output
461    section, which means that the addend must be adjusted
462    accordingly.  */
463
464 static bfd_boolean
465 mep_elf_relocate_section
466     (bfd *                   output_bfd ATTRIBUTE_UNUSED,
467      struct bfd_link_info *  info,
468      bfd *                   input_bfd,
469      asection *              input_section,
470      bfd_byte *              contents,
471      Elf_Internal_Rela *     relocs,
472      Elf_Internal_Sym *      local_syms,
473      asection **             local_sections)
474 {
475   Elf_Internal_Shdr *           symtab_hdr;
476   struct elf_link_hash_entry ** sym_hashes;
477   Elf_Internal_Rela *           rel;
478   Elf_Internal_Rela *           relend;
479
480   symtab_hdr = & elf_tdata (input_bfd)->symtab_hdr;
481   sym_hashes = elf_sym_hashes (input_bfd);
482   relend     = relocs + input_section->reloc_count;
483
484   mep_info = info;
485
486   for (rel = relocs; rel < relend; rel ++)
487     {
488       reloc_howto_type *           howto;
489       unsigned long                r_symndx;
490       Elf_Internal_Sym *           sym;
491       asection *                   sec;
492       struct elf_link_hash_entry * h;
493       bfd_vma                      relocation;
494       bfd_reloc_status_type        r;
495       const char *                 name = NULL;
496       int                          r_type;
497
498       r_type = ELF32_R_TYPE (rel->r_info);
499
500       r_symndx = ELF32_R_SYM (rel->r_info);
501
502       if (info->relocatable)
503         {
504           /* This is a relocatable link.  We don't have to change
505              anything, unless the reloc is against a section symbol,
506              in which case we have to adjust according to where the
507              section symbol winds up in the output section.  */
508           if (r_symndx < symtab_hdr->sh_info)
509             {
510               sym = local_syms + r_symndx;
511
512               if (ELF_ST_TYPE (sym->st_info) == STT_SECTION)
513                 {
514                   sec = local_sections [r_symndx];
515                   rel->r_addend += sec->output_offset + sym->st_value;
516                 }
517             }
518
519           continue;
520         }
521
522       /* Is this a complex relocation?  */
523       if (ELF32_R_TYPE (rel->r_info) == R_RELC)
524         {
525           bfd_elf_perform_complex_relocation (output_bfd, info,
526                                               input_bfd, input_section, contents,
527                                               rel, local_syms, local_sections);
528           continue;
529         }
530
531       /* This is a final link.  */
532       howto  = mep_elf_howto_table + ELF32_R_TYPE (rel->r_info);
533       h      = NULL;
534       sym    = NULL;
535       sec    = NULL;
536
537       if (r_symndx < symtab_hdr->sh_info)
538         {
539           sym = local_syms + r_symndx;
540           sec = local_sections [r_symndx];
541           relocation = _bfd_elf_rela_local_sym (output_bfd, sym, &sec, rel);
542
543           name = bfd_elf_string_from_elf_section
544             (input_bfd, symtab_hdr->sh_link, sym->st_name);
545           name = (name == NULL) ? bfd_section_name (input_bfd, sec) : name;
546 #if 0
547           fprintf (stderr, "local: sec: %s, sym: %s (%d), value: %x + %x + %x addend %x\n",
548                    sec->name, name, sym->st_name,
549                    sec->output_section->vma, sec->output_offset,
550                    sym->st_value, rel->r_addend);
551 #endif
552         }
553       else
554         {
555           h = sym_hashes [r_symndx];
556
557           while (h->root.type == bfd_link_hash_indirect
558                  || h->root.type == bfd_link_hash_warning)
559             h = (struct elf_link_hash_entry *) h->root.u.i.link;
560
561           name = h->root.root.string;
562
563           if (h->root.type == bfd_link_hash_defined
564               || h->root.type == bfd_link_hash_defweak)
565             {
566               sec = h->root.u.def.section;
567               relocation = (h->root.u.def.value
568                             + sec->output_section->vma
569                             + sec->output_offset);
570 #if 0
571               fprintf (stderr,
572                        "defined: sec: %s, name: %s, value: %x + %x + %x gives: %x\n",
573                        sec->name, name, h->root.u.def.value,
574                        sec->output_section->vma, sec->output_offset, relocation);
575 #endif
576             }
577           else if (h->root.type == bfd_link_hash_undefweak)
578             {
579 #if 0
580               fprintf (stderr, "undefined: sec: %s, name: %s\n",
581                        sec->name, name);
582 #endif
583               relocation = 0;
584             }
585           else
586             {
587               if (! ((*info->callbacks->undefined_symbol)
588                      (info, h->root.root.string, input_bfd,
589                       input_section, rel->r_offset,
590                       (!info->shared && info->unresolved_syms_in_objects == RM_GENERATE_ERROR))))
591                 return FALSE;
592 #if 0
593               fprintf (stderr, "unknown: name: %s\n", name);
594 #endif
595               relocation = 0;
596             }
597         }
598
599       switch (r_type)
600         {
601         default:
602           r = mep_final_link_relocate (howto, input_bfd, input_section,
603                                          contents, rel, relocation);
604           break;
605         }
606
607       if (r != bfd_reloc_ok)
608         {
609           const char * msg = (const char *) NULL;
610
611           switch (r)
612             {
613             case bfd_reloc_overflow:
614               r = info->callbacks->reloc_overflow
615                 (info, (h ? &h->root : NULL), name, howto->name, (bfd_vma) 0,
616                  input_bfd, input_section, rel->r_offset);
617               break;
618
619             case bfd_reloc_undefined:
620               r = info->callbacks->undefined_symbol
621                 (info, name, input_bfd, input_section, rel->r_offset, TRUE);
622               break;
623
624             case bfd_reloc_outofrange:
625               msg = _("internal error: out of range error");
626               break;
627
628             case bfd_reloc_notsupported:
629               msg = _("internal error: unsupported relocation error");
630               break;
631
632             case bfd_reloc_dangerous:
633               msg = _("internal error: dangerous relocation");
634               break;
635
636             default:
637               msg = _("internal error: unknown error");
638               break;
639             }
640
641           if (msg)
642             r = info->callbacks->warning
643               (info, msg, name, input_bfd, input_section, rel->r_offset);
644
645           if (! r)
646             return FALSE;
647         }
648     }
649
650   if (warn_tp)
651     info->callbacks->undefined_symbol
652       (info, "__tpbase", input_bfd, input_section, warn_tp-1, TRUE);
653   if (warn_sda)
654     info->callbacks->undefined_symbol
655       (info, "__sdabase", input_bfd, input_section, warn_sda-1, TRUE);
656   if (warn_sda || warn_tp)
657     return FALSE;
658
659   return TRUE;
660 }
661 \f
662
663 /* Update the got entry reference counts for the section being
664    removed.  */
665
666 static bfd_boolean
667 mep_elf_gc_sweep_hook
668     (bfd *                     abfd ATTRIBUTE_UNUSED,
669      struct bfd_link_info *    info ATTRIBUTE_UNUSED,
670      asection *                sec ATTRIBUTE_UNUSED,
671      const Elf_Internal_Rela * relocs ATTRIBUTE_UNUSED)
672 {
673   return TRUE;
674 }
675
676 /* Return the section that should be marked against GC for a given
677    relocation.  */
678
679 static asection *
680 mep_elf_gc_mark_hook
681     (asection *                   sec,
682      struct bfd_link_info *       info ATTRIBUTE_UNUSED,
683      Elf_Internal_Rela *          rel,
684      struct elf_link_hash_entry * h,
685      Elf_Internal_Sym *           sym)
686 {
687   if (h != NULL)
688     {
689       switch (ELF32_R_TYPE (rel->r_info))
690         {
691         default:
692           switch (h->root.type)
693             {
694             case bfd_link_hash_defined:
695             case bfd_link_hash_defweak:
696               return h->root.u.def.section;
697
698             case bfd_link_hash_common:
699               return h->root.u.c.p->section;
700
701             default:
702               break;
703             }
704         }
705     }
706   else
707     {
708       if (!(elf_bad_symtab (sec->owner)
709             && ELF_ST_BIND (sym->st_info) != STB_LOCAL)
710           && ! ((sym->st_shndx <= 0 || sym->st_shndx >= SHN_LORESERVE)
711                 && sym->st_shndx != SHN_COMMON))
712         return bfd_section_from_elf_index (sec->owner, sym->st_shndx);
713     }
714
715   return NULL;
716 }
717
718 \f
719 /* Function to set the ELF flag bits.  */
720
721 static bfd_boolean
722 mep_elf_set_private_flags (bfd *    abfd,
723                            flagword flags)
724 {
725   elf_elfheader (abfd)->e_flags = flags;
726   elf_flags_init (abfd) = TRUE;
727   return TRUE;
728 }
729
730 static bfd_boolean
731 mep_elf_copy_private_bfd_data (bfd * ibfd, bfd * obfd)
732 {
733   if (bfd_get_flavour (ibfd) != bfd_target_elf_flavour
734       || bfd_get_flavour (obfd) != bfd_target_elf_flavour)
735     return TRUE;
736
737   elf_elfheader (obfd)->e_flags = elf_elfheader (ibfd)->e_flags;
738   elf_flags_init (obfd) = TRUE;
739   return TRUE;
740 }
741
742 /* Merge backend specific data from an object file to the output
743    object file when linking.  */
744
745 static bfd_boolean
746 mep_elf_merge_private_bfd_data (bfd * ibfd, bfd * obfd)
747 {
748   static bfd *last_ibfd = 0;
749   flagword old_flags, new_flags;
750   flagword old_partial, new_partial;
751
752   /* Check if we have the same endianess.  */
753   if (_bfd_generic_verify_endian_match (ibfd, obfd) == FALSE)
754     return FALSE;
755
756   new_flags = elf_elfheader (ibfd)->e_flags;
757   old_flags = elf_elfheader (obfd)->e_flags;
758
759 #ifdef DEBUG
760   _bfd_error_handler ("%B: old_flags = 0x%.8lx, new_flags = 0x%.8lx, init = %s",
761                       ibfd, old_flags, new_flags, elf_flags_init (obfd) ? "yes" : "no");
762 #endif
763
764     /* First call, no flags set.  */
765     if (!elf_flags_init (obfd))
766     {
767       elf_flags_init (obfd) = TRUE;
768       old_flags = new_flags;
769     }
770   else if ((new_flags | old_flags) & EF_MEP_LIBRARY)
771     {
772       /* Non-library flags trump library flags.  The choice doesn't really
773          matter if both OLD_FLAGS and NEW_FLAGS have EF_MEP_LIBRARY set.  */
774       if (old_flags & EF_MEP_LIBRARY)
775         old_flags = new_flags;
776     }
777   else
778     {
779       /* Make sure they're for the same mach.  Allow upgrade from the "mep"
780          mach.  */
781       new_partial = (new_flags & EF_MEP_CPU_MASK);
782       old_partial = (old_flags & EF_MEP_CPU_MASK);
783       if (new_partial == old_partial)
784         ;
785       else if (new_partial == EF_MEP_CPU_MEP)
786         ;
787       else if (old_partial == EF_MEP_CPU_MEP)
788         old_flags = (old_flags & ~EF_MEP_CPU_MASK) | new_partial;
789       else
790         {
791           _bfd_error_handler (_("%B and %B are for different cores"), last_ibfd, ibfd);
792           bfd_set_error (bfd_error_invalid_target);
793           return FALSE;
794         }
795
796       /* Make sure they're for the same me_module.  Allow basic config to
797          mix with any other.  */
798       new_partial = (new_flags & EF_MEP_INDEX_MASK);
799       old_partial = (old_flags & EF_MEP_INDEX_MASK);
800       if (new_partial == old_partial)
801         ;
802       else if (new_partial == 0)
803         ;
804       else if (old_partial == 0)
805         old_flags = (old_flags & ~EF_MEP_INDEX_MASK) | new_partial;
806       else
807         {
808           _bfd_error_handler (_("%B and %B are for different configurations"), last_ibfd, ibfd);
809           bfd_set_error (bfd_error_invalid_target);
810           return FALSE;
811         }
812     }
813
814   elf_elfheader (obfd)->e_flags = old_flags;
815   last_ibfd = ibfd;
816   return TRUE;
817 }
818
819 /* This will be edited by the MeP configration tool.  */
820 static const char * config_names[] =
821 {
822   "basic"
823   /* start-mepcfgtool */
824   ,"simple"
825   ,"fmax"
826   /* end-mepcfgtool */
827 };
828
829 static const char * core_names[] =
830 {
831   "MeP", "MeP-c2", "MeP-c3", "MeP-h1"
832 };
833
834 static bfd_boolean
835 mep_elf_print_private_bfd_data (bfd * abfd, void * ptr)
836 {
837   FILE *   file = (FILE *) ptr;
838   flagword flags, partial_flags;
839
840   BFD_ASSERT (abfd != NULL && ptr != NULL);
841
842   /* Print normal ELF private data.  */
843   _bfd_elf_print_private_bfd_data (abfd, ptr);
844
845   flags = elf_elfheader (abfd)->e_flags;
846   fprintf (file, _("private flags = 0x%lx"), (long)flags);
847
848   partial_flags = (flags & EF_MEP_CPU_MASK) >> 24;
849   if (partial_flags < ARRAY_SIZE (core_names))
850     fprintf (file, "  core: %s", core_names[(long)partial_flags]);
851
852   partial_flags = flags & EF_MEP_INDEX_MASK;
853   if (partial_flags < ARRAY_SIZE (config_names))
854     fprintf (file, "  me_module: %s", config_names[(long)partial_flags]);
855
856   fputc ('\n', file);
857
858   return TRUE;
859 }
860
861 /* Return the machine subcode from the ELF e_flags header.  */
862
863 static int
864 elf32_mep_machine (bfd * abfd)
865 {
866   switch (elf_elfheader (abfd)->e_flags & EF_MEP_CPU_MASK)
867     {
868     default: break;
869     case EF_MEP_CPU_C2: return bfd_mach_mep;
870     case EF_MEP_CPU_C3: return bfd_mach_mep;
871     case EF_MEP_CPU_C4: return bfd_mach_mep;
872     case EF_MEP_CPU_H1: return bfd_mach_mep_h1;
873     }
874
875   return bfd_mach_mep;
876 }
877
878 static bfd_boolean
879 mep_elf_object_p (bfd * abfd)
880 {
881   /* Irix 5 and 6 is broken.  Object file symbol tables are not always
882      sorted correctly such that local symbols preceed global symbols,
883      and the sh_info field in the symbol table is not always right.  */
884   /* This is needed for the RELC support code.  */
885   elf_bad_symtab (abfd) = TRUE;
886   bfd_default_set_arch_mach (abfd, bfd_arch_mep, elf32_mep_machine (abfd));
887   return TRUE;
888 }
889
890 static bfd_boolean
891 mep_elf_section_flags (flagword * flags, const Elf_Internal_Shdr * hdr)
892 {
893   if (hdr->sh_flags & SHF_MEP_VLIW)
894     * flags |= SEC_MEP_VLIW;
895   return TRUE;
896 }
897
898 static bfd_boolean
899 mep_elf_fake_sections (bfd *               abfd ATTRIBUTE_UNUSED,
900                        Elf_Internal_Shdr * hdr,
901                        asection *          sec)
902 {
903   if (sec->flags & SEC_MEP_VLIW)
904     hdr->sh_flags |= SHF_MEP_VLIW;
905   return TRUE;
906 }
907
908 \f
909 #define ELF_ARCH                bfd_arch_mep
910 #define ELF_MACHINE_CODE        EM_CYGNUS_MEP
911 #define ELF_MAXPAGESIZE         0x1000
912
913 #define TARGET_BIG_SYM          bfd_elf32_mep_vec
914 #define TARGET_BIG_NAME         "elf32-mep"
915
916 #define TARGET_LITTLE_SYM       bfd_elf32_mep_little_vec
917 #define TARGET_LITTLE_NAME      "elf32-mep-little"
918
919 #define elf_info_to_howto_rel                   NULL
920 #define elf_info_to_howto                       mep_info_to_howto_rela
921 #define elf_backend_relocate_section            mep_elf_relocate_section
922 #define elf_backend_gc_mark_hook                mep_elf_gc_mark_hook
923 #define elf_backend_gc_sweep_hook               mep_elf_gc_sweep_hook
924 #define elf_backend_check_relocs                mep_elf_check_relocs
925 #define elf_backend_object_p                    mep_elf_object_p
926 #define elf_backend_section_flags               mep_elf_section_flags
927 #define elf_backend_fake_sections               mep_elf_fake_sections
928
929 #define elf_backend_can_gc_sections             1
930
931 #define bfd_elf32_bfd_reloc_type_lookup         mep_reloc_type_lookup
932 #define bfd_elf32_bfd_set_private_flags         mep_elf_set_private_flags
933 #define bfd_elf32_bfd_copy_private_bfd_data     mep_elf_copy_private_bfd_data
934 #define bfd_elf32_bfd_merge_private_bfd_data    mep_elf_merge_private_bfd_data
935 #define bfd_elf32_bfd_print_private_bfd_data    mep_elf_print_private_bfd_data
936
937 /* We use only the RELA entries.  */
938 #define USE_RELA
939
940 #include "elf32-target.h"