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