1/* SPARC-specific support for 64-bit ELF
2   Copyright 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002,
3   2003, 2004, 2005, 2007 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/sparc.h"
26#include "opcode/sparc.h"
27#include "elfxx-sparc.h"
28
29/* In case we're on a 32-bit machine, construct a 64-bit "-1" value.  */
30#define MINUS_ONE (~ (bfd_vma) 0)
31
32/* Due to the way how we handle R_SPARC_OLO10, each entry in a SHT_RELA
33   section can represent up to two relocs, we must tell the user to allocate
34   more space.  */
35
36static long
37elf64_sparc_get_reloc_upper_bound (bfd *abfd ATTRIBUTE_UNUSED, asection *sec)
38{
39  return (sec->reloc_count * 2 + 1) * sizeof (arelent *);
40}
41
42static long
43elf64_sparc_get_dynamic_reloc_upper_bound (bfd *abfd)
44{
45  return _bfd_elf_get_dynamic_reloc_upper_bound (abfd) * 2;
46}
47
48/* Read  relocations for ASECT from REL_HDR.  There are RELOC_COUNT of
49   them.  We cannot use generic elf routines for this,  because R_SPARC_OLO10
50   has secondary addend in ELF64_R_TYPE_DATA.  We handle it as two relocations
51   for the same location,  R_SPARC_LO10 and R_SPARC_13.  */
52
53static bfd_boolean
54elf64_sparc_slurp_one_reloc_table (bfd *abfd, asection *asect,
55				   Elf_Internal_Shdr *rel_hdr,
56				   asymbol **symbols, bfd_boolean dynamic)
57{
58  PTR allocated = NULL;
59  bfd_byte *native_relocs;
60  arelent *relent;
61  unsigned int i;
62  int entsize;
63  bfd_size_type count;
64  arelent *relents;
65
66  allocated = (PTR) bfd_malloc (rel_hdr->sh_size);
67  if (allocated == NULL)
68    goto error_return;
69
70  if (bfd_seek (abfd, rel_hdr->sh_offset, SEEK_SET) != 0
71      || bfd_bread (allocated, rel_hdr->sh_size, abfd) != rel_hdr->sh_size)
72    goto error_return;
73
74  native_relocs = (bfd_byte *) allocated;
75
76  relents = asect->relocation + canon_reloc_count (asect);
77
78  entsize = rel_hdr->sh_entsize;
79  BFD_ASSERT (entsize == sizeof (Elf64_External_Rela));
80
81  count = rel_hdr->sh_size / entsize;
82
83  for (i = 0, relent = relents; i < count;
84       i++, relent++, native_relocs += entsize)
85    {
86      Elf_Internal_Rela rela;
87      unsigned int r_type;
88
89      bfd_elf64_swap_reloca_in (abfd, native_relocs, &rela);
90
91      /* The address of an ELF reloc is section relative for an object
92	 file, and absolute for an executable file or shared library.
93	 The address of a normal BFD reloc is always section relative,
94	 and the address of a dynamic reloc is absolute..  */
95      if ((abfd->flags & (EXEC_P | DYNAMIC)) == 0 || dynamic)
96	relent->address = rela.r_offset;
97      else
98	relent->address = rela.r_offset - asect->vma;
99
100      if (ELF64_R_SYM (rela.r_info) == 0)
101	relent->sym_ptr_ptr = bfd_abs_section_ptr->symbol_ptr_ptr;
102      else
103	{
104	  asymbol **ps, *s;
105
106	  ps = symbols + ELF64_R_SYM (rela.r_info) - 1;
107	  s = *ps;
108
109	  /* Canonicalize ELF section symbols.  FIXME: Why?  */
110	  if ((s->flags & BSF_SECTION_SYM) == 0)
111	    relent->sym_ptr_ptr = ps;
112	  else
113	    relent->sym_ptr_ptr = s->section->symbol_ptr_ptr;
114	}
115
116      relent->addend = rela.r_addend;
117
118      r_type = ELF64_R_TYPE_ID (rela.r_info);
119      if (r_type == R_SPARC_OLO10)
120	{
121	  relent->howto = _bfd_sparc_elf_info_to_howto_ptr (R_SPARC_LO10);
122	  relent[1].address = relent->address;
123	  relent++;
124	  relent->sym_ptr_ptr = bfd_abs_section_ptr->symbol_ptr_ptr;
125	  relent->addend = ELF64_R_TYPE_DATA (rela.r_info);
126	  relent->howto = _bfd_sparc_elf_info_to_howto_ptr (R_SPARC_13);
127	}
128      else
129	relent->howto = _bfd_sparc_elf_info_to_howto_ptr (r_type);
130    }
131
132  canon_reloc_count (asect) += relent - relents;
133
134  if (allocated != NULL)
135    free (allocated);
136
137  return TRUE;
138
139 error_return:
140  if (allocated != NULL)
141    free (allocated);
142  return FALSE;
143}
144
145/* Read in and swap the external relocs.  */
146
147static bfd_boolean
148elf64_sparc_slurp_reloc_table (bfd *abfd, asection *asect,
149			       asymbol **symbols, bfd_boolean dynamic)
150{
151  struct bfd_elf_section_data * const d = elf_section_data (asect);
152  Elf_Internal_Shdr *rel_hdr;
153  Elf_Internal_Shdr *rel_hdr2;
154  bfd_size_type amt;
155
156  if (asect->relocation != NULL)
157    return TRUE;
158
159  if (! dynamic)
160    {
161      if ((asect->flags & SEC_RELOC) == 0
162	  || asect->reloc_count == 0)
163	return TRUE;
164
165      rel_hdr = &d->rel_hdr;
166      rel_hdr2 = d->rel_hdr2;
167
168      BFD_ASSERT (asect->rel_filepos == rel_hdr->sh_offset
169		  || (rel_hdr2 && asect->rel_filepos == rel_hdr2->sh_offset));
170    }
171  else
172    {
173      /* Note that ASECT->RELOC_COUNT tends not to be accurate in this
174	 case because relocations against this section may use the
175	 dynamic symbol table, and in that case bfd_section_from_shdr
176	 in elf.c does not update the RELOC_COUNT.  */
177      if (asect->size == 0)
178	return TRUE;
179
180      rel_hdr = &d->this_hdr;
181      asect->reloc_count = NUM_SHDR_ENTRIES (rel_hdr);
182      rel_hdr2 = NULL;
183    }
184
185  amt = asect->reloc_count;
186  amt *= 2 * sizeof (arelent);
187  asect->relocation = (arelent *) bfd_alloc (abfd, amt);
188  if (asect->relocation == NULL)
189    return FALSE;
190
191  /* The elf64_sparc_slurp_one_reloc_table routine increments
192     canon_reloc_count.  */
193  canon_reloc_count (asect) = 0;
194
195  if (!elf64_sparc_slurp_one_reloc_table (abfd, asect, rel_hdr, symbols,
196					  dynamic))
197    return FALSE;
198
199  if (rel_hdr2
200      && !elf64_sparc_slurp_one_reloc_table (abfd, asect, rel_hdr2, symbols,
201					     dynamic))
202    return FALSE;
203
204  return TRUE;
205}
206
207/* Canonicalize the relocs.  */
208
209static long
210elf64_sparc_canonicalize_reloc (bfd *abfd, sec_ptr section,
211				arelent **relptr, asymbol **symbols)
212{
213  arelent *tblptr;
214  unsigned int i;
215  const struct elf_backend_data *bed = get_elf_backend_data (abfd);
216
217  if (! bed->s->slurp_reloc_table (abfd, section, symbols, FALSE))
218    return -1;
219
220  tblptr = section->relocation;
221  for (i = 0; i < canon_reloc_count (section); i++)
222    *relptr++ = tblptr++;
223
224  *relptr = NULL;
225
226  return canon_reloc_count (section);
227}
228
229
230/* Canonicalize the dynamic relocation entries.  Note that we return
231   the dynamic relocations as a single block, although they are
232   actually associated with particular sections; the interface, which
233   was designed for SunOS style shared libraries, expects that there
234   is only one set of dynamic relocs.  Any section that was actually
235   installed in the BFD, and has type SHT_REL or SHT_RELA, and uses
236   the dynamic symbol table, is considered to be a dynamic reloc
237   section.  */
238
239static long
240elf64_sparc_canonicalize_dynamic_reloc (bfd *abfd, arelent **storage,
241					asymbol **syms)
242{
243  asection *s;
244  long ret;
245
246  if (elf_dynsymtab (abfd) == 0)
247    {
248      bfd_set_error (bfd_error_invalid_operation);
249      return -1;
250    }
251
252  ret = 0;
253  for (s = abfd->sections; s != NULL; s = s->next)
254    {
255      if (elf_section_data (s)->this_hdr.sh_link == elf_dynsymtab (abfd)
256	  && (elf_section_data (s)->this_hdr.sh_type == SHT_RELA))
257	{
258	  arelent *p;
259	  long count, i;
260
261	  if (! elf64_sparc_slurp_reloc_table (abfd, s, syms, TRUE))
262	    return -1;
263	  count = canon_reloc_count (s);
264	  p = s->relocation;
265	  for (i = 0; i < count; i++)
266	    *storage++ = p++;
267	  ret += count;
268	}
269    }
270
271  *storage = NULL;
272
273  return ret;
274}
275
276/* Write out the relocs.  */
277
278static void
279elf64_sparc_write_relocs (bfd *abfd, asection *sec, PTR data)
280{
281  bfd_boolean *failedp = (bfd_boolean *) data;
282  Elf_Internal_Shdr *rela_hdr;
283  bfd_vma addr_offset;
284  Elf64_External_Rela *outbound_relocas, *src_rela;
285  unsigned int idx, count;
286  asymbol *last_sym = 0;
287  int last_sym_idx = 0;
288
289  /* If we have already failed, don't do anything.  */
290  if (*failedp)
291    return;
292
293  if ((sec->flags & SEC_RELOC) == 0)
294    return;
295
296  /* The linker backend writes the relocs out itself, and sets the
297     reloc_count field to zero to inhibit writing them here.  Also,
298     sometimes the SEC_RELOC flag gets set even when there aren't any
299     relocs.  */
300  if (sec->reloc_count == 0)
301    return;
302
303  /* We can combine two relocs that refer to the same address
304     into R_SPARC_OLO10 if first one is R_SPARC_LO10 and the
305     latter is R_SPARC_13 with no associated symbol.  */
306  count = 0;
307  for (idx = 0; idx < sec->reloc_count; idx++)
308    {
309      bfd_vma addr;
310
311      ++count;
312
313      addr = sec->orelocation[idx]->address;
314      if (sec->orelocation[idx]->howto->type == R_SPARC_LO10
315	  && idx < sec->reloc_count - 1)
316	{
317	  arelent *r = sec->orelocation[idx + 1];
318
319	  if (r->howto->type == R_SPARC_13
320	      && r->address == addr
321	      && bfd_is_abs_section ((*r->sym_ptr_ptr)->section)
322	      && (*r->sym_ptr_ptr)->value == 0)
323	    ++idx;
324	}
325    }
326
327  rela_hdr = &elf_section_data (sec)->rel_hdr;
328
329  rela_hdr->sh_size = rela_hdr->sh_entsize * count;
330  rela_hdr->contents = (PTR) bfd_alloc (abfd, rela_hdr->sh_size);
331  if (rela_hdr->contents == NULL)
332    {
333      *failedp = TRUE;
334      return;
335    }
336
337  /* Figure out whether the relocations are RELA or REL relocations.  */
338  if (rela_hdr->sh_type != SHT_RELA)
339    abort ();
340
341  /* The address of an ELF reloc is section relative for an object
342     file, and absolute for an executable file or shared library.
343     The address of a BFD reloc is always section relative.  */
344  addr_offset = 0;
345  if ((abfd->flags & (EXEC_P | DYNAMIC)) != 0)
346    addr_offset = sec->vma;
347
348  /* orelocation has the data, reloc_count has the count...  */
349  outbound_relocas = (Elf64_External_Rela *) rela_hdr->contents;
350  src_rela = outbound_relocas;
351
352  for (idx = 0; idx < sec->reloc_count; idx++)
353    {
354      Elf_Internal_Rela dst_rela;
355      arelent *ptr;
356      asymbol *sym;
357      int n;
358
359      ptr = sec->orelocation[idx];
360      sym = *ptr->sym_ptr_ptr;
361      if (sym == last_sym)
362	n = last_sym_idx;
363      else if (bfd_is_abs_section (sym->section) && sym->value == 0)
364	n = STN_UNDEF;
365      else
366	{
367	  last_sym = sym;
368	  n = _bfd_elf_symbol_from_bfd_symbol (abfd, &sym);
369	  if (n < 0)
370	    {
371	      *failedp = TRUE;
372	      return;
373	    }
374	  last_sym_idx = n;
375	}
376
377      if ((*ptr->sym_ptr_ptr)->the_bfd != NULL
378	  && (*ptr->sym_ptr_ptr)->the_bfd->xvec != abfd->xvec
379	  && ! _bfd_elf_validate_reloc (abfd, ptr))
380	{
381	  *failedp = TRUE;
382	  return;
383	}
384
385      if (ptr->howto->type == R_SPARC_LO10
386	  && idx < sec->reloc_count - 1)
387	{
388	  arelent *r = sec->orelocation[idx + 1];
389
390	  if (r->howto->type == R_SPARC_13
391	      && r->address == ptr->address
392	      && bfd_is_abs_section ((*r->sym_ptr_ptr)->section)
393	      && (*r->sym_ptr_ptr)->value == 0)
394	    {
395	      idx++;
396	      dst_rela.r_info
397		= ELF64_R_INFO (n, ELF64_R_TYPE_INFO (r->addend,
398						      R_SPARC_OLO10));
399	    }
400	  else
401	    dst_rela.r_info = ELF64_R_INFO (n, R_SPARC_LO10);
402	}
403      else
404	dst_rela.r_info = ELF64_R_INFO (n, ptr->howto->type);
405
406      dst_rela.r_offset = ptr->address + addr_offset;
407      dst_rela.r_addend = ptr->addend;
408
409      bfd_elf64_swap_reloca_out (abfd, &dst_rela, (bfd_byte *) src_rela);
410      ++src_rela;
411    }
412}
413
414/* Hook called by the linker routine which adds symbols from an object
415   file.  We use it for STT_REGISTER symbols.  */
416
417static bfd_boolean
418elf64_sparc_add_symbol_hook (bfd *abfd, struct bfd_link_info *info,
419			     Elf_Internal_Sym *sym, const char **namep,
420			     flagword *flagsp ATTRIBUTE_UNUSED,
421			     asection **secp ATTRIBUTE_UNUSED,
422			     bfd_vma *valp ATTRIBUTE_UNUSED)
423{
424  static const char *const stt_types[] = { "NOTYPE", "OBJECT", "FUNCTION" };
425
426  if (ELF_ST_TYPE (sym->st_info) == STT_REGISTER)
427    {
428      int reg;
429      struct _bfd_sparc_elf_app_reg *p;
430
431      reg = (int)sym->st_value;
432      switch (reg & ~1)
433	{
434	case 2: reg -= 2; break;
435	case 6: reg -= 4; break;
436	default:
437          (*_bfd_error_handler)
438            (_("%B: Only registers %%g[2367] can be declared using STT_REGISTER"),
439             abfd);
440	  return FALSE;
441	}
442
443      if (info->hash->creator != abfd->xvec
444	  || (abfd->flags & DYNAMIC) != 0)
445        {
446	  /* STT_REGISTER only works when linking an elf64_sparc object.
447	     If STT_REGISTER comes from a dynamic object, don't put it into
448	     the output bfd.  The dynamic linker will recheck it.  */
449	  *namep = NULL;
450	  return TRUE;
451        }
452
453      p = _bfd_sparc_elf_hash_table(info)->app_regs + reg;
454
455      if (p->name != NULL && strcmp (p->name, *namep))
456	{
457          (*_bfd_error_handler)
458            (_("Register %%g%d used incompatibly: %s in %B, previously %s in %B"),
459             abfd, p->abfd, (int) sym->st_value,
460             **namep ? *namep : "#scratch",
461             *p->name ? p->name : "#scratch");
462	  return FALSE;
463	}
464
465      if (p->name == NULL)
466	{
467	  if (**namep)
468	    {
469	      struct elf_link_hash_entry *h;
470
471	      h = (struct elf_link_hash_entry *)
472		bfd_link_hash_lookup (info->hash, *namep, FALSE, FALSE, FALSE);
473
474	      if (h != NULL)
475		{
476		  unsigned char type = h->type;
477
478		  if (type > STT_FUNC)
479		    type = 0;
480		  (*_bfd_error_handler)
481		    (_("Symbol `%s' has differing types: REGISTER in %B, previously %s in %B"),
482		     abfd, p->abfd, *namep, stt_types[type]);
483		  return FALSE;
484		}
485
486	      p->name = bfd_hash_allocate (&info->hash->table,
487					   strlen (*namep) + 1);
488	      if (!p->name)
489		return FALSE;
490
491	      strcpy (p->name, *namep);
492	    }
493	  else
494	    p->name = "";
495	  p->bind = ELF_ST_BIND (sym->st_info);
496	  p->abfd = abfd;
497	  p->shndx = sym->st_shndx;
498	}
499      else
500	{
501	  if (p->bind == STB_WEAK
502	      && ELF_ST_BIND (sym->st_info) == STB_GLOBAL)
503	    {
504	      p->bind = STB_GLOBAL;
505	      p->abfd = abfd;
506	    }
507	}
508      *namep = NULL;
509      return TRUE;
510    }
511  else if (*namep && **namep
512	   && info->hash->creator == abfd->xvec)
513    {
514      int i;
515      struct _bfd_sparc_elf_app_reg *p;
516
517      p = _bfd_sparc_elf_hash_table(info)->app_regs;
518      for (i = 0; i < 4; i++, p++)
519	if (p->name != NULL && ! strcmp (p->name, *namep))
520	  {
521	    unsigned char type = ELF_ST_TYPE (sym->st_info);
522
523	    if (type > STT_FUNC)
524	      type = 0;
525	    (*_bfd_error_handler)
526	      (_("Symbol `%s' has differing types: %s in %B, previously REGISTER in %B"),
527	       abfd, p->abfd, *namep, stt_types[type]);
528	    return FALSE;
529	  }
530    }
531  return TRUE;
532}
533
534/* This function takes care of emitting STT_REGISTER symbols
535   which we cannot easily keep in the symbol hash table.  */
536
537static bfd_boolean
538elf64_sparc_output_arch_syms (bfd *output_bfd ATTRIBUTE_UNUSED,
539			      struct bfd_link_info *info,
540			      PTR finfo, bfd_boolean (*func) (PTR, const char *,
541							      Elf_Internal_Sym *,
542							      asection *,
543							      struct elf_link_hash_entry *))
544{
545  int reg;
546  struct _bfd_sparc_elf_app_reg *app_regs =
547    _bfd_sparc_elf_hash_table(info)->app_regs;
548  Elf_Internal_Sym sym;
549
550  /* We arranged in size_dynamic_sections to put the STT_REGISTER entries
551     at the end of the dynlocal list, so they came at the end of the local
552     symbols in the symtab.  Except that they aren't STB_LOCAL, so we need
553     to back up symtab->sh_info.  */
554  if (elf_hash_table (info)->dynlocal)
555    {
556      bfd * dynobj = elf_hash_table (info)->dynobj;
557      asection *dynsymsec = bfd_get_section_by_name (dynobj, ".dynsym");
558      struct elf_link_local_dynamic_entry *e;
559
560      for (e = elf_hash_table (info)->dynlocal; e ; e = e->next)
561	if (e->input_indx == -1)
562	  break;
563      if (e)
564	{
565	  elf_section_data (dynsymsec->output_section)->this_hdr.sh_info
566	    = e->dynindx;
567	}
568    }
569
570  if (info->strip == strip_all)
571    return TRUE;
572
573  for (reg = 0; reg < 4; reg++)
574    if (app_regs [reg].name != NULL)
575      {
576	if (info->strip == strip_some
577	    && bfd_hash_lookup (info->keep_hash,
578				app_regs [reg].name,
579				FALSE, FALSE) == NULL)
580	  continue;
581
582	sym.st_value = reg < 2 ? reg + 2 : reg + 4;
583	sym.st_size = 0;
584	sym.st_other = 0;
585	sym.st_info = ELF_ST_INFO (app_regs [reg].bind, STT_REGISTER);
586	sym.st_shndx = app_regs [reg].shndx;
587	if (! (*func) (finfo, app_regs [reg].name, &sym,
588		       sym.st_shndx == SHN_ABS
589			 ? bfd_abs_section_ptr : bfd_und_section_ptr,
590		       NULL))
591	  return FALSE;
592      }
593
594  return TRUE;
595}
596
597static int
598elf64_sparc_get_symbol_type (Elf_Internal_Sym *elf_sym, int type)
599{
600  if (ELF_ST_TYPE (elf_sym->st_info) == STT_REGISTER)
601    return STT_REGISTER;
602  else
603    return type;
604}
605
606/* A STB_GLOBAL,STT_REGISTER symbol should be BSF_GLOBAL
607   even in SHN_UNDEF section.  */
608
609static void
610elf64_sparc_symbol_processing (bfd *abfd ATTRIBUTE_UNUSED, asymbol *asym)
611{
612  elf_symbol_type *elfsym;
613
614  elfsym = (elf_symbol_type *) asym;
615  if (elfsym->internal_elf_sym.st_info
616      == ELF_ST_INFO (STB_GLOBAL, STT_REGISTER))
617    {
618      asym->flags |= BSF_GLOBAL;
619    }
620}
621
622
623/* Functions for dealing with the e_flags field.  */
624
625/* Merge backend specific data from an object file to the output
626   object file when linking.  */
627
628static bfd_boolean
629elf64_sparc_merge_private_bfd_data (bfd *ibfd, bfd *obfd)
630{
631  bfd_boolean error;
632  flagword new_flags, old_flags;
633  int new_mm, old_mm;
634
635  if (bfd_get_flavour (ibfd) != bfd_target_elf_flavour
636      || bfd_get_flavour (obfd) != bfd_target_elf_flavour)
637    return TRUE;
638
639  new_flags = elf_elfheader (ibfd)->e_flags;
640  old_flags = elf_elfheader (obfd)->e_flags;
641
642  if (!elf_flags_init (obfd))   /* First call, no flags set */
643    {
644      elf_flags_init (obfd) = TRUE;
645      elf_elfheader (obfd)->e_flags = new_flags;
646    }
647
648  else if (new_flags == old_flags)      /* Compatible flags are ok */
649    ;
650
651  else                                  /* Incompatible flags */
652    {
653      error = FALSE;
654
655#define EF_SPARC_ISA_EXTENSIONS \
656  (EF_SPARC_SUN_US1 | EF_SPARC_SUN_US3 | EF_SPARC_HAL_R1)
657
658      if ((ibfd->flags & DYNAMIC) != 0)
659	{
660	  /* We don't want dynamic objects memory ordering and
661	     architecture to have any role. That's what dynamic linker
662	     should do.  */
663	  new_flags &= ~(EF_SPARCV9_MM | EF_SPARC_ISA_EXTENSIONS);
664	  new_flags |= (old_flags
665			& (EF_SPARCV9_MM | EF_SPARC_ISA_EXTENSIONS));
666	}
667      else
668	{
669	  /* Choose the highest architecture requirements.  */
670	  old_flags |= (new_flags & EF_SPARC_ISA_EXTENSIONS);
671	  new_flags |= (old_flags & EF_SPARC_ISA_EXTENSIONS);
672	  if ((old_flags & (EF_SPARC_SUN_US1 | EF_SPARC_SUN_US3))
673	      && (old_flags & EF_SPARC_HAL_R1))
674	    {
675	      error = TRUE;
676	      (*_bfd_error_handler)
677		(_("%B: linking UltraSPARC specific with HAL specific code"),
678		 ibfd);
679	    }
680	  /* Choose the most restrictive memory ordering.  */
681	  old_mm = (old_flags & EF_SPARCV9_MM);
682	  new_mm = (new_flags & EF_SPARCV9_MM);
683	  old_flags &= ~EF_SPARCV9_MM;
684	  new_flags &= ~EF_SPARCV9_MM;
685	  if (new_mm < old_mm)
686	    old_mm = new_mm;
687	  old_flags |= old_mm;
688	  new_flags |= old_mm;
689	}
690
691      /* Warn about any other mismatches */
692      if (new_flags != old_flags)
693        {
694          error = TRUE;
695          (*_bfd_error_handler)
696            (_("%B: uses different e_flags (0x%lx) fields than previous modules (0x%lx)"),
697             ibfd, (long) new_flags, (long) old_flags);
698        }
699
700      elf_elfheader (obfd)->e_flags = old_flags;
701
702      if (error)
703        {
704          bfd_set_error (bfd_error_bad_value);
705          return FALSE;
706        }
707    }
708  return TRUE;
709}
710
711/* MARCO: Set the correct entry size for the .stab section.  */
712
713static bfd_boolean
714elf64_sparc_fake_sections (bfd *abfd ATTRIBUTE_UNUSED,
715			   Elf_Internal_Shdr *hdr ATTRIBUTE_UNUSED,
716			   asection *sec)
717{
718  const char *name;
719
720  name = bfd_get_section_name (abfd, sec);
721
722  if (strcmp (name, ".stab") == 0)
723    {
724      /* Even in the 64bit case the stab entries are only 12 bytes long.  */
725      elf_section_data (sec)->this_hdr.sh_entsize = 12;
726    }
727
728  return TRUE;
729}
730
731/* Print a STT_REGISTER symbol to file FILE.  */
732
733static const char *
734elf64_sparc_print_symbol_all (bfd *abfd ATTRIBUTE_UNUSED, PTR filep,
735			      asymbol *symbol)
736{
737  FILE *file = (FILE *) filep;
738  int reg, type;
739
740  if (ELF_ST_TYPE (((elf_symbol_type *) symbol)->internal_elf_sym.st_info)
741      != STT_REGISTER)
742    return NULL;
743
744  reg = ((elf_symbol_type *) symbol)->internal_elf_sym.st_value;
745  type = symbol->flags;
746  fprintf (file, "REG_%c%c%11s%c%c    R", "GOLI" [reg / 8], '0' + (reg & 7), "",
747		 ((type & BSF_LOCAL)
748		  ? (type & BSF_GLOBAL) ? '!' : 'l'
749	          : (type & BSF_GLOBAL) ? 'g' : ' '),
750	         (type & BSF_WEAK) ? 'w' : ' ');
751  if (symbol->name == NULL || symbol->name [0] == '\0')
752    return "#scratch";
753  else
754    return symbol->name;
755}
756
757static enum elf_reloc_type_class
758elf64_sparc_reloc_type_class (const Elf_Internal_Rela *rela)
759{
760  switch ((int) ELF64_R_TYPE (rela->r_info))
761    {
762    case R_SPARC_RELATIVE:
763      return reloc_class_relative;
764    case R_SPARC_JMP_SLOT:
765      return reloc_class_plt;
766    case R_SPARC_COPY:
767      return reloc_class_copy;
768    default:
769      return reloc_class_normal;
770    }
771}
772
773/* Relocations in the 64 bit SPARC ELF ABI are more complex than in
774   standard ELF, because R_SPARC_OLO10 has secondary addend in
775   ELF64_R_TYPE_DATA field.  This structure is used to redirect the
776   relocation handling routines.  */
777
778const struct elf_size_info elf64_sparc_size_info =
779{
780  sizeof (Elf64_External_Ehdr),
781  sizeof (Elf64_External_Phdr),
782  sizeof (Elf64_External_Shdr),
783  sizeof (Elf64_External_Rel),
784  sizeof (Elf64_External_Rela),
785  sizeof (Elf64_External_Sym),
786  sizeof (Elf64_External_Dyn),
787  sizeof (Elf_External_Note),
788  4,		/* hash-table entry size.  */
789  /* Internal relocations per external relocations.
790     For link purposes we use just 1 internal per
791     1 external, for assembly and slurp symbol table
792     we use 2.  */
793  1,
794  64,		/* arch_size.  */
795  3,		/* log_file_align.  */
796  ELFCLASS64,
797  EV_CURRENT,
798  bfd_elf64_write_out_phdrs,
799  bfd_elf64_write_shdrs_and_ehdr,
800  elf64_sparc_write_relocs,
801  bfd_elf64_swap_symbol_in,
802  bfd_elf64_swap_symbol_out,
803  elf64_sparc_slurp_reloc_table,
804  bfd_elf64_slurp_symbol_table,
805  bfd_elf64_swap_dyn_in,
806  bfd_elf64_swap_dyn_out,
807  bfd_elf64_swap_reloc_in,
808  bfd_elf64_swap_reloc_out,
809  bfd_elf64_swap_reloca_in,
810  bfd_elf64_swap_reloca_out
811};
812
813#define TARGET_BIG_SYM	bfd_elf64_sparc_vec
814#define TARGET_BIG_NAME	"elf64-sparc"
815#define ELF_ARCH	bfd_arch_sparc
816#define ELF_MAXPAGESIZE 0x100000
817#define ELF_COMMONPAGESIZE 0x2000
818
819/* This is the official ABI value.  */
820#define ELF_MACHINE_CODE EM_SPARCV9
821
822/* This is the value that we used before the ABI was released.  */
823#define ELF_MACHINE_ALT1 EM_OLD_SPARCV9
824
825#define elf_backend_reloc_type_class \
826  elf64_sparc_reloc_type_class
827#define bfd_elf64_get_reloc_upper_bound \
828  elf64_sparc_get_reloc_upper_bound
829#define bfd_elf64_get_dynamic_reloc_upper_bound \
830  elf64_sparc_get_dynamic_reloc_upper_bound
831#define bfd_elf64_canonicalize_reloc \
832  elf64_sparc_canonicalize_reloc
833#define bfd_elf64_canonicalize_dynamic_reloc \
834  elf64_sparc_canonicalize_dynamic_reloc
835#define elf_backend_add_symbol_hook \
836  elf64_sparc_add_symbol_hook
837#define elf_backend_get_symbol_type \
838  elf64_sparc_get_symbol_type
839#define elf_backend_symbol_processing \
840  elf64_sparc_symbol_processing
841#define elf_backend_print_symbol_all \
842  elf64_sparc_print_symbol_all
843#define elf_backend_output_arch_syms \
844  elf64_sparc_output_arch_syms
845#define bfd_elf64_bfd_merge_private_bfd_data \
846  elf64_sparc_merge_private_bfd_data
847#define elf_backend_fake_sections \
848  elf64_sparc_fake_sections
849#define elf_backend_size_info \
850  elf64_sparc_size_info
851
852#define elf_backend_plt_sym_val	\
853  _bfd_sparc_elf_plt_sym_val
854#define bfd_elf64_bfd_link_hash_table_create \
855  _bfd_sparc_elf_link_hash_table_create
856#define elf_info_to_howto \
857  _bfd_sparc_elf_info_to_howto
858#define elf_backend_copy_indirect_symbol \
859  _bfd_sparc_elf_copy_indirect_symbol
860#define bfd_elf64_bfd_reloc_type_lookup \
861  _bfd_sparc_elf_reloc_type_lookup
862#define bfd_elf64_bfd_reloc_name_lookup \
863  _bfd_sparc_elf_reloc_name_lookup
864#define bfd_elf64_bfd_relax_section \
865  _bfd_sparc_elf_relax_section
866#define bfd_elf64_new_section_hook \
867  _bfd_sparc_elf_new_section_hook
868
869#define elf_backend_create_dynamic_sections \
870  _bfd_sparc_elf_create_dynamic_sections
871#define elf_backend_relocs_compatible \
872  _bfd_elf_relocs_compatible
873#define elf_backend_check_relocs \
874  _bfd_sparc_elf_check_relocs
875#define elf_backend_adjust_dynamic_symbol \
876  _bfd_sparc_elf_adjust_dynamic_symbol
877#define elf_backend_omit_section_dynsym \
878  _bfd_sparc_elf_omit_section_dynsym
879#define elf_backend_size_dynamic_sections \
880  _bfd_sparc_elf_size_dynamic_sections
881#define elf_backend_relocate_section \
882  _bfd_sparc_elf_relocate_section
883#define elf_backend_finish_dynamic_symbol \
884  _bfd_sparc_elf_finish_dynamic_symbol
885#define elf_backend_finish_dynamic_sections \
886  _bfd_sparc_elf_finish_dynamic_sections
887
888#define bfd_elf64_mkobject \
889  _bfd_sparc_elf_mkobject
890#define elf_backend_object_p \
891  _bfd_sparc_elf_object_p
892#define elf_backend_gc_mark_hook \
893  _bfd_sparc_elf_gc_mark_hook
894#define elf_backend_gc_sweep_hook \
895  _bfd_sparc_elf_gc_sweep_hook
896#define elf_backend_init_index_section \
897  _bfd_elf_init_1_index_section
898
899#define elf_backend_can_gc_sections 1
900#define elf_backend_can_refcount 1
901#define elf_backend_want_got_plt 0
902#define elf_backend_plt_readonly 0
903#define elf_backend_want_plt_sym 1
904#define elf_backend_got_header_size 8
905#define elf_backend_rela_normal 1
906
907/* Section 5.2.4 of the ABI specifies a 256-byte boundary for the table.  */
908#define elf_backend_plt_alignment 8
909
910#include "elf64-target.h"
911
912/* FreeBSD support */
913#undef  TARGET_BIG_SYM
914#define TARGET_BIG_SYM bfd_elf64_sparc_freebsd_vec
915#undef  TARGET_BIG_NAME
916#define TARGET_BIG_NAME "elf64-sparc-freebsd"
917#undef	ELF_OSABI
918#define	ELF_OSABI ELFOSABI_FREEBSD
919
920#undef  elf_backend_post_process_headers
921#define elf_backend_post_process_headers	_bfd_elf_set_osabi
922#undef  elf64_bed
923#define elf64_bed				elf64_sparc_fbsd_bed
924
925#include "elf64-target.h"
926
927