1*3d8817e4Smiod /* OpenRISC-specific support for 32-bit ELF.
2*3d8817e4Smiod Copyright 2001, 2002, 2003, 2004, 2005 Free Software Foundation, Inc.
3*3d8817e4Smiod Contributed by Johan Rydberg, jrydberg@opencores.org
4*3d8817e4Smiod
5*3d8817e4Smiod This file is part of BFD, the Binary File Descriptor library.
6*3d8817e4Smiod
7*3d8817e4Smiod This program is free software; you can redistribute it and/or modify
8*3d8817e4Smiod it under the terms of the GNU General Public License as published by
9*3d8817e4Smiod the Free Software Foundation; either version 2 of the License, or
10*3d8817e4Smiod (at your option) any later version.
11*3d8817e4Smiod
12*3d8817e4Smiod This program is distributed in the hope that it will be useful,
13*3d8817e4Smiod but WITHOUT ANY WARRANTY; without even the implied warranty of
14*3d8817e4Smiod MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15*3d8817e4Smiod GNU General Public License for more details.
16*3d8817e4Smiod
17*3d8817e4Smiod You should have received a copy of the GNU General Public License
18*3d8817e4Smiod along with this program; if not, write to the Free Software
19*3d8817e4Smiod Foundation, Inc., 51 Franklin Street - Fifth Floor, Boston, MA 02110-1301,
20*3d8817e4Smiod USA. */
21*3d8817e4Smiod
22*3d8817e4Smiod #include "bfd.h"
23*3d8817e4Smiod #include "sysdep.h"
24*3d8817e4Smiod #include "libbfd.h"
25*3d8817e4Smiod #include "elf-bfd.h"
26*3d8817e4Smiod #include "elf/openrisc.h"
27*3d8817e4Smiod #include "libiberty.h"
28*3d8817e4Smiod
29*3d8817e4Smiod static reloc_howto_type openrisc_elf_howto_table[] =
30*3d8817e4Smiod {
31*3d8817e4Smiod /* This reloc does nothing. */
32*3d8817e4Smiod HOWTO (R_OPENRISC_NONE, /* type */
33*3d8817e4Smiod 0, /* rightshift */
34*3d8817e4Smiod 2, /* size (0 = byte, 1 = short, 2 = long) */
35*3d8817e4Smiod 32, /* bitsize */
36*3d8817e4Smiod FALSE, /* pc_relative */
37*3d8817e4Smiod 0, /* bitpos */
38*3d8817e4Smiod complain_overflow_bitfield, /* complain_on_overflow */
39*3d8817e4Smiod bfd_elf_generic_reloc, /* special_function */
40*3d8817e4Smiod "R_OPENRISC_NONE", /* name */
41*3d8817e4Smiod FALSE, /* partial_inplace */
42*3d8817e4Smiod 0, /* src_mask */
43*3d8817e4Smiod 0, /* dst_mask */
44*3d8817e4Smiod FALSE), /* pcrel_offset */
45*3d8817e4Smiod
46*3d8817e4Smiod /* A PC relative 26 bit relocation, right shifted by 2. */
47*3d8817e4Smiod HOWTO (R_OPENRISC_INSN_REL_26, /* type */
48*3d8817e4Smiod 2, /* rightshift */
49*3d8817e4Smiod 2, /* size (0 = byte, 1 = short, 2 = long) */
50*3d8817e4Smiod 26, /* bitsize */
51*3d8817e4Smiod TRUE, /* pc_relative */
52*3d8817e4Smiod 0, /* bitpos */
53*3d8817e4Smiod complain_overflow_signed, /* complain_on_overflow */
54*3d8817e4Smiod bfd_elf_generic_reloc, /* special_function */
55*3d8817e4Smiod "R_OPENRISC_INSN_REL_26", /* name */
56*3d8817e4Smiod FALSE, /* partial_inplace */
57*3d8817e4Smiod 0x00000000, /* src_mask */
58*3d8817e4Smiod 0x03ffffff, /* dst_mask */
59*3d8817e4Smiod FALSE), /* pcrel_offset */
60*3d8817e4Smiod
61*3d8817e4Smiod /* A absolute 26 bit relocation, right shifted by 2. */
62*3d8817e4Smiod HOWTO (R_OPENRISC_INSN_ABS_26, /* type */
63*3d8817e4Smiod 2, /* rightshift */
64*3d8817e4Smiod 2, /* size (0 = byte, 1 = short, 2 = long) */
65*3d8817e4Smiod 26, /* bitsize */
66*3d8817e4Smiod FALSE, /* pc_relative */
67*3d8817e4Smiod 0, /* bitpos */
68*3d8817e4Smiod complain_overflow_signed, /* complain_on_overflow */
69*3d8817e4Smiod bfd_elf_generic_reloc, /* special_function */
70*3d8817e4Smiod "R_OPENRISC_INSN_ABS_26", /* name */
71*3d8817e4Smiod FALSE, /* partial_inplace */
72*3d8817e4Smiod 0x00000000, /* src_mask */
73*3d8817e4Smiod 0x03ffffff, /* dst_mask */
74*3d8817e4Smiod FALSE), /* pcrel_offset */
75*3d8817e4Smiod
76*3d8817e4Smiod HOWTO (R_OPENRISC_LO_16_IN_INSN, /* type */
77*3d8817e4Smiod 0, /* rightshift */
78*3d8817e4Smiod 1, /* size (0 = byte, 1 = short, 2 = long) */
79*3d8817e4Smiod 16, /* bitsize */
80*3d8817e4Smiod FALSE, /* pc_relative */
81*3d8817e4Smiod 0, /* bitpos */
82*3d8817e4Smiod complain_overflow_dont, /* complain_on_overflow */
83*3d8817e4Smiod bfd_elf_generic_reloc, /* special_function */
84*3d8817e4Smiod "R_OPENRISC_LO_16_IN_INSN", /* name */
85*3d8817e4Smiod FALSE, /* partial_inplace */
86*3d8817e4Smiod 0, /* src_mask */
87*3d8817e4Smiod 0x0000ffff, /* dst_mask */
88*3d8817e4Smiod FALSE), /* pcrel_offset */
89*3d8817e4Smiod
90*3d8817e4Smiod HOWTO (R_OPENRISC_HI_16_IN_INSN, /* type */
91*3d8817e4Smiod 16, /* rightshift */
92*3d8817e4Smiod 1, /* size (0 = byte, 1 = short, 2 = long) */
93*3d8817e4Smiod 16, /* bitsize */
94*3d8817e4Smiod FALSE, /* pc_relative */
95*3d8817e4Smiod 0, /* bitpos */
96*3d8817e4Smiod complain_overflow_dont, /* complain_on_overflow */
97*3d8817e4Smiod bfd_elf_generic_reloc, /* special_function */
98*3d8817e4Smiod "R_OPENRISC_HI_16_IN_INSN", /* name */
99*3d8817e4Smiod FALSE, /* partial_inplace */
100*3d8817e4Smiod 0, /* src_mask */
101*3d8817e4Smiod 0x0000ffff, /* dst_mask */
102*3d8817e4Smiod FALSE), /* pcrel_offset */
103*3d8817e4Smiod
104*3d8817e4Smiod /* An 8 bit absolute relocation. */
105*3d8817e4Smiod HOWTO (R_OPENRISC_8, /* type */
106*3d8817e4Smiod 0, /* rightshift */
107*3d8817e4Smiod 0, /* size (0 = byte, 1 = short, 2 = long) */
108*3d8817e4Smiod 8, /* bitsize */
109*3d8817e4Smiod FALSE, /* pc_relative */
110*3d8817e4Smiod 0, /* bitpos */
111*3d8817e4Smiod complain_overflow_bitfield, /* complain_on_overflow */
112*3d8817e4Smiod bfd_elf_generic_reloc, /* special_function */
113*3d8817e4Smiod "R_OPENRISC_8", /* name */
114*3d8817e4Smiod TRUE, /* partial_inplace */
115*3d8817e4Smiod 0x0000, /* src_mask */
116*3d8817e4Smiod 0x00ff, /* dst_mask */
117*3d8817e4Smiod FALSE), /* pcrel_offset */
118*3d8817e4Smiod
119*3d8817e4Smiod /* A 16 bit absolute relocation. */
120*3d8817e4Smiod HOWTO (R_OPENRISC_16, /* type */
121*3d8817e4Smiod 0, /* rightshift */
122*3d8817e4Smiod 1, /* size (0 = byte, 1 = short, 2 = long) */
123*3d8817e4Smiod 16, /* bitsize */
124*3d8817e4Smiod FALSE, /* pc_relative */
125*3d8817e4Smiod 0, /* bitpos */
126*3d8817e4Smiod complain_overflow_bitfield, /* complain_on_overflow */
127*3d8817e4Smiod bfd_elf_generic_reloc, /* special_function */
128*3d8817e4Smiod "R_OPENRISC_16", /* name */
129*3d8817e4Smiod TRUE, /* partial_inplace */
130*3d8817e4Smiod 0x00000000, /* src_mask */
131*3d8817e4Smiod 0x0000ffff, /* dst_mask */
132*3d8817e4Smiod FALSE), /* pcrel_offset */
133*3d8817e4Smiod
134*3d8817e4Smiod /* A 32 bit absolute relocation. */
135*3d8817e4Smiod HOWTO (R_OPENRISC_32, /* type */
136*3d8817e4Smiod 0, /* rightshift */
137*3d8817e4Smiod 2, /* size (0 = byte, 1 = short, 2 = long) */
138*3d8817e4Smiod 32, /* bitsize */
139*3d8817e4Smiod FALSE, /* pc_relative */
140*3d8817e4Smiod 0, /* bitpos */
141*3d8817e4Smiod complain_overflow_bitfield, /* complain_on_overflow */
142*3d8817e4Smiod bfd_elf_generic_reloc, /* special_function */
143*3d8817e4Smiod "R_OPENRISC_32", /* name */
144*3d8817e4Smiod TRUE, /* partial_inplace */
145*3d8817e4Smiod 0x00000000, /* src_mask */
146*3d8817e4Smiod 0xffffffff, /* dst_mask */
147*3d8817e4Smiod FALSE), /* pcrel_offset */
148*3d8817e4Smiod
149*3d8817e4Smiod /* GNU extension to record C++ vtable hierarchy. */
150*3d8817e4Smiod HOWTO (R_OPENRISC_GNU_VTINHERIT, /* type */
151*3d8817e4Smiod 0, /* rightshift */
152*3d8817e4Smiod 2, /* size (0 = byte, 1 = short, 2 = long) */
153*3d8817e4Smiod 0, /* bitsize */
154*3d8817e4Smiod FALSE, /* pc_relative */
155*3d8817e4Smiod 0, /* bitpos */
156*3d8817e4Smiod complain_overflow_dont, /* complain_on_overflow */
157*3d8817e4Smiod NULL, /* special_function */
158*3d8817e4Smiod "R_OPENRISC_GNU_VTINHERIT", /* name */
159*3d8817e4Smiod FALSE, /* partial_inplace */
160*3d8817e4Smiod 0, /* src_mask */
161*3d8817e4Smiod 0, /* dst_mask */
162*3d8817e4Smiod FALSE), /* pcrel_offset */
163*3d8817e4Smiod
164*3d8817e4Smiod /* GNU extension to record C++ vtable member usage. */
165*3d8817e4Smiod HOWTO (R_OPENRISC_GNU_VTENTRY, /* type */
166*3d8817e4Smiod 0, /* rightshift */
167*3d8817e4Smiod 2, /* size (0 = byte, 1 = short, 2 = long) */
168*3d8817e4Smiod 0, /* bitsize */
169*3d8817e4Smiod FALSE, /* pc_relative */
170*3d8817e4Smiod 0, /* bitpos */
171*3d8817e4Smiod complain_overflow_dont, /* complain_on_overflow */
172*3d8817e4Smiod _bfd_elf_rel_vtable_reloc_fn, /* special_function */
173*3d8817e4Smiod "R_OPENRISC_GNU_VTENTRY", /* name */
174*3d8817e4Smiod FALSE, /* partial_inplace */
175*3d8817e4Smiod 0, /* src_mask */
176*3d8817e4Smiod 0, /* dst_mask */
177*3d8817e4Smiod FALSE), /* pcrel_offset */
178*3d8817e4Smiod };
179*3d8817e4Smiod
180*3d8817e4Smiod /* Map BFD reloc types to OpenRISC ELF reloc types. */
181*3d8817e4Smiod
182*3d8817e4Smiod struct openrisc_reloc_map
183*3d8817e4Smiod {
184*3d8817e4Smiod bfd_reloc_code_real_type bfd_reloc_val;
185*3d8817e4Smiod unsigned int openrisc_reloc_val;
186*3d8817e4Smiod };
187*3d8817e4Smiod
188*3d8817e4Smiod static const struct openrisc_reloc_map openrisc_reloc_map[] =
189*3d8817e4Smiod {
190*3d8817e4Smiod { BFD_RELOC_NONE, R_OPENRISC_NONE },
191*3d8817e4Smiod { BFD_RELOC_32, R_OPENRISC_32 },
192*3d8817e4Smiod { BFD_RELOC_16, R_OPENRISC_16 },
193*3d8817e4Smiod { BFD_RELOC_8, R_OPENRISC_8 },
194*3d8817e4Smiod { BFD_RELOC_OPENRISC_REL_26,R_OPENRISC_INSN_REL_26 },
195*3d8817e4Smiod { BFD_RELOC_OPENRISC_ABS_26,R_OPENRISC_INSN_ABS_26 },
196*3d8817e4Smiod { BFD_RELOC_HI16, R_OPENRISC_HI_16_IN_INSN },
197*3d8817e4Smiod { BFD_RELOC_LO16, R_OPENRISC_LO_16_IN_INSN },
198*3d8817e4Smiod { BFD_RELOC_VTABLE_INHERIT, R_OPENRISC_GNU_VTINHERIT },
199*3d8817e4Smiod { BFD_RELOC_VTABLE_ENTRY, R_OPENRISC_GNU_VTENTRY }
200*3d8817e4Smiod };
201*3d8817e4Smiod
202*3d8817e4Smiod static reloc_howto_type *
openrisc_reloc_type_lookup(bfd * abfd ATTRIBUTE_UNUSED,bfd_reloc_code_real_type code)203*3d8817e4Smiod openrisc_reloc_type_lookup (bfd * abfd ATTRIBUTE_UNUSED,
204*3d8817e4Smiod bfd_reloc_code_real_type code)
205*3d8817e4Smiod {
206*3d8817e4Smiod unsigned int i;
207*3d8817e4Smiod
208*3d8817e4Smiod for (i = ARRAY_SIZE (openrisc_reloc_map); --i;)
209*3d8817e4Smiod if (openrisc_reloc_map[i].bfd_reloc_val == code)
210*3d8817e4Smiod return & openrisc_elf_howto_table[openrisc_reloc_map[i].
211*3d8817e4Smiod openrisc_reloc_val];
212*3d8817e4Smiod
213*3d8817e4Smiod return NULL;
214*3d8817e4Smiod }
215*3d8817e4Smiod
216*3d8817e4Smiod /* Set the howto pointer for an OpenRISC ELF reloc. */
217*3d8817e4Smiod
218*3d8817e4Smiod static void
openrisc_info_to_howto_rela(bfd * abfd ATTRIBUTE_UNUSED,arelent * cache_ptr,Elf_Internal_Rela * dst)219*3d8817e4Smiod openrisc_info_to_howto_rela (bfd * abfd ATTRIBUTE_UNUSED,
220*3d8817e4Smiod arelent * cache_ptr,
221*3d8817e4Smiod Elf_Internal_Rela * dst)
222*3d8817e4Smiod {
223*3d8817e4Smiod unsigned int r_type;
224*3d8817e4Smiod
225*3d8817e4Smiod r_type = ELF32_R_TYPE (dst->r_info);
226*3d8817e4Smiod BFD_ASSERT (r_type < (unsigned int) R_OPENRISC_max);
227*3d8817e4Smiod cache_ptr->howto = & openrisc_elf_howto_table[r_type];
228*3d8817e4Smiod }
229*3d8817e4Smiod
230*3d8817e4Smiod /* Perform a single relocation. By default we use the standard BFD
231*3d8817e4Smiod routines, but a few relocs, we have to do them ourselves. */
232*3d8817e4Smiod
233*3d8817e4Smiod static bfd_reloc_status_type
openrisc_final_link_relocate(reloc_howto_type * howto,bfd * input_bfd,asection * input_section,bfd_byte * contents,Elf_Internal_Rela * rel,bfd_vma relocation)234*3d8817e4Smiod openrisc_final_link_relocate (reloc_howto_type *howto,
235*3d8817e4Smiod bfd *input_bfd,
236*3d8817e4Smiod asection *input_section,
237*3d8817e4Smiod bfd_byte *contents,
238*3d8817e4Smiod Elf_Internal_Rela *rel,
239*3d8817e4Smiod bfd_vma relocation)
240*3d8817e4Smiod {
241*3d8817e4Smiod bfd_reloc_status_type r = bfd_reloc_ok;
242*3d8817e4Smiod
243*3d8817e4Smiod switch (howto->type)
244*3d8817e4Smiod {
245*3d8817e4Smiod case R_OPENRISC_LO_16_IN_INSN:
246*3d8817e4Smiod relocation &= 0xffff;
247*3d8817e4Smiod r = _bfd_final_link_relocate (howto, input_bfd, input_section,
248*3d8817e4Smiod contents, rel->r_offset,
249*3d8817e4Smiod relocation, rel->r_addend);
250*3d8817e4Smiod break;
251*3d8817e4Smiod
252*3d8817e4Smiod default:
253*3d8817e4Smiod r = _bfd_final_link_relocate (howto, input_bfd, input_section,
254*3d8817e4Smiod contents, rel->r_offset,
255*3d8817e4Smiod relocation, rel->r_addend);
256*3d8817e4Smiod }
257*3d8817e4Smiod
258*3d8817e4Smiod return r;
259*3d8817e4Smiod }
260*3d8817e4Smiod
261*3d8817e4Smiod /* Relocate an OpenRISC ELF section.
262*3d8817e4Smiod
263*3d8817e4Smiod The RELOCATE_SECTION function is called by the new ELF backend linker
264*3d8817e4Smiod to handle the relocations for a section.
265*3d8817e4Smiod
266*3d8817e4Smiod The relocs are always passed as Rela structures; if the section
267*3d8817e4Smiod actually uses Rel structures, the r_addend field will always be
268*3d8817e4Smiod zero.
269*3d8817e4Smiod
270*3d8817e4Smiod This function is responsible for adjusting the section contents as
271*3d8817e4Smiod necessary, and (if using Rela relocs and generating a relocatable
272*3d8817e4Smiod output file) adjusting the reloc addend as necessary.
273*3d8817e4Smiod
274*3d8817e4Smiod This function does not have to worry about setting the reloc
275*3d8817e4Smiod address or the reloc symbol index.
276*3d8817e4Smiod
277*3d8817e4Smiod LOCAL_SYMS is a pointer to the swapped in local symbols.
278*3d8817e4Smiod
279*3d8817e4Smiod LOCAL_SECTIONS is an array giving the section in the input file
280*3d8817e4Smiod corresponding to the st_shndx field of each local symbol.
281*3d8817e4Smiod
282*3d8817e4Smiod The global hash table entry for the global symbols can be found
283*3d8817e4Smiod via elf_sym_hashes (input_bfd).
284*3d8817e4Smiod
285*3d8817e4Smiod When generating relocatable output, this function must handle
286*3d8817e4Smiod STB_LOCAL/STT_SECTION symbols specially. The output symbol is
287*3d8817e4Smiod going to be the section symbol corresponding to the output
288*3d8817e4Smiod section, which means that the addend must be adjusted
289*3d8817e4Smiod accordingly. */
290*3d8817e4Smiod
291*3d8817e4Smiod static bfd_boolean
openrisc_elf_relocate_section(bfd * output_bfd,struct bfd_link_info * info,bfd * input_bfd,asection * input_section,bfd_byte * contents,Elf_Internal_Rela * relocs,Elf_Internal_Sym * local_syms,asection ** local_sections)292*3d8817e4Smiod openrisc_elf_relocate_section (bfd *output_bfd,
293*3d8817e4Smiod struct bfd_link_info *info,
294*3d8817e4Smiod bfd *input_bfd,
295*3d8817e4Smiod asection *input_section,
296*3d8817e4Smiod bfd_byte *contents,
297*3d8817e4Smiod Elf_Internal_Rela *relocs,
298*3d8817e4Smiod Elf_Internal_Sym *local_syms,
299*3d8817e4Smiod asection **local_sections)
300*3d8817e4Smiod {
301*3d8817e4Smiod Elf_Internal_Shdr *symtab_hdr;
302*3d8817e4Smiod struct elf_link_hash_entry **sym_hashes;
303*3d8817e4Smiod Elf_Internal_Rela *rel;
304*3d8817e4Smiod Elf_Internal_Rela *relend;
305*3d8817e4Smiod
306*3d8817e4Smiod if (info->relocatable)
307*3d8817e4Smiod return TRUE;
308*3d8817e4Smiod
309*3d8817e4Smiod symtab_hdr = &elf_tdata (input_bfd)->symtab_hdr;
310*3d8817e4Smiod sym_hashes = elf_sym_hashes (input_bfd);
311*3d8817e4Smiod relend = relocs + input_section->reloc_count;
312*3d8817e4Smiod
313*3d8817e4Smiod for (rel = relocs; rel < relend; rel++)
314*3d8817e4Smiod {
315*3d8817e4Smiod reloc_howto_type *howto;
316*3d8817e4Smiod unsigned long r_symndx;
317*3d8817e4Smiod Elf_Internal_Sym *sym;
318*3d8817e4Smiod asection *sec;
319*3d8817e4Smiod struct elf_link_hash_entry *h;
320*3d8817e4Smiod bfd_vma relocation;
321*3d8817e4Smiod bfd_reloc_status_type r;
322*3d8817e4Smiod const char *name = NULL;
323*3d8817e4Smiod int r_type;
324*3d8817e4Smiod
325*3d8817e4Smiod r_type = ELF32_R_TYPE (rel->r_info);
326*3d8817e4Smiod r_symndx = ELF32_R_SYM (rel->r_info);
327*3d8817e4Smiod
328*3d8817e4Smiod if (r_type == R_OPENRISC_GNU_VTINHERIT
329*3d8817e4Smiod || r_type == R_OPENRISC_GNU_VTENTRY)
330*3d8817e4Smiod continue;
331*3d8817e4Smiod
332*3d8817e4Smiod if ((unsigned int) r_type >
333*3d8817e4Smiod (sizeof openrisc_elf_howto_table / sizeof (reloc_howto_type)))
334*3d8817e4Smiod abort ();
335*3d8817e4Smiod
336*3d8817e4Smiod /* This is a final link. */
337*3d8817e4Smiod howto = openrisc_elf_howto_table + ELF32_R_TYPE (rel->r_info);
338*3d8817e4Smiod h = NULL;
339*3d8817e4Smiod sym = NULL;
340*3d8817e4Smiod sec = NULL;
341*3d8817e4Smiod
342*3d8817e4Smiod if (r_symndx < symtab_hdr->sh_info)
343*3d8817e4Smiod {
344*3d8817e4Smiod sym = local_syms + r_symndx;
345*3d8817e4Smiod sec = local_sections[r_symndx];
346*3d8817e4Smiod relocation = _bfd_elf_rela_local_sym (output_bfd, sym, &sec, rel);
347*3d8817e4Smiod
348*3d8817e4Smiod name = bfd_elf_string_from_elf_section
349*3d8817e4Smiod (input_bfd, symtab_hdr->sh_link, sym->st_name);
350*3d8817e4Smiod name = (name == NULL) ? bfd_section_name (input_bfd, sec) : name;
351*3d8817e4Smiod }
352*3d8817e4Smiod else
353*3d8817e4Smiod {
354*3d8817e4Smiod bfd_boolean unresolved_reloc, warned;
355*3d8817e4Smiod
356*3d8817e4Smiod RELOC_FOR_GLOBAL_SYMBOL (info, input_bfd, input_section, rel,
357*3d8817e4Smiod r_symndx, symtab_hdr, sym_hashes,
358*3d8817e4Smiod h, sec, relocation,
359*3d8817e4Smiod unresolved_reloc, warned);
360*3d8817e4Smiod }
361*3d8817e4Smiod
362*3d8817e4Smiod r = openrisc_final_link_relocate (howto, input_bfd, input_section,
363*3d8817e4Smiod contents, rel, relocation);
364*3d8817e4Smiod
365*3d8817e4Smiod if (r != bfd_reloc_ok)
366*3d8817e4Smiod {
367*3d8817e4Smiod const char *msg = NULL;
368*3d8817e4Smiod
369*3d8817e4Smiod switch (r)
370*3d8817e4Smiod {
371*3d8817e4Smiod case bfd_reloc_overflow:
372*3d8817e4Smiod r = info->callbacks->reloc_overflow
373*3d8817e4Smiod (info, (h ? &h->root : NULL), name, howto->name,
374*3d8817e4Smiod (bfd_vma) 0, input_bfd, input_section, rel->r_offset);
375*3d8817e4Smiod break;
376*3d8817e4Smiod
377*3d8817e4Smiod case bfd_reloc_undefined:
378*3d8817e4Smiod r = info->callbacks->undefined_symbol
379*3d8817e4Smiod (info, name, input_bfd, input_section, rel->r_offset, TRUE);
380*3d8817e4Smiod break;
381*3d8817e4Smiod
382*3d8817e4Smiod case bfd_reloc_outofrange:
383*3d8817e4Smiod msg = _("internal error: out of range error");
384*3d8817e4Smiod break;
385*3d8817e4Smiod
386*3d8817e4Smiod case bfd_reloc_notsupported:
387*3d8817e4Smiod msg = _("internal error: unsupported relocation error");
388*3d8817e4Smiod break;
389*3d8817e4Smiod
390*3d8817e4Smiod case bfd_reloc_dangerous:
391*3d8817e4Smiod msg = _("internal error: dangerous relocation");
392*3d8817e4Smiod break;
393*3d8817e4Smiod
394*3d8817e4Smiod default:
395*3d8817e4Smiod msg = _("internal error: unknown error");
396*3d8817e4Smiod break;
397*3d8817e4Smiod }
398*3d8817e4Smiod
399*3d8817e4Smiod if (msg)
400*3d8817e4Smiod r = info->callbacks->warning
401*3d8817e4Smiod (info, msg, name, input_bfd, input_section, rel->r_offset);
402*3d8817e4Smiod
403*3d8817e4Smiod if (!r)
404*3d8817e4Smiod return FALSE;
405*3d8817e4Smiod }
406*3d8817e4Smiod }
407*3d8817e4Smiod
408*3d8817e4Smiod return TRUE;
409*3d8817e4Smiod }
410*3d8817e4Smiod
411*3d8817e4Smiod /* Return the section that should be marked against GC for a given
412*3d8817e4Smiod relocation. */
413*3d8817e4Smiod
414*3d8817e4Smiod static asection *
openrisc_elf_gc_mark_hook(asection * sec,struct bfd_link_info * info ATTRIBUTE_UNUSED,Elf_Internal_Rela * rel,struct elf_link_hash_entry * h,Elf_Internal_Sym * sym)415*3d8817e4Smiod openrisc_elf_gc_mark_hook (asection *sec,
416*3d8817e4Smiod struct bfd_link_info *info ATTRIBUTE_UNUSED,
417*3d8817e4Smiod Elf_Internal_Rela *rel,
418*3d8817e4Smiod struct elf_link_hash_entry *h,
419*3d8817e4Smiod Elf_Internal_Sym *sym)
420*3d8817e4Smiod {
421*3d8817e4Smiod if (h == NULL)
422*3d8817e4Smiod return bfd_section_from_elf_index (sec->owner, sym->st_shndx);
423*3d8817e4Smiod
424*3d8817e4Smiod switch (ELF32_R_TYPE (rel->r_info))
425*3d8817e4Smiod {
426*3d8817e4Smiod case R_OPENRISC_GNU_VTINHERIT:
427*3d8817e4Smiod case R_OPENRISC_GNU_VTENTRY:
428*3d8817e4Smiod break;
429*3d8817e4Smiod
430*3d8817e4Smiod default:
431*3d8817e4Smiod switch (h->root.type)
432*3d8817e4Smiod {
433*3d8817e4Smiod case bfd_link_hash_defined:
434*3d8817e4Smiod case bfd_link_hash_defweak:
435*3d8817e4Smiod return h->root.u.def.section;
436*3d8817e4Smiod
437*3d8817e4Smiod case bfd_link_hash_common:
438*3d8817e4Smiod return h->root.u.c.p->section;
439*3d8817e4Smiod
440*3d8817e4Smiod default:
441*3d8817e4Smiod break;
442*3d8817e4Smiod }
443*3d8817e4Smiod }
444*3d8817e4Smiod
445*3d8817e4Smiod return NULL;
446*3d8817e4Smiod }
447*3d8817e4Smiod
448*3d8817e4Smiod /* Update the got entry reference counts for the section being removed. */
449*3d8817e4Smiod
450*3d8817e4Smiod static bfd_boolean
openrisc_elf_gc_sweep_hook(bfd * abfd ATTRIBUTE_UNUSED,struct bfd_link_info * info ATTRIBUTE_UNUSED,asection * sec ATTRIBUTE_UNUSED,const Elf_Internal_Rela * relocs ATTRIBUTE_UNUSED)451*3d8817e4Smiod openrisc_elf_gc_sweep_hook (bfd *abfd ATTRIBUTE_UNUSED,
452*3d8817e4Smiod struct bfd_link_info *info ATTRIBUTE_UNUSED,
453*3d8817e4Smiod asection *sec ATTRIBUTE_UNUSED,
454*3d8817e4Smiod const Elf_Internal_Rela *relocs ATTRIBUTE_UNUSED)
455*3d8817e4Smiod {
456*3d8817e4Smiod return TRUE;
457*3d8817e4Smiod }
458*3d8817e4Smiod
459*3d8817e4Smiod /* Look through the relocs for a section during the first phase.
460*3d8817e4Smiod Since we don't do .gots or .plts, we just need to consider the
461*3d8817e4Smiod virtual table relocs for gc. */
462*3d8817e4Smiod
463*3d8817e4Smiod static bfd_boolean
openrisc_elf_check_relocs(bfd * abfd,struct bfd_link_info * info,asection * sec,const Elf_Internal_Rela * relocs)464*3d8817e4Smiod openrisc_elf_check_relocs (bfd *abfd,
465*3d8817e4Smiod struct bfd_link_info *info,
466*3d8817e4Smiod asection *sec,
467*3d8817e4Smiod const Elf_Internal_Rela *relocs)
468*3d8817e4Smiod {
469*3d8817e4Smiod Elf_Internal_Shdr *symtab_hdr;
470*3d8817e4Smiod struct elf_link_hash_entry **sym_hashes, **sym_hashes_end;
471*3d8817e4Smiod const Elf_Internal_Rela *rel;
472*3d8817e4Smiod const Elf_Internal_Rela *rel_end;
473*3d8817e4Smiod
474*3d8817e4Smiod if (info->relocatable)
475*3d8817e4Smiod return TRUE;
476*3d8817e4Smiod
477*3d8817e4Smiod symtab_hdr = &elf_tdata (abfd)->symtab_hdr;
478*3d8817e4Smiod sym_hashes = elf_sym_hashes (abfd);
479*3d8817e4Smiod sym_hashes_end =
480*3d8817e4Smiod sym_hashes + symtab_hdr->sh_size / sizeof (Elf32_External_Sym);
481*3d8817e4Smiod if (!elf_bad_symtab (abfd))
482*3d8817e4Smiod sym_hashes_end -= symtab_hdr->sh_info;
483*3d8817e4Smiod
484*3d8817e4Smiod rel_end = relocs + sec->reloc_count;
485*3d8817e4Smiod for (rel = relocs; rel < rel_end; rel++)
486*3d8817e4Smiod {
487*3d8817e4Smiod struct elf_link_hash_entry *h;
488*3d8817e4Smiod unsigned long r_symndx;
489*3d8817e4Smiod
490*3d8817e4Smiod r_symndx = ELF32_R_SYM (rel->r_info);
491*3d8817e4Smiod if (r_symndx < symtab_hdr->sh_info)
492*3d8817e4Smiod h = NULL;
493*3d8817e4Smiod else
494*3d8817e4Smiod {
495*3d8817e4Smiod h = sym_hashes[r_symndx - symtab_hdr->sh_info];
496*3d8817e4Smiod while (h->root.type == bfd_link_hash_indirect
497*3d8817e4Smiod || h->root.type == bfd_link_hash_warning)
498*3d8817e4Smiod h = (struct elf_link_hash_entry *) h->root.u.i.link;
499*3d8817e4Smiod }
500*3d8817e4Smiod
501*3d8817e4Smiod switch (ELF32_R_TYPE (rel->r_info))
502*3d8817e4Smiod {
503*3d8817e4Smiod /* This relocation describes the C++ object vtable hierarchy.
504*3d8817e4Smiod Reconstruct it for later use during GC. */
505*3d8817e4Smiod case R_OPENRISC_GNU_VTINHERIT:
506*3d8817e4Smiod if (!bfd_elf_gc_record_vtinherit (abfd, sec, h, rel->r_offset))
507*3d8817e4Smiod return FALSE;
508*3d8817e4Smiod break;
509*3d8817e4Smiod
510*3d8817e4Smiod /* This relocation describes which C++ vtable entries are actually
511*3d8817e4Smiod used. Record for later use during GC. */
512*3d8817e4Smiod case R_OPENRISC_GNU_VTENTRY:
513*3d8817e4Smiod if (!bfd_elf_gc_record_vtentry (abfd, sec, h, rel->r_addend))
514*3d8817e4Smiod return FALSE;
515*3d8817e4Smiod break;
516*3d8817e4Smiod }
517*3d8817e4Smiod }
518*3d8817e4Smiod
519*3d8817e4Smiod return TRUE;
520*3d8817e4Smiod }
521*3d8817e4Smiod
522*3d8817e4Smiod /* Set the right machine number. */
523*3d8817e4Smiod
524*3d8817e4Smiod static bfd_boolean
openrisc_elf_object_p(bfd * abfd)525*3d8817e4Smiod openrisc_elf_object_p (bfd *abfd)
526*3d8817e4Smiod {
527*3d8817e4Smiod bfd_default_set_arch_mach (abfd, bfd_arch_openrisc, 0);
528*3d8817e4Smiod return TRUE;
529*3d8817e4Smiod }
530*3d8817e4Smiod
531*3d8817e4Smiod /* Store the machine number in the flags field. */
532*3d8817e4Smiod
533*3d8817e4Smiod static void
openrisc_elf_final_write_processing(bfd * abfd,bfd_boolean linker ATTRIBUTE_UNUSED)534*3d8817e4Smiod openrisc_elf_final_write_processing (bfd *abfd,
535*3d8817e4Smiod bfd_boolean linker ATTRIBUTE_UNUSED)
536*3d8817e4Smiod {
537*3d8817e4Smiod unsigned long val;
538*3d8817e4Smiod
539*3d8817e4Smiod switch (bfd_get_mach (abfd))
540*3d8817e4Smiod {
541*3d8817e4Smiod default:
542*3d8817e4Smiod val = 0;
543*3d8817e4Smiod break;
544*3d8817e4Smiod }
545*3d8817e4Smiod
546*3d8817e4Smiod elf_elfheader (abfd)->e_flags &= ~0xf;
547*3d8817e4Smiod elf_elfheader (abfd)->e_flags |= val;
548*3d8817e4Smiod }
549*3d8817e4Smiod
550*3d8817e4Smiod
551*3d8817e4Smiod #define ELF_ARCH bfd_arch_openrisc
552*3d8817e4Smiod #define ELF_MACHINE_CODE EM_OPENRISC
553*3d8817e4Smiod #define ELF_MACHINE_ALT1 EM_OPENRISC_OLD
554*3d8817e4Smiod #define ELF_MAXPAGESIZE 0x1000
555*3d8817e4Smiod
556*3d8817e4Smiod #define TARGET_BIG_SYM bfd_elf32_openrisc_vec
557*3d8817e4Smiod #define TARGET_BIG_NAME "elf32-openrisc"
558*3d8817e4Smiod
559*3d8817e4Smiod #define elf_info_to_howto_rel NULL
560*3d8817e4Smiod #define elf_info_to_howto openrisc_info_to_howto_rela
561*3d8817e4Smiod #define elf_backend_relocate_section openrisc_elf_relocate_section
562*3d8817e4Smiod #define elf_backend_gc_mark_hook openrisc_elf_gc_mark_hook
563*3d8817e4Smiod #define elf_backend_gc_sweep_hook openrisc_elf_gc_sweep_hook
564*3d8817e4Smiod #define elf_backend_check_relocs openrisc_elf_check_relocs
565*3d8817e4Smiod
566*3d8817e4Smiod #define elf_backend_can_gc_sections 1
567*3d8817e4Smiod #define elf_backend_rela_normal 1
568*3d8817e4Smiod
569*3d8817e4Smiod #define bfd_elf32_bfd_reloc_type_lookup openrisc_reloc_type_lookup
570*3d8817e4Smiod
571*3d8817e4Smiod #define elf_backend_object_p openrisc_elf_object_p
572*3d8817e4Smiod #define elf_backend_final_write_processing openrisc_elf_final_write_processing
573*3d8817e4Smiod
574*3d8817e4Smiod #include "elf32-target.h"
575