1/* DLX specific support for 32-bit ELF
2   Copyright 2002, 2003, 2004, 2005 Free Software Foundation, Inc.
3
4   This file is part of BFD, the Binary File Descriptor library.
5
6   This program is free software; you can redistribute it and/or modify
7   it under the terms of the GNU General Public License as published by
8   the Free Software Foundation; either version 2 of the License, or
9   (at your option) any later version.
10
11   This program is distributed in the hope that it will be useful,
12   but WITHOUT ANY WARRANTY; without even the implied warranty of
13   MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14   GNU General Public License for more details.
15
16   You should have received a copy of the GNU General Public License
17   along with this program; if not, write to the Free Software
18   Foundation, Inc., 51 Franklin Street - Fifth Floor, Boston,
19   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/dlx.h"
26
27#define USE_REL 1
28
29#define bfd_elf32_bfd_reloc_type_lookup elf32_dlx_reloc_type_lookup
30#define elf_info_to_howto               elf32_dlx_info_to_howto
31#define elf_info_to_howto_rel           elf32_dlx_info_to_howto_rel
32#define elf_backend_check_relocs        elf32_dlx_check_relocs
33
34/* The gas default behavior is not to preform the %hi modifier so that the
35   GNU assembler can have the lower 16 bits offset placed in the insn, BUT
36   we do like the gas to indicate it is %hi reloc type so when we in the link
37   loader phase we can have the corrected hi16 vale replace the buggous lo16
38   value that was placed there by gas.  */
39
40static int skip_dlx_elf_hi16_reloc = 0;
41
42extern int set_dlx_skip_hi16_flag (int);
43
44int
45set_dlx_skip_hi16_flag (int flag)
46{
47  skip_dlx_elf_hi16_reloc = flag;
48  return flag;
49}
50
51static bfd_reloc_status_type
52_bfd_dlx_elf_hi16_reloc (bfd *abfd,
53			 arelent *reloc_entry,
54			 asymbol *symbol,
55			 void * data,
56			 asection *input_section,
57			 bfd *output_bfd,
58			 char **error_message)
59{
60  bfd_reloc_status_type ret;
61  bfd_vma relocation;
62
63  /* If the skip flag is set then we simply do the generic relocating, this
64     is more of a hack for dlx gas/gld, so we do not need to do the %hi/%lo
65     fixup like mips gld did.   */
66  if (skip_dlx_elf_hi16_reloc)
67    return bfd_elf_generic_reloc (abfd, reloc_entry, symbol, data,
68                          input_section, output_bfd, error_message);
69
70  /* If we're relocating, and this an external symbol, we don't want
71     to change anything.  */
72  if (output_bfd != (bfd *) NULL
73      && (symbol->flags & BSF_SECTION_SYM) == 0
74      && reloc_entry->addend == 0)
75    {
76      reloc_entry->address += input_section->output_offset;
77      return bfd_reloc_ok;
78    }
79
80  ret = bfd_reloc_ok;
81
82  if (bfd_is_und_section (symbol->section)
83      && output_bfd == (bfd *) NULL)
84    ret = bfd_reloc_undefined;
85
86  relocation = (bfd_is_com_section (symbol->section)) ? 0 : symbol->value;
87  relocation += symbol->section->output_section->vma;
88  relocation += symbol->section->output_offset;
89  relocation += reloc_entry->addend;
90  relocation += bfd_get_16 (abfd, (bfd_byte *)data + reloc_entry->address);
91
92  if (reloc_entry->address > bfd_get_section_limit (abfd, input_section))
93    return bfd_reloc_outofrange;
94
95  bfd_put_16 (abfd, (short)((relocation >> 16) & 0xFFFF),
96              (bfd_byte *)data + reloc_entry->address);
97
98  return ret;
99}
100
101/* ELF relocs are against symbols.  If we are producing relocatable
102   output, and the reloc is against an external symbol, and nothing
103   has given us any additional addend, the resulting reloc will also
104   be against the same symbol.  In such a case, we don't want to
105   change anything about the way the reloc is handled, since it will
106   all be done at final link time.  Rather than put special case code
107   into bfd_perform_relocation, all the reloc types use this howto
108   function.  It just short circuits the reloc if producing
109   relocatable output against an external symbol.  */
110
111static bfd_reloc_status_type
112elf32_dlx_relocate16 (bfd *abfd,
113		      arelent *reloc_entry,
114		      asymbol *symbol,
115		      void * data,
116		      asection *input_section,
117		      bfd *output_bfd,
118		      char **error_message ATTRIBUTE_UNUSED)
119{
120  unsigned long insn, vallo, allignment;
121  int           val;
122
123  /* HACK: I think this first condition is necessary when producing
124     relocatable output.  After the end of HACK, the code is identical
125     to bfd_elf_generic_reloc().  I would _guess_ the first change
126     belongs there rather than here.  martindo 1998-10-23.  */
127
128  if (skip_dlx_elf_hi16_reloc)
129    return bfd_elf_generic_reloc (abfd, reloc_entry, symbol, data,
130                                 input_section, output_bfd, error_message);
131
132  /* Check undefined section and undefined symbols.  */
133  if (bfd_is_und_section (symbol->section)
134      && output_bfd == (bfd *) NULL)
135    return bfd_reloc_undefined;
136
137  /* Can not support a long jump to sections other then .text.  */
138  if (strcmp (input_section->name, symbol->section->output_section->name) != 0)
139    {
140      fprintf (stderr,
141	       "BFD Link Error: branch (PC rel16) to section (%s) not supported\n",
142	       symbol->section->output_section->name);
143      return bfd_reloc_undefined;
144    }
145
146  insn  = bfd_get_32 (abfd, (bfd_byte *)data + reloc_entry->address);
147  allignment = 1 << (input_section->output_section->alignment_power - 1);
148  vallo = insn & 0x0000FFFF;
149
150  if (vallo & 0x8000)
151    vallo = ~(vallo | 0xFFFF0000) + 1;
152
153  /* vallo points to the vma of next instruction.  */
154  vallo += (((unsigned long)(input_section->output_section->vma +
155                           input_section->output_offset) +
156            allignment) & ~allignment);
157
158  /* val is the displacement (PC relative to next instruction).  */
159  val =  (symbol->section->output_offset +
160	  symbol->section->output_section->vma +
161	  symbol->value) - vallo;
162
163  if (abs ((int) val) > 0x00007FFF)
164    return bfd_reloc_outofrange;
165
166  insn  = (insn & 0xFFFF0000) | (val & 0x0000FFFF);
167
168  bfd_put_32 (abfd, insn,
169              (bfd_byte *) data + reloc_entry->address);
170
171  return bfd_reloc_ok;
172}
173
174static bfd_reloc_status_type
175elf32_dlx_relocate26 (bfd *abfd,
176		      arelent *reloc_entry,
177		      asymbol *symbol,
178		      void * data,
179		      asection *input_section,
180		      bfd *output_bfd,
181		      char **error_message ATTRIBUTE_UNUSED)
182{
183  unsigned long insn, vallo, allignment;
184  int           val;
185
186  /* HACK: I think this first condition is necessary when producing
187     relocatable output.  After the end of HACK, the code is identical
188     to bfd_elf_generic_reloc().  I would _guess_ the first change
189     belongs there rather than here.  martindo 1998-10-23.  */
190
191  if (skip_dlx_elf_hi16_reloc)
192    return bfd_elf_generic_reloc (abfd, reloc_entry, symbol, data,
193                                 input_section, output_bfd, error_message);
194
195  /* Check undefined section and undefined symbols.  */
196  if (bfd_is_und_section (symbol->section)
197      && output_bfd == (bfd *) NULL)
198    return bfd_reloc_undefined;
199
200  /* Can not support a long jump to sections other then .text   */
201  if (strcmp (input_section->name, symbol->section->output_section->name) != 0)
202    {
203      fprintf (stderr,
204	       "BFD Link Error: jump (PC rel26) to section (%s) not supported\n",
205	       symbol->section->output_section->name);
206      return bfd_reloc_undefined;
207    }
208
209  insn  = bfd_get_32 (abfd, (bfd_byte *)data + reloc_entry->address);
210  allignment = 1 << (input_section->output_section->alignment_power - 1);
211  vallo = insn & 0x03FFFFFF;
212
213  if (vallo & 0x03000000)
214    vallo = ~(vallo | 0xFC000000) + 1;
215
216  /* vallo is the vma for the next instruction.  */
217  vallo += (((unsigned long) (input_section->output_section->vma +
218			      input_section->output_offset) +
219	     allignment) & ~allignment);
220
221  /* val is the displacement (PC relative to next instruction).  */
222  val = (symbol->section->output_offset +
223	 symbol->section->output_section->vma + symbol->value)
224    - vallo;
225
226  if (abs ((int) val) > 0x01FFFFFF)
227    return bfd_reloc_outofrange;
228
229  insn  = (insn & 0xFC000000) | (val & 0x03FFFFFF);
230  bfd_put_32 (abfd, insn,
231              (bfd_byte *) data + reloc_entry->address);
232
233  return bfd_reloc_ok;
234}
235
236static reloc_howto_type dlx_elf_howto_table[]=
237{
238  /* No relocation.  */
239  HOWTO (R_DLX_NONE,            /* Type. */
240	 0,                     /* Rightshift.  */
241	 0,                     /* size (0 = byte, 1 = short, 2 = long).  */
242	 0,                     /* Bitsize.  */
243	 FALSE,                 /* PC_relative.  */
244	 0,                     /* Bitpos.  */
245	 complain_overflow_dont,/* Complain_on_overflow.  */
246	 bfd_elf_generic_reloc, /* Special_function.  */
247	 "R_DLX_NONE",          /* Name.  */
248	 FALSE,                 /* Partial_inplace.  */
249	 0,                     /* Src_mask.  */
250	 0,                     /* Dst_mask.  */
251	 FALSE),                /* PCrel_offset.  */
252
253  /* 8 bit relocation.  */
254  HOWTO (R_DLX_RELOC_8,         /* Type. */
255	 0,                     /* Rightshift.  */
256	 0,                     /* Size (0 = byte, 1 = short, 2 = long).  */
257	 8,                     /* Bitsize.  */
258	 FALSE,                 /* PC_relative.  */
259	 0,                     /* Bitpos.  */
260	 complain_overflow_dont,/* Complain_on_overflow.  */
261	 bfd_elf_generic_reloc, /* Special_function.  */
262	 "R_DLX_RELOC_8",       /* Name.  */
263	 TRUE,                  /* Partial_inplace.  */
264	 0xff,                  /* Src_mask.  */
265	 0xff,                  /* Dst_mask.  */
266	 FALSE),                /* PCrel_offset.  */
267
268  /* 16 bit relocation.  */
269  HOWTO (R_DLX_RELOC_16,        /* Type. */
270	 0,                     /* Rightshift.  */
271	 1,                     /* Size (0 = byte, 1 = short, 2 = long).  */
272	 16,                    /* Bitsize.  */
273	 FALSE,                 /* PC_relative.  */
274	 0,                     /* Bitpos.  */
275	 complain_overflow_dont,/* Complain_on_overflow.  */
276	 bfd_elf_generic_reloc, /* Special_function.  */
277	 "R_DLX_RELOC_16",      /* Name.  */
278	 TRUE,                  /* Partial_inplace.  */
279	 0xffff,                /* Src_mask.  */
280	 0xffff,                /* Dst_mask.  */
281	 FALSE),                /* PCrel_offset.  */
282
283  /* 32 bit relocation.  */
284  HOWTO (R_DLX_RELOC_32,        /* Type. */
285	 0,                     /* Rightshift.  */
286	 2,                     /* Size (0 = byte, 1 = short, 2 = long).  */
287	 32,                    /* Bitsize.  */
288	 FALSE,                 /* PC_relative.  */
289	 0,                     /* Bitpos.  */
290	 complain_overflow_dont,/* Complain_on_overflow.  */
291	 bfd_elf_generic_reloc, /* Special_function.  */
292	 "R_DLX_RELOC_32",      /* Name.  */
293	 TRUE,                  /* Partial_inplace.  */
294	 0xffffffff,            /* Src_mask.  */
295	 0xffffffff,            /* Dst_mask.  */
296	 FALSE),                /* PCrel_offset.  */
297
298  /* GNU extension to record C++ vtable hierarchy.  */
299  HOWTO (R_DLX_GNU_VTINHERIT,   /* Type. */
300	 0,			/* Rightshift.  */
301	 2,			/* Size (0 = byte, 1 = short, 2 = long).  */
302	 0,			/* Bitsize.  */
303	 FALSE,			/* PC_relative.  */
304	 0,			/* Bitpos.  */
305	 complain_overflow_dont,/* Complain_on_overflow.  */
306	 NULL,			/* Special_function.  */
307	 "R_DLX_GNU_VTINHERIT", /* Name.  */
308	 FALSE,			/* Partial_inplace.  */
309	 0,			/* Src_mask.  */
310	 0,			/* Dst_mask.  */
311	 FALSE),		/* PCrel_offset.  */
312
313  /* GNU extension to record C++ vtable member usage.  */
314  HOWTO (R_DLX_GNU_VTENTRY,     /* Type. */
315	 0,			/* Rightshift.  */
316	 2,			/* Size (0 = byte, 1 = short, 2 = long).  */
317	 0,			/* Bitsize.  */
318	 FALSE,			/* PC_relative.  */
319	 0,			/* Bitpos.  */
320	 complain_overflow_dont,/* Complain_on_overflow.  */
321	 _bfd_elf_rel_vtable_reloc_fn,/* Special_function.  */
322	 "R_DLX_GNU_VTENTRY",	/* Name.  */
323	 FALSE,		  	/* Partial_inplace.  */
324	 0,			/* Src_mask.  */
325	 0,			/* Dst_mask.  */
326	 FALSE)		  	/* PCrel_offset.  */
327};
328
329/* 16 bit offset for pc-relative branches.  */
330static reloc_howto_type elf_dlx_gnu_rel16_s2 =
331  HOWTO (R_DLX_RELOC_16_PCREL,  /* Type. */
332	 0,                     /* Rightshift.  */
333	 1,                     /* Size (0 = byte, 1 = short, 2 = long).  */
334	 16,                    /* Bitsize.  */
335	 TRUE,                  /* PC_relative.  */
336	 0,                     /* Bitpos.  */
337	 complain_overflow_signed, /* Complain_on_overflow.  */
338	 elf32_dlx_relocate16,  /* Special_function.  */
339	 "R_DLX_RELOC_16_PCREL",/* Name.  */
340	 TRUE,                  /* Partial_inplace.  */
341	 0xffff,                /* Src_mask.  */
342	 0xffff,                /* Dst_mask.  */
343	 TRUE);                 /* PCrel_offset.  */
344
345/* 26 bit offset for pc-relative branches.  */
346static reloc_howto_type elf_dlx_gnu_rel26_s2 =
347  HOWTO (R_DLX_RELOC_26_PCREL,  /* Type. */
348	 0,                     /* Rightshift.  */
349	 2,                     /* Size (0 = byte, 1 = short, 2 = long).  */
350	 26,                    /* Bitsize.  */
351	 TRUE,                  /* PC_relative.  */
352	 0,                     /* Bitpos.  */
353	 complain_overflow_dont,/* Complain_on_overflow.  */
354	 elf32_dlx_relocate26,  /* Special_function.  */
355	 "R_DLX_RELOC_26_PCREL",/* Name.  */
356	 TRUE,                  /* Partial_inplace.  */
357	 0xffff,                /* Src_mask.  */
358	 0xffff,                /* Dst_mask.  */
359	 TRUE);                 /* PCrel_offset.  */
360
361/* High 16 bits of symbol value.  */
362static reloc_howto_type elf_dlx_reloc_16_hi =
363  HOWTO (R_DLX_RELOC_16_HI,     /* Type. */
364	 16,                    /* Rightshift.  */
365	 2,                     /* Size (0 = byte, 1 = short, 2 = long).  */
366	 32,                    /* Bitsize.  */
367	 FALSE,                 /* PC_relative.  */
368	 0,                     /* Bitpos.  */
369	 complain_overflow_dont,/* Complain_on_overflow.  */
370	 _bfd_dlx_elf_hi16_reloc,/* Special_function.  */
371	 "R_DLX_RELOC_16_HI",   /* Name.  */
372	 TRUE,                  /* Partial_inplace.  */
373	 0xFFFF,                /* Src_mask.  */
374	 0xffff,                /* Dst_mask.  */
375	 FALSE);                /* PCrel_offset.  */
376
377  /* Low 16 bits of symbol value.  */
378static reloc_howto_type elf_dlx_reloc_16_lo =
379  HOWTO (R_DLX_RELOC_16_LO,     /* Type. */
380	 0,                     /* Rightshift.  */
381	 1,                     /* Size (0 = byte, 1 = short, 2 = long).  */
382	 16,                    /* Bitsize.  */
383	 FALSE,                 /* PC_relative.  */
384	 0,                     /* Bitpos.  */
385	 complain_overflow_dont,/* Complain_on_overflow.  */
386	 bfd_elf_generic_reloc, /* Special_function.  */
387	 "R_DLX_RELOC_16_LO",   /* Name.  */
388	 TRUE,                  /* Partial_inplace.  */
389	 0xffff,                /* Src_mask.  */
390	 0xffff,                /* Dst_mask.  */
391	 FALSE);                /* PCrel_offset.  */
392
393/* A mapping from BFD reloc types to DLX ELF reloc types.
394   Stolen from elf32-mips.c.
395
396   More about this table - for dlx elf relocation we do not really
397   need this table, if we have a rtype defined in this table will
398   caused tc_gen_relocate confused and die on us, but if we remove
399   this table it will caused more problem, so for now simple solution
400   is to remove those entries which may cause problem.  */
401struct elf_reloc_map
402{
403  bfd_reloc_code_real_type bfd_reloc_val;
404  enum elf_dlx_reloc_type elf_reloc_val;
405};
406
407static const struct elf_reloc_map dlx_reloc_map[] =
408{
409  { BFD_RELOC_NONE,           R_DLX_NONE },
410  { BFD_RELOC_16,             R_DLX_RELOC_16 },
411  { BFD_RELOC_32,             R_DLX_RELOC_32 },
412  { BFD_RELOC_DLX_HI16_S,     R_DLX_RELOC_16_HI },
413  { BFD_RELOC_DLX_LO16,       R_DLX_RELOC_16_LO },
414  { BFD_RELOC_VTABLE_INHERIT,	R_DLX_GNU_VTINHERIT },
415  { BFD_RELOC_VTABLE_ENTRY,	R_DLX_GNU_VTENTRY }
416};
417
418/* Look through the relocs for a section during the first phase.
419   Since we don't do .gots or .plts, we just need to consider the
420   virtual table relocs for gc.  */
421
422static bfd_boolean
423elf32_dlx_check_relocs (bfd *abfd,
424			struct bfd_link_info *info,
425			asection *sec,
426			const Elf_Internal_Rela *relocs)
427{
428  Elf_Internal_Shdr *symtab_hdr;
429  struct elf_link_hash_entry **sym_hashes, **sym_hashes_end;
430  const Elf_Internal_Rela *rel;
431  const Elf_Internal_Rela *rel_end;
432
433  if (info->relocatable)
434    return TRUE;
435
436  symtab_hdr = &elf_tdata (abfd)->symtab_hdr;
437  sym_hashes = elf_sym_hashes (abfd);
438  sym_hashes_end = sym_hashes + symtab_hdr->sh_size / sizeof (Elf32_External_Sym);
439  if (!elf_bad_symtab (abfd))
440    sym_hashes_end -= symtab_hdr->sh_info;
441
442  rel_end = relocs + sec->reloc_count;
443  for (rel = relocs; rel < rel_end; rel++)
444    {
445      struct elf_link_hash_entry *h;
446      unsigned long r_symndx;
447
448      r_symndx = ELF32_R_SYM (rel->r_info);
449      if (r_symndx < symtab_hdr->sh_info)
450        h = NULL;
451      else
452	{
453	  h = sym_hashes[r_symndx - symtab_hdr->sh_info];
454	  while (h->root.type == bfd_link_hash_indirect
455		 || h->root.type == bfd_link_hash_warning)
456	    h = (struct elf_link_hash_entry *) h->root.u.i.link;
457	}
458
459      switch (ELF32_R_TYPE (rel->r_info))
460        {
461        /* This relocation describes the C++ object vtable hierarchy.
462           Reconstruct it for later use during GC.  */
463        case R_DLX_GNU_VTINHERIT:
464          if (!bfd_elf_gc_record_vtinherit (abfd, sec, h, rel->r_offset))
465            return FALSE;
466          break;
467
468        /* This relocation describes which C++ vtable entries are actually
469           used.  Record for later use during GC.  */
470        case R_DLX_GNU_VTENTRY:
471          if (!bfd_elf_gc_record_vtentry (abfd, sec, h, rel->r_addend))
472            return FALSE;
473          break;
474        }
475    }
476
477  return TRUE;
478}
479
480/* Given a BFD reloc type, return a howto structure.  */
481
482static reloc_howto_type *
483elf32_dlx_reloc_type_lookup (bfd *abfd ATTRIBUTE_UNUSED,
484			     bfd_reloc_code_real_type code)
485{
486  unsigned int i;
487
488  for (i = 0; i < sizeof (dlx_reloc_map) / sizeof (struct elf_reloc_map); i++)
489    if (dlx_reloc_map[i].bfd_reloc_val == code)
490      return &dlx_elf_howto_table[(int) dlx_reloc_map[i].elf_reloc_val];
491
492  switch (code)
493    {
494    default:
495      bfd_set_error (bfd_error_bad_value);
496      return NULL;
497    case BFD_RELOC_16_PCREL_S2:
498      return &elf_dlx_gnu_rel16_s2;
499    case BFD_RELOC_DLX_JMP26:
500      return &elf_dlx_gnu_rel26_s2;
501    case BFD_RELOC_HI16_S:
502      return &elf_dlx_reloc_16_hi;
503    case BFD_RELOC_LO16:
504      return &elf_dlx_reloc_16_lo;
505    }
506}
507
508static reloc_howto_type *
509dlx_rtype_to_howto (unsigned int r_type)
510{
511  switch (r_type)
512    {
513    case R_DLX_RELOC_16_PCREL:
514      return & elf_dlx_gnu_rel16_s2;
515      break;
516    case R_DLX_RELOC_26_PCREL:
517      return & elf_dlx_gnu_rel26_s2;
518      break;
519    case R_DLX_RELOC_16_HI:
520      return & elf_dlx_reloc_16_hi;
521      break;
522    case R_DLX_RELOC_16_LO:
523      return & elf_dlx_reloc_16_lo;
524      break;
525
526    default:
527      BFD_ASSERT (r_type < (unsigned int) R_DLX_max);
528      return & dlx_elf_howto_table[r_type];
529      break;
530    }
531}
532
533static void
534elf32_dlx_info_to_howto (bfd * abfd ATTRIBUTE_UNUSED,
535			 arelent * cache_ptr ATTRIBUTE_UNUSED,
536			 Elf_Internal_Rela * dst ATTRIBUTE_UNUSED)
537{
538  abort ();
539}
540
541static void
542elf32_dlx_info_to_howto_rel (bfd *abfd ATTRIBUTE_UNUSED,
543			     arelent *cache_ptr,
544			     Elf_Internal_Rela *dst)
545{
546  unsigned int r_type;
547
548  r_type = ELF32_R_TYPE (dst->r_info);
549  cache_ptr->howto = dlx_rtype_to_howto (r_type);
550  return;
551}
552
553#define TARGET_BIG_SYM          bfd_elf32_dlx_big_vec
554#define TARGET_BIG_NAME         "elf32-dlx"
555#define ELF_ARCH                bfd_arch_dlx
556#define ELF_MACHINE_CODE        EM_DLX
557#define ELF_MAXPAGESIZE         1 /* FIXME: This number is wrong,  It should be the page size in bytes.  */
558
559#include "elf32-target.h"
560