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