OSDN Git Service

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