elfnn-ia64.c revision 1.7
1/* IA-64 support for 64-bit ELF
2   Copyright (C) 1998-2020 Free Software Foundation, Inc.
3   Contributed by David Mosberger-Tang <davidm@hpl.hp.com>
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 3 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,
20   MA 02110-1301, USA.  */
21
22#include "sysdep.h"
23#include "bfd.h"
24#include "libbfd.h"
25#include "elf-bfd.h"
26#include "opcode/ia64.h"
27#include "elf/ia64.h"
28#include "objalloc.h"
29#include "hashtab.h"
30#include "elfxx-ia64.h"
31
32#define ARCH_SIZE	NN
33
34#if ARCH_SIZE == 64
35#define	LOG_SECTION_ALIGN	3
36#endif
37
38#if ARCH_SIZE == 32
39#define	LOG_SECTION_ALIGN	2
40#endif
41
42#define is_ia64_elf(bfd)			   \
43  (bfd_get_flavour (bfd) == bfd_target_elf_flavour \
44   && elf_object_id (bfd) == IA64_ELF_DATA)
45
46typedef struct bfd_hash_entry *(*new_hash_entry_func)
47  (struct bfd_hash_entry *, struct bfd_hash_table *, const char *);
48
49/* In dynamically (linker-) created sections, we generally need to keep track
50   of the place a symbol or expression got allocated to. This is done via hash
51   tables that store entries of the following type.  */
52
53struct elfNN_ia64_dyn_sym_info
54{
55  /* The addend for which this entry is relevant.  */
56  bfd_vma addend;
57
58  bfd_vma got_offset;
59  bfd_vma fptr_offset;
60  bfd_vma pltoff_offset;
61  bfd_vma plt_offset;
62  bfd_vma plt2_offset;
63  bfd_vma tprel_offset;
64  bfd_vma dtpmod_offset;
65  bfd_vma dtprel_offset;
66
67  /* The symbol table entry, if any, that this was derived from.  */
68  struct elf_link_hash_entry *h;
69
70  /* Used to count non-got, non-plt relocations for delayed sizing
71     of relocation sections.  */
72  struct elfNN_ia64_dyn_reloc_entry
73  {
74    struct elfNN_ia64_dyn_reloc_entry *next;
75    asection *srel;
76    int type;
77    int count;
78
79    /* Is this reloc against readonly section? */
80    bfd_boolean reltext;
81  } *reloc_entries;
82
83  /* TRUE when the section contents have been updated.  */
84  unsigned got_done : 1;
85  unsigned fptr_done : 1;
86  unsigned pltoff_done : 1;
87  unsigned tprel_done : 1;
88  unsigned dtpmod_done : 1;
89  unsigned dtprel_done : 1;
90
91  /* TRUE for the different kinds of linker data we want created.  */
92  unsigned want_got : 1;
93  unsigned want_gotx : 1;
94  unsigned want_fptr : 1;
95  unsigned want_ltoff_fptr : 1;
96  unsigned want_plt : 1;
97  unsigned want_plt2 : 1;
98  unsigned want_pltoff : 1;
99  unsigned want_tprel : 1;
100  unsigned want_dtpmod : 1;
101  unsigned want_dtprel : 1;
102};
103
104struct elfNN_ia64_local_hash_entry
105{
106  int id;
107  unsigned int r_sym;
108  /* The number of elements in elfNN_ia64_dyn_sym_info array.  */
109  unsigned int count;
110  /* The number of sorted elements in elfNN_ia64_dyn_sym_info array.  */
111  unsigned int sorted_count;
112  /* The size of elfNN_ia64_dyn_sym_info array.  */
113  unsigned int size;
114  /* The array of elfNN_ia64_dyn_sym_info.  */
115  struct elfNN_ia64_dyn_sym_info *info;
116
117  /* TRUE if this hash entry's addends was translated for
118     SHF_MERGE optimization.  */
119  unsigned sec_merge_done : 1;
120};
121
122struct elfNN_ia64_link_hash_entry
123{
124  struct elf_link_hash_entry root;
125  /* The number of elements in elfNN_ia64_dyn_sym_info array.  */
126  unsigned int count;
127  /* The number of sorted elements in elfNN_ia64_dyn_sym_info array.  */
128  unsigned int sorted_count;
129  /* The size of elfNN_ia64_dyn_sym_info array.  */
130  unsigned int size;
131  /* The array of elfNN_ia64_dyn_sym_info.  */
132  struct elfNN_ia64_dyn_sym_info *info;
133};
134
135struct elfNN_ia64_link_hash_table
136{
137  /* The main hash table.  */
138  struct elf_link_hash_table root;
139
140  asection *fptr_sec;		/* Function descriptor table (or NULL).  */
141  asection *rel_fptr_sec;	/* Dynamic relocation section for same.  */
142  asection *pltoff_sec;		/* Private descriptors for plt (or NULL).  */
143  asection *rel_pltoff_sec;	/* Dynamic relocation section for same.  */
144
145  bfd_size_type minplt_entries;	/* Number of minplt entries.  */
146  unsigned reltext : 1;		/* Are there relocs against readonly sections?  */
147  unsigned self_dtpmod_done : 1;/* Has self DTPMOD entry been finished?  */
148  bfd_vma self_dtpmod_offset;	/* .got offset to self DTPMOD entry.  */
149  /* There are maybe R_IA64_GPREL22 relocations, including those
150     optimized from R_IA64_LTOFF22X, against non-SHF_IA_64_SHORT
151     sections.  We need to record those sections so that we can choose
152     a proper GP to cover all R_IA64_GPREL22 relocations.  */
153  asection *max_short_sec;	/* Maximum short output section.  */
154  bfd_vma max_short_offset;	/* Maximum short offset.  */
155  asection *min_short_sec;	/* Minimum short output section.  */
156  bfd_vma min_short_offset;	/* Minimum short offset.  */
157
158  htab_t loc_hash_table;
159  void *loc_hash_memory;
160};
161
162struct elfNN_ia64_allocate_data
163{
164  struct bfd_link_info *info;
165  bfd_size_type ofs;
166  bfd_boolean only_got;
167};
168
169#define elfNN_ia64_hash_table(p) \
170  (elf_hash_table_id ((struct elf_link_hash_table *) ((p)->hash)) \
171  == IA64_ELF_DATA ? ((struct elfNN_ia64_link_hash_table *) ((p)->hash)) : NULL)
172
173static struct elfNN_ia64_dyn_sym_info * get_dyn_sym_info
174  (struct elfNN_ia64_link_hash_table *ia64_info,
175   struct elf_link_hash_entry *h,
176   bfd *abfd, const Elf_Internal_Rela *rel, bfd_boolean create);
177static bfd_boolean elfNN_ia64_dynamic_symbol_p
178  (struct elf_link_hash_entry *h, struct bfd_link_info *info, int);
179static bfd_boolean elfNN_ia64_choose_gp
180  (bfd *abfd, struct bfd_link_info *info, bfd_boolean final);
181static void elfNN_ia64_dyn_sym_traverse
182  (struct elfNN_ia64_link_hash_table *ia64_info,
183   bfd_boolean (*func) (struct elfNN_ia64_dyn_sym_info *, void *),
184   void * info);
185static bfd_boolean allocate_global_data_got
186  (struct elfNN_ia64_dyn_sym_info *dyn_i, void * data);
187static bfd_boolean allocate_global_fptr_got
188  (struct elfNN_ia64_dyn_sym_info *dyn_i, void * data);
189static bfd_boolean allocate_local_got
190  (struct elfNN_ia64_dyn_sym_info *dyn_i, void * data);
191static bfd_boolean elfNN_ia64_hpux_vec
192  (const bfd_target *vec);
193static bfd_boolean allocate_dynrel_entries
194  (struct elfNN_ia64_dyn_sym_info *dyn_i, void * data);
195static asection *get_pltoff
196  (bfd *abfd, struct bfd_link_info *info,
197   struct elfNN_ia64_link_hash_table *ia64_info);
198
199/* ia64-specific relocation.  */
200
201/* Given a ELF reloc, return the matching HOWTO structure.  */
202
203static bfd_boolean
204elfNN_ia64_info_to_howto (bfd *abfd ATTRIBUTE_UNUSED,
205			  arelent *bfd_reloc,
206			  Elf_Internal_Rela *elf_reloc)
207{
208  unsigned int r_type = ELF32_R_TYPE (elf_reloc->r_info);
209
210  bfd_reloc->howto = ia64_elf_lookup_howto (r_type);
211  if (bfd_reloc->howto == NULL)
212    {
213      /* xgettext:c-format */
214      _bfd_error_handler (_("%pB: unsupported relocation type %#x"),
215			  abfd, r_type);
216      bfd_set_error (bfd_error_bad_value);
217      return FALSE;
218    }
219
220  return TRUE;
221}
222
223#define PLT_HEADER_SIZE		(3 * 16)
224#define PLT_MIN_ENTRY_SIZE	(1 * 16)
225#define PLT_FULL_ENTRY_SIZE	(2 * 16)
226#define PLT_RESERVED_WORDS	3
227
228static const bfd_byte plt_header[PLT_HEADER_SIZE] =
229{
230  0x0b, 0x10, 0x00, 0x1c, 0x00, 0x21,  /*   [MMI]	mov r2=r14;;	   */
231  0xe0, 0x00, 0x08, 0x00, 0x48, 0x00,  /*		addl r14=0,r2	   */
232  0x00, 0x00, 0x04, 0x00,	       /*		nop.i 0x0;;	   */
233  0x0b, 0x80, 0x20, 0x1c, 0x18, 0x14,  /*   [MMI]	ld8 r16=[r14],8;;  */
234  0x10, 0x41, 0x38, 0x30, 0x28, 0x00,  /*		ld8 r17=[r14],8	   */
235  0x00, 0x00, 0x04, 0x00,	       /*		nop.i 0x0;;	   */
236  0x11, 0x08, 0x00, 0x1c, 0x18, 0x10,  /*   [MIB]	ld8 r1=[r14]	   */
237  0x60, 0x88, 0x04, 0x80, 0x03, 0x00,  /*		mov b6=r17	   */
238  0x60, 0x00, 0x80, 0x00	       /*		br.few b6;;	   */
239};
240
241static const bfd_byte plt_min_entry[PLT_MIN_ENTRY_SIZE] =
242{
243  0x11, 0x78, 0x00, 0x00, 0x00, 0x24,  /*   [MIB]	mov r15=0	   */
244  0x00, 0x00, 0x00, 0x02, 0x00, 0x00,  /*		nop.i 0x0	   */
245  0x00, 0x00, 0x00, 0x40	       /*		br.few 0 <PLT0>;;  */
246};
247
248static const bfd_byte plt_full_entry[PLT_FULL_ENTRY_SIZE] =
249{
250  0x0b, 0x78, 0x00, 0x02, 0x00, 0x24,  /*   [MMI]	addl r15=0,r1;;	   */
251  0x00, 0x41, 0x3c, 0x70, 0x29, 0xc0,  /*		ld8.acq r16=[r15],8*/
252  0x01, 0x08, 0x00, 0x84,	       /*		mov r14=r1;;	   */
253  0x11, 0x08, 0x00, 0x1e, 0x18, 0x10,  /*   [MIB]	ld8 r1=[r15]	   */
254  0x60, 0x80, 0x04, 0x80, 0x03, 0x00,  /*		mov b6=r16	   */
255  0x60, 0x00, 0x80, 0x00	       /*		br.few b6;;	   */
256};
257
258#define ELF_DYNAMIC_INTERPRETER "/usr/lib/ld.so.1"
259
260static const bfd_byte oor_brl[16] =
261{
262  0x05, 0x00, 0x00, 0x00, 0x01, 0x00,  /*  [MLX]	nop.m 0		   */
263  0x00, 0x00, 0x00, 0x00, 0x00, 0x00,  /*		brl.sptk.few tgt;; */
264  0x00, 0x00, 0x00, 0xc0
265};
266
267static const bfd_byte oor_ip[48] =
268{
269  0x04, 0x00, 0x00, 0x00, 0x01, 0x00,  /*  [MLX]	nop.m 0		   */
270  0x00, 0x00, 0x00, 0x00, 0x00, 0xe0,  /*		movl r15=0	   */
271  0x01, 0x00, 0x00, 0x60,
272  0x03, 0x00, 0x00, 0x00, 0x01, 0x00,  /*  [MII]	nop.m 0		   */
273  0x00, 0x01, 0x00, 0x60, 0x00, 0x00,  /*		mov r16=ip;;	   */
274  0xf2, 0x80, 0x00, 0x80,	       /*		add r16=r15,r16;;  */
275  0x11, 0x00, 0x00, 0x00, 0x01, 0x00,  /*  [MIB]	nop.m 0		   */
276  0x60, 0x80, 0x04, 0x80, 0x03, 0x00,  /*		mov b6=r16	   */
277  0x60, 0x00, 0x80, 0x00	       /*		br b6;;		   */
278};
279
280static size_t oor_branch_size = sizeof (oor_brl);
281
282void
283bfd_elfNN_ia64_after_parse (int itanium)
284{
285  oor_branch_size = itanium ? sizeof (oor_ip) : sizeof (oor_brl);
286}
287
288
289/* Rename some of the generic section flags to better document how they
290   are used here.  */
291#define skip_relax_pass_0 sec_flg0
292#define skip_relax_pass_1 sec_flg1
293
294/* These functions do relaxation for IA-64 ELF.  */
295
296static void
297elfNN_ia64_update_short_info (asection *sec, bfd_vma offset,
298			      struct elfNN_ia64_link_hash_table *ia64_info)
299{
300  /* Skip ABS and SHF_IA_64_SHORT sections.  */
301  if (sec == bfd_abs_section_ptr
302      || (sec->flags & SEC_SMALL_DATA) != 0)
303    return;
304
305  if (!ia64_info->min_short_sec)
306    {
307      ia64_info->max_short_sec = sec;
308      ia64_info->max_short_offset = offset;
309      ia64_info->min_short_sec = sec;
310      ia64_info->min_short_offset = offset;
311    }
312  else if (sec == ia64_info->max_short_sec
313	   && offset > ia64_info->max_short_offset)
314    ia64_info->max_short_offset = offset;
315  else if (sec == ia64_info->min_short_sec
316	   && offset < ia64_info->min_short_offset)
317    ia64_info->min_short_offset = offset;
318  else if (sec->output_section->vma
319	   > ia64_info->max_short_sec->vma)
320    {
321      ia64_info->max_short_sec = sec;
322      ia64_info->max_short_offset = offset;
323    }
324  else if (sec->output_section->vma
325	   < ia64_info->min_short_sec->vma)
326    {
327      ia64_info->min_short_sec = sec;
328      ia64_info->min_short_offset = offset;
329    }
330}
331
332static bfd_boolean
333elfNN_ia64_relax_section (bfd *abfd, asection *sec,
334			  struct bfd_link_info *link_info,
335			  bfd_boolean *again)
336{
337  struct one_fixup
338    {
339      struct one_fixup *next;
340      asection *tsec;
341      bfd_vma toff;
342      bfd_vma trampoff;
343    };
344
345  Elf_Internal_Shdr *symtab_hdr;
346  Elf_Internal_Rela *internal_relocs;
347  Elf_Internal_Rela *irel, *irelend;
348  bfd_byte *contents;
349  Elf_Internal_Sym *isymbuf = NULL;
350  struct elfNN_ia64_link_hash_table *ia64_info;
351  struct one_fixup *fixups = NULL;
352  bfd_boolean changed_contents = FALSE;
353  bfd_boolean changed_relocs = FALSE;
354  bfd_boolean changed_got = FALSE;
355  bfd_boolean skip_relax_pass_0 = TRUE;
356  bfd_boolean skip_relax_pass_1 = TRUE;
357  bfd_vma gp = 0;
358
359  /* Assume we're not going to change any sizes, and we'll only need
360     one pass.  */
361  *again = FALSE;
362
363  if (bfd_link_relocatable (link_info))
364    (*link_info->callbacks->einfo)
365      (_("%P%F: --relax and -r may not be used together\n"));
366
367  /* Don't even try to relax for non-ELF outputs.  */
368  if (!is_elf_hash_table (link_info->hash))
369    return FALSE;
370
371  /* Nothing to do if there are no relocations or there is no need for
372     the current pass.  */
373  if ((sec->flags & SEC_RELOC) == 0
374      || sec->reloc_count == 0
375      || (link_info->relax_pass == 0 && sec->skip_relax_pass_0)
376      || (link_info->relax_pass == 1 && sec->skip_relax_pass_1))
377    return TRUE;
378
379  ia64_info = elfNN_ia64_hash_table (link_info);
380  if (ia64_info == NULL)
381    return FALSE;
382
383  symtab_hdr = &elf_tdata (abfd)->symtab_hdr;
384
385  /* Load the relocations for this section.  */
386  internal_relocs = (_bfd_elf_link_read_relocs
387		     (abfd, sec, NULL, (Elf_Internal_Rela *) NULL,
388		      link_info->keep_memory));
389  if (internal_relocs == NULL)
390    return FALSE;
391
392  irelend = internal_relocs + sec->reloc_count;
393
394  /* Get the section contents.  */
395  if (elf_section_data (sec)->this_hdr.contents != NULL)
396    contents = elf_section_data (sec)->this_hdr.contents;
397  else
398    {
399      if (!bfd_malloc_and_get_section (abfd, sec, &contents))
400	goto error_return;
401    }
402
403  for (irel = internal_relocs; irel < irelend; irel++)
404    {
405      unsigned long r_type = ELFNN_R_TYPE (irel->r_info);
406      bfd_vma symaddr, reladdr, trampoff, toff, roff;
407      asection *tsec;
408      struct one_fixup *f;
409      bfd_size_type amt;
410      bfd_boolean is_branch;
411      struct elfNN_ia64_dyn_sym_info *dyn_i;
412      char symtype;
413
414      switch (r_type)
415	{
416	case R_IA64_PCREL21B:
417	case R_IA64_PCREL21BI:
418	case R_IA64_PCREL21M:
419	case R_IA64_PCREL21F:
420	  /* In pass 1, all br relaxations are done. We can skip it. */
421	  if (link_info->relax_pass == 1)
422	    continue;
423	  skip_relax_pass_0 = FALSE;
424	  is_branch = TRUE;
425	  break;
426
427	case R_IA64_PCREL60B:
428	  /* We can't optimize brl to br in pass 0 since br relaxations
429	     will increase the code size. Defer it to pass 1.  */
430	  if (link_info->relax_pass == 0)
431	    {
432	      skip_relax_pass_1 = FALSE;
433	      continue;
434	    }
435	  is_branch = TRUE;
436	  break;
437
438	case R_IA64_GPREL22:
439	  /* Update max_short_sec/min_short_sec.  */
440
441	case R_IA64_LTOFF22X:
442	case R_IA64_LDXMOV:
443	  /* We can't relax ldx/mov in pass 0 since br relaxations will
444	     increase the code size. Defer it to pass 1.  */
445	  if (link_info->relax_pass == 0)
446	    {
447	      skip_relax_pass_1 = FALSE;
448	      continue;
449	    }
450	  is_branch = FALSE;
451	  break;
452
453	default:
454	  continue;
455	}
456
457      /* Get the value of the symbol referred to by the reloc.  */
458      if (ELFNN_R_SYM (irel->r_info) < symtab_hdr->sh_info)
459	{
460	  /* A local symbol.  */
461	  Elf_Internal_Sym *isym;
462
463	  /* Read this BFD's local symbols.  */
464	  if (isymbuf == NULL)
465	    {
466	      isymbuf = (Elf_Internal_Sym *) symtab_hdr->contents;
467	      if (isymbuf == NULL)
468		isymbuf = bfd_elf_get_elf_syms (abfd, symtab_hdr,
469						symtab_hdr->sh_info, 0,
470						NULL, NULL, NULL);
471	      if (isymbuf == 0)
472		goto error_return;
473	    }
474
475	  isym = isymbuf + ELFNN_R_SYM (irel->r_info);
476	  if (isym->st_shndx == SHN_UNDEF)
477	    continue;	/* We can't do anything with undefined symbols.  */
478	  else if (isym->st_shndx == SHN_ABS)
479	    tsec = bfd_abs_section_ptr;
480	  else if (isym->st_shndx == SHN_COMMON)
481	    tsec = bfd_com_section_ptr;
482	  else if (isym->st_shndx == SHN_IA_64_ANSI_COMMON)
483	    tsec = bfd_com_section_ptr;
484	  else
485	    tsec = bfd_section_from_elf_index (abfd, isym->st_shndx);
486
487	  toff = isym->st_value;
488	  dyn_i = get_dyn_sym_info (ia64_info, NULL, abfd, irel, FALSE);
489	  symtype = ELF_ST_TYPE (isym->st_info);
490	}
491      else
492	{
493	  unsigned long indx;
494	  struct elf_link_hash_entry *h;
495
496	  indx = ELFNN_R_SYM (irel->r_info) - symtab_hdr->sh_info;
497	  h = elf_sym_hashes (abfd)[indx];
498	  BFD_ASSERT (h != NULL);
499
500	  while (h->root.type == bfd_link_hash_indirect
501		 || h->root.type == bfd_link_hash_warning)
502	    h = (struct elf_link_hash_entry *) h->root.u.i.link;
503
504	  dyn_i = get_dyn_sym_info (ia64_info, h, abfd, irel, FALSE);
505
506	  /* For branches to dynamic symbols, we're interested instead
507	     in a branch to the PLT entry.  */
508	  if (is_branch && dyn_i && dyn_i->want_plt2)
509	    {
510	      /* Internal branches shouldn't be sent to the PLT.
511		 Leave this for now and we'll give an error later.  */
512	      if (r_type != R_IA64_PCREL21B)
513		continue;
514
515	      tsec = ia64_info->root.splt;
516	      toff = dyn_i->plt2_offset;
517	      BFD_ASSERT (irel->r_addend == 0);
518	    }
519
520	  /* Can't do anything else with dynamic symbols.  */
521	  else if (elfNN_ia64_dynamic_symbol_p (h, link_info, r_type))
522	    continue;
523
524	  else
525	    {
526	      /* We can't do anything with undefined symbols.  */
527	      if (h->root.type == bfd_link_hash_undefined
528		  || h->root.type == bfd_link_hash_undefweak)
529		continue;
530
531	      tsec = h->root.u.def.section;
532	      toff = h->root.u.def.value;
533	    }
534
535	  symtype = h->type;
536	}
537
538      if (tsec->sec_info_type == SEC_INFO_TYPE_MERGE)
539	{
540	  /* At this stage in linking, no SEC_MERGE symbol has been
541	     adjusted, so all references to such symbols need to be
542	     passed through _bfd_merged_section_offset.  (Later, in
543	     relocate_section, all SEC_MERGE symbols *except* for
544	     section symbols have been adjusted.)
545
546	     gas may reduce relocations against symbols in SEC_MERGE
547	     sections to a relocation against the section symbol when
548	     the original addend was zero.  When the reloc is against
549	     a section symbol we should include the addend in the
550	     offset passed to _bfd_merged_section_offset, since the
551	     location of interest is the original symbol.  On the
552	     other hand, an access to "sym+addend" where "sym" is not
553	     a section symbol should not include the addend;  Such an
554	     access is presumed to be an offset from "sym";  The
555	     location of interest is just "sym".  */
556	   if (symtype == STT_SECTION)
557	     toff += irel->r_addend;
558
559	   toff = _bfd_merged_section_offset (abfd, &tsec,
560					      elf_section_data (tsec)->sec_info,
561					      toff);
562
563	   if (symtype != STT_SECTION)
564	     toff += irel->r_addend;
565	}
566      else
567	toff += irel->r_addend;
568
569      symaddr = tsec->output_section->vma + tsec->output_offset + toff;
570
571      roff = irel->r_offset;
572
573      if (is_branch)
574	{
575	  bfd_signed_vma offset;
576
577	  reladdr = (sec->output_section->vma
578		     + sec->output_offset
579		     + roff) & (bfd_vma) -4;
580
581	  /* The .plt section is aligned at 32byte and the .text section
582	     is aligned at 64byte. The .text section is right after the
583	     .plt section.  After the first relaxation pass, linker may
584	     increase the gap between the .plt and .text sections up
585	     to 32byte.  We assume linker will always insert 32byte
586	     between the .plt and .text sections after the first
587	     relaxation pass.  */
588	  if (tsec == ia64_info->root.splt)
589	    offset = -0x1000000 + 32;
590	  else
591	    offset = -0x1000000;
592
593	  /* If the branch is in range, no need to do anything.  */
594	  if ((bfd_signed_vma) (symaddr - reladdr) >= offset
595	      && (bfd_signed_vma) (symaddr - reladdr) <= 0x0FFFFF0)
596	    {
597	      /* If the 60-bit branch is in 21-bit range, optimize it. */
598	      if (r_type == R_IA64_PCREL60B)
599		{
600		  ia64_elf_relax_brl (contents, roff);
601
602		  irel->r_info
603		    = ELFNN_R_INFO (ELFNN_R_SYM (irel->r_info),
604				    R_IA64_PCREL21B);
605
606		  /* If the original relocation offset points to slot
607		     1, change it to slot 2.  */
608		  if ((irel->r_offset & 3) == 1)
609		    irel->r_offset += 1;
610
611		  changed_contents = TRUE;
612		  changed_relocs = TRUE;
613		}
614
615	      continue;
616	    }
617	  else if (r_type == R_IA64_PCREL60B)
618	    continue;
619	  else if (ia64_elf_relax_br (contents, roff))
620	    {
621	      irel->r_info
622		= ELFNN_R_INFO (ELFNN_R_SYM (irel->r_info),
623				R_IA64_PCREL60B);
624
625	      /* Make the relocation offset point to slot 1.  */
626	      irel->r_offset = (irel->r_offset & ~((bfd_vma) 0x3)) + 1;
627
628	      changed_contents = TRUE;
629	      changed_relocs = TRUE;
630	      continue;
631	    }
632
633	  /* We can't put a trampoline in a .init/.fini section. Issue
634	     an error.  */
635	  if (strcmp (sec->output_section->name, ".init") == 0
636	      || strcmp (sec->output_section->name, ".fini") == 0)
637	    {
638	      _bfd_error_handler
639		/* xgettext:c-format */
640		(_("%pB: can't relax br at %#" PRIx64 " in section `%pA';"
641		   " please use brl or indirect branch"),
642		 sec->owner, (uint64_t) roff, sec);
643	      bfd_set_error (bfd_error_bad_value);
644	      goto error_return;
645	    }
646
647	  /* If the branch and target are in the same section, you've
648	     got one honking big section and we can't help you unless
649	     you are branching backwards.  You'll get an error message
650	     later.  */
651	  if (tsec == sec && toff > roff)
652	    continue;
653
654	  /* Look for an existing fixup to this address.  */
655	  for (f = fixups; f ; f = f->next)
656	    if (f->tsec == tsec && f->toff == toff)
657	      break;
658
659	  if (f == NULL)
660	    {
661	      /* Two alternatives: If it's a branch to a PLT entry, we can
662		 make a copy of the FULL_PLT entry.  Otherwise, we'll have
663		 to use a `brl' insn to get where we're going.  */
664
665	      size_t size;
666
667	      if (tsec == ia64_info->root.splt)
668		size = sizeof (plt_full_entry);
669	      else
670		size = oor_branch_size;
671
672	      /* Resize the current section to make room for the new branch. */
673	      trampoff = (sec->size + 15) & (bfd_vma) -16;
674
675	      /* If trampoline is out of range, there is nothing we
676		 can do.  */
677	      offset = trampoff - (roff & (bfd_vma) -4);
678	      if (offset < -0x1000000 || offset > 0x0FFFFF0)
679		continue;
680
681	      amt = trampoff + size;
682	      contents = (bfd_byte *) bfd_realloc (contents, amt);
683	      if (contents == NULL)
684		goto error_return;
685	      sec->size = amt;
686
687	      if (tsec == ia64_info->root.splt)
688		{
689		  memcpy (contents + trampoff, plt_full_entry, size);
690
691		  /* Hijack the old relocation for use as the PLTOFF reloc.  */
692		  irel->r_info = ELFNN_R_INFO (ELFNN_R_SYM (irel->r_info),
693					       R_IA64_PLTOFF22);
694		  irel->r_offset = trampoff;
695		}
696	      else
697		{
698		  if (size == sizeof (oor_ip))
699		    {
700		      memcpy (contents + trampoff, oor_ip, size);
701		      irel->r_info = ELFNN_R_INFO (ELFNN_R_SYM (irel->r_info),
702						   R_IA64_PCREL64I);
703		      irel->r_addend -= 16;
704		      irel->r_offset = trampoff + 2;
705		    }
706		  else
707		    {
708		      memcpy (contents + trampoff, oor_brl, size);
709		      irel->r_info = ELFNN_R_INFO (ELFNN_R_SYM (irel->r_info),
710						   R_IA64_PCREL60B);
711		      irel->r_offset = trampoff + 2;
712		    }
713
714		}
715
716	      /* Record the fixup so we don't do it again this section.  */
717	      f = (struct one_fixup *)
718		bfd_malloc ((bfd_size_type) sizeof (*f));
719	      f->next = fixups;
720	      f->tsec = tsec;
721	      f->toff = toff;
722	      f->trampoff = trampoff;
723	      fixups = f;
724	    }
725	  else
726	    {
727	      /* If trampoline is out of range, there is nothing we
728		 can do.  */
729	      offset = f->trampoff - (roff & (bfd_vma) -4);
730	      if (offset < -0x1000000 || offset > 0x0FFFFF0)
731		continue;
732
733	      /* Nop out the reloc, since we're finalizing things here.  */
734	      irel->r_info = ELFNN_R_INFO (0, R_IA64_NONE);
735	    }
736
737	  /* Fix up the existing branch to hit the trampoline.  */
738	  if (ia64_elf_install_value (contents + roff, offset, r_type)
739	      != bfd_reloc_ok)
740	    goto error_return;
741
742	  changed_contents = TRUE;
743	  changed_relocs = TRUE;
744	}
745      else
746	{
747	  /* Fetch the gp.  */
748	  if (gp == 0)
749	    {
750	      bfd *obfd = sec->output_section->owner;
751	      gp = _bfd_get_gp_value (obfd);
752	      if (gp == 0)
753		{
754		  if (!elfNN_ia64_choose_gp (obfd, link_info, FALSE))
755		    goto error_return;
756		  gp = _bfd_get_gp_value (obfd);
757		}
758	    }
759
760	  /* If the data is out of range, do nothing.  */
761	  if ((bfd_signed_vma) (symaddr - gp) >= 0x200000
762	      ||(bfd_signed_vma) (symaddr - gp) < -0x200000)
763	    continue;
764
765	  if (r_type == R_IA64_GPREL22)
766	    elfNN_ia64_update_short_info (tsec->output_section,
767					  tsec->output_offset + toff,
768					  ia64_info);
769	  else if (r_type == R_IA64_LTOFF22X)
770	    {
771	      irel->r_info = ELFNN_R_INFO (ELFNN_R_SYM (irel->r_info),
772					   R_IA64_GPREL22);
773	      changed_relocs = TRUE;
774	      if (dyn_i->want_gotx)
775		{
776		  dyn_i->want_gotx = 0;
777		  changed_got |= !dyn_i->want_got;
778		}
779
780	      elfNN_ia64_update_short_info (tsec->output_section,
781					    tsec->output_offset + toff,
782					    ia64_info);
783	    }
784	  else
785	    {
786	      ia64_elf_relax_ldxmov (contents, roff);
787	      irel->r_info = ELFNN_R_INFO (0, R_IA64_NONE);
788	      changed_contents = TRUE;
789	      changed_relocs = TRUE;
790	    }
791	}
792    }
793
794  /* ??? If we created fixups, this may push the code segment large
795     enough that the data segment moves, which will change the GP.
796     Reset the GP so that we re-calculate next round.  We need to
797     do this at the _beginning_ of the next round; now will not do.  */
798
799  /* Clean up and go home.  */
800  while (fixups)
801    {
802      struct one_fixup *f = fixups;
803      fixups = fixups->next;
804      free (f);
805    }
806
807  if (isymbuf != NULL
808      && symtab_hdr->contents != (unsigned char *) isymbuf)
809    {
810      if (! link_info->keep_memory)
811	free (isymbuf);
812      else
813	{
814	  /* Cache the symbols for elf_link_input_bfd.  */
815	  symtab_hdr->contents = (unsigned char *) isymbuf;
816	}
817    }
818
819  if (contents != NULL
820      && elf_section_data (sec)->this_hdr.contents != contents)
821    {
822      if (!changed_contents && !link_info->keep_memory)
823	free (contents);
824      else
825	{
826	  /* Cache the section contents for elf_link_input_bfd.  */
827	  elf_section_data (sec)->this_hdr.contents = contents;
828	}
829    }
830
831  if (elf_section_data (sec)->relocs != internal_relocs)
832    {
833      if (!changed_relocs)
834	free (internal_relocs);
835      else
836	elf_section_data (sec)->relocs = internal_relocs;
837    }
838
839  if (changed_got)
840    {
841      struct elfNN_ia64_allocate_data data;
842      data.info = link_info;
843      data.ofs = 0;
844      ia64_info->self_dtpmod_offset = (bfd_vma) -1;
845
846      elfNN_ia64_dyn_sym_traverse (ia64_info, allocate_global_data_got, &data);
847      elfNN_ia64_dyn_sym_traverse (ia64_info, allocate_global_fptr_got, &data);
848      elfNN_ia64_dyn_sym_traverse (ia64_info, allocate_local_got, &data);
849      ia64_info->root.sgot->size = data.ofs;
850
851      if (ia64_info->root.dynamic_sections_created
852	  && ia64_info->root.srelgot != NULL)
853	{
854	  /* Resize .rela.got.  */
855	  ia64_info->root.srelgot->size = 0;
856	  if (bfd_link_pic (link_info)
857	      && ia64_info->self_dtpmod_offset != (bfd_vma) -1)
858	    ia64_info->root.srelgot->size += sizeof (ElfNN_External_Rela);
859	  data.only_got = TRUE;
860	  elfNN_ia64_dyn_sym_traverse (ia64_info, allocate_dynrel_entries,
861				       &data);
862	}
863    }
864
865  if (link_info->relax_pass == 0)
866    {
867      /* Pass 0 is only needed to relax br.  */
868      sec->skip_relax_pass_0 = skip_relax_pass_0;
869      sec->skip_relax_pass_1 = skip_relax_pass_1;
870    }
871
872  *again = changed_contents || changed_relocs;
873  return TRUE;
874
875 error_return:
876  if (isymbuf != NULL && (unsigned char *) isymbuf != symtab_hdr->contents)
877    free (isymbuf);
878  if (contents != NULL
879      && elf_section_data (sec)->this_hdr.contents != contents)
880    free (contents);
881  if (internal_relocs != NULL
882      && elf_section_data (sec)->relocs != internal_relocs)
883    free (internal_relocs);
884  return FALSE;
885}
886#undef skip_relax_pass_0
887#undef skip_relax_pass_1
888
889/* Return TRUE if NAME is an unwind table section name.  */
890
891static inline bfd_boolean
892is_unwind_section_name (bfd *abfd, const char *name)
893{
894  if (elfNN_ia64_hpux_vec (abfd->xvec)
895      && !strcmp (name, ELF_STRING_ia64_unwind_hdr))
896    return FALSE;
897
898  return ((CONST_STRNEQ (name, ELF_STRING_ia64_unwind)
899	   && ! CONST_STRNEQ (name, ELF_STRING_ia64_unwind_info))
900	  || CONST_STRNEQ (name, ELF_STRING_ia64_unwind_once));
901}
902
903/* Handle an IA-64 specific section when reading an object file.  This
904   is called when bfd_section_from_shdr finds a section with an unknown
905   type.  */
906
907static bfd_boolean
908elfNN_ia64_section_from_shdr (bfd *abfd,
909			      Elf_Internal_Shdr *hdr,
910			      const char *name,
911			      int shindex)
912{
913  /* There ought to be a place to keep ELF backend specific flags, but
914     at the moment there isn't one.  We just keep track of the
915     sections by their name, instead.  Fortunately, the ABI gives
916     suggested names for all the MIPS specific sections, so we will
917     probably get away with this.  */
918  switch (hdr->sh_type)
919    {
920    case SHT_IA_64_UNWIND:
921    case SHT_IA_64_HP_OPT_ANOT:
922      break;
923
924    case SHT_IA_64_EXT:
925      if (strcmp (name, ELF_STRING_ia64_archext) != 0)
926	return FALSE;
927      break;
928
929    default:
930      return FALSE;
931    }
932
933  if (! _bfd_elf_make_section_from_shdr (abfd, hdr, name, shindex))
934    return FALSE;
935
936  return TRUE;
937}
938
939/* Convert IA-64 specific section flags to bfd internal section flags.  */
940
941/* ??? There is no bfd internal flag equivalent to the SHF_IA_64_NORECOV
942   flag.  */
943
944static bfd_boolean
945elfNN_ia64_section_flags (flagword *flags,
946			  const Elf_Internal_Shdr *hdr)
947{
948  if (hdr->sh_flags & SHF_IA_64_SHORT)
949    *flags |= SEC_SMALL_DATA;
950
951  return TRUE;
952}
953
954/* Set the correct type for an IA-64 ELF section.  We do this by the
955   section name, which is a hack, but ought to work.  */
956
957static bfd_boolean
958elfNN_ia64_fake_sections (bfd *abfd, Elf_Internal_Shdr *hdr,
959			  asection *sec)
960{
961  const char *name;
962
963  name = bfd_section_name (sec);
964
965  if (is_unwind_section_name (abfd, name))
966    {
967      /* We don't have the sections numbered at this point, so sh_info
968	 is set later, in elfNN_ia64_final_write_processing.  */
969      hdr->sh_type = SHT_IA_64_UNWIND;
970      hdr->sh_flags |= SHF_LINK_ORDER;
971    }
972  else if (strcmp (name, ELF_STRING_ia64_archext) == 0)
973    hdr->sh_type = SHT_IA_64_EXT;
974  else if (strcmp (name, ".HP.opt_annot") == 0)
975    hdr->sh_type = SHT_IA_64_HP_OPT_ANOT;
976  else if (strcmp (name, ".reloc") == 0)
977    /* This is an ugly, but unfortunately necessary hack that is
978       needed when producing EFI binaries on IA-64. It tells
979       elf.c:elf_fake_sections() not to consider ".reloc" as a section
980       containing ELF relocation info.  We need this hack in order to
981       be able to generate ELF binaries that can be translated into
982       EFI applications (which are essentially COFF objects).  Those
983       files contain a COFF ".reloc" section inside an ELFNN object,
984       which would normally cause BFD to segfault because it would
985       attempt to interpret this section as containing relocation
986       entries for section "oc".  With this hack enabled, ".reloc"
987       will be treated as a normal data section, which will avoid the
988       segfault.  However, you won't be able to create an ELFNN binary
989       with a section named "oc" that needs relocations, but that's
990       the kind of ugly side-effects you get when detecting section
991       types based on their names...  In practice, this limitation is
992       unlikely to bite.  */
993    hdr->sh_type = SHT_PROGBITS;
994
995  if (sec->flags & SEC_SMALL_DATA)
996    hdr->sh_flags |= SHF_IA_64_SHORT;
997
998  /* Some HP linkers look for the SHF_IA_64_HP_TLS flag instead of SHF_TLS. */
999
1000  if (elfNN_ia64_hpux_vec (abfd->xvec) && (sec->flags & SHF_TLS))
1001    hdr->sh_flags |= SHF_IA_64_HP_TLS;
1002
1003  return TRUE;
1004}
1005
1006/* The final processing done just before writing out an IA-64 ELF
1007   object file.  */
1008
1009static bfd_boolean
1010elfNN_ia64_final_write_processing (bfd *abfd)
1011{
1012  Elf_Internal_Shdr *hdr;
1013  asection *s;
1014
1015  for (s = abfd->sections; s; s = s->next)
1016    {
1017      hdr = &elf_section_data (s)->this_hdr;
1018      switch (hdr->sh_type)
1019	{
1020	case SHT_IA_64_UNWIND:
1021	  /* The IA-64 processor-specific ABI requires setting sh_link
1022	     to the unwind section, whereas HP-UX requires sh_info to
1023	     do so.  For maximum compatibility, we'll set both for
1024	     now... */
1025	  hdr->sh_info = hdr->sh_link;
1026	  break;
1027	}
1028    }
1029
1030  if (! elf_flags_init (abfd))
1031    {
1032      unsigned long flags = 0;
1033
1034      if (abfd->xvec->byteorder == BFD_ENDIAN_BIG)
1035	flags |= EF_IA_64_BE;
1036      if (bfd_get_mach (abfd) == bfd_mach_ia64_elf64)
1037	flags |= EF_IA_64_ABI64;
1038
1039      elf_elfheader(abfd)->e_flags = flags;
1040      elf_flags_init (abfd) = TRUE;
1041    }
1042  return _bfd_elf_final_write_processing (abfd);
1043}
1044
1045/* Hook called by the linker routine which adds symbols from an object
1046   file.  We use it to put .comm items in .sbss, and not .bss.  */
1047
1048static bfd_boolean
1049elfNN_ia64_add_symbol_hook (bfd *abfd,
1050			    struct bfd_link_info *info,
1051			    Elf_Internal_Sym *sym,
1052			    const char **namep ATTRIBUTE_UNUSED,
1053			    flagword *flagsp ATTRIBUTE_UNUSED,
1054			    asection **secp,
1055			    bfd_vma *valp)
1056{
1057  if (sym->st_shndx == SHN_COMMON
1058      && !bfd_link_relocatable (info)
1059      && sym->st_size <= elf_gp_size (abfd))
1060    {
1061      /* Common symbols less than or equal to -G nn bytes are
1062	 automatically put into .sbss.  */
1063
1064      asection *scomm = bfd_get_section_by_name (abfd, ".scommon");
1065
1066      if (scomm == NULL)
1067	{
1068	  scomm = bfd_make_section_with_flags (abfd, ".scommon",
1069					       (SEC_ALLOC
1070						| SEC_IS_COMMON
1071						| SEC_LINKER_CREATED));
1072	  if (scomm == NULL)
1073	    return FALSE;
1074	}
1075
1076      *secp = scomm;
1077      *valp = sym->st_size;
1078    }
1079
1080  return TRUE;
1081}
1082
1083/* Return the number of additional phdrs we will need.  */
1084
1085static int
1086elfNN_ia64_additional_program_headers (bfd *abfd,
1087				       struct bfd_link_info *info ATTRIBUTE_UNUSED)
1088{
1089  asection *s;
1090  int ret = 0;
1091
1092  /* See if we need a PT_IA_64_ARCHEXT segment.  */
1093  s = bfd_get_section_by_name (abfd, ELF_STRING_ia64_archext);
1094  if (s && (s->flags & SEC_LOAD))
1095    ++ret;
1096
1097  /* Count how many PT_IA_64_UNWIND segments we need.  */
1098  for (s = abfd->sections; s; s = s->next)
1099    if (is_unwind_section_name (abfd, s->name) && (s->flags & SEC_LOAD))
1100      ++ret;
1101
1102  return ret;
1103}
1104
1105static bfd_boolean
1106elfNN_ia64_modify_segment_map (bfd *abfd,
1107			       struct bfd_link_info *info ATTRIBUTE_UNUSED)
1108{
1109  struct elf_segment_map *m, **pm;
1110  Elf_Internal_Shdr *hdr;
1111  asection *s;
1112
1113  /* If we need a PT_IA_64_ARCHEXT segment, it must come before
1114     all PT_LOAD segments.  */
1115  s = bfd_get_section_by_name (abfd, ELF_STRING_ia64_archext);
1116  if (s && (s->flags & SEC_LOAD))
1117    {
1118      for (m = elf_seg_map (abfd); m != NULL; m = m->next)
1119	if (m->p_type == PT_IA_64_ARCHEXT)
1120	  break;
1121      if (m == NULL)
1122	{
1123	  m = ((struct elf_segment_map *)
1124	       bfd_zalloc (abfd, (bfd_size_type) sizeof *m));
1125	  if (m == NULL)
1126	    return FALSE;
1127
1128	  m->p_type = PT_IA_64_ARCHEXT;
1129	  m->count = 1;
1130	  m->sections[0] = s;
1131
1132	  /* We want to put it after the PHDR and INTERP segments.  */
1133	  pm = &elf_seg_map (abfd);
1134	  while (*pm != NULL
1135		 && ((*pm)->p_type == PT_PHDR
1136		     || (*pm)->p_type == PT_INTERP))
1137	    pm = &(*pm)->next;
1138
1139	  m->next = *pm;
1140	  *pm = m;
1141	}
1142    }
1143
1144  /* Install PT_IA_64_UNWIND segments, if needed.  */
1145  for (s = abfd->sections; s; s = s->next)
1146    {
1147      hdr = &elf_section_data (s)->this_hdr;
1148      if (hdr->sh_type != SHT_IA_64_UNWIND)
1149	continue;
1150
1151      if (s && (s->flags & SEC_LOAD))
1152	{
1153	  for (m = elf_seg_map (abfd); m != NULL; m = m->next)
1154	    if (m->p_type == PT_IA_64_UNWIND)
1155	      {
1156		int i;
1157
1158		/* Look through all sections in the unwind segment
1159		   for a match since there may be multiple sections
1160		   to a segment.  */
1161		for (i = m->count - 1; i >= 0; --i)
1162		  if (m->sections[i] == s)
1163		    break;
1164
1165		if (i >= 0)
1166		  break;
1167	      }
1168
1169	  if (m == NULL)
1170	    {
1171	      m = ((struct elf_segment_map *)
1172		   bfd_zalloc (abfd, (bfd_size_type) sizeof *m));
1173	      if (m == NULL)
1174		return FALSE;
1175
1176	      m->p_type = PT_IA_64_UNWIND;
1177	      m->count = 1;
1178	      m->sections[0] = s;
1179	      m->next = NULL;
1180
1181	      /* We want to put it last.  */
1182	      pm = &elf_seg_map (abfd);
1183	      while (*pm != NULL)
1184		pm = &(*pm)->next;
1185	      *pm = m;
1186	    }
1187	}
1188    }
1189
1190  return TRUE;
1191}
1192
1193/* Turn on PF_IA_64_NORECOV if needed.  This involves traversing all of
1194   the input sections for each output section in the segment and testing
1195   for SHF_IA_64_NORECOV on each.  */
1196
1197static bfd_boolean
1198elfNN_ia64_modify_headers (bfd *abfd, struct bfd_link_info *info)
1199{
1200  struct elf_obj_tdata *tdata = elf_tdata (abfd);
1201  struct elf_segment_map *m;
1202  Elf_Internal_Phdr *p;
1203
1204  for (p = tdata->phdr, m = elf_seg_map (abfd); m != NULL; m = m->next, p++)
1205    if (m->p_type == PT_LOAD)
1206      {
1207	int i;
1208	for (i = m->count - 1; i >= 0; --i)
1209	  {
1210	    struct bfd_link_order *order = m->sections[i]->map_head.link_order;
1211
1212	    while (order != NULL)
1213	      {
1214		if (order->type == bfd_indirect_link_order)
1215		  {
1216		    asection *is = order->u.indirect.section;
1217		    bfd_vma flags = elf_section_data(is)->this_hdr.sh_flags;
1218		    if (flags & SHF_IA_64_NORECOV)
1219		      {
1220			p->p_flags |= PF_IA_64_NORECOV;
1221			goto found;
1222		      }
1223		  }
1224		order = order->next;
1225	      }
1226	  }
1227      found:;
1228      }
1229
1230  return _bfd_elf_modify_headers (abfd, info);
1231}
1232
1233/* According to the Tahoe assembler spec, all labels starting with a
1234   '.' are local.  */
1235
1236static bfd_boolean
1237elfNN_ia64_is_local_label_name (bfd *abfd ATTRIBUTE_UNUSED,
1238				const char *name)
1239{
1240  return name[0] == '.';
1241}
1242
1243/* Should we do dynamic things to this symbol?  */
1244
1245static bfd_boolean
1246elfNN_ia64_dynamic_symbol_p (struct elf_link_hash_entry *h,
1247			     struct bfd_link_info *info, int r_type)
1248{
1249  bfd_boolean ignore_protected
1250    = ((r_type & 0xf8) == 0x40		/* FPTR relocs */
1251       || (r_type & 0xf8) == 0x50);	/* LTOFF_FPTR relocs */
1252
1253  return _bfd_elf_dynamic_symbol_p (h, info, ignore_protected);
1254}
1255
1256static struct bfd_hash_entry*
1257elfNN_ia64_new_elf_hash_entry (struct bfd_hash_entry *entry,
1258			       struct bfd_hash_table *table,
1259			       const char *string)
1260{
1261  struct elfNN_ia64_link_hash_entry *ret;
1262  ret = (struct elfNN_ia64_link_hash_entry *) entry;
1263
1264  /* Allocate the structure if it has not already been allocated by a
1265     subclass.  */
1266  if (!ret)
1267    ret = bfd_hash_allocate (table, sizeof (*ret));
1268
1269  if (!ret)
1270    return 0;
1271
1272  /* Call the allocation method of the superclass.  */
1273  ret = ((struct elfNN_ia64_link_hash_entry *)
1274	 _bfd_elf_link_hash_newfunc ((struct bfd_hash_entry *) ret,
1275				     table, string));
1276
1277  ret->info = NULL;
1278  ret->count = 0;
1279  ret->sorted_count = 0;
1280  ret->size = 0;
1281  return (struct bfd_hash_entry *) ret;
1282}
1283
1284static void
1285elfNN_ia64_hash_copy_indirect (struct bfd_link_info *info,
1286			       struct elf_link_hash_entry *xdir,
1287			       struct elf_link_hash_entry *xind)
1288{
1289  struct elfNN_ia64_link_hash_entry *dir, *ind;
1290
1291  dir = (struct elfNN_ia64_link_hash_entry *) xdir;
1292  ind = (struct elfNN_ia64_link_hash_entry *) xind;
1293
1294  /* Copy down any references that we may have already seen to the
1295     symbol which just became indirect.  */
1296
1297  if (dir->root.versioned != versioned_hidden)
1298    dir->root.ref_dynamic |= ind->root.ref_dynamic;
1299  dir->root.ref_regular |= ind->root.ref_regular;
1300  dir->root.ref_regular_nonweak |= ind->root.ref_regular_nonweak;
1301  dir->root.needs_plt |= ind->root.needs_plt;
1302
1303  if (ind->root.root.type != bfd_link_hash_indirect)
1304    return;
1305
1306  /* Copy over the got and plt data.  This would have been done
1307     by check_relocs.  */
1308
1309  if (ind->info != NULL)
1310    {
1311      struct elfNN_ia64_dyn_sym_info *dyn_i;
1312      unsigned int count;
1313
1314      if (dir->info)
1315	free (dir->info);
1316
1317      dir->info = ind->info;
1318      dir->count = ind->count;
1319      dir->sorted_count = ind->sorted_count;
1320      dir->size = ind->size;
1321
1322      ind->info = NULL;
1323      ind->count = 0;
1324      ind->sorted_count = 0;
1325      ind->size = 0;
1326
1327      /* Fix up the dyn_sym_info pointers to the global symbol.  */
1328      for (count = dir->count, dyn_i = dir->info;
1329	   count != 0;
1330	   count--, dyn_i++)
1331	dyn_i->h = &dir->root;
1332    }
1333
1334  /* Copy over the dynindx.  */
1335
1336  if (ind->root.dynindx != -1)
1337    {
1338      if (dir->root.dynindx != -1)
1339	_bfd_elf_strtab_delref (elf_hash_table (info)->dynstr,
1340				dir->root.dynstr_index);
1341      dir->root.dynindx = ind->root.dynindx;
1342      dir->root.dynstr_index = ind->root.dynstr_index;
1343      ind->root.dynindx = -1;
1344      ind->root.dynstr_index = 0;
1345    }
1346}
1347
1348static void
1349elfNN_ia64_hash_hide_symbol (struct bfd_link_info *info,
1350			     struct elf_link_hash_entry *xh,
1351			     bfd_boolean force_local)
1352{
1353  struct elfNN_ia64_link_hash_entry *h;
1354  struct elfNN_ia64_dyn_sym_info *dyn_i;
1355  unsigned int count;
1356
1357  h = (struct elfNN_ia64_link_hash_entry *)xh;
1358
1359  _bfd_elf_link_hash_hide_symbol (info, &h->root, force_local);
1360
1361  for (count = h->count, dyn_i = h->info;
1362       count != 0;
1363       count--, dyn_i++)
1364    {
1365      dyn_i->want_plt2 = 0;
1366      dyn_i->want_plt = 0;
1367    }
1368}
1369
1370/* Compute a hash of a local hash entry.  */
1371
1372static hashval_t
1373elfNN_ia64_local_htab_hash (const void *ptr)
1374{
1375  struct elfNN_ia64_local_hash_entry *entry
1376    = (struct elfNN_ia64_local_hash_entry *) ptr;
1377
1378  return ELF_LOCAL_SYMBOL_HASH (entry->id, entry->r_sym);
1379}
1380
1381/* Compare local hash entries.  */
1382
1383static int
1384elfNN_ia64_local_htab_eq (const void *ptr1, const void *ptr2)
1385{
1386  struct elfNN_ia64_local_hash_entry *entry1
1387    = (struct elfNN_ia64_local_hash_entry *) ptr1;
1388  struct elfNN_ia64_local_hash_entry *entry2
1389    = (struct elfNN_ia64_local_hash_entry *) ptr2;
1390
1391  return entry1->id == entry2->id && entry1->r_sym == entry2->r_sym;
1392}
1393
1394/* Free the global elfNN_ia64_dyn_sym_info array.  */
1395
1396static bfd_boolean
1397elfNN_ia64_global_dyn_info_free (void **xentry,
1398				 void * unused ATTRIBUTE_UNUSED)
1399{
1400  struct elfNN_ia64_link_hash_entry *entry
1401    = (struct elfNN_ia64_link_hash_entry *) xentry;
1402
1403  if (entry->info)
1404    {
1405      free (entry->info);
1406      entry->info = NULL;
1407      entry->count = 0;
1408      entry->sorted_count = 0;
1409      entry->size = 0;
1410    }
1411
1412  return TRUE;
1413}
1414
1415/* Free the local elfNN_ia64_dyn_sym_info array.  */
1416
1417static bfd_boolean
1418elfNN_ia64_local_dyn_info_free (void **slot,
1419				void * unused ATTRIBUTE_UNUSED)
1420{
1421  struct elfNN_ia64_local_hash_entry *entry
1422    = (struct elfNN_ia64_local_hash_entry *) *slot;
1423
1424  if (entry->info)
1425    {
1426      free (entry->info);
1427      entry->info = NULL;
1428      entry->count = 0;
1429      entry->sorted_count = 0;
1430      entry->size = 0;
1431    }
1432
1433  return TRUE;
1434}
1435
1436/* Destroy IA-64 linker hash table.  */
1437
1438static void
1439elfNN_ia64_link_hash_table_free (bfd *obfd)
1440{
1441  struct elfNN_ia64_link_hash_table *ia64_info
1442    = (struct elfNN_ia64_link_hash_table *) obfd->link.hash;
1443  if (ia64_info->loc_hash_table)
1444    {
1445      htab_traverse (ia64_info->loc_hash_table,
1446		     elfNN_ia64_local_dyn_info_free, NULL);
1447      htab_delete (ia64_info->loc_hash_table);
1448    }
1449  if (ia64_info->loc_hash_memory)
1450    objalloc_free ((struct objalloc *) ia64_info->loc_hash_memory);
1451  elf_link_hash_traverse (&ia64_info->root,
1452			  elfNN_ia64_global_dyn_info_free, NULL);
1453  _bfd_elf_link_hash_table_free (obfd);
1454}
1455
1456/* Create the derived linker hash table.  The IA-64 ELF port uses this
1457   derived hash table to keep information specific to the IA-64 ElF
1458   linker (without using static variables).  */
1459
1460static struct bfd_link_hash_table *
1461elfNN_ia64_hash_table_create (bfd *abfd)
1462{
1463  struct elfNN_ia64_link_hash_table *ret;
1464
1465  ret = bfd_zmalloc ((bfd_size_type) sizeof (*ret));
1466  if (!ret)
1467    return NULL;
1468
1469  if (!_bfd_elf_link_hash_table_init (&ret->root, abfd,
1470				      elfNN_ia64_new_elf_hash_entry,
1471				      sizeof (struct elfNN_ia64_link_hash_entry),
1472				      IA64_ELF_DATA))
1473    {
1474      free (ret);
1475      return NULL;
1476    }
1477
1478  ret->loc_hash_table = htab_try_create (1024, elfNN_ia64_local_htab_hash,
1479					 elfNN_ia64_local_htab_eq, NULL);
1480  ret->loc_hash_memory = objalloc_create ();
1481  if (!ret->loc_hash_table || !ret->loc_hash_memory)
1482    {
1483      elfNN_ia64_link_hash_table_free (abfd);
1484      return NULL;
1485    }
1486  ret->root.root.hash_table_free = elfNN_ia64_link_hash_table_free;
1487
1488  return &ret->root.root;
1489}
1490
1491/* Traverse both local and global hash tables.  */
1492
1493struct elfNN_ia64_dyn_sym_traverse_data
1494{
1495  bfd_boolean (*func) (struct elfNN_ia64_dyn_sym_info *, void *);
1496  void * data;
1497};
1498
1499static bfd_boolean
1500elfNN_ia64_global_dyn_sym_thunk (struct bfd_hash_entry *xentry,
1501				 void * xdata)
1502{
1503  struct elfNN_ia64_link_hash_entry *entry
1504    = (struct elfNN_ia64_link_hash_entry *) xentry;
1505  struct elfNN_ia64_dyn_sym_traverse_data *data
1506    = (struct elfNN_ia64_dyn_sym_traverse_data *) xdata;
1507  struct elfNN_ia64_dyn_sym_info *dyn_i;
1508  unsigned int count;
1509
1510  for (count = entry->count, dyn_i = entry->info;
1511       count != 0;
1512       count--, dyn_i++)
1513    if (! (*data->func) (dyn_i, data->data))
1514      return FALSE;
1515  return TRUE;
1516}
1517
1518static bfd_boolean
1519elfNN_ia64_local_dyn_sym_thunk (void **slot, void * xdata)
1520{
1521  struct elfNN_ia64_local_hash_entry *entry
1522    = (struct elfNN_ia64_local_hash_entry *) *slot;
1523  struct elfNN_ia64_dyn_sym_traverse_data *data
1524    = (struct elfNN_ia64_dyn_sym_traverse_data *) xdata;
1525  struct elfNN_ia64_dyn_sym_info *dyn_i;
1526  unsigned int count;
1527
1528  for (count = entry->count, dyn_i = entry->info;
1529       count != 0;
1530       count--, dyn_i++)
1531    if (! (*data->func) (dyn_i, data->data))
1532      return FALSE;
1533  return TRUE;
1534}
1535
1536static void
1537elfNN_ia64_dyn_sym_traverse (struct elfNN_ia64_link_hash_table *ia64_info,
1538			     bfd_boolean (*func) (struct elfNN_ia64_dyn_sym_info *, void *),
1539			     void * data)
1540{
1541  struct elfNN_ia64_dyn_sym_traverse_data xdata;
1542
1543  xdata.func = func;
1544  xdata.data = data;
1545
1546  elf_link_hash_traverse (&ia64_info->root,
1547			  elfNN_ia64_global_dyn_sym_thunk, &xdata);
1548  htab_traverse (ia64_info->loc_hash_table,
1549		 elfNN_ia64_local_dyn_sym_thunk, &xdata);
1550}
1551
1552static bfd_boolean
1553elfNN_ia64_create_dynamic_sections (bfd *abfd,
1554				    struct bfd_link_info *info)
1555{
1556  struct elfNN_ia64_link_hash_table *ia64_info;
1557  asection *s;
1558
1559  if (! _bfd_elf_create_dynamic_sections (abfd, info))
1560    return FALSE;
1561
1562  ia64_info = elfNN_ia64_hash_table (info);
1563  if (ia64_info == NULL)
1564    return FALSE;
1565
1566  {
1567    flagword flags = bfd_section_flags (ia64_info->root.sgot);
1568    bfd_set_section_flags (ia64_info->root.sgot, SEC_SMALL_DATA | flags);
1569    /* The .got section is always aligned at 8 bytes.  */
1570    if (!bfd_set_section_alignment (ia64_info->root.sgot, 3))
1571      return FALSE;
1572  }
1573
1574  if (!get_pltoff (abfd, info, ia64_info))
1575    return FALSE;
1576
1577  s = bfd_make_section_anyway_with_flags (abfd, ".rela.IA_64.pltoff",
1578					  (SEC_ALLOC | SEC_LOAD
1579					   | SEC_HAS_CONTENTS
1580					   | SEC_IN_MEMORY
1581					   | SEC_LINKER_CREATED
1582					   | SEC_READONLY));
1583  if (s == NULL
1584      || !bfd_set_section_alignment (s, LOG_SECTION_ALIGN))
1585    return FALSE;
1586  ia64_info->rel_pltoff_sec = s;
1587
1588  return TRUE;
1589}
1590
1591/* Find and/or create a hash entry for local symbol.  */
1592static struct elfNN_ia64_local_hash_entry *
1593get_local_sym_hash (struct elfNN_ia64_link_hash_table *ia64_info,
1594		    bfd *abfd, const Elf_Internal_Rela *rel,
1595		    bfd_boolean create)
1596{
1597  struct elfNN_ia64_local_hash_entry e, *ret;
1598  asection *sec = abfd->sections;
1599  hashval_t h = ELF_LOCAL_SYMBOL_HASH (sec->id,
1600				       ELFNN_R_SYM (rel->r_info));
1601  void **slot;
1602
1603  e.id = sec->id;
1604  e.r_sym = ELFNN_R_SYM (rel->r_info);
1605  slot = htab_find_slot_with_hash (ia64_info->loc_hash_table, &e, h,
1606				   create ? INSERT : NO_INSERT);
1607
1608  if (!slot)
1609    return NULL;
1610
1611  if (*slot)
1612    return (struct elfNN_ia64_local_hash_entry *) *slot;
1613
1614  ret = (struct elfNN_ia64_local_hash_entry *)
1615	objalloc_alloc ((struct objalloc *) ia64_info->loc_hash_memory,
1616			sizeof (struct elfNN_ia64_local_hash_entry));
1617  if (ret)
1618    {
1619      memset (ret, 0, sizeof (*ret));
1620      ret->id = sec->id;
1621      ret->r_sym = ELFNN_R_SYM (rel->r_info);
1622      *slot = ret;
1623    }
1624  return ret;
1625}
1626
1627/* Used to sort elfNN_ia64_dyn_sym_info array.  */
1628
1629static int
1630addend_compare (const void *xp, const void *yp)
1631{
1632  const struct elfNN_ia64_dyn_sym_info *x
1633    = (const struct elfNN_ia64_dyn_sym_info *) xp;
1634  const struct elfNN_ia64_dyn_sym_info *y
1635    = (const struct elfNN_ia64_dyn_sym_info *) yp;
1636
1637  return x->addend < y->addend ? -1 : x->addend > y->addend ? 1 : 0;
1638}
1639
1640/* Sort elfNN_ia64_dyn_sym_info array and remove duplicates.  */
1641
1642static unsigned int
1643sort_dyn_sym_info (struct elfNN_ia64_dyn_sym_info *info,
1644		   unsigned int count)
1645{
1646  bfd_vma curr, prev, got_offset;
1647  unsigned int i, kept, dupes, diff, dest, src, len;
1648
1649  qsort (info, count, sizeof (*info), addend_compare);
1650
1651  /* Find the first duplicate.  */
1652  prev = info [0].addend;
1653  got_offset = info [0].got_offset;
1654  for (i = 1; i < count; i++)
1655    {
1656      curr = info [i].addend;
1657      if (curr == prev)
1658	{
1659	  /* For duplicates, make sure that GOT_OFFSET is valid.  */
1660	  if (got_offset == (bfd_vma) -1)
1661	    got_offset = info [i].got_offset;
1662	  break;
1663	}
1664      got_offset = info [i].got_offset;
1665      prev = curr;
1666    }
1667
1668  /* We may move a block of elements to here.  */
1669  dest = i++;
1670
1671  /* Remove duplicates.  */
1672  if (i < count)
1673    {
1674      while (i < count)
1675	{
1676	  /* For duplicates, make sure that the kept one has a valid
1677	     got_offset.  */
1678	  kept = dest - 1;
1679	  if (got_offset != (bfd_vma) -1)
1680	    info [kept].got_offset = got_offset;
1681
1682	  curr = info [i].addend;
1683	  got_offset = info [i].got_offset;
1684
1685	  /* Move a block of elements whose first one is different from
1686	     the previous.  */
1687	  if (curr == prev)
1688	    {
1689	      for (src = i + 1; src < count; src++)
1690		{
1691		  if (info [src].addend != curr)
1692		    break;
1693		  /* For duplicates, make sure that GOT_OFFSET is
1694		     valid.  */
1695		  if (got_offset == (bfd_vma) -1)
1696		    got_offset = info [src].got_offset;
1697		}
1698
1699	      /* Make sure that the kept one has a valid got_offset.  */
1700	      if (got_offset != (bfd_vma) -1)
1701		info [kept].got_offset = got_offset;
1702	    }
1703	  else
1704	    src = i;
1705
1706	  if (src >= count)
1707	    break;
1708
1709	  /* Find the next duplicate.  SRC will be kept.  */
1710	  prev = info [src].addend;
1711	  got_offset = info [src].got_offset;
1712	  for (dupes = src + 1; dupes < count; dupes ++)
1713	    {
1714	      curr = info [dupes].addend;
1715	      if (curr == prev)
1716		{
1717		  /* Make sure that got_offset is valid.  */
1718		  if (got_offset == (bfd_vma) -1)
1719		    got_offset = info [dupes].got_offset;
1720
1721		  /* For duplicates, make sure that the kept one has
1722		     a valid got_offset.  */
1723		  if (got_offset != (bfd_vma) -1)
1724		    info [dupes - 1].got_offset = got_offset;
1725		  break;
1726		}
1727	      got_offset = info [dupes].got_offset;
1728	      prev = curr;
1729	    }
1730
1731	  /* How much to move.  */
1732	  len = dupes - src;
1733	  i = dupes + 1;
1734
1735	  if (len == 1 && dupes < count)
1736	    {
1737	      /* If we only move 1 element, we combine it with the next
1738		 one.  There must be at least a duplicate.  Find the
1739		 next different one.  */
1740	      for (diff = dupes + 1, src++; diff < count; diff++, src++)
1741		{
1742		  if (info [diff].addend != curr)
1743		    break;
1744		  /* Make sure that got_offset is valid.  */
1745		  if (got_offset == (bfd_vma) -1)
1746		    got_offset = info [diff].got_offset;
1747		}
1748
1749	      /* Makre sure that the last duplicated one has an valid
1750		 offset.  */
1751	      BFD_ASSERT (curr == prev);
1752	      if (got_offset != (bfd_vma) -1)
1753		info [diff - 1].got_offset = got_offset;
1754
1755	      if (diff < count)
1756		{
1757		  /* Find the next duplicate.  Track the current valid
1758		     offset.  */
1759		  prev = info [diff].addend;
1760		  got_offset = info [diff].got_offset;
1761		  for (dupes = diff + 1; dupes < count; dupes ++)
1762		    {
1763		      curr = info [dupes].addend;
1764		      if (curr == prev)
1765			{
1766			  /* For duplicates, make sure that GOT_OFFSET
1767			     is valid.  */
1768			  if (got_offset == (bfd_vma) -1)
1769			    got_offset = info [dupes].got_offset;
1770			  break;
1771			}
1772		      got_offset = info [dupes].got_offset;
1773		      prev = curr;
1774		      diff++;
1775		    }
1776
1777		  len = diff - src + 1;
1778		  i = diff + 1;
1779		}
1780	    }
1781
1782	  memmove (&info [dest], &info [src], len * sizeof (*info));
1783
1784	  dest += len;
1785	}
1786
1787      count = dest;
1788    }
1789  else
1790    {
1791      /* When we get here, either there is no duplicate at all or
1792	 the only duplicate is the last element.  */
1793      if (dest < count)
1794	{
1795	  /* If the last element is a duplicate, make sure that the
1796	     kept one has a valid got_offset.  We also update count.  */
1797	  if (got_offset != (bfd_vma) -1)
1798	    info [dest - 1].got_offset = got_offset;
1799	  count = dest;
1800	}
1801    }
1802
1803  return count;
1804}
1805
1806/* Find and/or create a descriptor for dynamic symbol info.  This will
1807   vary based on global or local symbol, and the addend to the reloc.
1808
1809   We don't sort when inserting.  Also, we sort and eliminate
1810   duplicates if there is an unsorted section.  Typically, this will
1811   only happen once, because we do all insertions before lookups.  We
1812   then use bsearch to do a lookup.  This also allows lookups to be
1813   fast.  So we have fast insertion (O(log N) due to duplicate check),
1814   fast lookup (O(log N)) and one sort (O(N log N) expected time).
1815   Previously, all lookups were O(N) because of the use of the linked
1816   list and also all insertions were O(N) because of the check for
1817   duplicates.  There are some complications here because the array
1818   size grows occasionally, which may add an O(N) factor, but this
1819   should be rare.  Also,  we free the excess array allocation, which
1820   requires a copy which is O(N), but this only happens once.  */
1821
1822static struct elfNN_ia64_dyn_sym_info *
1823get_dyn_sym_info (struct elfNN_ia64_link_hash_table *ia64_info,
1824		  struct elf_link_hash_entry *h, bfd *abfd,
1825		  const Elf_Internal_Rela *rel, bfd_boolean create)
1826{
1827  struct elfNN_ia64_dyn_sym_info **info_p, *info, *dyn_i, key;
1828  unsigned int *count_p, *sorted_count_p, *size_p;
1829  unsigned int count, sorted_count, size;
1830  bfd_vma addend = rel ? rel->r_addend : 0;
1831  bfd_size_type amt;
1832
1833  if (h)
1834    {
1835      struct elfNN_ia64_link_hash_entry *global_h;
1836
1837      global_h = (struct elfNN_ia64_link_hash_entry *) h;
1838      info_p = &global_h->info;
1839      count_p = &global_h->count;
1840      sorted_count_p = &global_h->sorted_count;
1841      size_p = &global_h->size;
1842    }
1843  else
1844    {
1845      struct elfNN_ia64_local_hash_entry *loc_h;
1846
1847      loc_h = get_local_sym_hash (ia64_info, abfd, rel, create);
1848      if (!loc_h)
1849	{
1850	  BFD_ASSERT (!create);
1851	  return NULL;
1852	}
1853
1854      info_p = &loc_h->info;
1855      count_p = &loc_h->count;
1856      sorted_count_p = &loc_h->sorted_count;
1857      size_p = &loc_h->size;
1858    }
1859
1860  count = *count_p;
1861  sorted_count = *sorted_count_p;
1862  size = *size_p;
1863  info = *info_p;
1864  if (create)
1865    {
1866      /* When we create the array, we don't check for duplicates,
1867	 except in the previously sorted section if one exists, and
1868	 against the last inserted entry.  This allows insertions to
1869	 be fast.  */
1870      if (info)
1871	{
1872	  if (sorted_count)
1873	    {
1874	      /* Try bsearch first on the sorted section.  */
1875	      key.addend = addend;
1876	      dyn_i = bsearch (&key, info, sorted_count,
1877			       sizeof (*info), addend_compare);
1878
1879	      if (dyn_i)
1880		{
1881		  return dyn_i;
1882		}
1883	    }
1884
1885	  /* Do a quick check for the last inserted entry.  */
1886	  dyn_i = info + count - 1;
1887	  if (dyn_i->addend == addend)
1888	    {
1889	      return dyn_i;
1890	    }
1891	}
1892
1893      if (size == 0)
1894	{
1895	  /* It is the very first element. We create the array of size
1896	     1.  */
1897	  size = 1;
1898	  amt = size * sizeof (*info);
1899	  info = bfd_malloc (amt);
1900	}
1901      else if (size <= count)
1902	{
1903	  /* We double the array size every time when we reach the
1904	     size limit.  */
1905	  size += size;
1906	  amt = size * sizeof (*info);
1907	  info = bfd_realloc (info, amt);
1908	}
1909      else
1910	goto has_space;
1911
1912      if (info == NULL)
1913	return NULL;
1914      *size_p = size;
1915      *info_p = info;
1916
1917has_space:
1918      /* Append the new one to the array.  */
1919      dyn_i = info + count;
1920      memset (dyn_i, 0, sizeof (*dyn_i));
1921      dyn_i->got_offset = (bfd_vma) -1;
1922      dyn_i->addend = addend;
1923
1924      /* We increment count only since the new ones are unsorted and
1925	 may have duplicate.  */
1926      (*count_p)++;
1927    }
1928  else
1929    {
1930      /* It is a lookup without insertion.  Sort array if part of the
1931	 array isn't sorted.  */
1932      if (count != sorted_count)
1933	{
1934	  count = sort_dyn_sym_info (info, count);
1935	  *count_p = count;
1936	  *sorted_count_p = count;
1937	}
1938
1939      /* Free unused memory.  */
1940      if (size != count)
1941	{
1942	  amt = count * sizeof (*info);
1943	  info = bfd_malloc (amt);
1944	  if (info != NULL)
1945	    {
1946	      memcpy (info, *info_p, amt);
1947	      free (*info_p);
1948	      *size_p = count;
1949	      *info_p = info;
1950	    }
1951	}
1952
1953      key.addend = addend;
1954      dyn_i = bsearch (&key, info, count,
1955		       sizeof (*info), addend_compare);
1956    }
1957
1958  return dyn_i;
1959}
1960
1961static asection *
1962get_got (bfd *abfd, struct bfd_link_info *info,
1963	 struct elfNN_ia64_link_hash_table *ia64_info)
1964{
1965  asection *got;
1966  bfd *dynobj;
1967
1968  got = ia64_info->root.sgot;
1969  if (!got)
1970    {
1971      flagword flags;
1972
1973      dynobj = ia64_info->root.dynobj;
1974      if (!dynobj)
1975	ia64_info->root.dynobj = dynobj = abfd;
1976      if (!_bfd_elf_create_got_section (dynobj, info))
1977	return NULL;
1978
1979      got = ia64_info->root.sgot;
1980
1981      /* The .got section is always aligned at 8 bytes.  */
1982      if (!bfd_set_section_alignment (got, 3))
1983	return NULL;
1984
1985      flags = bfd_section_flags (got);
1986      if (!bfd_set_section_flags (got, SEC_SMALL_DATA | flags))
1987	return NULL;
1988    }
1989
1990  return got;
1991}
1992
1993/* Create function descriptor section (.opd).  This section is called .opd
1994   because it contains "official procedure descriptors".  The "official"
1995   refers to the fact that these descriptors are used when taking the address
1996   of a procedure, thus ensuring a unique address for each procedure.  */
1997
1998static asection *
1999get_fptr (bfd *abfd, struct bfd_link_info *info,
2000	  struct elfNN_ia64_link_hash_table *ia64_info)
2001{
2002  asection *fptr;
2003  bfd *dynobj;
2004
2005  fptr = ia64_info->fptr_sec;
2006  if (!fptr)
2007    {
2008      dynobj = ia64_info->root.dynobj;
2009      if (!dynobj)
2010	ia64_info->root.dynobj = dynobj = abfd;
2011
2012      fptr = bfd_make_section_anyway_with_flags (dynobj, ".opd",
2013						 (SEC_ALLOC
2014						  | SEC_LOAD
2015						  | SEC_HAS_CONTENTS
2016						  | SEC_IN_MEMORY
2017						  | (bfd_link_pie (info)
2018						     ? 0 : SEC_READONLY)
2019						  | SEC_LINKER_CREATED));
2020      if (!fptr
2021	  || !bfd_set_section_alignment (fptr, 4))
2022	{
2023	  BFD_ASSERT (0);
2024	  return NULL;
2025	}
2026
2027      ia64_info->fptr_sec = fptr;
2028
2029      if (bfd_link_pie (info))
2030	{
2031	  asection *fptr_rel;
2032	  fptr_rel = bfd_make_section_anyway_with_flags (dynobj, ".rela.opd",
2033							 (SEC_ALLOC | SEC_LOAD
2034							  | SEC_HAS_CONTENTS
2035							  | SEC_IN_MEMORY
2036							  | SEC_LINKER_CREATED
2037							  | SEC_READONLY));
2038	  if (fptr_rel == NULL
2039	      || !bfd_set_section_alignment (fptr_rel, LOG_SECTION_ALIGN))
2040	    {
2041	      BFD_ASSERT (0);
2042	      return NULL;
2043	    }
2044
2045	  ia64_info->rel_fptr_sec = fptr_rel;
2046	}
2047    }
2048
2049  return fptr;
2050}
2051
2052static asection *
2053get_pltoff (bfd *abfd, struct bfd_link_info *info ATTRIBUTE_UNUSED,
2054	    struct elfNN_ia64_link_hash_table *ia64_info)
2055{
2056  asection *pltoff;
2057  bfd *dynobj;
2058
2059  pltoff = ia64_info->pltoff_sec;
2060  if (!pltoff)
2061    {
2062      dynobj = ia64_info->root.dynobj;
2063      if (!dynobj)
2064	ia64_info->root.dynobj = dynobj = abfd;
2065
2066      pltoff = bfd_make_section_anyway_with_flags (dynobj,
2067						   ELF_STRING_ia64_pltoff,
2068						   (SEC_ALLOC
2069						    | SEC_LOAD
2070						    | SEC_HAS_CONTENTS
2071						    | SEC_IN_MEMORY
2072						    | SEC_SMALL_DATA
2073						    | SEC_LINKER_CREATED));
2074      if (!pltoff
2075	  || !bfd_set_section_alignment (pltoff, 4))
2076	{
2077	  BFD_ASSERT (0);
2078	  return NULL;
2079	}
2080
2081      ia64_info->pltoff_sec = pltoff;
2082    }
2083
2084  return pltoff;
2085}
2086
2087static asection *
2088get_reloc_section (bfd *abfd,
2089		   struct elfNN_ia64_link_hash_table *ia64_info,
2090		   asection *sec, bfd_boolean create)
2091{
2092  const char *srel_name;
2093  asection *srel;
2094  bfd *dynobj;
2095
2096  srel_name = (bfd_elf_string_from_elf_section
2097	       (abfd, elf_elfheader(abfd)->e_shstrndx,
2098		_bfd_elf_single_rel_hdr (sec)->sh_name));
2099  if (srel_name == NULL)
2100    return NULL;
2101
2102  dynobj = ia64_info->root.dynobj;
2103  if (!dynobj)
2104    ia64_info->root.dynobj = dynobj = abfd;
2105
2106  srel = bfd_get_linker_section (dynobj, srel_name);
2107  if (srel == NULL && create)
2108    {
2109      srel = bfd_make_section_anyway_with_flags (dynobj, srel_name,
2110						 (SEC_ALLOC | SEC_LOAD
2111						  | SEC_HAS_CONTENTS
2112						  | SEC_IN_MEMORY
2113						  | SEC_LINKER_CREATED
2114						  | SEC_READONLY));
2115      if (srel == NULL
2116	  || !bfd_set_section_alignment (srel, LOG_SECTION_ALIGN))
2117	return NULL;
2118    }
2119
2120  return srel;
2121}
2122
2123static bfd_boolean
2124count_dyn_reloc (bfd *abfd, struct elfNN_ia64_dyn_sym_info *dyn_i,
2125		 asection *srel, int type, bfd_boolean reltext)
2126{
2127  struct elfNN_ia64_dyn_reloc_entry *rent;
2128
2129  for (rent = dyn_i->reloc_entries; rent; rent = rent->next)
2130    if (rent->srel == srel && rent->type == type)
2131      break;
2132
2133  if (!rent)
2134    {
2135      rent = ((struct elfNN_ia64_dyn_reloc_entry *)
2136	      bfd_alloc (abfd, (bfd_size_type) sizeof (*rent)));
2137      if (!rent)
2138	return FALSE;
2139
2140      rent->next = dyn_i->reloc_entries;
2141      rent->srel = srel;
2142      rent->type = type;
2143      rent->count = 0;
2144      dyn_i->reloc_entries = rent;
2145    }
2146  rent->reltext = reltext;
2147  rent->count++;
2148
2149  return TRUE;
2150}
2151
2152static bfd_boolean
2153elfNN_ia64_check_relocs (bfd *abfd, struct bfd_link_info *info,
2154			 asection *sec,
2155			 const Elf_Internal_Rela *relocs)
2156{
2157  struct elfNN_ia64_link_hash_table *ia64_info;
2158  const Elf_Internal_Rela *relend;
2159  Elf_Internal_Shdr *symtab_hdr;
2160  const Elf_Internal_Rela *rel;
2161  asection *got, *fptr, *srel, *pltoff;
2162  enum {
2163    NEED_GOT = 1,
2164    NEED_GOTX = 2,
2165    NEED_FPTR = 4,
2166    NEED_PLTOFF = 8,
2167    NEED_MIN_PLT = 16,
2168    NEED_FULL_PLT = 32,
2169    NEED_DYNREL = 64,
2170    NEED_LTOFF_FPTR = 128,
2171    NEED_TPREL = 256,
2172    NEED_DTPMOD = 512,
2173    NEED_DTPREL = 1024
2174  };
2175  int need_entry;
2176  struct elf_link_hash_entry *h;
2177  unsigned long r_symndx;
2178  bfd_boolean maybe_dynamic;
2179
2180  if (bfd_link_relocatable (info))
2181    return TRUE;
2182
2183  symtab_hdr = &elf_tdata (abfd)->symtab_hdr;
2184  ia64_info = elfNN_ia64_hash_table (info);
2185  if (ia64_info == NULL)
2186    return FALSE;
2187
2188  got = fptr = srel = pltoff = NULL;
2189
2190  relend = relocs + sec->reloc_count;
2191
2192  /* We scan relocations first to create dynamic relocation arrays.  We
2193     modified get_dyn_sym_info to allow fast insertion and support fast
2194     lookup in the next loop.  */
2195  for (rel = relocs; rel < relend; ++rel)
2196    {
2197      r_symndx = ELFNN_R_SYM (rel->r_info);
2198      if (r_symndx >= symtab_hdr->sh_info)
2199	{
2200	  long indx = r_symndx - symtab_hdr->sh_info;
2201	  h = elf_sym_hashes (abfd)[indx];
2202	  while (h->root.type == bfd_link_hash_indirect
2203		 || h->root.type == bfd_link_hash_warning)
2204	    h = (struct elf_link_hash_entry *) h->root.u.i.link;
2205	}
2206      else
2207	h = NULL;
2208
2209      if (h && UNDEFWEAK_NO_DYNAMIC_RELOC (info, h))
2210	continue;
2211
2212      /* We can only get preliminary data on whether a symbol is
2213	 locally or externally defined, as not all of the input files
2214	 have yet been processed.  Do something with what we know, as
2215	 this may help reduce memory usage and processing time later.  */
2216      maybe_dynamic = (h && ((!bfd_link_executable (info)
2217			      && (!SYMBOLIC_BIND (info, h)
2218				  || info->unresolved_syms_in_shared_libs == RM_IGNORE))
2219			     || !h->def_regular
2220			     || h->root.type == bfd_link_hash_defweak));
2221
2222      need_entry = 0;
2223      switch (ELFNN_R_TYPE (rel->r_info))
2224	{
2225	case R_IA64_TPREL64MSB:
2226	case R_IA64_TPREL64LSB:
2227	  if (bfd_link_pic (info) || maybe_dynamic)
2228	    need_entry = NEED_DYNREL;
2229	  break;
2230
2231	case R_IA64_LTOFF_TPREL22:
2232	  need_entry = NEED_TPREL;
2233	  if (bfd_link_pic (info))
2234	    info->flags |= DF_STATIC_TLS;
2235	  break;
2236
2237	case R_IA64_DTPREL32MSB:
2238	case R_IA64_DTPREL32LSB:
2239	case R_IA64_DTPREL64MSB:
2240	case R_IA64_DTPREL64LSB:
2241	  if (bfd_link_pic (info) || maybe_dynamic)
2242	    need_entry = NEED_DYNREL;
2243	  break;
2244
2245	case R_IA64_LTOFF_DTPREL22:
2246	  need_entry = NEED_DTPREL;
2247	  break;
2248
2249	case R_IA64_DTPMOD64MSB:
2250	case R_IA64_DTPMOD64LSB:
2251	  if (bfd_link_pic (info) || maybe_dynamic)
2252	    need_entry = NEED_DYNREL;
2253	  break;
2254
2255	case R_IA64_LTOFF_DTPMOD22:
2256	  need_entry = NEED_DTPMOD;
2257	  break;
2258
2259	case R_IA64_LTOFF_FPTR22:
2260	case R_IA64_LTOFF_FPTR64I:
2261	case R_IA64_LTOFF_FPTR32MSB:
2262	case R_IA64_LTOFF_FPTR32LSB:
2263	case R_IA64_LTOFF_FPTR64MSB:
2264	case R_IA64_LTOFF_FPTR64LSB:
2265	  need_entry = NEED_FPTR | NEED_GOT | NEED_LTOFF_FPTR;
2266	  break;
2267
2268	case R_IA64_FPTR64I:
2269	case R_IA64_FPTR32MSB:
2270	case R_IA64_FPTR32LSB:
2271	case R_IA64_FPTR64MSB:
2272	case R_IA64_FPTR64LSB:
2273	  if (bfd_link_pic (info) || h)
2274	    need_entry = NEED_FPTR | NEED_DYNREL;
2275	  else
2276	    need_entry = NEED_FPTR;
2277	  break;
2278
2279	case R_IA64_LTOFF22:
2280	case R_IA64_LTOFF64I:
2281	  need_entry = NEED_GOT;
2282	  break;
2283
2284	case R_IA64_LTOFF22X:
2285	  need_entry = NEED_GOTX;
2286	  break;
2287
2288	case R_IA64_PLTOFF22:
2289	case R_IA64_PLTOFF64I:
2290	case R_IA64_PLTOFF64MSB:
2291	case R_IA64_PLTOFF64LSB:
2292	  need_entry = NEED_PLTOFF;
2293	  if (h)
2294	    {
2295	      if (maybe_dynamic)
2296		need_entry |= NEED_MIN_PLT;
2297	    }
2298	  else
2299	    {
2300	      (*info->callbacks->warning)
2301		(info, _("@pltoff reloc against local symbol"), 0,
2302		 abfd, 0, (bfd_vma) 0);
2303	    }
2304	  break;
2305
2306	case R_IA64_PCREL21B:
2307	case R_IA64_PCREL60B:
2308	  /* Depending on where this symbol is defined, we may or may not
2309	     need a full plt entry.  Only skip if we know we'll not need
2310	     the entry -- static or symbolic, and the symbol definition
2311	     has already been seen.  */
2312	  if (maybe_dynamic && rel->r_addend == 0)
2313	    need_entry = NEED_FULL_PLT;
2314	  break;
2315
2316	case R_IA64_IMM14:
2317	case R_IA64_IMM22:
2318	case R_IA64_IMM64:
2319	case R_IA64_DIR32MSB:
2320	case R_IA64_DIR32LSB:
2321	case R_IA64_DIR64MSB:
2322	case R_IA64_DIR64LSB:
2323	  /* Shared objects will always need at least a REL relocation.  */
2324	  if (bfd_link_pic (info) || maybe_dynamic)
2325	    need_entry = NEED_DYNREL;
2326	  break;
2327
2328	case R_IA64_IPLTMSB:
2329	case R_IA64_IPLTLSB:
2330	  /* Shared objects will always need at least a REL relocation.  */
2331	  if (bfd_link_pic (info) || maybe_dynamic)
2332	    need_entry = NEED_DYNREL;
2333	  break;
2334
2335	case R_IA64_PCREL22:
2336	case R_IA64_PCREL64I:
2337	case R_IA64_PCREL32MSB:
2338	case R_IA64_PCREL32LSB:
2339	case R_IA64_PCREL64MSB:
2340	case R_IA64_PCREL64LSB:
2341	  if (maybe_dynamic)
2342	    need_entry = NEED_DYNREL;
2343	  break;
2344	}
2345
2346      if (!need_entry)
2347	continue;
2348
2349      if ((need_entry & NEED_FPTR) != 0
2350	  && rel->r_addend)
2351	{
2352	  (*info->callbacks->warning)
2353	    (info, _("non-zero addend in @fptr reloc"), 0,
2354	     abfd, 0, (bfd_vma) 0);
2355	}
2356
2357      if (get_dyn_sym_info (ia64_info, h, abfd, rel, TRUE) == NULL)
2358	return FALSE;
2359    }
2360
2361  /* Now, we only do lookup without insertion, which is very fast
2362     with the modified get_dyn_sym_info.  */
2363  for (rel = relocs; rel < relend; ++rel)
2364    {
2365      struct elfNN_ia64_dyn_sym_info *dyn_i;
2366      int dynrel_type = R_IA64_NONE;
2367
2368      r_symndx = ELFNN_R_SYM (rel->r_info);
2369      if (r_symndx >= symtab_hdr->sh_info)
2370	{
2371	  /* We're dealing with a global symbol -- find its hash entry
2372	     and mark it as being referenced.  */
2373	  long indx = r_symndx - symtab_hdr->sh_info;
2374	  h = elf_sym_hashes (abfd)[indx];
2375	  while (h->root.type == bfd_link_hash_indirect
2376		 || h->root.type == bfd_link_hash_warning)
2377	    h = (struct elf_link_hash_entry *) h->root.u.i.link;
2378
2379	  /* PR15323, ref flags aren't set for references in the same
2380	     object.  */
2381	  h->ref_regular = 1;
2382	}
2383      else
2384	h = NULL;
2385
2386      if (h && UNDEFWEAK_NO_DYNAMIC_RELOC (info, h))
2387	continue;
2388
2389      /* We can only get preliminary data on whether a symbol is
2390	 locally or externally defined, as not all of the input files
2391	 have yet been processed.  Do something with what we know, as
2392	 this may help reduce memory usage and processing time later.  */
2393      maybe_dynamic = (h && ((!bfd_link_executable (info)
2394			      && (!SYMBOLIC_BIND (info, h)
2395				  || info->unresolved_syms_in_shared_libs == RM_IGNORE))
2396			     || !h->def_regular
2397			     || h->root.type == bfd_link_hash_defweak));
2398
2399      need_entry = 0;
2400      switch (ELFNN_R_TYPE (rel->r_info))
2401	{
2402	case R_IA64_TPREL64MSB:
2403	case R_IA64_TPREL64LSB:
2404	  if (bfd_link_pic (info) || maybe_dynamic)
2405	    need_entry = NEED_DYNREL;
2406	  dynrel_type = R_IA64_TPREL64LSB;
2407	  if (bfd_link_pic (info))
2408	    info->flags |= DF_STATIC_TLS;
2409	  break;
2410
2411	case R_IA64_LTOFF_TPREL22:
2412	  need_entry = NEED_TPREL;
2413	  if (bfd_link_pic (info))
2414	    info->flags |= DF_STATIC_TLS;
2415	  break;
2416
2417	case R_IA64_DTPREL32MSB:
2418	case R_IA64_DTPREL32LSB:
2419	case R_IA64_DTPREL64MSB:
2420	case R_IA64_DTPREL64LSB:
2421	  if (bfd_link_pic (info) || maybe_dynamic)
2422	    need_entry = NEED_DYNREL;
2423	  dynrel_type = R_IA64_DTPRELNNLSB;
2424	  break;
2425
2426	case R_IA64_LTOFF_DTPREL22:
2427	  need_entry = NEED_DTPREL;
2428	  break;
2429
2430	case R_IA64_DTPMOD64MSB:
2431	case R_IA64_DTPMOD64LSB:
2432	  if (bfd_link_pic (info) || maybe_dynamic)
2433	    need_entry = NEED_DYNREL;
2434	  dynrel_type = R_IA64_DTPMOD64LSB;
2435	  break;
2436
2437	case R_IA64_LTOFF_DTPMOD22:
2438	  need_entry = NEED_DTPMOD;
2439	  break;
2440
2441	case R_IA64_LTOFF_FPTR22:
2442	case R_IA64_LTOFF_FPTR64I:
2443	case R_IA64_LTOFF_FPTR32MSB:
2444	case R_IA64_LTOFF_FPTR32LSB:
2445	case R_IA64_LTOFF_FPTR64MSB:
2446	case R_IA64_LTOFF_FPTR64LSB:
2447	  need_entry = NEED_FPTR | NEED_GOT | NEED_LTOFF_FPTR;
2448	  break;
2449
2450	case R_IA64_FPTR64I:
2451	case R_IA64_FPTR32MSB:
2452	case R_IA64_FPTR32LSB:
2453	case R_IA64_FPTR64MSB:
2454	case R_IA64_FPTR64LSB:
2455	  if (bfd_link_pic (info) || h)
2456	    need_entry = NEED_FPTR | NEED_DYNREL;
2457	  else
2458	    need_entry = NEED_FPTR;
2459	  dynrel_type = R_IA64_FPTRNNLSB;
2460	  break;
2461
2462	case R_IA64_LTOFF22:
2463	case R_IA64_LTOFF64I:
2464	  need_entry = NEED_GOT;
2465	  break;
2466
2467	case R_IA64_LTOFF22X:
2468	  need_entry = NEED_GOTX;
2469	  break;
2470
2471	case R_IA64_PLTOFF22:
2472	case R_IA64_PLTOFF64I:
2473	case R_IA64_PLTOFF64MSB:
2474	case R_IA64_PLTOFF64LSB:
2475	  need_entry = NEED_PLTOFF;
2476	  if (h)
2477	    {
2478	      if (maybe_dynamic)
2479		need_entry |= NEED_MIN_PLT;
2480	    }
2481	  break;
2482
2483	case R_IA64_PCREL21B:
2484	case R_IA64_PCREL60B:
2485	  /* Depending on where this symbol is defined, we may or may not
2486	     need a full plt entry.  Only skip if we know we'll not need
2487	     the entry -- static or symbolic, and the symbol definition
2488	     has already been seen.  */
2489	  if (maybe_dynamic && rel->r_addend == 0)
2490	    need_entry = NEED_FULL_PLT;
2491	  break;
2492
2493	case R_IA64_IMM14:
2494	case R_IA64_IMM22:
2495	case R_IA64_IMM64:
2496	case R_IA64_DIR32MSB:
2497	case R_IA64_DIR32LSB:
2498	case R_IA64_DIR64MSB:
2499	case R_IA64_DIR64LSB:
2500	  /* Shared objects will always need at least a REL relocation.  */
2501	  if (bfd_link_pic (info) || maybe_dynamic)
2502	    need_entry = NEED_DYNREL;
2503	  dynrel_type = R_IA64_DIRNNLSB;
2504	  break;
2505
2506	case R_IA64_IPLTMSB:
2507	case R_IA64_IPLTLSB:
2508	  /* Shared objects will always need at least a REL relocation.  */
2509	  if (bfd_link_pic (info) || maybe_dynamic)
2510	    need_entry = NEED_DYNREL;
2511	  dynrel_type = R_IA64_IPLTLSB;
2512	  break;
2513
2514	case R_IA64_PCREL22:
2515	case R_IA64_PCREL64I:
2516	case R_IA64_PCREL32MSB:
2517	case R_IA64_PCREL32LSB:
2518	case R_IA64_PCREL64MSB:
2519	case R_IA64_PCREL64LSB:
2520	  if (maybe_dynamic)
2521	    need_entry = NEED_DYNREL;
2522	  dynrel_type = R_IA64_PCRELNNLSB;
2523	  break;
2524	}
2525
2526      if (!need_entry)
2527	continue;
2528
2529      dyn_i = get_dyn_sym_info (ia64_info, h, abfd, rel, FALSE);
2530
2531      /* Record whether or not this is a local symbol.  */
2532      dyn_i->h = h;
2533
2534      /* Create what's needed.  */
2535      if (need_entry & (NEED_GOT | NEED_GOTX | NEED_TPREL
2536			| NEED_DTPMOD | NEED_DTPREL))
2537	{
2538	  if (!got)
2539	    {
2540	      got = get_got (abfd, info, ia64_info);
2541	      if (!got)
2542		return FALSE;
2543	    }
2544	  if (need_entry & NEED_GOT)
2545	    dyn_i->want_got = 1;
2546	  if (need_entry & NEED_GOTX)
2547	    dyn_i->want_gotx = 1;
2548	  if (need_entry & NEED_TPREL)
2549	    dyn_i->want_tprel = 1;
2550	  if (need_entry & NEED_DTPMOD)
2551	    dyn_i->want_dtpmod = 1;
2552	  if (need_entry & NEED_DTPREL)
2553	    dyn_i->want_dtprel = 1;
2554	}
2555      if (need_entry & NEED_FPTR)
2556	{
2557	  if (!fptr)
2558	    {
2559	      fptr = get_fptr (abfd, info, ia64_info);
2560	      if (!fptr)
2561		return FALSE;
2562	    }
2563
2564	  /* FPTRs for shared libraries are allocated by the dynamic
2565	     linker.  Make sure this local symbol will appear in the
2566	     dynamic symbol table.  */
2567	  if (!h && bfd_link_pic (info))
2568	    {
2569	      if (! (bfd_elf_link_record_local_dynamic_symbol
2570		     (info, abfd, (long) r_symndx)))
2571		return FALSE;
2572	    }
2573
2574	  dyn_i->want_fptr = 1;
2575	}
2576      if (need_entry & NEED_LTOFF_FPTR)
2577	dyn_i->want_ltoff_fptr = 1;
2578      if (need_entry & (NEED_MIN_PLT | NEED_FULL_PLT))
2579	{
2580	  if (!ia64_info->root.dynobj)
2581	    ia64_info->root.dynobj = abfd;
2582	  h->needs_plt = 1;
2583	  dyn_i->want_plt = 1;
2584	}
2585      if (need_entry & NEED_FULL_PLT)
2586	dyn_i->want_plt2 = 1;
2587      if (need_entry & NEED_PLTOFF)
2588	{
2589	  /* This is needed here, in case @pltoff is used in a non-shared
2590	     link.  */
2591	  if (!pltoff)
2592	    {
2593	      pltoff = get_pltoff (abfd, info, ia64_info);
2594	      if (!pltoff)
2595		return FALSE;
2596	    }
2597
2598	  dyn_i->want_pltoff = 1;
2599	}
2600      if ((need_entry & NEED_DYNREL) && (sec->flags & SEC_ALLOC))
2601	{
2602	  if (!srel)
2603	    {
2604	      srel = get_reloc_section (abfd, ia64_info, sec, TRUE);
2605	      if (!srel)
2606		return FALSE;
2607	    }
2608	  if (!count_dyn_reloc (abfd, dyn_i, srel, dynrel_type,
2609				(sec->flags & SEC_READONLY) != 0))
2610	    return FALSE;
2611	}
2612    }
2613
2614  return TRUE;
2615}
2616
2617/* For cleanliness, and potentially faster dynamic loading, allocate
2618   external GOT entries first.  */
2619
2620static bfd_boolean
2621allocate_global_data_got (struct elfNN_ia64_dyn_sym_info *dyn_i,
2622			  void * data)
2623{
2624  struct elfNN_ia64_allocate_data *x = (struct elfNN_ia64_allocate_data *)data;
2625
2626  if ((dyn_i->want_got || dyn_i->want_gotx)
2627      && ! dyn_i->want_fptr
2628      && elfNN_ia64_dynamic_symbol_p (dyn_i->h, x->info, 0))
2629     {
2630       dyn_i->got_offset = x->ofs;
2631       x->ofs += 8;
2632     }
2633  if (dyn_i->want_tprel)
2634    {
2635      dyn_i->tprel_offset = x->ofs;
2636      x->ofs += 8;
2637    }
2638  if (dyn_i->want_dtpmod)
2639    {
2640      if (elfNN_ia64_dynamic_symbol_p (dyn_i->h, x->info, 0))
2641	{
2642	  dyn_i->dtpmod_offset = x->ofs;
2643	  x->ofs += 8;
2644	}
2645      else
2646	{
2647	  struct elfNN_ia64_link_hash_table *ia64_info;
2648
2649	  ia64_info = elfNN_ia64_hash_table (x->info);
2650	  if (ia64_info == NULL)
2651	    return FALSE;
2652
2653	  if (ia64_info->self_dtpmod_offset == (bfd_vma) -1)
2654	    {
2655	      ia64_info->self_dtpmod_offset = x->ofs;
2656	      x->ofs += 8;
2657	    }
2658	  dyn_i->dtpmod_offset = ia64_info->self_dtpmod_offset;
2659	}
2660    }
2661  if (dyn_i->want_dtprel)
2662    {
2663      dyn_i->dtprel_offset = x->ofs;
2664      x->ofs += 8;
2665    }
2666  return TRUE;
2667}
2668
2669/* Next, allocate all the GOT entries used by LTOFF_FPTR relocs.  */
2670
2671static bfd_boolean
2672allocate_global_fptr_got (struct elfNN_ia64_dyn_sym_info *dyn_i,
2673			  void * data)
2674{
2675  struct elfNN_ia64_allocate_data *x = (struct elfNN_ia64_allocate_data *)data;
2676
2677  if (dyn_i->want_got
2678      && dyn_i->want_fptr
2679      && elfNN_ia64_dynamic_symbol_p (dyn_i->h, x->info, R_IA64_FPTRNNLSB))
2680    {
2681      dyn_i->got_offset = x->ofs;
2682      x->ofs += 8;
2683    }
2684  return TRUE;
2685}
2686
2687/* Lastly, allocate all the GOT entries for local data.  */
2688
2689static bfd_boolean
2690allocate_local_got (struct elfNN_ia64_dyn_sym_info *dyn_i,
2691		    void * data)
2692{
2693  struct elfNN_ia64_allocate_data *x = (struct elfNN_ia64_allocate_data *)data;
2694
2695  if ((dyn_i->want_got || dyn_i->want_gotx)
2696      && !elfNN_ia64_dynamic_symbol_p (dyn_i->h, x->info, 0))
2697    {
2698      dyn_i->got_offset = x->ofs;
2699      x->ofs += 8;
2700    }
2701  return TRUE;
2702}
2703
2704/* Search for the index of a global symbol in it's defining object file.  */
2705
2706static long
2707global_sym_index (struct elf_link_hash_entry *h)
2708{
2709  struct elf_link_hash_entry **p;
2710  bfd *obj;
2711
2712  BFD_ASSERT (h->root.type == bfd_link_hash_defined
2713	      || h->root.type == bfd_link_hash_defweak);
2714
2715  obj = h->root.u.def.section->owner;
2716  for (p = elf_sym_hashes (obj); *p != h; ++p)
2717    continue;
2718
2719  return p - elf_sym_hashes (obj) + elf_tdata (obj)->symtab_hdr.sh_info;
2720}
2721
2722/* Allocate function descriptors.  We can do these for every function
2723   in a main executable that is not exported.  */
2724
2725static bfd_boolean
2726allocate_fptr (struct elfNN_ia64_dyn_sym_info *dyn_i, void * data)
2727{
2728  struct elfNN_ia64_allocate_data *x = (struct elfNN_ia64_allocate_data *)data;
2729
2730  if (dyn_i->want_fptr)
2731    {
2732      struct elf_link_hash_entry *h = dyn_i->h;
2733
2734      if (h)
2735	while (h->root.type == bfd_link_hash_indirect
2736	       || h->root.type == bfd_link_hash_warning)
2737	  h = (struct elf_link_hash_entry *) h->root.u.i.link;
2738
2739      if (!bfd_link_executable (x->info)
2740	  && (!h
2741	      || (ELF_ST_VISIBILITY (h->other) == STV_DEFAULT
2742		  && !UNDEFWEAK_NO_DYNAMIC_RELOC (x->info, h))
2743	      || (h->root.type != bfd_link_hash_undefweak
2744		  && h->root.type != bfd_link_hash_undefined)))
2745	{
2746	  if (h && h->dynindx == -1)
2747	    {
2748	      BFD_ASSERT ((h->root.type == bfd_link_hash_defined)
2749			  || (h->root.type == bfd_link_hash_defweak));
2750
2751	      if (!bfd_elf_link_record_local_dynamic_symbol
2752		    (x->info, h->root.u.def.section->owner,
2753		     global_sym_index (h)))
2754		return FALSE;
2755	    }
2756
2757	  dyn_i->want_fptr = 0;
2758	}
2759      else if (h == NULL || h->dynindx == -1)
2760	{
2761	  dyn_i->fptr_offset = x->ofs;
2762	  x->ofs += 16;
2763	}
2764      else
2765	dyn_i->want_fptr = 0;
2766    }
2767  return TRUE;
2768}
2769
2770/* Allocate all the minimal PLT entries.  */
2771
2772static bfd_boolean
2773allocate_plt_entries (struct elfNN_ia64_dyn_sym_info *dyn_i,
2774		      void * data)
2775{
2776  struct elfNN_ia64_allocate_data *x = (struct elfNN_ia64_allocate_data *)data;
2777
2778  if (dyn_i->want_plt)
2779    {
2780      struct elf_link_hash_entry *h = dyn_i->h;
2781
2782      if (h)
2783	while (h->root.type == bfd_link_hash_indirect
2784	       || h->root.type == bfd_link_hash_warning)
2785	  h = (struct elf_link_hash_entry *) h->root.u.i.link;
2786
2787      /* ??? Versioned symbols seem to lose NEEDS_PLT.  */
2788      if (elfNN_ia64_dynamic_symbol_p (h, x->info, 0))
2789	{
2790	  bfd_size_type offset = x->ofs;
2791	  if (offset == 0)
2792	    offset = PLT_HEADER_SIZE;
2793	  dyn_i->plt_offset = offset;
2794	  x->ofs = offset + PLT_MIN_ENTRY_SIZE;
2795
2796	  dyn_i->want_pltoff = 1;
2797	}
2798      else
2799	{
2800	  dyn_i->want_plt = 0;
2801	  dyn_i->want_plt2 = 0;
2802	}
2803    }
2804  return TRUE;
2805}
2806
2807/* Allocate all the full PLT entries.  */
2808
2809static bfd_boolean
2810allocate_plt2_entries (struct elfNN_ia64_dyn_sym_info *dyn_i,
2811		       void * data)
2812{
2813  struct elfNN_ia64_allocate_data *x = (struct elfNN_ia64_allocate_data *)data;
2814
2815  if (dyn_i->want_plt2)
2816    {
2817      struct elf_link_hash_entry *h = dyn_i->h;
2818      bfd_size_type ofs = x->ofs;
2819
2820      dyn_i->plt2_offset = ofs;
2821      x->ofs = ofs + PLT_FULL_ENTRY_SIZE;
2822
2823      while (h->root.type == bfd_link_hash_indirect
2824	     || h->root.type == bfd_link_hash_warning)
2825	h = (struct elf_link_hash_entry *) h->root.u.i.link;
2826      dyn_i->h->plt.offset = ofs;
2827    }
2828  return TRUE;
2829}
2830
2831/* Allocate all the PLTOFF entries requested by relocations and
2832   plt entries.  We can't share space with allocated FPTR entries,
2833   because the latter are not necessarily addressable by the GP.
2834   ??? Relaxation might be able to determine that they are.  */
2835
2836static bfd_boolean
2837allocate_pltoff_entries (struct elfNN_ia64_dyn_sym_info *dyn_i,
2838			 void * data)
2839{
2840  struct elfNN_ia64_allocate_data *x = (struct elfNN_ia64_allocate_data *)data;
2841
2842  if (dyn_i->want_pltoff)
2843    {
2844      dyn_i->pltoff_offset = x->ofs;
2845      x->ofs += 16;
2846    }
2847  return TRUE;
2848}
2849
2850/* Allocate dynamic relocations for those symbols that turned out
2851   to be dynamic.  */
2852
2853static bfd_boolean
2854allocate_dynrel_entries (struct elfNN_ia64_dyn_sym_info *dyn_i,
2855			 void * data)
2856{
2857  struct elfNN_ia64_allocate_data *x = (struct elfNN_ia64_allocate_data *)data;
2858  struct elfNN_ia64_link_hash_table *ia64_info;
2859  struct elfNN_ia64_dyn_reloc_entry *rent;
2860  bfd_boolean dynamic_symbol, shared, resolved_zero;
2861
2862  ia64_info = elfNN_ia64_hash_table (x->info);
2863  if (ia64_info == NULL)
2864    return FALSE;
2865
2866  /* Note that this can't be used in relation to FPTR relocs below.  */
2867  dynamic_symbol = elfNN_ia64_dynamic_symbol_p (dyn_i->h, x->info, 0);
2868
2869  shared = bfd_link_pic (x->info);
2870  resolved_zero = (dyn_i->h
2871		   && UNDEFWEAK_NO_DYNAMIC_RELOC (x->info,
2872						       dyn_i->h));
2873
2874  /* Take care of the GOT and PLT relocations.  */
2875
2876  if ((!resolved_zero
2877       && (dynamic_symbol || shared)
2878       && (dyn_i->want_got || dyn_i->want_gotx))
2879      || (dyn_i->want_ltoff_fptr
2880	  && dyn_i->h
2881	  && dyn_i->h->dynindx != -1))
2882    {
2883      if (!dyn_i->want_ltoff_fptr
2884	  || !bfd_link_pie (x->info)
2885	  || dyn_i->h == NULL
2886	  || dyn_i->h->root.type != bfd_link_hash_undefweak)
2887	ia64_info->root.srelgot->size += sizeof (ElfNN_External_Rela);
2888    }
2889  if ((dynamic_symbol || shared) && dyn_i->want_tprel)
2890    ia64_info->root.srelgot->size += sizeof (ElfNN_External_Rela);
2891  if (dynamic_symbol && dyn_i->want_dtpmod)
2892    ia64_info->root.srelgot->size += sizeof (ElfNN_External_Rela);
2893  if (dynamic_symbol && dyn_i->want_dtprel)
2894    ia64_info->root.srelgot->size += sizeof (ElfNN_External_Rela);
2895
2896  if (x->only_got)
2897    return TRUE;
2898
2899  if (ia64_info->rel_fptr_sec && dyn_i->want_fptr)
2900    {
2901      if (dyn_i->h == NULL || dyn_i->h->root.type != bfd_link_hash_undefweak)
2902	ia64_info->rel_fptr_sec->size += sizeof (ElfNN_External_Rela);
2903    }
2904
2905  if (!resolved_zero && dyn_i->want_pltoff)
2906    {
2907      bfd_size_type t = 0;
2908
2909      /* Dynamic symbols get one IPLT relocation.  Local symbols in
2910	 shared libraries get two REL relocations.  Local symbols in
2911	 main applications get nothing.  */
2912      if (dynamic_symbol)
2913	t = sizeof (ElfNN_External_Rela);
2914      else if (shared)
2915	t = 2 * sizeof (ElfNN_External_Rela);
2916
2917      ia64_info->rel_pltoff_sec->size += t;
2918    }
2919
2920  /* Take care of the normal data relocations.  */
2921
2922  for (rent = dyn_i->reloc_entries; rent; rent = rent->next)
2923    {
2924      int count = rent->count;
2925
2926      switch (rent->type)
2927	{
2928	case R_IA64_FPTR32LSB:
2929	case R_IA64_FPTR64LSB:
2930	  /* Allocate one iff !want_fptr and not PIE, which by this point
2931	     will be true only if we're actually allocating one statically
2932	     in the main executable.  Position independent executables
2933	     need a relative reloc.  */
2934	  if (dyn_i->want_fptr && !bfd_link_pie (x->info))
2935	    continue;
2936	  break;
2937	case R_IA64_PCREL32LSB:
2938	case R_IA64_PCREL64LSB:
2939	  if (!dynamic_symbol)
2940	    continue;
2941	  break;
2942	case R_IA64_DIR32LSB:
2943	case R_IA64_DIR64LSB:
2944	  if (!dynamic_symbol && !shared)
2945	    continue;
2946	  break;
2947	case R_IA64_IPLTLSB:
2948	  if (!dynamic_symbol && !shared)
2949	    continue;
2950	  /* Use two REL relocations for IPLT relocations
2951	     against local symbols.  */
2952	  if (!dynamic_symbol)
2953	    count *= 2;
2954	  break;
2955	case R_IA64_DTPREL32LSB:
2956	case R_IA64_TPREL64LSB:
2957	case R_IA64_DTPREL64LSB:
2958	case R_IA64_DTPMOD64LSB:
2959	  break;
2960	default:
2961	  abort ();
2962	}
2963      if (rent->reltext)
2964	ia64_info->reltext = 1;
2965      rent->srel->size += sizeof (ElfNN_External_Rela) * count;
2966    }
2967
2968  return TRUE;
2969}
2970
2971static bfd_boolean
2972elfNN_ia64_adjust_dynamic_symbol (struct bfd_link_info *info ATTRIBUTE_UNUSED,
2973				  struct elf_link_hash_entry *h)
2974{
2975  /* ??? Undefined symbols with PLT entries should be re-defined
2976     to be the PLT entry.  */
2977
2978  /* If this is a weak symbol, and there is a real definition, the
2979     processor independent code will have arranged for us to see the
2980     real definition first, and we can just use the same value.  */
2981  if (h->is_weakalias)
2982    {
2983      struct elf_link_hash_entry *def = weakdef (h);
2984      BFD_ASSERT (def->root.type == bfd_link_hash_defined);
2985      h->root.u.def.section = def->root.u.def.section;
2986      h->root.u.def.value = def->root.u.def.value;
2987      return TRUE;
2988    }
2989
2990  /* If this is a reference to a symbol defined by a dynamic object which
2991     is not a function, we might allocate the symbol in our .dynbss section
2992     and allocate a COPY dynamic relocation.
2993
2994     But IA-64 code is canonically PIC, so as a rule we can avoid this sort
2995     of hackery.  */
2996
2997  return TRUE;
2998}
2999
3000static bfd_boolean
3001elfNN_ia64_size_dynamic_sections (bfd *output_bfd ATTRIBUTE_UNUSED,
3002				  struct bfd_link_info *info)
3003{
3004  struct elfNN_ia64_allocate_data data;
3005  struct elfNN_ia64_link_hash_table *ia64_info;
3006  asection *sec;
3007  bfd *dynobj;
3008  bfd_boolean relplt = FALSE;
3009
3010  ia64_info = elfNN_ia64_hash_table (info);
3011  if (ia64_info == NULL)
3012    return FALSE;
3013  dynobj = ia64_info->root.dynobj;
3014  ia64_info->self_dtpmod_offset = (bfd_vma) -1;
3015  BFD_ASSERT(dynobj != NULL);
3016  data.info = info;
3017
3018  /* Set the contents of the .interp section to the interpreter.  */
3019  if (ia64_info->root.dynamic_sections_created
3020      && bfd_link_executable (info) && !info->nointerp)
3021    {
3022      sec = bfd_get_linker_section (dynobj, ".interp");
3023      BFD_ASSERT (sec != NULL);
3024      sec->contents = (bfd_byte *) ELF_DYNAMIC_INTERPRETER;
3025      sec->size = strlen (ELF_DYNAMIC_INTERPRETER) + 1;
3026    }
3027
3028  /* Allocate the GOT entries.  */
3029
3030  if (ia64_info->root.sgot)
3031    {
3032      data.ofs = 0;
3033      elfNN_ia64_dyn_sym_traverse (ia64_info, allocate_global_data_got, &data);
3034      elfNN_ia64_dyn_sym_traverse (ia64_info, allocate_global_fptr_got, &data);
3035      elfNN_ia64_dyn_sym_traverse (ia64_info, allocate_local_got, &data);
3036      ia64_info->root.sgot->size = data.ofs;
3037    }
3038
3039  /* Allocate the FPTR entries.  */
3040
3041  if (ia64_info->fptr_sec)
3042    {
3043      data.ofs = 0;
3044      elfNN_ia64_dyn_sym_traverse (ia64_info, allocate_fptr, &data);
3045      ia64_info->fptr_sec->size = data.ofs;
3046    }
3047
3048  /* Now that we've seen all of the input files, we can decide which
3049     symbols need plt entries.  Allocate the minimal PLT entries first.
3050     We do this even though dynamic_sections_created may be FALSE, because
3051     this has the side-effect of clearing want_plt and want_plt2.  */
3052
3053  data.ofs = 0;
3054  elfNN_ia64_dyn_sym_traverse (ia64_info, allocate_plt_entries, &data);
3055
3056  ia64_info->minplt_entries = 0;
3057  if (data.ofs)
3058    {
3059      ia64_info->minplt_entries
3060	= (data.ofs - PLT_HEADER_SIZE) / PLT_MIN_ENTRY_SIZE;
3061    }
3062
3063  /* Align the pointer for the plt2 entries.  */
3064  data.ofs = (data.ofs + 31) & (bfd_vma) -32;
3065
3066  elfNN_ia64_dyn_sym_traverse (ia64_info, allocate_plt2_entries, &data);
3067  if (data.ofs != 0 || ia64_info->root.dynamic_sections_created)
3068    {
3069      /* FIXME: we always reserve the memory for dynamic linker even if
3070	 there are no PLT entries since dynamic linker may assume the
3071	 reserved memory always exists.  */
3072
3073      BFD_ASSERT (ia64_info->root.dynamic_sections_created);
3074
3075      ia64_info->root.splt->size = data.ofs;
3076
3077      /* If we've got a .plt, we need some extra memory for the dynamic
3078	 linker.  We stuff these in .got.plt.  */
3079      ia64_info->root.sgotplt->size = 8 * PLT_RESERVED_WORDS;
3080    }
3081
3082  /* Allocate the PLTOFF entries.  */
3083
3084  if (ia64_info->pltoff_sec)
3085    {
3086      data.ofs = 0;
3087      elfNN_ia64_dyn_sym_traverse (ia64_info, allocate_pltoff_entries, &data);
3088      ia64_info->pltoff_sec->size = data.ofs;
3089    }
3090
3091  if (ia64_info->root.dynamic_sections_created)
3092    {
3093      /* Allocate space for the dynamic relocations that turned out to be
3094	 required.  */
3095
3096      if (bfd_link_pic (info) && ia64_info->self_dtpmod_offset != (bfd_vma) -1)
3097	ia64_info->root.srelgot->size += sizeof (ElfNN_External_Rela);
3098      data.only_got = FALSE;
3099      elfNN_ia64_dyn_sym_traverse (ia64_info, allocate_dynrel_entries, &data);
3100    }
3101
3102  /* We have now determined the sizes of the various dynamic sections.
3103     Allocate memory for them.  */
3104  for (sec = dynobj->sections; sec != NULL; sec = sec->next)
3105    {
3106      bfd_boolean strip;
3107
3108      if (!(sec->flags & SEC_LINKER_CREATED))
3109	continue;
3110
3111      /* If we don't need this section, strip it from the output file.
3112	 There were several sections primarily related to dynamic
3113	 linking that must be create before the linker maps input
3114	 sections to output sections.  The linker does that before
3115	 bfd_elf_size_dynamic_sections is called, and it is that
3116	 function which decides whether anything needs to go into
3117	 these sections.  */
3118
3119      strip = (sec->size == 0);
3120
3121      if (sec == ia64_info->root.sgot)
3122	strip = FALSE;
3123      else if (sec == ia64_info->root.srelgot)
3124	{
3125	  if (strip)
3126	    ia64_info->root.srelgot = NULL;
3127	  else
3128	    /* We use the reloc_count field as a counter if we need to
3129	       copy relocs into the output file.  */
3130	    sec->reloc_count = 0;
3131	}
3132      else if (sec == ia64_info->fptr_sec)
3133	{
3134	  if (strip)
3135	    ia64_info->fptr_sec = NULL;
3136	}
3137      else if (sec == ia64_info->rel_fptr_sec)
3138	{
3139	  if (strip)
3140	    ia64_info->rel_fptr_sec = NULL;
3141	  else
3142	    /* We use the reloc_count field as a counter if we need to
3143	       copy relocs into the output file.  */
3144	    sec->reloc_count = 0;
3145	}
3146      else if (sec == ia64_info->root.splt)
3147	{
3148	  if (strip)
3149	    ia64_info->root.splt = NULL;
3150	}
3151      else if (sec == ia64_info->pltoff_sec)
3152	{
3153	  if (strip)
3154	    ia64_info->pltoff_sec = NULL;
3155	}
3156      else if (sec == ia64_info->rel_pltoff_sec)
3157	{
3158	  if (strip)
3159	    ia64_info->rel_pltoff_sec = NULL;
3160	  else
3161	    {
3162	      relplt = TRUE;
3163	      /* We use the reloc_count field as a counter if we need to
3164		 copy relocs into the output file.  */
3165	      sec->reloc_count = 0;
3166	    }
3167	}
3168      else
3169	{
3170	  const char *name;
3171
3172	  /* It's OK to base decisions on the section name, because none
3173	     of the dynobj section names depend upon the input files.  */
3174	  name = bfd_section_name (sec);
3175
3176	  if (strcmp (name, ".got.plt") == 0)
3177	    strip = FALSE;
3178	  else if (CONST_STRNEQ (name, ".rel"))
3179	    {
3180	      if (!strip)
3181		{
3182		  /* We use the reloc_count field as a counter if we need to
3183		     copy relocs into the output file.  */
3184		  sec->reloc_count = 0;
3185		}
3186	    }
3187	  else
3188	    continue;
3189	}
3190
3191      if (strip)
3192	sec->flags |= SEC_EXCLUDE;
3193      else
3194	{
3195	  /* Allocate memory for the section contents.  */
3196	  sec->contents = (bfd_byte *) bfd_zalloc (dynobj, sec->size);
3197	  if (sec->contents == NULL && sec->size != 0)
3198	    return FALSE;
3199	}
3200    }
3201
3202  if (ia64_info->root.dynamic_sections_created)
3203    {
3204      /* Add some entries to the .dynamic section.  We fill in the values
3205	 later (in finish_dynamic_sections) but we must add the entries now
3206	 so that we get the correct size for the .dynamic section.  */
3207
3208      if (bfd_link_executable (info))
3209	{
3210	  /* The DT_DEBUG entry is filled in by the dynamic linker and used
3211	     by the debugger.  */
3212#define add_dynamic_entry(TAG, VAL) \
3213  _bfd_elf_add_dynamic_entry (info, TAG, VAL)
3214
3215	  if (!add_dynamic_entry (DT_DEBUG, 0))
3216	    return FALSE;
3217	}
3218
3219      if (!add_dynamic_entry (DT_IA_64_PLT_RESERVE, 0))
3220	return FALSE;
3221      if (!add_dynamic_entry (DT_PLTGOT, 0))
3222	return FALSE;
3223
3224      if (relplt)
3225	{
3226	  if (!add_dynamic_entry (DT_PLTRELSZ, 0)
3227	      || !add_dynamic_entry (DT_PLTREL, DT_RELA)
3228	      || !add_dynamic_entry (DT_JMPREL, 0))
3229	    return FALSE;
3230	}
3231
3232      if (!add_dynamic_entry (DT_RELA, 0)
3233	  || !add_dynamic_entry (DT_RELASZ, 0)
3234	  || !add_dynamic_entry (DT_RELAENT, sizeof (ElfNN_External_Rela)))
3235	return FALSE;
3236
3237      if (ia64_info->reltext)
3238	{
3239	  if (!add_dynamic_entry (DT_TEXTREL, 0))
3240	    return FALSE;
3241	  info->flags |= DF_TEXTREL;
3242	}
3243    }
3244
3245  /* ??? Perhaps force __gp local.  */
3246
3247  return TRUE;
3248}
3249
3250static void
3251elfNN_ia64_install_dyn_reloc (bfd *abfd, struct bfd_link_info *info,
3252			      asection *sec, asection *srel,
3253			      bfd_vma offset, unsigned int type,
3254			      long dynindx, bfd_vma addend)
3255{
3256  Elf_Internal_Rela outrel;
3257  bfd_byte *loc;
3258
3259  BFD_ASSERT (dynindx != -1);
3260  outrel.r_info = ELFNN_R_INFO (dynindx, type);
3261  outrel.r_addend = addend;
3262  outrel.r_offset = _bfd_elf_section_offset (abfd, info, sec, offset);
3263  if (outrel.r_offset >= (bfd_vma) -2)
3264    {
3265      /* Run for the hills.  We shouldn't be outputting a relocation
3266	 for this.  So do what everyone else does and output a no-op.  */
3267      outrel.r_info = ELFNN_R_INFO (0, R_IA64_NONE);
3268      outrel.r_addend = 0;
3269      outrel.r_offset = 0;
3270    }
3271  else
3272    outrel.r_offset += sec->output_section->vma + sec->output_offset;
3273
3274  loc = srel->contents;
3275  loc += srel->reloc_count++ * sizeof (ElfNN_External_Rela);
3276  bfd_elfNN_swap_reloca_out (abfd, &outrel, loc);
3277  BFD_ASSERT (sizeof (ElfNN_External_Rela) * srel->reloc_count <= srel->size);
3278}
3279
3280/* Store an entry for target address TARGET_ADDR in the linkage table
3281   and return the gp-relative address of the linkage table entry.  */
3282
3283static bfd_vma
3284set_got_entry (bfd *abfd, struct bfd_link_info *info,
3285	       struct elfNN_ia64_dyn_sym_info *dyn_i,
3286	       long dynindx, bfd_vma addend, bfd_vma value,
3287	       unsigned int dyn_r_type)
3288{
3289  struct elfNN_ia64_link_hash_table *ia64_info;
3290  asection *got_sec;
3291  bfd_boolean done;
3292  bfd_vma got_offset;
3293
3294  ia64_info = elfNN_ia64_hash_table (info);
3295  if (ia64_info == NULL)
3296    return 0;
3297
3298  got_sec = ia64_info->root.sgot;
3299
3300  switch (dyn_r_type)
3301    {
3302    case R_IA64_TPREL64LSB:
3303      done = dyn_i->tprel_done;
3304      dyn_i->tprel_done = TRUE;
3305      got_offset = dyn_i->tprel_offset;
3306      break;
3307    case R_IA64_DTPMOD64LSB:
3308      if (dyn_i->dtpmod_offset != ia64_info->self_dtpmod_offset)
3309	{
3310	  done = dyn_i->dtpmod_done;
3311	  dyn_i->dtpmod_done = TRUE;
3312	}
3313      else
3314	{
3315	  done = ia64_info->self_dtpmod_done;
3316	  ia64_info->self_dtpmod_done = TRUE;
3317	  dynindx = 0;
3318	}
3319      got_offset = dyn_i->dtpmod_offset;
3320      break;
3321    case R_IA64_DTPREL32LSB:
3322    case R_IA64_DTPREL64LSB:
3323      done = dyn_i->dtprel_done;
3324      dyn_i->dtprel_done = TRUE;
3325      got_offset = dyn_i->dtprel_offset;
3326      break;
3327    default:
3328      done = dyn_i->got_done;
3329      dyn_i->got_done = TRUE;
3330      got_offset = dyn_i->got_offset;
3331      break;
3332    }
3333
3334  BFD_ASSERT ((got_offset & 7) == 0);
3335
3336  if (! done)
3337    {
3338      /* Store the target address in the linkage table entry.  */
3339      bfd_put_64 (abfd, value, got_sec->contents + got_offset);
3340
3341      /* Install a dynamic relocation if needed.  */
3342      if (((bfd_link_pic (info)
3343	    && (!dyn_i->h
3344		|| (ELF_ST_VISIBILITY (dyn_i->h->other) == STV_DEFAULT
3345		    && !UNDEFWEAK_NO_DYNAMIC_RELOC (info, dyn_i->h))
3346		|| dyn_i->h->root.type != bfd_link_hash_undefweak)
3347	    && dyn_r_type != R_IA64_DTPREL32LSB
3348	    && dyn_r_type != R_IA64_DTPREL64LSB)
3349	   || elfNN_ia64_dynamic_symbol_p (dyn_i->h, info, dyn_r_type)
3350	   || (dynindx != -1
3351	       && (dyn_r_type == R_IA64_FPTR32LSB
3352		   || dyn_r_type == R_IA64_FPTR64LSB)))
3353	  && (!dyn_i->want_ltoff_fptr
3354	      || !bfd_link_pie (info)
3355	      || !dyn_i->h
3356	      || dyn_i->h->root.type != bfd_link_hash_undefweak))
3357	{
3358	  if (dynindx == -1
3359	      && dyn_r_type != R_IA64_TPREL64LSB
3360	      && dyn_r_type != R_IA64_DTPMOD64LSB
3361	      && dyn_r_type != R_IA64_DTPREL32LSB
3362	      && dyn_r_type != R_IA64_DTPREL64LSB)
3363	    {
3364	      dyn_r_type = R_IA64_RELNNLSB;
3365	      dynindx = 0;
3366	      addend = value;
3367	    }
3368
3369	  if (bfd_big_endian (abfd))
3370	    {
3371	      switch (dyn_r_type)
3372		{
3373		case R_IA64_REL32LSB:
3374		  dyn_r_type = R_IA64_REL32MSB;
3375		  break;
3376		case R_IA64_DIR32LSB:
3377		  dyn_r_type = R_IA64_DIR32MSB;
3378		  break;
3379		case R_IA64_FPTR32LSB:
3380		  dyn_r_type = R_IA64_FPTR32MSB;
3381		  break;
3382		case R_IA64_DTPREL32LSB:
3383		  dyn_r_type = R_IA64_DTPREL32MSB;
3384		  break;
3385		case R_IA64_REL64LSB:
3386		  dyn_r_type = R_IA64_REL64MSB;
3387		  break;
3388		case R_IA64_DIR64LSB:
3389		  dyn_r_type = R_IA64_DIR64MSB;
3390		  break;
3391		case R_IA64_FPTR64LSB:
3392		  dyn_r_type = R_IA64_FPTR64MSB;
3393		  break;
3394		case R_IA64_TPREL64LSB:
3395		  dyn_r_type = R_IA64_TPREL64MSB;
3396		  break;
3397		case R_IA64_DTPMOD64LSB:
3398		  dyn_r_type = R_IA64_DTPMOD64MSB;
3399		  break;
3400		case R_IA64_DTPREL64LSB:
3401		  dyn_r_type = R_IA64_DTPREL64MSB;
3402		  break;
3403		default:
3404		  BFD_ASSERT (FALSE);
3405		  break;
3406		}
3407	    }
3408
3409	  elfNN_ia64_install_dyn_reloc (abfd, NULL, got_sec,
3410					ia64_info->root.srelgot,
3411					got_offset, dyn_r_type,
3412					dynindx, addend);
3413	}
3414    }
3415
3416  /* Return the address of the linkage table entry.  */
3417  value = (got_sec->output_section->vma
3418	   + got_sec->output_offset
3419	   + got_offset);
3420
3421  return value;
3422}
3423
3424/* Fill in a function descriptor consisting of the function's code
3425   address and its global pointer.  Return the descriptor's address.  */
3426
3427static bfd_vma
3428set_fptr_entry (bfd *abfd, struct bfd_link_info *info,
3429		struct elfNN_ia64_dyn_sym_info *dyn_i,
3430		bfd_vma value)
3431{
3432  struct elfNN_ia64_link_hash_table *ia64_info;
3433  asection *fptr_sec;
3434
3435  ia64_info = elfNN_ia64_hash_table (info);
3436  if (ia64_info == NULL)
3437    return 0;
3438
3439  fptr_sec = ia64_info->fptr_sec;
3440
3441  if (!dyn_i->fptr_done)
3442    {
3443      dyn_i->fptr_done = 1;
3444
3445      /* Fill in the function descriptor.  */
3446      bfd_put_64 (abfd, value, fptr_sec->contents + dyn_i->fptr_offset);
3447      bfd_put_64 (abfd, _bfd_get_gp_value (abfd),
3448		  fptr_sec->contents + dyn_i->fptr_offset + 8);
3449      if (ia64_info->rel_fptr_sec)
3450	{
3451	  Elf_Internal_Rela outrel;
3452	  bfd_byte *loc;
3453
3454	  if (bfd_little_endian (abfd))
3455	    outrel.r_info = ELFNN_R_INFO (0, R_IA64_IPLTLSB);
3456	  else
3457	    outrel.r_info = ELFNN_R_INFO (0, R_IA64_IPLTMSB);
3458	  outrel.r_addend = value;
3459	  outrel.r_offset = (fptr_sec->output_section->vma
3460			     + fptr_sec->output_offset
3461			     + dyn_i->fptr_offset);
3462	  loc = ia64_info->rel_fptr_sec->contents;
3463	  loc += ia64_info->rel_fptr_sec->reloc_count++
3464		 * sizeof (ElfNN_External_Rela);
3465	  bfd_elfNN_swap_reloca_out (abfd, &outrel, loc);
3466	}
3467    }
3468
3469  /* Return the descriptor's address.  */
3470  value = (fptr_sec->output_section->vma
3471	   + fptr_sec->output_offset
3472	   + dyn_i->fptr_offset);
3473
3474  return value;
3475}
3476
3477/* Fill in a PLTOFF entry consisting of the function's code address
3478   and its global pointer.  Return the descriptor's address.  */
3479
3480static bfd_vma
3481set_pltoff_entry (bfd *abfd, struct bfd_link_info *info,
3482		  struct elfNN_ia64_dyn_sym_info *dyn_i,
3483		  bfd_vma value, bfd_boolean is_plt)
3484{
3485  struct elfNN_ia64_link_hash_table *ia64_info;
3486  asection *pltoff_sec;
3487
3488  ia64_info = elfNN_ia64_hash_table (info);
3489  if (ia64_info == NULL)
3490    return 0;
3491
3492  pltoff_sec = ia64_info->pltoff_sec;
3493
3494  /* Don't do anything if this symbol uses a real PLT entry.  In
3495     that case, we'll fill this in during finish_dynamic_symbol.  */
3496  if ((! dyn_i->want_plt || is_plt)
3497      && !dyn_i->pltoff_done)
3498    {
3499      bfd_vma gp = _bfd_get_gp_value (abfd);
3500
3501      /* Fill in the function descriptor.  */
3502      bfd_put_64 (abfd, value, pltoff_sec->contents + dyn_i->pltoff_offset);
3503      bfd_put_64 (abfd, gp, pltoff_sec->contents + dyn_i->pltoff_offset + 8);
3504
3505      /* Install dynamic relocations if needed.  */
3506      if (!is_plt
3507	  && bfd_link_pic (info)
3508	  && (!dyn_i->h
3509	      || (ELF_ST_VISIBILITY (dyn_i->h->other) == STV_DEFAULT
3510		  && !UNDEFWEAK_NO_DYNAMIC_RELOC (info, dyn_i->h))
3511	      || dyn_i->h->root.type != bfd_link_hash_undefweak))
3512	{
3513	  unsigned int dyn_r_type;
3514
3515	  if (bfd_big_endian (abfd))
3516	    dyn_r_type = R_IA64_RELNNMSB;
3517	  else
3518	    dyn_r_type = R_IA64_RELNNLSB;
3519
3520	  elfNN_ia64_install_dyn_reloc (abfd, NULL, pltoff_sec,
3521					ia64_info->rel_pltoff_sec,
3522					dyn_i->pltoff_offset,
3523					dyn_r_type, 0, value);
3524	  elfNN_ia64_install_dyn_reloc (abfd, NULL, pltoff_sec,
3525					ia64_info->rel_pltoff_sec,
3526					dyn_i->pltoff_offset + ARCH_SIZE / 8,
3527					dyn_r_type, 0, gp);
3528	}
3529
3530      dyn_i->pltoff_done = 1;
3531    }
3532
3533  /* Return the descriptor's address.  */
3534  value = (pltoff_sec->output_section->vma
3535	   + pltoff_sec->output_offset
3536	   + dyn_i->pltoff_offset);
3537
3538  return value;
3539}
3540
3541/* Return the base VMA address which should be subtracted from real addresses
3542   when resolving @tprel() relocation.
3543   Main program TLS (whose template starts at PT_TLS p_vaddr)
3544   is assigned offset round(2 * size of pointer, PT_TLS p_align).  */
3545
3546static bfd_vma
3547elfNN_ia64_tprel_base (struct bfd_link_info *info)
3548{
3549  asection *tls_sec = elf_hash_table (info)->tls_sec;
3550  return tls_sec->vma - align_power ((bfd_vma) ARCH_SIZE / 4,
3551				     tls_sec->alignment_power);
3552}
3553
3554/* Return the base VMA address which should be subtracted from real addresses
3555   when resolving @dtprel() relocation.
3556   This is PT_TLS segment p_vaddr.  */
3557
3558static bfd_vma
3559elfNN_ia64_dtprel_base (struct bfd_link_info *info)
3560{
3561  return elf_hash_table (info)->tls_sec->vma;
3562}
3563
3564/* Called through qsort to sort the .IA_64.unwind section during a
3565   non-relocatable link.  Set elfNN_ia64_unwind_entry_compare_bfd
3566   to the output bfd so we can do proper endianness frobbing.  */
3567
3568static bfd *elfNN_ia64_unwind_entry_compare_bfd;
3569
3570static int
3571elfNN_ia64_unwind_entry_compare (const void * a, const void * b)
3572{
3573  bfd_vma av, bv;
3574
3575  av = bfd_get_64 (elfNN_ia64_unwind_entry_compare_bfd, a);
3576  bv = bfd_get_64 (elfNN_ia64_unwind_entry_compare_bfd, b);
3577
3578  return (av < bv ? -1 : av > bv ? 1 : 0);
3579}
3580
3581/* Make sure we've got ourselves a nice fat __gp value.  */
3582static bfd_boolean
3583elfNN_ia64_choose_gp (bfd *abfd, struct bfd_link_info *info, bfd_boolean final)
3584{
3585  bfd_vma min_vma = (bfd_vma) -1, max_vma = 0;
3586  bfd_vma min_short_vma = min_vma, max_short_vma = 0;
3587  struct elf_link_hash_entry *gp;
3588  bfd_vma gp_val;
3589  asection *os;
3590  struct elfNN_ia64_link_hash_table *ia64_info;
3591
3592  ia64_info = elfNN_ia64_hash_table (info);
3593  if (ia64_info == NULL)
3594    return FALSE;
3595
3596  /* Find the min and max vma of all sections marked short.  Also collect
3597     min and max vma of any type, for use in selecting a nice gp.  */
3598  for (os = abfd->sections; os ; os = os->next)
3599    {
3600      bfd_vma lo, hi;
3601
3602      if ((os->flags & SEC_ALLOC) == 0)
3603	continue;
3604
3605      lo = os->vma;
3606      /* When this function is called from elfNN_ia64_final_link
3607	 the correct value to use is os->size.  When called from
3608	 elfNN_ia64_relax_section we are in the middle of section
3609	 sizing; some sections will already have os->size set, others
3610	 will have os->size zero and os->rawsize the previous size.  */
3611      hi = os->vma + (!final && os->rawsize ? os->rawsize : os->size);
3612      if (hi < lo)
3613	hi = (bfd_vma) -1;
3614
3615      if (min_vma > lo)
3616	min_vma = lo;
3617      if (max_vma < hi)
3618	max_vma = hi;
3619      if (os->flags & SEC_SMALL_DATA)
3620	{
3621	  if (min_short_vma > lo)
3622	    min_short_vma = lo;
3623	  if (max_short_vma < hi)
3624	    max_short_vma = hi;
3625	}
3626    }
3627
3628  if (ia64_info->min_short_sec)
3629    {
3630      if (min_short_vma
3631	  > (ia64_info->min_short_sec->vma
3632	     + ia64_info->min_short_offset))
3633	min_short_vma = (ia64_info->min_short_sec->vma
3634			 + ia64_info->min_short_offset);
3635      if (max_short_vma
3636	  < (ia64_info->max_short_sec->vma
3637	     + ia64_info->max_short_offset))
3638	max_short_vma = (ia64_info->max_short_sec->vma
3639			 + ia64_info->max_short_offset);
3640    }
3641
3642  /* See if the user wants to force a value.  */
3643  gp = elf_link_hash_lookup (elf_hash_table (info), "__gp", FALSE,
3644			     FALSE, FALSE);
3645
3646  if (gp
3647      && (gp->root.type == bfd_link_hash_defined
3648	  || gp->root.type == bfd_link_hash_defweak))
3649    {
3650      asection *gp_sec = gp->root.u.def.section;
3651      gp_val = (gp->root.u.def.value
3652		+ gp_sec->output_section->vma
3653		+ gp_sec->output_offset);
3654    }
3655  else
3656    {
3657      /* Pick a sensible value.  */
3658
3659      if (ia64_info->min_short_sec)
3660	{
3661	  bfd_vma short_range = max_short_vma - min_short_vma;
3662
3663	  /* If min_short_sec is set, pick one in the middle bewteen
3664	     min_short_vma and max_short_vma.  */
3665	  if (short_range >= 0x400000)
3666	    goto overflow;
3667	  gp_val = min_short_vma + short_range / 2;
3668	}
3669      else
3670	{
3671	  asection *got_sec = ia64_info->root.sgot;
3672
3673	  /* Start with just the address of the .got.  */
3674	  if (got_sec)
3675	    gp_val = got_sec->output_section->vma;
3676	  else if (max_short_vma != 0)
3677	    gp_val = min_short_vma;
3678	  else if (max_vma - min_vma < 0x200000)
3679	    gp_val = min_vma;
3680	  else
3681	    gp_val = max_vma - 0x200000 + 8;
3682	}
3683
3684      /* If it is possible to address the entire image, but we
3685	 don't with the choice above, adjust.  */
3686      if (max_vma - min_vma < 0x400000
3687	  && (max_vma - gp_val >= 0x200000
3688	      || gp_val - min_vma > 0x200000))
3689	gp_val = min_vma + 0x200000;
3690      else if (max_short_vma != 0)
3691	{
3692	  /* If we don't cover all the short data, adjust.  */
3693	  if (max_short_vma - gp_val >= 0x200000)
3694	    gp_val = min_short_vma + 0x200000;
3695
3696	  /* If we're addressing stuff past the end, adjust back.  */
3697	  if (gp_val > max_vma)
3698	    gp_val = max_vma - 0x200000 + 8;
3699	}
3700    }
3701
3702  /* Validate whether all SHF_IA_64_SHORT sections are within
3703     range of the chosen GP.  */
3704
3705  if (max_short_vma != 0)
3706    {
3707      if (max_short_vma - min_short_vma >= 0x400000)
3708	{
3709overflow:
3710	  _bfd_error_handler
3711	    /* xgettext:c-format */
3712	    (_("%pB: short data segment overflowed (%#" PRIx64 " >= 0x400000)"),
3713	     abfd, (uint64_t) (max_short_vma - min_short_vma));
3714	  return FALSE;
3715	}
3716      else if ((gp_val > min_short_vma
3717		&& gp_val - min_short_vma > 0x200000)
3718	       || (gp_val < max_short_vma
3719		   && max_short_vma - gp_val >= 0x200000))
3720	{
3721	  _bfd_error_handler
3722	    (_("%pB: __gp does not cover short data segment"), abfd);
3723	  return FALSE;
3724	}
3725    }
3726
3727  _bfd_set_gp_value (abfd, gp_val);
3728
3729  return TRUE;
3730}
3731
3732static bfd_boolean
3733elfNN_ia64_final_link (bfd *abfd, struct bfd_link_info *info)
3734{
3735  struct elfNN_ia64_link_hash_table *ia64_info;
3736  asection *unwind_output_sec;
3737
3738  ia64_info = elfNN_ia64_hash_table (info);
3739  if (ia64_info == NULL)
3740    return FALSE;
3741
3742  /* Make sure we've got ourselves a nice fat __gp value.  */
3743  if (!bfd_link_relocatable (info))
3744    {
3745      bfd_vma gp_val;
3746      struct elf_link_hash_entry *gp;
3747
3748      /* We assume after gp is set, section size will only decrease. We
3749	 need to adjust gp for it.  */
3750      _bfd_set_gp_value (abfd, 0);
3751      if (! elfNN_ia64_choose_gp (abfd, info, TRUE))
3752	return FALSE;
3753      gp_val = _bfd_get_gp_value (abfd);
3754
3755      gp = elf_link_hash_lookup (elf_hash_table (info), "__gp", FALSE,
3756				 FALSE, FALSE);
3757      if (gp)
3758	{
3759	  gp->root.type = bfd_link_hash_defined;
3760	  gp->root.u.def.value = gp_val;
3761	  gp->root.u.def.section = bfd_abs_section_ptr;
3762	}
3763    }
3764
3765  /* If we're producing a final executable, we need to sort the contents
3766     of the .IA_64.unwind section.  Force this section to be relocated
3767     into memory rather than written immediately to the output file.  */
3768  unwind_output_sec = NULL;
3769  if (!bfd_link_relocatable (info))
3770    {
3771      asection *s = bfd_get_section_by_name (abfd, ELF_STRING_ia64_unwind);
3772      if (s)
3773	{
3774	  unwind_output_sec = s->output_section;
3775	  unwind_output_sec->contents
3776	    = bfd_malloc (unwind_output_sec->size);
3777	  if (unwind_output_sec->contents == NULL)
3778	    return FALSE;
3779	}
3780    }
3781
3782  /* Invoke the regular ELF backend linker to do all the work.  */
3783  if (!bfd_elf_final_link (abfd, info))
3784    return FALSE;
3785
3786  if (unwind_output_sec)
3787    {
3788      elfNN_ia64_unwind_entry_compare_bfd = abfd;
3789      qsort (unwind_output_sec->contents,
3790	     (size_t) (unwind_output_sec->size / 24),
3791	     24,
3792	     elfNN_ia64_unwind_entry_compare);
3793
3794      if (! bfd_set_section_contents (abfd, unwind_output_sec,
3795				      unwind_output_sec->contents, (bfd_vma) 0,
3796				      unwind_output_sec->size))
3797	return FALSE;
3798    }
3799
3800  return TRUE;
3801}
3802
3803static bfd_boolean
3804elfNN_ia64_relocate_section (bfd *output_bfd,
3805			     struct bfd_link_info *info,
3806			     bfd *input_bfd,
3807			     asection *input_section,
3808			     bfd_byte *contents,
3809			     Elf_Internal_Rela *relocs,
3810			     Elf_Internal_Sym *local_syms,
3811			     asection **local_sections)
3812{
3813  struct elfNN_ia64_link_hash_table *ia64_info;
3814  Elf_Internal_Shdr *symtab_hdr;
3815  Elf_Internal_Rela *rel;
3816  Elf_Internal_Rela *relend;
3817  asection *srel;
3818  bfd_boolean ret_val = TRUE;	/* for non-fatal errors */
3819  bfd_vma gp_val;
3820
3821  symtab_hdr = &elf_tdata (input_bfd)->symtab_hdr;
3822  ia64_info = elfNN_ia64_hash_table (info);
3823  if (ia64_info == NULL)
3824    return FALSE;
3825
3826  /* Infect various flags from the input section to the output section.  */
3827  if (bfd_link_relocatable (info))
3828    {
3829      bfd_vma flags;
3830
3831      flags = elf_section_data(input_section)->this_hdr.sh_flags;
3832      flags &= SHF_IA_64_NORECOV;
3833
3834      elf_section_data(input_section->output_section)
3835	->this_hdr.sh_flags |= flags;
3836    }
3837
3838  gp_val = _bfd_get_gp_value (output_bfd);
3839  srel = get_reloc_section (input_bfd, ia64_info, input_section, FALSE);
3840
3841  rel = relocs;
3842  relend = relocs + input_section->reloc_count;
3843  for (; rel < relend; ++rel)
3844    {
3845      struct elf_link_hash_entry *h;
3846      struct elfNN_ia64_dyn_sym_info *dyn_i;
3847      bfd_reloc_status_type r;
3848      reloc_howto_type *howto;
3849      unsigned long r_symndx;
3850      Elf_Internal_Sym *sym;
3851      unsigned int r_type;
3852      bfd_vma value;
3853      asection *sym_sec;
3854      bfd_byte *hit_addr;
3855      bfd_boolean dynamic_symbol_p;
3856      bfd_boolean undef_weak_ref;
3857
3858      r_type = ELFNN_R_TYPE (rel->r_info);
3859      if (r_type > R_IA64_MAX_RELOC_CODE)
3860	{
3861	  /* xgettext:c-format */
3862	  _bfd_error_handler (_("%pB: unsupported relocation type %#x"),
3863			      input_bfd, (int) r_type);
3864	  bfd_set_error (bfd_error_bad_value);
3865	  ret_val = FALSE;
3866	  continue;
3867	}
3868
3869      howto = ia64_elf_lookup_howto (r_type);
3870      if (howto == NULL)
3871	{
3872	  ret_val = FALSE;
3873	  continue;
3874	}
3875
3876      r_symndx = ELFNN_R_SYM (rel->r_info);
3877      h = NULL;
3878      sym = NULL;
3879      sym_sec = NULL;
3880      undef_weak_ref = FALSE;
3881
3882      if (r_symndx < symtab_hdr->sh_info)
3883	{
3884	  /* Reloc against local symbol.  */
3885	  asection *msec;
3886	  sym = local_syms + r_symndx;
3887	  sym_sec = local_sections[r_symndx];
3888	  msec = sym_sec;
3889	  value = _bfd_elf_rela_local_sym (output_bfd, sym, &msec, rel);
3890	  if (!bfd_link_relocatable (info)
3891	      && (sym_sec->flags & SEC_MERGE) != 0
3892	      && ELF_ST_TYPE (sym->st_info) == STT_SECTION
3893	      && sym_sec->sec_info_type == SEC_INFO_TYPE_MERGE)
3894	    {
3895	      struct elfNN_ia64_local_hash_entry *loc_h;
3896
3897	      loc_h = get_local_sym_hash (ia64_info, input_bfd, rel, FALSE);
3898	      if (loc_h && ! loc_h->sec_merge_done)
3899		{
3900		  struct elfNN_ia64_dyn_sym_info *dynent;
3901		  unsigned int count;
3902
3903		  for (count = loc_h->count, dynent = loc_h->info;
3904		       count != 0;
3905		       count--, dynent++)
3906		    {
3907		      msec = sym_sec;
3908		      dynent->addend =
3909			_bfd_merged_section_offset (output_bfd, &msec,
3910						    elf_section_data (msec)->
3911						    sec_info,
3912						    sym->st_value
3913						    + dynent->addend);
3914		      dynent->addend -= sym->st_value;
3915		      dynent->addend += msec->output_section->vma
3916					+ msec->output_offset
3917					- sym_sec->output_section->vma
3918					- sym_sec->output_offset;
3919		    }
3920
3921		  /* We may have introduced duplicated entries. We need
3922		     to remove them properly.  */
3923		  count = sort_dyn_sym_info (loc_h->info, loc_h->count);
3924		  if (count != loc_h->count)
3925		    {
3926		      loc_h->count = count;
3927		      loc_h->sorted_count = count;
3928		    }
3929
3930		  loc_h->sec_merge_done = 1;
3931		}
3932	    }
3933	}
3934      else
3935	{
3936	  bfd_boolean unresolved_reloc;
3937	  bfd_boolean warned, ignored;
3938	  struct elf_link_hash_entry **sym_hashes = elf_sym_hashes (input_bfd);
3939
3940	  RELOC_FOR_GLOBAL_SYMBOL (info, input_bfd, input_section, rel,
3941				   r_symndx, symtab_hdr, sym_hashes,
3942				   h, sym_sec, value,
3943				   unresolved_reloc, warned, ignored);
3944
3945	  if (h->root.type == bfd_link_hash_undefweak)
3946	    undef_weak_ref = TRUE;
3947	  else if (warned || (ignored && bfd_link_executable (info)))
3948	    continue;
3949	}
3950
3951      if (sym_sec != NULL && discarded_section (sym_sec))
3952	RELOC_AGAINST_DISCARDED_SECTION (info, input_bfd, input_section,
3953					 rel, 1, relend, howto, 0, contents);
3954
3955      if (bfd_link_relocatable (info))
3956	continue;
3957
3958      hit_addr = contents + rel->r_offset;
3959      value += rel->r_addend;
3960      dynamic_symbol_p = elfNN_ia64_dynamic_symbol_p (h, info, r_type);
3961
3962      switch (r_type)
3963	{
3964	case R_IA64_NONE:
3965	case R_IA64_LDXMOV:
3966	  continue;
3967
3968	case R_IA64_IMM14:
3969	case R_IA64_IMM22:
3970	case R_IA64_IMM64:
3971	case R_IA64_DIR32MSB:
3972	case R_IA64_DIR32LSB:
3973	case R_IA64_DIR64MSB:
3974	case R_IA64_DIR64LSB:
3975	  /* Install a dynamic relocation for this reloc.  */
3976	  if ((dynamic_symbol_p || bfd_link_pic (info))
3977	      && !(h && UNDEFWEAK_NO_DYNAMIC_RELOC (info, h))
3978	      && r_symndx != STN_UNDEF
3979	      && (input_section->flags & SEC_ALLOC) != 0)
3980	    {
3981	      unsigned int dyn_r_type;
3982	      long dynindx;
3983	      bfd_vma addend;
3984
3985	      BFD_ASSERT (srel != NULL);
3986
3987	      switch (r_type)
3988		{
3989		case R_IA64_IMM14:
3990		case R_IA64_IMM22:
3991		case R_IA64_IMM64:
3992		  /* ??? People shouldn't be doing non-pic code in
3993		     shared libraries nor dynamic executables.  */
3994		  _bfd_error_handler
3995		    /* xgettext:c-format */
3996		    (_("%pB: non-pic code with imm relocation against dynamic symbol `%s'"),
3997		     input_bfd,
3998		     h ? h->root.root.string
3999		       : bfd_elf_sym_name (input_bfd, symtab_hdr, sym,
4000					   sym_sec));
4001		  ret_val = FALSE;
4002		  continue;
4003
4004		default:
4005		  break;
4006		}
4007
4008	      /* If we don't need dynamic symbol lookup, find a
4009		 matching RELATIVE relocation.  */
4010	      dyn_r_type = r_type;
4011	      if (dynamic_symbol_p)
4012		{
4013		  dynindx = h->dynindx;
4014		  addend = rel->r_addend;
4015		  value = 0;
4016		}
4017	      else
4018		{
4019		  switch (r_type)
4020		    {
4021		    case R_IA64_DIR32MSB:
4022		      dyn_r_type = R_IA64_REL32MSB;
4023		      break;
4024		    case R_IA64_DIR32LSB:
4025		      dyn_r_type = R_IA64_REL32LSB;
4026		      break;
4027		    case R_IA64_DIR64MSB:
4028		      dyn_r_type = R_IA64_REL64MSB;
4029		      break;
4030		    case R_IA64_DIR64LSB:
4031		      dyn_r_type = R_IA64_REL64LSB;
4032		      break;
4033
4034		    default:
4035		      break;
4036		    }
4037		  dynindx = 0;
4038		  addend = value;
4039		}
4040
4041	      elfNN_ia64_install_dyn_reloc (output_bfd, info, input_section,
4042					    srel, rel->r_offset, dyn_r_type,
4043					    dynindx, addend);
4044	    }
4045	  /* Fall through.  */
4046
4047	case R_IA64_LTV32MSB:
4048	case R_IA64_LTV32LSB:
4049	case R_IA64_LTV64MSB:
4050	case R_IA64_LTV64LSB:
4051	  r = ia64_elf_install_value (hit_addr, value, r_type);
4052	  break;
4053
4054	case R_IA64_GPREL22:
4055	case R_IA64_GPREL64I:
4056	case R_IA64_GPREL32MSB:
4057	case R_IA64_GPREL32LSB:
4058	case R_IA64_GPREL64MSB:
4059	case R_IA64_GPREL64LSB:
4060	  if (dynamic_symbol_p)
4061	    {
4062	      _bfd_error_handler
4063		/* xgettext:c-format */
4064		(_("%pB: @gprel relocation against dynamic symbol %s"),
4065		 input_bfd,
4066		 h ? h->root.root.string
4067		   : bfd_elf_sym_name (input_bfd, symtab_hdr, sym,
4068				       sym_sec));
4069	      ret_val = FALSE;
4070	      continue;
4071	    }
4072	  value -= gp_val;
4073	  r = ia64_elf_install_value (hit_addr, value, r_type);
4074	  break;
4075
4076	case R_IA64_LTOFF22:
4077	case R_IA64_LTOFF22X:
4078	case R_IA64_LTOFF64I:
4079	  dyn_i = get_dyn_sym_info (ia64_info, h, input_bfd, rel, FALSE);
4080	  value = set_got_entry (input_bfd, info, dyn_i, (h ? h->dynindx : -1),
4081				 rel->r_addend, value, R_IA64_DIRNNLSB);
4082	  value -= gp_val;
4083	  r = ia64_elf_install_value (hit_addr, value, r_type);
4084	  break;
4085
4086	case R_IA64_PLTOFF22:
4087	case R_IA64_PLTOFF64I:
4088	case R_IA64_PLTOFF64MSB:
4089	case R_IA64_PLTOFF64LSB:
4090	  dyn_i = get_dyn_sym_info (ia64_info, h, input_bfd, rel, FALSE);
4091	  value = set_pltoff_entry (output_bfd, info, dyn_i, value, FALSE);
4092	  value -= gp_val;
4093	  r = ia64_elf_install_value (hit_addr, value, r_type);
4094	  break;
4095
4096	case R_IA64_FPTR64I:
4097	case R_IA64_FPTR32MSB:
4098	case R_IA64_FPTR32LSB:
4099	case R_IA64_FPTR64MSB:
4100	case R_IA64_FPTR64LSB:
4101	  dyn_i = get_dyn_sym_info (ia64_info, h, input_bfd, rel, FALSE);
4102	  if (dyn_i->want_fptr)
4103	    {
4104	      if (!undef_weak_ref)
4105		value = set_fptr_entry (output_bfd, info, dyn_i, value);
4106	    }
4107	  if (!dyn_i->want_fptr || bfd_link_pie (info))
4108	    {
4109	      long dynindx;
4110	      unsigned int dyn_r_type = r_type;
4111	      bfd_vma addend = rel->r_addend;
4112
4113	      /* Otherwise, we expect the dynamic linker to create
4114		 the entry.  */
4115
4116	      if (dyn_i->want_fptr)
4117		{
4118		  if (r_type == R_IA64_FPTR64I)
4119		    {
4120		      /* We can't represent this without a dynamic symbol.
4121			 Adjust the relocation to be against an output
4122			 section symbol, which are always present in the
4123			 dynamic symbol table.  */
4124		      /* ??? People shouldn't be doing non-pic code in
4125			 shared libraries.  Hork.  */
4126		      _bfd_error_handler
4127			(_("%pB: linking non-pic code in a position independent executable"),
4128			 input_bfd);
4129		      ret_val = FALSE;
4130		      continue;
4131		    }
4132		  dynindx = 0;
4133		  addend = value;
4134		  dyn_r_type = r_type + R_IA64_RELNNLSB - R_IA64_FPTRNNLSB;
4135		}
4136	      else if (h)
4137		{
4138		  if (h->dynindx != -1)
4139		    dynindx = h->dynindx;
4140		  else
4141		    dynindx = (_bfd_elf_link_lookup_local_dynindx
4142			       (info, h->root.u.def.section->owner,
4143				global_sym_index (h)));
4144		  value = 0;
4145		}
4146	      else
4147		{
4148		  dynindx = (_bfd_elf_link_lookup_local_dynindx
4149			     (info, input_bfd, (long) r_symndx));
4150		  value = 0;
4151		}
4152
4153	      elfNN_ia64_install_dyn_reloc (output_bfd, info, input_section,
4154					    srel, rel->r_offset, dyn_r_type,
4155					    dynindx, addend);
4156	    }
4157
4158	  r = ia64_elf_install_value (hit_addr, value, r_type);
4159	  break;
4160
4161	case R_IA64_LTOFF_FPTR22:
4162	case R_IA64_LTOFF_FPTR64I:
4163	case R_IA64_LTOFF_FPTR32MSB:
4164	case R_IA64_LTOFF_FPTR32LSB:
4165	case R_IA64_LTOFF_FPTR64MSB:
4166	case R_IA64_LTOFF_FPTR64LSB:
4167	  {
4168	    long dynindx;
4169
4170	    dyn_i = get_dyn_sym_info (ia64_info, h, input_bfd, rel, FALSE);
4171	    if (dyn_i->want_fptr)
4172	      {
4173		BFD_ASSERT (h == NULL || h->dynindx == -1);
4174		if (!undef_weak_ref)
4175		  value = set_fptr_entry (output_bfd, info, dyn_i, value);
4176		dynindx = -1;
4177	      }
4178	    else
4179	      {
4180		/* Otherwise, we expect the dynamic linker to create
4181		   the entry.  */
4182		if (h)
4183		  {
4184		    if (h->dynindx != -1)
4185		      dynindx = h->dynindx;
4186		    else
4187		      dynindx = (_bfd_elf_link_lookup_local_dynindx
4188				 (info, h->root.u.def.section->owner,
4189				  global_sym_index (h)));
4190		  }
4191		else
4192		  dynindx = (_bfd_elf_link_lookup_local_dynindx
4193			     (info, input_bfd, (long) r_symndx));
4194		value = 0;
4195	      }
4196
4197	    value = set_got_entry (output_bfd, info, dyn_i, dynindx,
4198				   rel->r_addend, value, R_IA64_FPTRNNLSB);
4199	    value -= gp_val;
4200	    r = ia64_elf_install_value (hit_addr, value, r_type);
4201	  }
4202	  break;
4203
4204	case R_IA64_PCREL32MSB:
4205	case R_IA64_PCREL32LSB:
4206	case R_IA64_PCREL64MSB:
4207	case R_IA64_PCREL64LSB:
4208	  /* Install a dynamic relocation for this reloc.  */
4209	  if (dynamic_symbol_p && r_symndx != STN_UNDEF)
4210	    {
4211	      BFD_ASSERT (srel != NULL);
4212
4213	      elfNN_ia64_install_dyn_reloc (output_bfd, info, input_section,
4214					    srel, rel->r_offset, r_type,
4215					    h->dynindx, rel->r_addend);
4216	    }
4217	  goto finish_pcrel;
4218
4219	case R_IA64_PCREL21B:
4220	case R_IA64_PCREL60B:
4221	  /* We should have created a PLT entry for any dynamic symbol.  */
4222	  dyn_i = NULL;
4223	  if (h)
4224	    dyn_i = get_dyn_sym_info (ia64_info, h, NULL, NULL, FALSE);
4225
4226	  if (dyn_i && dyn_i->want_plt2)
4227	    {
4228	      /* Should have caught this earlier.  */
4229	      BFD_ASSERT (rel->r_addend == 0);
4230
4231	      value = (ia64_info->root.splt->output_section->vma
4232		       + ia64_info->root.splt->output_offset
4233		       + dyn_i->plt2_offset);
4234	    }
4235	  else
4236	    {
4237	      /* Since there's no PLT entry, Validate that this is
4238		 locally defined.  */
4239	      BFD_ASSERT (undef_weak_ref || sym_sec->output_section != NULL);
4240
4241	      /* If the symbol is undef_weak, we shouldn't be trying
4242		 to call it.  There's every chance that we'd wind up
4243		 with an out-of-range fixup here.  Don't bother setting
4244		 any value at all.  */
4245	      if (undef_weak_ref)
4246		continue;
4247	    }
4248	  goto finish_pcrel;
4249
4250	case R_IA64_PCREL21BI:
4251	case R_IA64_PCREL21F:
4252	case R_IA64_PCREL21M:
4253	case R_IA64_PCREL22:
4254	case R_IA64_PCREL64I:
4255	  /* The PCREL21BI reloc is specifically not intended for use with
4256	     dynamic relocs.  PCREL21F and PCREL21M are used for speculation
4257	     fixup code, and thus probably ought not be dynamic.  The
4258	     PCREL22 and PCREL64I relocs aren't emitted as dynamic relocs.  */
4259	  if (dynamic_symbol_p)
4260	    {
4261	      const char *msg;
4262
4263	      if (r_type == R_IA64_PCREL21BI)
4264		/* xgettext:c-format */
4265		msg = _("%pB: @internal branch to dynamic symbol %s");
4266	      else if (r_type == R_IA64_PCREL21F || r_type == R_IA64_PCREL21M)
4267		/* xgettext:c-format */
4268		msg = _("%pB: speculation fixup to dynamic symbol %s");
4269	      else
4270		/* xgettext:c-format */
4271		msg = _("%pB: @pcrel relocation against dynamic symbol %s");
4272	      _bfd_error_handler (msg, input_bfd,
4273				  h ? h->root.root.string
4274				  : bfd_elf_sym_name (input_bfd,
4275						      symtab_hdr,
4276						      sym,
4277						      sym_sec));
4278	      ret_val = FALSE;
4279	      continue;
4280	    }
4281	  goto finish_pcrel;
4282
4283	finish_pcrel:
4284	  /* Make pc-relative.  */
4285	  value -= (input_section->output_section->vma
4286		    + input_section->output_offset
4287		    + rel->r_offset) & ~ (bfd_vma) 0x3;
4288	  r = ia64_elf_install_value (hit_addr, value, r_type);
4289	  break;
4290
4291	case R_IA64_SEGREL32MSB:
4292	case R_IA64_SEGREL32LSB:
4293	case R_IA64_SEGREL64MSB:
4294	case R_IA64_SEGREL64LSB:
4295	    {
4296	      /* Find the segment that contains the output_section.  */
4297	      Elf_Internal_Phdr *p = _bfd_elf_find_segment_containing_section
4298		(output_bfd, input_section->output_section);
4299
4300	      if (p == NULL)
4301		{
4302		  r = bfd_reloc_notsupported;
4303		}
4304	      else
4305		{
4306		  /* The VMA of the segment is the vaddr of the associated
4307		     program header.  */
4308		  if (value > p->p_vaddr)
4309		    value -= p->p_vaddr;
4310		  else
4311		    value = 0;
4312		  r = ia64_elf_install_value (hit_addr, value, r_type);
4313		}
4314	      break;
4315	    }
4316
4317	case R_IA64_SECREL32MSB:
4318	case R_IA64_SECREL32LSB:
4319	case R_IA64_SECREL64MSB:
4320	case R_IA64_SECREL64LSB:
4321	  /* Make output-section relative to section where the symbol
4322	     is defined. PR 475  */
4323	  if (sym_sec)
4324	    value -= sym_sec->output_section->vma;
4325	  r = ia64_elf_install_value (hit_addr, value, r_type);
4326	  break;
4327
4328	case R_IA64_IPLTMSB:
4329	case R_IA64_IPLTLSB:
4330	  /* Install a dynamic relocation for this reloc.  */
4331	  if ((dynamic_symbol_p || bfd_link_pic (info))
4332	      && (input_section->flags & SEC_ALLOC) != 0)
4333	    {
4334	      BFD_ASSERT (srel != NULL);
4335
4336	      /* If we don't need dynamic symbol lookup, install two
4337		 RELATIVE relocations.  */
4338	      if (!dynamic_symbol_p)
4339		{
4340		  unsigned int dyn_r_type;
4341
4342		  if (r_type == R_IA64_IPLTMSB)
4343		    dyn_r_type = R_IA64_REL64MSB;
4344		  else
4345		    dyn_r_type = R_IA64_REL64LSB;
4346
4347		  elfNN_ia64_install_dyn_reloc (output_bfd, info,
4348						input_section,
4349						srel, rel->r_offset,
4350						dyn_r_type, 0, value);
4351		  elfNN_ia64_install_dyn_reloc (output_bfd, info,
4352						input_section,
4353						srel, rel->r_offset + 8,
4354						dyn_r_type, 0, gp_val);
4355		}
4356	      else
4357		elfNN_ia64_install_dyn_reloc (output_bfd, info, input_section,
4358					      srel, rel->r_offset, r_type,
4359					      h->dynindx, rel->r_addend);
4360	    }
4361
4362	  if (r_type == R_IA64_IPLTMSB)
4363	    r_type = R_IA64_DIR64MSB;
4364	  else
4365	    r_type = R_IA64_DIR64LSB;
4366	  ia64_elf_install_value (hit_addr, value, r_type);
4367	  r = ia64_elf_install_value (hit_addr + 8, gp_val, r_type);
4368	  break;
4369
4370	case R_IA64_TPREL14:
4371	case R_IA64_TPREL22:
4372	case R_IA64_TPREL64I:
4373	  if (elf_hash_table (info)->tls_sec == NULL)
4374	    goto missing_tls_sec;
4375	  value -= elfNN_ia64_tprel_base (info);
4376	  r = ia64_elf_install_value (hit_addr, value, r_type);
4377	  break;
4378
4379	case R_IA64_DTPREL14:
4380	case R_IA64_DTPREL22:
4381	case R_IA64_DTPREL64I:
4382	case R_IA64_DTPREL32LSB:
4383	case R_IA64_DTPREL32MSB:
4384	case R_IA64_DTPREL64LSB:
4385	case R_IA64_DTPREL64MSB:
4386	  if (elf_hash_table (info)->tls_sec == NULL)
4387	    goto missing_tls_sec;
4388	  value -= elfNN_ia64_dtprel_base (info);
4389	  r = ia64_elf_install_value (hit_addr, value, r_type);
4390	  break;
4391
4392	case R_IA64_LTOFF_TPREL22:
4393	case R_IA64_LTOFF_DTPMOD22:
4394	case R_IA64_LTOFF_DTPREL22:
4395	  {
4396	    int got_r_type;
4397	    long dynindx = h ? h->dynindx : -1;
4398	    bfd_vma r_addend = rel->r_addend;
4399
4400	    switch (r_type)
4401	      {
4402	      default:
4403	      case R_IA64_LTOFF_TPREL22:
4404		if (!dynamic_symbol_p)
4405		  {
4406		    if (elf_hash_table (info)->tls_sec == NULL)
4407		      goto missing_tls_sec;
4408		    if (!bfd_link_pic (info))
4409		      value -= elfNN_ia64_tprel_base (info);
4410		    else
4411		      {
4412			r_addend += value - elfNN_ia64_dtprel_base (info);
4413			dynindx = 0;
4414		      }
4415		  }
4416		got_r_type = R_IA64_TPREL64LSB;
4417		break;
4418	      case R_IA64_LTOFF_DTPMOD22:
4419		if (!dynamic_symbol_p && !bfd_link_pic (info))
4420		  value = 1;
4421		got_r_type = R_IA64_DTPMOD64LSB;
4422		break;
4423	      case R_IA64_LTOFF_DTPREL22:
4424		if (!dynamic_symbol_p)
4425		  {
4426		    if (elf_hash_table (info)->tls_sec == NULL)
4427		      goto missing_tls_sec;
4428		    value -= elfNN_ia64_dtprel_base (info);
4429		  }
4430		got_r_type = R_IA64_DTPRELNNLSB;
4431		break;
4432	      }
4433	    dyn_i = get_dyn_sym_info (ia64_info, h, input_bfd, rel, FALSE);
4434	    value = set_got_entry (input_bfd, info, dyn_i, dynindx, r_addend,
4435				   value, got_r_type);
4436	    value -= gp_val;
4437	    r = ia64_elf_install_value (hit_addr, value, r_type);
4438	  }
4439	  break;
4440
4441	default:
4442	  r = bfd_reloc_notsupported;
4443	  break;
4444	}
4445
4446      switch (r)
4447	{
4448	case bfd_reloc_ok:
4449	  break;
4450
4451	case bfd_reloc_undefined:
4452	  /* This can happen for global table relative relocs if
4453	     __gp is undefined.  This is a panic situation so we
4454	     don't try to continue.  */
4455	  (*info->callbacks->undefined_symbol)
4456	    (info, "__gp", input_bfd, input_section, rel->r_offset, 1);
4457	  return FALSE;
4458
4459	case bfd_reloc_notsupported:
4460	  {
4461	    const char *name;
4462
4463	    if (h)
4464	      name = h->root.root.string;
4465	    else
4466	      name = bfd_elf_sym_name (input_bfd, symtab_hdr, sym,
4467				       sym_sec);
4468	    (*info->callbacks->warning) (info, _("unsupported reloc"),
4469					 name, input_bfd,
4470					 input_section, rel->r_offset);
4471	    ret_val = FALSE;
4472	  }
4473	  break;
4474
4475	case bfd_reloc_dangerous:
4476	case bfd_reloc_outofrange:
4477	case bfd_reloc_overflow:
4478	default:
4479missing_tls_sec:
4480	  {
4481	    const char *name;
4482
4483	    if (h)
4484	      name = h->root.root.string;
4485	    else
4486	      name = bfd_elf_sym_name (input_bfd, symtab_hdr, sym,
4487				       sym_sec);
4488
4489	    switch (r_type)
4490	      {
4491	      case R_IA64_TPREL14:
4492	      case R_IA64_TPREL22:
4493	      case R_IA64_TPREL64I:
4494	      case R_IA64_DTPREL14:
4495	      case R_IA64_DTPREL22:
4496	      case R_IA64_DTPREL64I:
4497	      case R_IA64_DTPREL32LSB:
4498	      case R_IA64_DTPREL32MSB:
4499	      case R_IA64_DTPREL64LSB:
4500	      case R_IA64_DTPREL64MSB:
4501	      case R_IA64_LTOFF_TPREL22:
4502	      case R_IA64_LTOFF_DTPMOD22:
4503	      case R_IA64_LTOFF_DTPREL22:
4504		_bfd_error_handler
4505		  /* xgettext:c-format */
4506		  (_("%pB: missing TLS section for relocation %s against `%s'"
4507		     " at %#" PRIx64 " in section `%pA'."),
4508		   input_bfd, howto->name, name,
4509		   (uint64_t) rel->r_offset, input_section);
4510		break;
4511
4512	      case R_IA64_PCREL21B:
4513	      case R_IA64_PCREL21BI:
4514	      case R_IA64_PCREL21M:
4515	      case R_IA64_PCREL21F:
4516		if (is_elf_hash_table (info->hash))
4517		  {
4518		    /* Relaxtion is always performed for ELF output.
4519		       Overflow failures for those relocations mean
4520		       that the section is too big to relax.  */
4521		    _bfd_error_handler
4522		      /* xgettext:c-format */
4523		      (_("%pB: Can't relax br (%s) to `%s' at %#" PRIx64
4524			 " in section `%pA' with size %#" PRIx64
4525			 " (> 0x1000000)."),
4526		       input_bfd, howto->name, name, (uint64_t) rel->r_offset,
4527		       input_section, (uint64_t) input_section->size);
4528		    break;
4529		  }
4530		/* Fall through.  */
4531	      default:
4532		(*info->callbacks->reloc_overflow) (info,
4533						    &h->root,
4534						    name,
4535						    howto->name,
4536						    (bfd_vma) 0,
4537						    input_bfd,
4538						    input_section,
4539						    rel->r_offset);
4540		break;
4541	      }
4542
4543	    ret_val = FALSE;
4544	  }
4545	  break;
4546	}
4547    }
4548
4549  return ret_val;
4550}
4551
4552static bfd_boolean
4553elfNN_ia64_finish_dynamic_symbol (bfd *output_bfd,
4554				  struct bfd_link_info *info,
4555				  struct elf_link_hash_entry *h,
4556				  Elf_Internal_Sym *sym)
4557{
4558  struct elfNN_ia64_link_hash_table *ia64_info;
4559  struct elfNN_ia64_dyn_sym_info *dyn_i;
4560
4561  ia64_info = elfNN_ia64_hash_table (info);
4562  if (ia64_info == NULL)
4563    return FALSE;
4564
4565  dyn_i = get_dyn_sym_info (ia64_info, h, NULL, NULL, FALSE);
4566
4567  /* Fill in the PLT data, if required.  */
4568  if (dyn_i && dyn_i->want_plt)
4569    {
4570      Elf_Internal_Rela outrel;
4571      bfd_byte *loc;
4572      asection *plt_sec;
4573      bfd_vma plt_addr, pltoff_addr, gp_val, plt_index;
4574
4575      gp_val = _bfd_get_gp_value (output_bfd);
4576
4577      /* Initialize the minimal PLT entry.  */
4578
4579      plt_index = (dyn_i->plt_offset - PLT_HEADER_SIZE) / PLT_MIN_ENTRY_SIZE;
4580      plt_sec = ia64_info->root.splt;
4581      loc = plt_sec->contents + dyn_i->plt_offset;
4582
4583      memcpy (loc, plt_min_entry, PLT_MIN_ENTRY_SIZE);
4584      ia64_elf_install_value (loc, plt_index, R_IA64_IMM22);
4585      ia64_elf_install_value (loc+2, -dyn_i->plt_offset, R_IA64_PCREL21B);
4586
4587      plt_addr = (plt_sec->output_section->vma
4588		  + plt_sec->output_offset
4589		  + dyn_i->plt_offset);
4590      pltoff_addr = set_pltoff_entry (output_bfd, info, dyn_i, plt_addr, TRUE);
4591
4592      /* Initialize the FULL PLT entry, if needed.  */
4593      if (dyn_i->want_plt2)
4594	{
4595	  loc = plt_sec->contents + dyn_i->plt2_offset;
4596
4597	  memcpy (loc, plt_full_entry, PLT_FULL_ENTRY_SIZE);
4598	  ia64_elf_install_value (loc, pltoff_addr - gp_val, R_IA64_IMM22);
4599
4600	  /* Mark the symbol as undefined, rather than as defined in the
4601	     plt section.  Leave the value alone.  */
4602	  /* ??? We didn't redefine it in adjust_dynamic_symbol in the
4603	     first place.  But perhaps elflink.c did some for us.  */
4604	  if (!h->def_regular)
4605	    sym->st_shndx = SHN_UNDEF;
4606	}
4607
4608      /* Create the dynamic relocation.  */
4609      outrel.r_offset = pltoff_addr;
4610      if (bfd_little_endian (output_bfd))
4611	outrel.r_info = ELFNN_R_INFO (h->dynindx, R_IA64_IPLTLSB);
4612      else
4613	outrel.r_info = ELFNN_R_INFO (h->dynindx, R_IA64_IPLTMSB);
4614      outrel.r_addend = 0;
4615
4616      /* This is fun.  In the .IA_64.pltoff section, we've got entries
4617	 that correspond both to real PLT entries, and those that
4618	 happened to resolve to local symbols but need to be created
4619	 to satisfy @pltoff relocations.  The .rela.IA_64.pltoff
4620	 relocations for the real PLT should come at the end of the
4621	 section, so that they can be indexed by plt entry at runtime.
4622
4623	 We emitted all of the relocations for the non-PLT @pltoff
4624	 entries during relocate_section.  So we can consider the
4625	 existing sec->reloc_count to be the base of the array of
4626	 PLT relocations.  */
4627
4628      loc = ia64_info->rel_pltoff_sec->contents;
4629      loc += ((ia64_info->rel_pltoff_sec->reloc_count + plt_index)
4630	      * sizeof (ElfNN_External_Rela));
4631      bfd_elfNN_swap_reloca_out (output_bfd, &outrel, loc);
4632    }
4633
4634  /* Mark some specially defined symbols as absolute.  */
4635  if (h == ia64_info->root.hdynamic
4636      || h == ia64_info->root.hgot
4637      || h == ia64_info->root.hplt)
4638    sym->st_shndx = SHN_ABS;
4639
4640  return TRUE;
4641}
4642
4643static bfd_boolean
4644elfNN_ia64_finish_dynamic_sections (bfd *abfd,
4645				    struct bfd_link_info *info)
4646{
4647  struct elfNN_ia64_link_hash_table *ia64_info;
4648  bfd *dynobj;
4649
4650  ia64_info = elfNN_ia64_hash_table (info);
4651  if (ia64_info == NULL)
4652    return FALSE;
4653
4654  dynobj = ia64_info->root.dynobj;
4655
4656  if (ia64_info->root.dynamic_sections_created)
4657    {
4658      ElfNN_External_Dyn *dyncon, *dynconend;
4659      asection *sdyn, *sgotplt;
4660      bfd_vma gp_val;
4661
4662      sdyn = bfd_get_linker_section (dynobj, ".dynamic");
4663      sgotplt = ia64_info->root.sgotplt;
4664      BFD_ASSERT (sdyn != NULL);
4665      dyncon = (ElfNN_External_Dyn *) sdyn->contents;
4666      dynconend = (ElfNN_External_Dyn *) (sdyn->contents + sdyn->size);
4667
4668      gp_val = _bfd_get_gp_value (abfd);
4669
4670      for (; dyncon < dynconend; dyncon++)
4671	{
4672	  Elf_Internal_Dyn dyn;
4673
4674	  bfd_elfNN_swap_dyn_in (dynobj, dyncon, &dyn);
4675
4676	  switch (dyn.d_tag)
4677	    {
4678	    case DT_PLTGOT:
4679	      dyn.d_un.d_ptr = gp_val;
4680	      break;
4681
4682	    case DT_PLTRELSZ:
4683	      dyn.d_un.d_val = (ia64_info->minplt_entries
4684				* sizeof (ElfNN_External_Rela));
4685	      break;
4686
4687	    case DT_JMPREL:
4688	      /* See the comment above in finish_dynamic_symbol.  */
4689	      dyn.d_un.d_ptr = (ia64_info->rel_pltoff_sec->output_section->vma
4690				+ ia64_info->rel_pltoff_sec->output_offset
4691				+ (ia64_info->rel_pltoff_sec->reloc_count
4692				   * sizeof (ElfNN_External_Rela)));
4693	      break;
4694
4695	    case DT_IA_64_PLT_RESERVE:
4696	      dyn.d_un.d_ptr = (sgotplt->output_section->vma
4697				+ sgotplt->output_offset);
4698	      break;
4699	    }
4700
4701	  bfd_elfNN_swap_dyn_out (abfd, &dyn, dyncon);
4702	}
4703
4704      /* Initialize the PLT0 entry.  */
4705      if (ia64_info->root.splt)
4706	{
4707	  bfd_byte *loc = ia64_info->root.splt->contents;
4708	  bfd_vma pltres;
4709
4710	  memcpy (loc, plt_header, PLT_HEADER_SIZE);
4711
4712	  pltres = (sgotplt->output_section->vma
4713		    + sgotplt->output_offset
4714		    - gp_val);
4715
4716	  ia64_elf_install_value (loc+1, pltres, R_IA64_GPREL22);
4717	}
4718    }
4719
4720  return TRUE;
4721}
4722
4723/* ELF file flag handling:  */
4724
4725/* Function to keep IA-64 specific file flags.  */
4726static bfd_boolean
4727elfNN_ia64_set_private_flags (bfd *abfd, flagword flags)
4728{
4729  BFD_ASSERT (!elf_flags_init (abfd)
4730	      || elf_elfheader (abfd)->e_flags == flags);
4731
4732  elf_elfheader (abfd)->e_flags = flags;
4733  elf_flags_init (abfd) = TRUE;
4734  return TRUE;
4735}
4736
4737/* Merge backend specific data from an object file to the output
4738   object file when linking.  */
4739
4740static bfd_boolean
4741elfNN_ia64_merge_private_bfd_data (bfd *ibfd, struct bfd_link_info *info)
4742{
4743  bfd *obfd = info->output_bfd;
4744  flagword out_flags;
4745  flagword in_flags;
4746  bfd_boolean ok = TRUE;
4747
4748  if (!is_ia64_elf (ibfd) || !is_ia64_elf (obfd))
4749    return TRUE;
4750
4751  in_flags  = elf_elfheader (ibfd)->e_flags;
4752  out_flags = elf_elfheader (obfd)->e_flags;
4753
4754  if (! elf_flags_init (obfd))
4755    {
4756      elf_flags_init (obfd) = TRUE;
4757      elf_elfheader (obfd)->e_flags = in_flags;
4758
4759      if (bfd_get_arch (obfd) == bfd_get_arch (ibfd)
4760	  && bfd_get_arch_info (obfd)->the_default)
4761	{
4762	  return bfd_set_arch_mach (obfd, bfd_get_arch (ibfd),
4763				    bfd_get_mach (ibfd));
4764	}
4765
4766      return TRUE;
4767    }
4768
4769  /* Check flag compatibility.  */
4770  if (in_flags == out_flags)
4771    return TRUE;
4772
4773  /* Output has EF_IA_64_REDUCEDFP set only if all inputs have it set.  */
4774  if (!(in_flags & EF_IA_64_REDUCEDFP) && (out_flags & EF_IA_64_REDUCEDFP))
4775    elf_elfheader (obfd)->e_flags &= ~EF_IA_64_REDUCEDFP;
4776
4777  if ((in_flags & EF_IA_64_TRAPNIL) != (out_flags & EF_IA_64_TRAPNIL))
4778    {
4779      _bfd_error_handler
4780	(_("%pB: linking trap-on-NULL-dereference with non-trapping files"),
4781	 ibfd);
4782
4783      bfd_set_error (bfd_error_bad_value);
4784      ok = FALSE;
4785    }
4786  if ((in_flags & EF_IA_64_BE) != (out_flags & EF_IA_64_BE))
4787    {
4788      _bfd_error_handler
4789	(_("%pB: linking big-endian files with little-endian files"),
4790	 ibfd);
4791
4792      bfd_set_error (bfd_error_bad_value);
4793      ok = FALSE;
4794    }
4795  if ((in_flags & EF_IA_64_ABI64) != (out_flags & EF_IA_64_ABI64))
4796    {
4797      _bfd_error_handler
4798	(_("%pB: linking 64-bit files with 32-bit files"),
4799	 ibfd);
4800
4801      bfd_set_error (bfd_error_bad_value);
4802      ok = FALSE;
4803    }
4804  if ((in_flags & EF_IA_64_CONS_GP) != (out_flags & EF_IA_64_CONS_GP))
4805    {
4806      _bfd_error_handler
4807	(_("%pB: linking constant-gp files with non-constant-gp files"),
4808	 ibfd);
4809
4810      bfd_set_error (bfd_error_bad_value);
4811      ok = FALSE;
4812    }
4813  if ((in_flags & EF_IA_64_NOFUNCDESC_CONS_GP)
4814      != (out_flags & EF_IA_64_NOFUNCDESC_CONS_GP))
4815    {
4816      _bfd_error_handler
4817	(_("%pB: linking auto-pic files with non-auto-pic files"),
4818	 ibfd);
4819
4820      bfd_set_error (bfd_error_bad_value);
4821      ok = FALSE;
4822    }
4823
4824  return ok;
4825}
4826
4827static bfd_boolean
4828elfNN_ia64_print_private_bfd_data (bfd *abfd, void * ptr)
4829{
4830  FILE *file = (FILE *) ptr;
4831  flagword flags = elf_elfheader (abfd)->e_flags;
4832
4833  BFD_ASSERT (abfd != NULL && ptr != NULL);
4834
4835  fprintf (file, "private flags = %s%s%s%s%s%s%s%s\n",
4836	   (flags & EF_IA_64_TRAPNIL) ? "TRAPNIL, " : "",
4837	   (flags & EF_IA_64_EXT) ? "EXT, " : "",
4838	   (flags & EF_IA_64_BE) ? "BE, " : "LE, ",
4839	   (flags & EF_IA_64_REDUCEDFP) ? "REDUCEDFP, " : "",
4840	   (flags & EF_IA_64_CONS_GP) ? "CONS_GP, " : "",
4841	   (flags & EF_IA_64_NOFUNCDESC_CONS_GP) ? "NOFUNCDESC_CONS_GP, " : "",
4842	   (flags & EF_IA_64_ABSOLUTE) ? "ABSOLUTE, " : "",
4843	   (flags & EF_IA_64_ABI64) ? "ABI64" : "ABI32");
4844
4845  _bfd_elf_print_private_bfd_data (abfd, ptr);
4846  return TRUE;
4847}
4848
4849static enum elf_reloc_type_class
4850elfNN_ia64_reloc_type_class (const struct bfd_link_info *info ATTRIBUTE_UNUSED,
4851			     const asection *rel_sec ATTRIBUTE_UNUSED,
4852			     const Elf_Internal_Rela *rela)
4853{
4854  switch ((int) ELFNN_R_TYPE (rela->r_info))
4855    {
4856    case R_IA64_REL32MSB:
4857    case R_IA64_REL32LSB:
4858    case R_IA64_REL64MSB:
4859    case R_IA64_REL64LSB:
4860      return reloc_class_relative;
4861    case R_IA64_IPLTMSB:
4862    case R_IA64_IPLTLSB:
4863      return reloc_class_plt;
4864    case R_IA64_COPY:
4865      return reloc_class_copy;
4866    default:
4867      return reloc_class_normal;
4868    }
4869}
4870
4871static const struct bfd_elf_special_section elfNN_ia64_special_sections[] =
4872{
4873  { STRING_COMMA_LEN (".sbss"),	 -1, SHT_NOBITS,   SHF_ALLOC + SHF_WRITE + SHF_IA_64_SHORT },
4874  { STRING_COMMA_LEN (".sdata"), -1, SHT_PROGBITS, SHF_ALLOC + SHF_WRITE + SHF_IA_64_SHORT },
4875  { NULL,		     0,	  0, 0,		   0 }
4876};
4877
4878static bfd_boolean
4879elfNN_ia64_object_p (bfd *abfd)
4880{
4881  asection *sec;
4882  asection *group, *unwi, *unw;
4883  flagword flags;
4884  const char *name;
4885  char *unwi_name, *unw_name;
4886  bfd_size_type amt;
4887
4888  if (abfd->flags & DYNAMIC)
4889    return TRUE;
4890
4891  /* Flags for fake group section.  */
4892  flags = (SEC_LINKER_CREATED | SEC_GROUP | SEC_LINK_ONCE
4893	   | SEC_EXCLUDE);
4894
4895  /* We add a fake section group for each .gnu.linkonce.t.* section,
4896     which isn't in a section group, and its unwind sections.  */
4897  for (sec = abfd->sections; sec != NULL; sec = sec->next)
4898    {
4899      if (elf_sec_group (sec) == NULL
4900	  && ((sec->flags & (SEC_LINK_ONCE | SEC_CODE | SEC_GROUP))
4901	      == (SEC_LINK_ONCE | SEC_CODE))
4902	  && CONST_STRNEQ (sec->name, ".gnu.linkonce.t."))
4903	{
4904	  name = sec->name + 16;
4905
4906	  amt = strlen (name) + sizeof (".gnu.linkonce.ia64unwi.");
4907	  unwi_name = bfd_alloc (abfd, amt);
4908	  if (!unwi_name)
4909	    return FALSE;
4910
4911	  strcpy (stpcpy (unwi_name, ".gnu.linkonce.ia64unwi."), name);
4912	  unwi = bfd_get_section_by_name (abfd, unwi_name);
4913
4914	  amt = strlen (name) + sizeof (".gnu.linkonce.ia64unw.");
4915	  unw_name = bfd_alloc (abfd, amt);
4916	  if (!unw_name)
4917	    return FALSE;
4918
4919	  strcpy (stpcpy (unw_name, ".gnu.linkonce.ia64unw."), name);
4920	  unw = bfd_get_section_by_name (abfd, unw_name);
4921
4922	  /* We need to create a fake group section for it and its
4923	     unwind sections.  */
4924	  group = bfd_make_section_anyway_with_flags (abfd, name,
4925						      flags);
4926	  if (group == NULL)
4927	    return FALSE;
4928
4929	  /* Move the fake group section to the beginning.  */
4930	  bfd_section_list_remove (abfd, group);
4931	  bfd_section_list_prepend (abfd, group);
4932
4933	  elf_next_in_group (group) = sec;
4934
4935	  elf_group_name (sec) = name;
4936	  elf_next_in_group (sec) = sec;
4937	  elf_sec_group (sec) = group;
4938
4939	  if (unwi)
4940	    {
4941	      elf_group_name (unwi) = name;
4942	      elf_next_in_group (unwi) = sec;
4943	      elf_next_in_group (sec) = unwi;
4944	      elf_sec_group (unwi) = group;
4945	    }
4946
4947	   if (unw)
4948	     {
4949	       elf_group_name (unw) = name;
4950	       if (unwi)
4951		 {
4952		   elf_next_in_group (unw) = elf_next_in_group (unwi);
4953		   elf_next_in_group (unwi) = unw;
4954		 }
4955	       else
4956		 {
4957		   elf_next_in_group (unw) = sec;
4958		   elf_next_in_group (sec) = unw;
4959		 }
4960	       elf_sec_group (unw) = group;
4961	     }
4962
4963	   /* Fake SHT_GROUP section header.  */
4964	  elf_section_data (group)->this_hdr.bfd_section = group;
4965	  elf_section_data (group)->this_hdr.sh_type = SHT_GROUP;
4966	}
4967    }
4968  return TRUE;
4969}
4970
4971static bfd_boolean
4972elfNN_ia64_hpux_vec (const bfd_target *vec)
4973{
4974  extern const bfd_target ia64_elfNN_hpux_be_vec;
4975  return (vec == &ia64_elfNN_hpux_be_vec);
4976}
4977
4978static bfd_boolean
4979elfNN_hpux_init_file_header (bfd *abfd, struct bfd_link_info *info)
4980{
4981  Elf_Internal_Ehdr *i_ehdrp;
4982
4983  if (!_bfd_elf_init_file_header (abfd, info))
4984    return FALSE;
4985
4986  i_ehdrp = elf_elfheader (abfd);
4987  i_ehdrp->e_ident[EI_OSABI] = get_elf_backend_data (abfd)->elf_osabi;
4988  i_ehdrp->e_ident[EI_ABIVERSION] = 1;
4989  return TRUE;
4990}
4991
4992static bfd_boolean
4993elfNN_hpux_backend_section_from_bfd_section (bfd *abfd ATTRIBUTE_UNUSED,
4994					     asection *sec, int *retval)
4995{
4996  if (bfd_is_com_section (sec))
4997    {
4998      *retval = SHN_IA_64_ANSI_COMMON;
4999      return TRUE;
5000    }
5001  return FALSE;
5002}
5003
5004static void
5005elfNN_hpux_backend_symbol_processing (bfd *abfd ATTRIBUTE_UNUSED,
5006				      asymbol *asym)
5007{
5008  elf_symbol_type *elfsym = (elf_symbol_type *) asym;
5009
5010  switch (elfsym->internal_elf_sym.st_shndx)
5011    {
5012    case SHN_IA_64_ANSI_COMMON:
5013      asym->section = bfd_com_section_ptr;
5014      asym->value = elfsym->internal_elf_sym.st_size;
5015      asym->flags &= ~BSF_GLOBAL;
5016      break;
5017    }
5018}
5019
5020#define TARGET_LITTLE_SYM		ia64_elfNN_le_vec
5021#define TARGET_LITTLE_NAME		"elfNN-ia64-little"
5022#define TARGET_BIG_SYM			ia64_elfNN_be_vec
5023#define TARGET_BIG_NAME			"elfNN-ia64-big"
5024#define ELF_ARCH			bfd_arch_ia64
5025#define ELF_TARGET_ID			IA64_ELF_DATA
5026#define ELF_MACHINE_CODE		EM_IA_64
5027#define ELF_MACHINE_ALT1		1999	/* EAS2.3 */
5028#define ELF_MACHINE_ALT2		1998	/* EAS2.2 */
5029#define ELF_MAXPAGESIZE			0x10000	/* 64KB */
5030#define ELF_COMMONPAGESIZE		0x4000	/* 16KB */
5031
5032#define elf_backend_section_from_shdr \
5033	elfNN_ia64_section_from_shdr
5034#define elf_backend_section_flags \
5035	elfNN_ia64_section_flags
5036#define elf_backend_fake_sections \
5037	elfNN_ia64_fake_sections
5038#define elf_backend_final_write_processing \
5039	elfNN_ia64_final_write_processing
5040#define elf_backend_add_symbol_hook \
5041	elfNN_ia64_add_symbol_hook
5042#define elf_backend_additional_program_headers \
5043	elfNN_ia64_additional_program_headers
5044#define elf_backend_modify_segment_map \
5045	elfNN_ia64_modify_segment_map
5046#define elf_backend_modify_headers \
5047	elfNN_ia64_modify_headers
5048#define elf_info_to_howto \
5049	elfNN_ia64_info_to_howto
5050
5051#define bfd_elfNN_bfd_reloc_type_lookup \
5052	ia64_elf_reloc_type_lookup
5053#define bfd_elfNN_bfd_reloc_name_lookup \
5054	ia64_elf_reloc_name_lookup
5055#define bfd_elfNN_bfd_is_local_label_name \
5056	elfNN_ia64_is_local_label_name
5057#define bfd_elfNN_bfd_relax_section \
5058	elfNN_ia64_relax_section
5059
5060#define elf_backend_object_p \
5061	elfNN_ia64_object_p
5062
5063/* Stuff for the BFD linker: */
5064#define bfd_elfNN_bfd_link_hash_table_create \
5065	elfNN_ia64_hash_table_create
5066#define elf_backend_create_dynamic_sections \
5067	elfNN_ia64_create_dynamic_sections
5068#define elf_backend_check_relocs \
5069	elfNN_ia64_check_relocs
5070#define elf_backend_adjust_dynamic_symbol \
5071	elfNN_ia64_adjust_dynamic_symbol
5072#define elf_backend_size_dynamic_sections \
5073	elfNN_ia64_size_dynamic_sections
5074#define elf_backend_omit_section_dynsym \
5075	_bfd_elf_omit_section_dynsym_all
5076#define elf_backend_relocate_section \
5077	elfNN_ia64_relocate_section
5078#define elf_backend_finish_dynamic_symbol \
5079	elfNN_ia64_finish_dynamic_symbol
5080#define elf_backend_finish_dynamic_sections \
5081	elfNN_ia64_finish_dynamic_sections
5082#define bfd_elfNN_bfd_final_link \
5083	elfNN_ia64_final_link
5084
5085#define bfd_elfNN_bfd_merge_private_bfd_data \
5086	elfNN_ia64_merge_private_bfd_data
5087#define bfd_elfNN_bfd_set_private_flags \
5088	elfNN_ia64_set_private_flags
5089#define bfd_elfNN_bfd_print_private_bfd_data \
5090	elfNN_ia64_print_private_bfd_data
5091
5092#define elf_backend_plt_readonly	1
5093#define elf_backend_can_gc_sections	1
5094#define elf_backend_want_plt_sym	0
5095#define elf_backend_plt_alignment	5
5096#define elf_backend_got_header_size	0
5097#define elf_backend_want_got_plt	1
5098#define elf_backend_may_use_rel_p	1
5099#define elf_backend_may_use_rela_p	1
5100#define elf_backend_default_use_rela_p	1
5101#define elf_backend_want_dynbss		0
5102#define elf_backend_copy_indirect_symbol elfNN_ia64_hash_copy_indirect
5103#define elf_backend_hide_symbol		elfNN_ia64_hash_hide_symbol
5104#define elf_backend_fixup_symbol	_bfd_elf_link_hash_fixup_symbol
5105#define elf_backend_reloc_type_class	elfNN_ia64_reloc_type_class
5106#define elf_backend_rela_normal		1
5107#define elf_backend_dtrel_excludes_plt	1
5108#define elf_backend_special_sections	elfNN_ia64_special_sections
5109#define elf_backend_default_execstack	0
5110
5111/* FIXME: PR 290: The Intel C compiler generates SHT_IA_64_UNWIND with
5112   SHF_LINK_ORDER. But it doesn't set the sh_link or sh_info fields.
5113   We don't want to flood users with so many error messages. We turn
5114   off the warning for now. It will be turned on later when the Intel
5115   compiler is fixed.   */
5116#define elf_backend_link_order_error_handler NULL
5117
5118#include "elfNN-target.h"
5119
5120/* HPUX-specific vectors.  */
5121
5122#undef  TARGET_LITTLE_SYM
5123#undef  TARGET_LITTLE_NAME
5124#undef  TARGET_BIG_SYM
5125#define TARGET_BIG_SYM			ia64_elfNN_hpux_be_vec
5126#undef	TARGET_BIG_NAME
5127#define TARGET_BIG_NAME			"elfNN-ia64-hpux-big"
5128
5129/* These are HP-UX specific functions.  */
5130
5131#undef  elf_backend_init_file_header
5132#define elf_backend_init_file_header elfNN_hpux_init_file_header
5133
5134#undef  elf_backend_section_from_bfd_section
5135#define elf_backend_section_from_bfd_section elfNN_hpux_backend_section_from_bfd_section
5136
5137#undef elf_backend_symbol_processing
5138#define elf_backend_symbol_processing elfNN_hpux_backend_symbol_processing
5139
5140#undef  elf_backend_want_p_paddr_set_to_zero
5141#define elf_backend_want_p_paddr_set_to_zero 1
5142
5143#undef ELF_COMMONPAGESIZE
5144#undef ELF_OSABI
5145#define ELF_OSABI			ELFOSABI_HPUX
5146
5147#undef  elfNN_bed
5148#define elfNN_bed elfNN_ia64_hpux_bed
5149
5150#include "elfNN-target.h"
5151