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