This lot mainly cleans up `comparison between signed and unsigned' gcc
[external/binutils.git] / bfd / elflink.h
1 /* ELF linker support.
2    Copyright 1995, 1996, 1997, 1998, 1999 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 2 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., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.  */
19
20 /* ELF linker code.  */
21
22 /* This struct is used to pass information to routines called via
23    elf_link_hash_traverse which must return failure.  */
24
25 struct elf_info_failed
26 {
27   boolean failed;
28   struct bfd_link_info *info;
29 };
30
31 static boolean elf_link_add_object_symbols
32   PARAMS ((bfd *, struct bfd_link_info *));
33 static boolean elf_link_add_archive_symbols
34   PARAMS ((bfd *, struct bfd_link_info *));
35 static boolean elf_merge_symbol
36   PARAMS ((bfd *, struct bfd_link_info *, const char *, Elf_Internal_Sym *,
37            asection **, bfd_vma *, struct elf_link_hash_entry **,
38            boolean *, boolean *, boolean *));
39 static boolean elf_export_symbol
40   PARAMS ((struct elf_link_hash_entry *, PTR));
41 static boolean elf_fix_symbol_flags
42   PARAMS ((struct elf_link_hash_entry *, struct elf_info_failed *));
43 static boolean elf_adjust_dynamic_symbol
44   PARAMS ((struct elf_link_hash_entry *, PTR));
45 static boolean elf_link_find_version_dependencies
46   PARAMS ((struct elf_link_hash_entry *, PTR));
47 static boolean elf_link_find_version_dependencies
48   PARAMS ((struct elf_link_hash_entry *, PTR));
49 static boolean elf_link_assign_sym_version
50   PARAMS ((struct elf_link_hash_entry *, PTR));
51 static boolean elf_collect_hash_codes
52   PARAMS ((struct elf_link_hash_entry *, PTR));
53 static boolean elf_link_read_relocs_from_section 
54   PARAMS ((bfd *, Elf_Internal_Shdr *, PTR, Elf_Internal_Rela *));
55 static void elf_link_output_relocs
56   PARAMS ((bfd *, asection *, Elf_Internal_Shdr *, Elf_Internal_Rela *));
57 static boolean elf_link_size_reloc_section
58   PARAMS ((bfd *, Elf_Internal_Shdr *, asection *));
59 static void elf_link_adjust_relocs 
60   PARAMS ((bfd *, Elf_Internal_Shdr *, unsigned int, 
61            struct elf_link_hash_entry **));
62
63 /* Given an ELF BFD, add symbols to the global hash table as
64    appropriate.  */
65
66 boolean
67 elf_bfd_link_add_symbols (abfd, info)
68      bfd *abfd;
69      struct bfd_link_info *info;
70 {
71   switch (bfd_get_format (abfd))
72     {
73     case bfd_object:
74       return elf_link_add_object_symbols (abfd, info);
75     case bfd_archive:
76       return elf_link_add_archive_symbols (abfd, info);
77     default:
78       bfd_set_error (bfd_error_wrong_format);
79       return false;
80     }
81 }
82 \f
83 /* Return true iff this is a non-common definition of a symbol.  */
84 static boolean
85 is_global_symbol_definition (abfd, sym)
86      bfd * abfd;
87      Elf_Internal_Sym * sym;
88 {
89   /* Local symbols do not count, but target specific ones might.  */
90   if (ELF_ST_BIND (sym->st_info) != STB_GLOBAL
91       && ELF_ST_BIND (sym->st_info) < STB_LOOS)
92     return false;
93
94   /* If the section is undefined, then so is the symbol.  */
95   if (sym->st_shndx == SHN_UNDEF)
96     return false;
97   
98   /* If the symbol is defined in the common section, then
99      it is a common definition and so does not count.  */
100   if (sym->st_shndx == SHN_COMMON)
101     return false;
102
103   /* If the symbol is in a target specific section then we
104      must rely upon the backend to tell us what it is.  */
105   if (sym->st_shndx >= SHN_LORESERVE && sym->st_shndx < SHN_ABS)
106     /* FIXME - this function is not coded yet:
107        
108        return _bfd_is_global_symbol_definition (abfd, sym);
109        
110        Instead for now assume that the definition is not global,
111        Even if this is wrong, at least the linker will behave
112        in the same way that it used to do.  */
113     return false;
114       
115   return true;
116 }
117
118
119 /* Search the symbol table of the archive element of the archive ABFD
120    whoes archove map contains a mention of SYMDEF, and determine if
121    the symbol is defined in this element.  */
122 static boolean
123 elf_link_is_defined_archive_symbol (abfd, symdef)
124      bfd * abfd;
125      carsym * symdef;
126 {
127   Elf_Internal_Shdr * hdr;
128   Elf_External_Sym *  esym;
129   Elf_External_Sym *  esymend;
130   Elf_External_Sym *  buf = NULL;
131   size_t symcount;
132   size_t extsymcount;
133   size_t extsymoff;
134   boolean result = false;
135   
136   abfd = _bfd_get_elt_at_filepos (abfd, symdef->file_offset);
137   if (abfd == (bfd *) NULL)
138     return false;
139
140   if (! bfd_check_format (abfd, bfd_object))
141     return false;
142
143   /* If we have already included the element containing this symbol in the
144      link then we do not need to include it again.  Just claim that any symbol
145      it contains is not a definition, so that our caller will not decide to
146      (re)include this element.  */
147   if (abfd->archive_pass)
148     return false;
149   
150   /* Select the appropriate symbol table.  */
151   if ((abfd->flags & DYNAMIC) == 0 || elf_dynsymtab (abfd) == 0)
152     hdr = &elf_tdata (abfd)->symtab_hdr;
153   else
154     hdr = &elf_tdata (abfd)->dynsymtab_hdr;
155
156   symcount = hdr->sh_size / sizeof (Elf_External_Sym);
157
158   /* The sh_info field of the symtab header tells us where the
159      external symbols start.  We don't care about the local symbols.  */
160   if (elf_bad_symtab (abfd))
161     {
162       extsymcount = symcount;
163       extsymoff = 0;
164     }
165   else
166     {
167       extsymcount = symcount - hdr->sh_info;
168       extsymoff = hdr->sh_info;
169     }
170
171   buf = ((Elf_External_Sym *)
172          bfd_malloc (extsymcount * sizeof (Elf_External_Sym)));
173   if (buf == NULL && extsymcount != 0)
174     return false;
175
176   /* Read in the symbol table.
177      FIXME:  This ought to be cached somewhere.  */
178   if (bfd_seek (abfd,
179                 hdr->sh_offset + extsymoff * sizeof (Elf_External_Sym),
180                 SEEK_SET) != 0
181       || (bfd_read ((PTR) buf, sizeof (Elf_External_Sym), extsymcount, abfd)
182           != extsymcount * sizeof (Elf_External_Sym)))
183     {
184       free (buf);
185       return false;
186     }
187
188   /* Scan the symbol table looking for SYMDEF.  */
189   esymend = buf + extsymcount;
190   for (esym = buf;
191        esym < esymend;
192        esym++)
193     {
194       Elf_Internal_Sym sym;
195       const char * name;
196
197       elf_swap_symbol_in (abfd, esym, & sym);
198
199       name = bfd_elf_string_from_elf_section (abfd, hdr->sh_link, sym.st_name);
200       if (name == (const char *) NULL)
201         break;
202
203       if (strcmp (name, symdef->name) == 0)
204         {
205           result = is_global_symbol_definition (abfd, & sym);
206           break;
207         }
208     }
209
210   free (buf);
211   
212   return result;
213 }
214 \f
215
216 /* Add symbols from an ELF archive file to the linker hash table.  We
217    don't use _bfd_generic_link_add_archive_symbols because of a
218    problem which arises on UnixWare.  The UnixWare libc.so is an
219    archive which includes an entry libc.so.1 which defines a bunch of
220    symbols.  The libc.so archive also includes a number of other
221    object files, which also define symbols, some of which are the same
222    as those defined in libc.so.1.  Correct linking requires that we
223    consider each object file in turn, and include it if it defines any
224    symbols we need.  _bfd_generic_link_add_archive_symbols does not do
225    this; it looks through the list of undefined symbols, and includes
226    any object file which defines them.  When this algorithm is used on
227    UnixWare, it winds up pulling in libc.so.1 early and defining a
228    bunch of symbols.  This means that some of the other objects in the
229    archive are not included in the link, which is incorrect since they
230    precede libc.so.1 in the archive.
231
232    Fortunately, ELF archive handling is simpler than that done by
233    _bfd_generic_link_add_archive_symbols, which has to allow for a.out
234    oddities.  In ELF, if we find a symbol in the archive map, and the
235    symbol is currently undefined, we know that we must pull in that
236    object file.
237
238    Unfortunately, we do have to make multiple passes over the symbol
239    table until nothing further is resolved.  */
240
241 static boolean
242 elf_link_add_archive_symbols (abfd, info)
243      bfd *abfd;
244      struct bfd_link_info *info;
245 {
246   symindex c;
247   boolean *defined = NULL;
248   boolean *included = NULL;
249   carsym *symdefs;
250   boolean loop;
251
252   if (! bfd_has_map (abfd))
253     {
254       /* An empty archive is a special case.  */
255       if (bfd_openr_next_archived_file (abfd, (bfd *) NULL) == NULL)
256         return true;
257       bfd_set_error (bfd_error_no_armap);
258       return false;
259     }
260
261   /* Keep track of all symbols we know to be already defined, and all
262      files we know to be already included.  This is to speed up the
263      second and subsequent passes.  */
264   c = bfd_ardata (abfd)->symdef_count;
265   if (c == 0)
266     return true;
267   defined = (boolean *) bfd_malloc (c * sizeof (boolean));
268   included = (boolean *) bfd_malloc (c * sizeof (boolean));
269   if (defined == (boolean *) NULL || included == (boolean *) NULL)
270     goto error_return;
271   memset (defined, 0, c * sizeof (boolean));
272   memset (included, 0, c * sizeof (boolean));
273
274   symdefs = bfd_ardata (abfd)->symdefs;
275
276   do
277     {
278       file_ptr last;
279       symindex i;
280       carsym *symdef;
281       carsym *symdefend;
282
283       loop = false;
284       last = -1;
285
286       symdef = symdefs;
287       symdefend = symdef + c;
288       for (i = 0; symdef < symdefend; symdef++, i++)
289         {
290           struct elf_link_hash_entry *h;
291           bfd *element;
292           struct bfd_link_hash_entry *undefs_tail;
293           symindex mark;
294
295           if (defined[i] || included[i])
296             continue;
297           if (symdef->file_offset == last)
298             {
299               included[i] = true;
300               continue;
301             }
302
303           h = elf_link_hash_lookup (elf_hash_table (info), symdef->name,
304                                     false, false, false);
305
306           if (h == NULL)
307             {
308               char *p, *copy;
309
310               /* If this is a default version (the name contains @@),
311                  look up the symbol again without the version.  The
312                  effect is that references to the symbol without the
313                  version will be matched by the default symbol in the
314                  archive.  */
315
316               p = strchr (symdef->name, ELF_VER_CHR);
317               if (p == NULL || p[1] != ELF_VER_CHR)
318                 continue;
319
320               copy = bfd_alloc (abfd, p - symdef->name + 1);
321               if (copy == NULL)
322                 goto error_return;
323               memcpy (copy, symdef->name, p - symdef->name);
324               copy[p - symdef->name] = '\0';
325
326               h = elf_link_hash_lookup (elf_hash_table (info), copy,
327                                         false, false, false);
328
329               bfd_release (abfd, copy);
330             }
331
332           if (h == NULL)
333             continue;
334
335           if (h->root.type == bfd_link_hash_common)
336             {
337               /* We currently have a common symbol.  The archive map contains
338                  a reference to this symbol, so we may want to include it.  We
339                  only want to include it however, if this archive element
340                  contains a definition of the symbol, not just another common
341                  declaration of it.
342
343                  Unfortunately some archivers (including GNU ar) will put
344                  declarations of common symbols into their archive maps, as
345                  well as real definitions, so we cannot just go by the archive
346                  map alone.  Instead we must read in the element's symbol
347                  table and check that to see what kind of symbol definition
348                  this is.  */
349               if (! elf_link_is_defined_archive_symbol (abfd, symdef))
350                 continue;
351             }
352           else if (h->root.type != bfd_link_hash_undefined)
353             {
354               if (h->root.type != bfd_link_hash_undefweak)
355                 defined[i] = true;
356               continue;
357             }
358
359           /* We need to include this archive member.  */
360
361           element = _bfd_get_elt_at_filepos (abfd, symdef->file_offset);
362           if (element == (bfd *) NULL)
363             goto error_return;
364
365           if (! bfd_check_format (element, bfd_object))
366             goto error_return;
367
368           /* Doublecheck that we have not included this object
369              already--it should be impossible, but there may be
370              something wrong with the archive.  */
371           if (element->archive_pass != 0)
372             {
373               bfd_set_error (bfd_error_bad_value);
374               goto error_return;
375             }
376           element->archive_pass = 1;
377
378           undefs_tail = info->hash->undefs_tail;
379
380           if (! (*info->callbacks->add_archive_element) (info, element,
381                                                          symdef->name))
382             goto error_return;
383           if (! elf_link_add_object_symbols (element, info))
384             goto error_return;
385
386           /* If there are any new undefined symbols, we need to make
387              another pass through the archive in order to see whether
388              they can be defined.  FIXME: This isn't perfect, because
389              common symbols wind up on undefs_tail and because an
390              undefined symbol which is defined later on in this pass
391              does not require another pass.  This isn't a bug, but it
392              does make the code less efficient than it could be.  */
393           if (undefs_tail != info->hash->undefs_tail)
394             loop = true;
395
396           /* Look backward to mark all symbols from this object file
397              which we have already seen in this pass.  */
398           mark = i;
399           do
400             {
401               included[mark] = true;
402               if (mark == 0)
403                 break;
404               --mark;
405             }
406           while (symdefs[mark].file_offset == symdef->file_offset);
407
408           /* We mark subsequent symbols from this object file as we go
409              on through the loop.  */
410           last = symdef->file_offset;
411         }
412     }
413   while (loop);
414
415   free (defined);
416   free (included);
417
418   return true;
419
420  error_return:
421   if (defined != (boolean *) NULL)
422     free (defined);
423   if (included != (boolean *) NULL)
424     free (included);
425   return false;
426 }
427
428 /* This function is called when we want to define a new symbol.  It
429    handles the various cases which arise when we find a definition in
430    a dynamic object, or when there is already a definition in a
431    dynamic object.  The new symbol is described by NAME, SYM, PSEC,
432    and PVALUE.  We set SYM_HASH to the hash table entry.  We set
433    OVERRIDE if the old symbol is overriding a new definition.  We set
434    TYPE_CHANGE_OK if it is OK for the type to change.  We set
435    SIZE_CHANGE_OK if it is OK for the size to change.  By OK to
436    change, we mean that we shouldn't warn if the type or size does
437    change.  */
438
439 static boolean
440 elf_merge_symbol (abfd, info, name, sym, psec, pvalue, sym_hash,
441                   override, type_change_ok, size_change_ok)
442      bfd *abfd;
443      struct bfd_link_info *info;
444      const char *name;
445      Elf_Internal_Sym *sym;
446      asection **psec;
447      bfd_vma *pvalue;
448      struct elf_link_hash_entry **sym_hash;
449      boolean *override;
450      boolean *type_change_ok;
451      boolean *size_change_ok;
452 {
453   asection *sec;
454   struct elf_link_hash_entry *h;
455   int bind;
456   bfd *oldbfd;
457   boolean newdyn, olddyn, olddef, newdef, newdyncommon, olddyncommon;
458
459   *override = false;
460
461   sec = *psec;
462   bind = ELF_ST_BIND (sym->st_info);
463
464   if (! bfd_is_und_section (sec))
465     h = elf_link_hash_lookup (elf_hash_table (info), name, true, false, false);
466   else
467     h = ((struct elf_link_hash_entry *)
468          bfd_wrapped_link_hash_lookup (abfd, info, name, true, false, false));
469   if (h == NULL)
470     return false;
471   *sym_hash = h;
472
473   /* This code is for coping with dynamic objects, and is only useful
474      if we are doing an ELF link.  */
475   if (info->hash->creator != abfd->xvec)
476     return true;
477
478   /* For merging, we only care about real symbols.  */
479
480   while (h->root.type == bfd_link_hash_indirect
481          || h->root.type == bfd_link_hash_warning)
482     h = (struct elf_link_hash_entry *) h->root.u.i.link;
483
484   /* If we just created the symbol, mark it as being an ELF symbol.
485      Other than that, there is nothing to do--there is no merge issue
486      with a newly defined symbol--so we just return.  */
487
488   if (h->root.type == bfd_link_hash_new)
489     {
490       h->elf_link_hash_flags &=~ ELF_LINK_NON_ELF;
491       return true;
492     }
493
494   /* OLDBFD is a BFD associated with the existing symbol.  */
495
496   switch (h->root.type)
497     {
498     default:
499       oldbfd = NULL;
500       break;
501
502     case bfd_link_hash_undefined:
503     case bfd_link_hash_undefweak:
504       oldbfd = h->root.u.undef.abfd;
505       break;
506
507     case bfd_link_hash_defined:
508     case bfd_link_hash_defweak:
509       oldbfd = h->root.u.def.section->owner;
510       break;
511
512     case bfd_link_hash_common:
513       oldbfd = h->root.u.c.p->section->owner;
514       break;
515     }
516
517   /* In cases involving weak versioned symbols, we may wind up trying
518      to merge a symbol with itself.  Catch that here, to avoid the
519      confusion that results if we try to override a symbol with
520      itself.  The additional tests catch cases like
521      _GLOBAL_OFFSET_TABLE_, which are regular symbols defined in a
522      dynamic object, which we do want to handle here.  */
523   if (abfd == oldbfd
524       && ((abfd->flags & DYNAMIC) == 0
525           || (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) == 0))
526     return true;
527
528   /* NEWDYN and OLDDYN indicate whether the new or old symbol,
529      respectively, is from a dynamic object.  */
530
531   if ((abfd->flags & DYNAMIC) != 0)
532     newdyn = true;
533   else
534     newdyn = false;
535
536   if (oldbfd != NULL)
537     olddyn = (oldbfd->flags & DYNAMIC) != 0;
538   else
539     {
540       asection *hsec;
541
542       /* This code handles the special SHN_MIPS_{TEXT,DATA} section
543          indices used by MIPS ELF.  */
544       switch (h->root.type)
545         {
546         default:
547           hsec = NULL;
548           break;
549
550         case bfd_link_hash_defined:
551         case bfd_link_hash_defweak:
552           hsec = h->root.u.def.section;
553           break;
554
555         case bfd_link_hash_common:
556           hsec = h->root.u.c.p->section;
557           break;
558         }
559
560       if (hsec == NULL)
561         olddyn = false;
562       else
563         olddyn = (hsec->symbol->flags & BSF_DYNAMIC) != 0;
564     }
565
566   /* NEWDEF and OLDDEF indicate whether the new or old symbol,
567      respectively, appear to be a definition rather than reference.  */
568
569   if (bfd_is_und_section (sec) || bfd_is_com_section (sec))
570     newdef = false;
571   else
572     newdef = true;
573
574   if (h->root.type == bfd_link_hash_undefined
575       || h->root.type == bfd_link_hash_undefweak
576       || h->root.type == bfd_link_hash_common)
577     olddef = false;
578   else
579     olddef = true;
580
581   /* NEWDYNCOMMON and OLDDYNCOMMON indicate whether the new or old
582      symbol, respectively, appears to be a common symbol in a dynamic
583      object.  If a symbol appears in an uninitialized section, and is
584      not weak, and is not a function, then it may be a common symbol
585      which was resolved when the dynamic object was created.  We want
586      to treat such symbols specially, because they raise special
587      considerations when setting the symbol size: if the symbol
588      appears as a common symbol in a regular object, and the size in
589      the regular object is larger, we must make sure that we use the
590      larger size.  This problematic case can always be avoided in C,
591      but it must be handled correctly when using Fortran shared
592      libraries.
593
594      Note that if NEWDYNCOMMON is set, NEWDEF will be set, and
595      likewise for OLDDYNCOMMON and OLDDEF.
596
597      Note that this test is just a heuristic, and that it is quite
598      possible to have an uninitialized symbol in a shared object which
599      is really a definition, rather than a common symbol.  This could
600      lead to some minor confusion when the symbol really is a common
601      symbol in some regular object.  However, I think it will be
602      harmless.  */
603
604   if (newdyn
605       && newdef
606       && (sec->flags & SEC_ALLOC) != 0
607       && (sec->flags & SEC_LOAD) == 0
608       && sym->st_size > 0
609       && bind != STB_WEAK
610       && ELF_ST_TYPE (sym->st_info) != STT_FUNC)
611     newdyncommon = true;
612   else
613     newdyncommon = false;
614
615   if (olddyn
616       && olddef
617       && h->root.type == bfd_link_hash_defined
618       && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC) != 0
619       && (h->root.u.def.section->flags & SEC_ALLOC) != 0
620       && (h->root.u.def.section->flags & SEC_LOAD) == 0
621       && h->size > 0
622       && h->type != STT_FUNC)
623     olddyncommon = true;
624   else
625     olddyncommon = false;
626
627   /* It's OK to change the type if either the existing symbol or the
628      new symbol is weak.  */
629
630   if (h->root.type == bfd_link_hash_defweak
631       || h->root.type == bfd_link_hash_undefweak
632       || bind == STB_WEAK)
633     *type_change_ok = true;
634
635   /* It's OK to change the size if either the existing symbol or the
636      new symbol is weak, or if the old symbol is undefined.  */
637
638   if (*type_change_ok
639       || h->root.type == bfd_link_hash_undefined)
640     *size_change_ok = true;
641
642   /* If both the old and the new symbols look like common symbols in a
643      dynamic object, set the size of the symbol to the larger of the
644      two.  */
645
646   if (olddyncommon
647       && newdyncommon
648       && sym->st_size != h->size)
649     {
650       /* Since we think we have two common symbols, issue a multiple
651          common warning if desired.  Note that we only warn if the
652          size is different.  If the size is the same, we simply let
653          the old symbol override the new one as normally happens with
654          symbols defined in dynamic objects.  */
655
656       if (! ((*info->callbacks->multiple_common)
657              (info, h->root.root.string, oldbfd, bfd_link_hash_common,
658               h->size, abfd, bfd_link_hash_common, sym->st_size)))
659         return false;
660
661       if (sym->st_size > h->size)
662         h->size = sym->st_size;
663
664       *size_change_ok = true;
665     }
666
667   /* If we are looking at a dynamic object, and we have found a
668      definition, we need to see if the symbol was already defined by
669      some other object.  If so, we want to use the existing
670      definition, and we do not want to report a multiple symbol
671      definition error; we do this by clobbering *PSEC to be
672      bfd_und_section_ptr.
673
674      We treat a common symbol as a definition if the symbol in the
675      shared library is a function, since common symbols always
676      represent variables; this can cause confusion in principle, but
677      any such confusion would seem to indicate an erroneous program or
678      shared library.  We also permit a common symbol in a regular
679      object to override a weak symbol in a shared object.
680
681      We prefer a non-weak definition in a shared library to a weak
682      definition in the executable.  */
683
684   if (newdyn
685       && newdef
686       && (olddef
687           || (h->root.type == bfd_link_hash_common
688               && (bind == STB_WEAK
689                   || ELF_ST_TYPE (sym->st_info) == STT_FUNC)))
690       && (h->root.type != bfd_link_hash_defweak
691           || bind == STB_WEAK))
692     {
693       *override = true;
694       newdef = false;
695       newdyncommon = false;
696
697       *psec = sec = bfd_und_section_ptr;
698       *size_change_ok = true;
699
700       /* If we get here when the old symbol is a common symbol, then
701          we are explicitly letting it override a weak symbol or
702          function in a dynamic object, and we don't want to warn about
703          a type change.  If the old symbol is a defined symbol, a type
704          change warning may still be appropriate.  */
705
706       if (h->root.type == bfd_link_hash_common)
707         *type_change_ok = true;
708     }
709
710   /* Handle the special case of an old common symbol merging with a
711      new symbol which looks like a common symbol in a shared object.
712      We change *PSEC and *PVALUE to make the new symbol look like a
713      common symbol, and let _bfd_generic_link_add_one_symbol will do
714      the right thing.  */
715
716   if (newdyncommon
717       && h->root.type == bfd_link_hash_common)
718     {
719       *override = true;
720       newdef = false;
721       newdyncommon = false;
722       *pvalue = sym->st_size;
723       *psec = sec = bfd_com_section_ptr;
724       *size_change_ok = true;
725     }
726
727   /* If the old symbol is from a dynamic object, and the new symbol is
728      a definition which is not from a dynamic object, then the new
729      symbol overrides the old symbol.  Symbols from regular files
730      always take precedence over symbols from dynamic objects, even if
731      they are defined after the dynamic object in the link.
732
733      As above, we again permit a common symbol in a regular object to
734      override a definition in a shared object if the shared object
735      symbol is a function or is weak.
736
737      As above, we permit a non-weak definition in a shared object to
738      override a weak definition in a regular object.  */
739
740   if (! newdyn
741       && (newdef
742           || (bfd_is_com_section (sec)
743               && (h->root.type == bfd_link_hash_defweak
744                   || h->type == STT_FUNC)))
745       && olddyn
746       && olddef
747       && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC) != 0
748       && (bind != STB_WEAK
749           || h->root.type == bfd_link_hash_defweak))
750     {
751       /* Change the hash table entry to undefined, and let
752          _bfd_generic_link_add_one_symbol do the right thing with the
753          new definition.  */
754
755       h->root.type = bfd_link_hash_undefined;
756       h->root.u.undef.abfd = h->root.u.def.section->owner;
757       *size_change_ok = true;
758
759       olddef = false;
760       olddyncommon = false;
761
762       /* We again permit a type change when a common symbol may be
763          overriding a function.  */
764
765       if (bfd_is_com_section (sec))
766         *type_change_ok = true;
767
768       /* This union may have been set to be non-NULL when this symbol
769          was seen in a dynamic object.  We must force the union to be
770          NULL, so that it is correct for a regular symbol.  */
771
772       h->verinfo.vertree = NULL;
773
774       /* In this special case, if H is the target of an indirection,
775          we want the caller to frob with H rather than with the
776          indirect symbol.  That will permit the caller to redefine the
777          target of the indirection, rather than the indirect symbol
778          itself.  FIXME: This will break the -y option if we store a
779          symbol with a different name.  */
780       *sym_hash = h;
781     }
782
783   /* Handle the special case of a new common symbol merging with an
784      old symbol that looks like it might be a common symbol defined in
785      a shared object.  Note that we have already handled the case in
786      which a new common symbol should simply override the definition
787      in the shared library.  */
788
789   if (! newdyn
790       && bfd_is_com_section (sec)
791       && olddyncommon)
792     {
793       /* It would be best if we could set the hash table entry to a
794          common symbol, but we don't know what to use for the section
795          or the alignment.  */
796       if (! ((*info->callbacks->multiple_common)
797              (info, h->root.root.string, oldbfd, bfd_link_hash_common,
798               h->size, abfd, bfd_link_hash_common, sym->st_size)))
799         return false;
800
801       /* If the predumed common symbol in the dynamic object is
802          larger, pretend that the new symbol has its size.  */
803
804       if (h->size > *pvalue)
805         *pvalue = h->size;
806
807       /* FIXME: We no longer know the alignment required by the symbol
808          in the dynamic object, so we just wind up using the one from
809          the regular object.  */
810
811       olddef = false;
812       olddyncommon = false;
813
814       h->root.type = bfd_link_hash_undefined;
815       h->root.u.undef.abfd = h->root.u.def.section->owner;
816
817       *size_change_ok = true;
818       *type_change_ok = true;
819
820       h->verinfo.vertree = NULL;
821     }
822
823   /* Handle the special case of a weak definition in a regular object
824      followed by a non-weak definition in a shared object.  In this
825      case, we prefer the definition in the shared object.  */
826   if (olddef
827       && h->root.type == bfd_link_hash_defweak
828       && newdef
829       && newdyn
830       && bind != STB_WEAK)
831     {
832       /* To make this work we have to frob the flags so that the rest
833          of the code does not think we are using the regular
834          definition.  */
835       if ((h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) != 0)
836         h->elf_link_hash_flags |= ELF_LINK_HASH_REF_REGULAR;
837       else if ((h->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC) != 0)
838         h->elf_link_hash_flags |= ELF_LINK_HASH_REF_DYNAMIC;
839       h->elf_link_hash_flags &= ~ (ELF_LINK_HASH_DEF_REGULAR
840                                    | ELF_LINK_HASH_DEF_DYNAMIC);
841
842       /* If H is the target of an indirection, we want the caller to
843          use H rather than the indirect symbol.  Otherwise if we are
844          defining a new indirect symbol we will wind up attaching it
845          to the entry we are overriding.  */
846       *sym_hash = h;
847     }
848
849   /* Handle the special case of a non-weak definition in a shared
850      object followed by a weak definition in a regular object.  In
851      this case we prefer to definition in the shared object.  To make
852      this work we have to tell the caller to not treat the new symbol
853      as a definition.  */
854   if (olddef
855       && olddyn
856       && h->root.type != bfd_link_hash_defweak
857       && newdef
858       && ! newdyn
859       && bind == STB_WEAK)
860     *override = true;
861
862   return true;
863 }
864
865 /* Add symbols from an ELF object file to the linker hash table.  */
866
867 static boolean
868 elf_link_add_object_symbols (abfd, info)
869      bfd *abfd;
870      struct bfd_link_info *info;
871 {
872   boolean (*add_symbol_hook) PARAMS ((bfd *, struct bfd_link_info *,
873                                       const Elf_Internal_Sym *,
874                                       const char **, flagword *,
875                                       asection **, bfd_vma *));
876   boolean (*check_relocs) PARAMS ((bfd *, struct bfd_link_info *,
877                                    asection *, const Elf_Internal_Rela *));
878   boolean collect;
879   Elf_Internal_Shdr *hdr;
880   size_t symcount;
881   size_t extsymcount;
882   size_t extsymoff;
883   Elf_External_Sym *buf = NULL;
884   struct elf_link_hash_entry **sym_hash;
885   boolean dynamic;
886   bfd_byte *dynver = NULL;
887   Elf_External_Versym *extversym = NULL;
888   Elf_External_Versym *ever;
889   Elf_External_Dyn *dynbuf = NULL;
890   struct elf_link_hash_entry *weaks;
891   Elf_External_Sym *esym;
892   Elf_External_Sym *esymend;
893   struct elf_backend_data *bed;
894
895   bed = get_elf_backend_data (abfd);
896   add_symbol_hook = bed->elf_add_symbol_hook;
897   collect = bed->collect;
898
899   if ((abfd->flags & DYNAMIC) == 0)
900     dynamic = false;
901   else
902     {
903       dynamic = true;
904
905       /* You can't use -r against a dynamic object.  Also, there's no
906          hope of using a dynamic object which does not exactly match
907          the format of the output file.  */
908       if (info->relocateable || info->hash->creator != abfd->xvec)
909         {
910           bfd_set_error (bfd_error_invalid_operation);
911           goto error_return;
912         }
913     }
914
915   /* As a GNU extension, any input sections which are named
916      .gnu.warning.SYMBOL are treated as warning symbols for the given
917      symbol.  This differs from .gnu.warning sections, which generate
918      warnings when they are included in an output file.  */
919   if (! info->shared)
920     {
921       asection *s;
922
923       for (s = abfd->sections; s != NULL; s = s->next)
924         {
925           const char *name;
926
927           name = bfd_get_section_name (abfd, s);
928           if (strncmp (name, ".gnu.warning.", sizeof ".gnu.warning." - 1) == 0)
929             {
930               char *msg;
931               bfd_size_type sz;
932
933               name += sizeof ".gnu.warning." - 1;
934
935               /* If this is a shared object, then look up the symbol
936                  in the hash table.  If it is there, and it is already
937                  been defined, then we will not be using the entry
938                  from this shared object, so we don't need to warn.
939                  FIXME: If we see the definition in a regular object
940                  later on, we will warn, but we shouldn't.  The only
941                  fix is to keep track of what warnings we are supposed
942                  to emit, and then handle them all at the end of the
943                  link.  */
944               if (dynamic && abfd->xvec == info->hash->creator)
945                 {
946                   struct elf_link_hash_entry *h;
947
948                   h = elf_link_hash_lookup (elf_hash_table (info), name,
949                                             false, false, true);
950
951                   /* FIXME: What about bfd_link_hash_common?  */
952                   if (h != NULL
953                       && (h->root.type == bfd_link_hash_defined
954                           || h->root.type == bfd_link_hash_defweak))
955                     {
956                       /* We don't want to issue this warning.  Clobber
957                          the section size so that the warning does not
958                          get copied into the output file.  */
959                       s->_raw_size = 0;
960                       continue;
961                     }
962                 }
963
964               sz = bfd_section_size (abfd, s);
965               msg = (char *) bfd_alloc (abfd, sz + 1);
966               if (msg == NULL)
967                 goto error_return;
968
969               if (! bfd_get_section_contents (abfd, s, msg, (file_ptr) 0, sz))
970                 goto error_return;
971
972               msg[sz] = '\0';
973
974               if (! (_bfd_generic_link_add_one_symbol
975                      (info, abfd, name, BSF_WARNING, s, (bfd_vma) 0, msg,
976                       false, collect, (struct bfd_link_hash_entry **) NULL)))
977                 goto error_return;
978
979               if (! info->relocateable)
980                 {
981                   /* Clobber the section size so that the warning does
982                      not get copied into the output file.  */
983                   s->_raw_size = 0;
984                 }
985             }
986         }
987     }
988
989   /* If this is a dynamic object, we always link against the .dynsym
990      symbol table, not the .symtab symbol table.  The dynamic linker
991      will only see the .dynsym symbol table, so there is no reason to
992      look at .symtab for a dynamic object.  */
993
994   if (! dynamic || elf_dynsymtab (abfd) == 0)
995     hdr = &elf_tdata (abfd)->symtab_hdr;
996   else
997     hdr = &elf_tdata (abfd)->dynsymtab_hdr;
998
999   if (dynamic)
1000     {
1001       /* Read in any version definitions.  */
1002
1003       if (! _bfd_elf_slurp_version_tables (abfd))
1004         goto error_return;
1005
1006       /* Read in the symbol versions, but don't bother to convert them
1007          to internal format.  */
1008       if (elf_dynversym (abfd) != 0)
1009         {
1010           Elf_Internal_Shdr *versymhdr;
1011
1012           versymhdr = &elf_tdata (abfd)->dynversym_hdr;
1013           extversym = (Elf_External_Versym *) bfd_malloc (hdr->sh_size);
1014           if (extversym == NULL)
1015             goto error_return;
1016           if (bfd_seek (abfd, versymhdr->sh_offset, SEEK_SET) != 0
1017               || (bfd_read ((PTR) extversym, 1, versymhdr->sh_size, abfd)
1018                   != versymhdr->sh_size))
1019             goto error_return;
1020         }
1021     }
1022
1023   symcount = hdr->sh_size / sizeof (Elf_External_Sym);
1024
1025   /* The sh_info field of the symtab header tells us where the
1026      external symbols start.  We don't care about the local symbols at
1027      this point.  */
1028   if (elf_bad_symtab (abfd))
1029     {
1030       extsymcount = symcount;
1031       extsymoff = 0;
1032     }
1033   else
1034     {
1035       extsymcount = symcount - hdr->sh_info;
1036       extsymoff = hdr->sh_info;
1037     }
1038
1039   buf = ((Elf_External_Sym *)
1040          bfd_malloc (extsymcount * sizeof (Elf_External_Sym)));
1041   if (buf == NULL && extsymcount != 0)
1042     goto error_return;
1043
1044   /* We store a pointer to the hash table entry for each external
1045      symbol.  */
1046   sym_hash = ((struct elf_link_hash_entry **)
1047               bfd_alloc (abfd,
1048                          extsymcount * sizeof (struct elf_link_hash_entry *)));
1049   if (sym_hash == NULL)
1050     goto error_return;
1051   elf_sym_hashes (abfd) = sym_hash;
1052
1053   if (! dynamic)
1054     {
1055       /* If we are creating a shared library, create all the dynamic
1056          sections immediately.  We need to attach them to something,
1057          so we attach them to this BFD, provided it is the right
1058          format.  FIXME: If there are no input BFD's of the same
1059          format as the output, we can't make a shared library.  */
1060       if (info->shared
1061           && ! elf_hash_table (info)->dynamic_sections_created
1062           && abfd->xvec == info->hash->creator)
1063         {
1064           if (! elf_link_create_dynamic_sections (abfd, info))
1065             goto error_return;
1066         }
1067     }
1068   else
1069     {
1070       asection *s;
1071       boolean add_needed;
1072       const char *name;
1073       bfd_size_type oldsize;
1074       bfd_size_type strindex;
1075
1076       /* Find the name to use in a DT_NEEDED entry that refers to this
1077          object.  If the object has a DT_SONAME entry, we use it.
1078          Otherwise, if the generic linker stuck something in
1079          elf_dt_name, we use that.  Otherwise, we just use the file
1080          name.  If the generic linker put a null string into
1081          elf_dt_name, we don't make a DT_NEEDED entry at all, even if
1082          there is a DT_SONAME entry.  */
1083       add_needed = true;
1084       name = bfd_get_filename (abfd);
1085       if (elf_dt_name (abfd) != NULL)
1086         {
1087           name = elf_dt_name (abfd);
1088           if (*name == '\0')
1089             add_needed = false;
1090         }
1091       s = bfd_get_section_by_name (abfd, ".dynamic");
1092       if (s != NULL)
1093         {
1094           Elf_External_Dyn *extdyn;
1095           Elf_External_Dyn *extdynend;
1096           int elfsec;
1097           unsigned long link;
1098
1099           dynbuf = (Elf_External_Dyn *) bfd_malloc ((size_t) s->_raw_size);
1100           if (dynbuf == NULL)
1101             goto error_return;
1102
1103           if (! bfd_get_section_contents (abfd, s, (PTR) dynbuf,
1104                                           (file_ptr) 0, s->_raw_size))
1105             goto error_return;
1106
1107           elfsec = _bfd_elf_section_from_bfd_section (abfd, s);
1108           if (elfsec == -1)
1109             goto error_return;
1110           link = elf_elfsections (abfd)[elfsec]->sh_link;
1111
1112           {
1113             /* The shared libraries distributed with hpux11 have a bogus
1114                sh_link field for the ".dynamic" section.  This code detects
1115                when LINK refers to a section that is not a string table and
1116                tries to find the string table for the ".dynsym" section
1117                instead.  */
1118             Elf_Internal_Shdr *hdr = elf_elfsections (abfd)[link];
1119             if (hdr->sh_type != SHT_STRTAB)
1120               {
1121                 asection *s = bfd_get_section_by_name (abfd, ".dynsym");
1122                 int elfsec = _bfd_elf_section_from_bfd_section (abfd, s);
1123                 if (elfsec == -1)
1124                   goto error_return;
1125                 link = elf_elfsections (abfd)[elfsec]->sh_link;
1126               }
1127           }
1128
1129           extdyn = dynbuf;
1130           extdynend = extdyn + s->_raw_size / sizeof (Elf_External_Dyn);
1131           for (; extdyn < extdynend; extdyn++)
1132             {
1133               Elf_Internal_Dyn dyn;
1134
1135               elf_swap_dyn_in (abfd, extdyn, &dyn);
1136               if (dyn.d_tag == DT_SONAME)
1137                 {
1138                   name = bfd_elf_string_from_elf_section (abfd, link,
1139                                                           dyn.d_un.d_val);
1140                   if (name == NULL)
1141                     goto error_return;
1142                 }
1143               if (dyn.d_tag == DT_NEEDED)
1144                 {
1145                   struct bfd_link_needed_list *n, **pn;
1146                   char *fnm, *anm;
1147
1148                   n = ((struct bfd_link_needed_list *)
1149                        bfd_alloc (abfd, sizeof (struct bfd_link_needed_list)));
1150                   fnm = bfd_elf_string_from_elf_section (abfd, link,
1151                                                          dyn.d_un.d_val);
1152                   if (n == NULL || fnm == NULL)
1153                     goto error_return;
1154                   anm = bfd_alloc (abfd, strlen (fnm) + 1);
1155                   if (anm == NULL)
1156                     goto error_return;
1157                   strcpy (anm, fnm);
1158                   n->name = anm;
1159                   n->by = abfd;
1160                   n->next = NULL;
1161                   for (pn = &elf_hash_table (info)->needed;
1162                        *pn != NULL;
1163                        pn = &(*pn)->next)
1164                     ;
1165                   *pn = n;
1166                 }
1167             }
1168
1169           free (dynbuf);
1170           dynbuf = NULL;
1171         }
1172
1173       /* We do not want to include any of the sections in a dynamic
1174          object in the output file.  We hack by simply clobbering the
1175          list of sections in the BFD.  This could be handled more
1176          cleanly by, say, a new section flag; the existing
1177          SEC_NEVER_LOAD flag is not the one we want, because that one
1178          still implies that the section takes up space in the output
1179          file.  */
1180       abfd->sections = NULL;
1181       abfd->section_count = 0;
1182
1183       /* If this is the first dynamic object found in the link, create
1184          the special sections required for dynamic linking.  */
1185       if (! elf_hash_table (info)->dynamic_sections_created)
1186         {
1187           if (! elf_link_create_dynamic_sections (abfd, info))
1188             goto error_return;
1189         }
1190
1191       if (add_needed)
1192         {
1193           /* Add a DT_NEEDED entry for this dynamic object.  */
1194           oldsize = _bfd_stringtab_size (elf_hash_table (info)->dynstr);
1195           strindex = _bfd_stringtab_add (elf_hash_table (info)->dynstr, name,
1196                                          true, false);
1197           if (strindex == (bfd_size_type) -1)
1198             goto error_return;
1199
1200           if (oldsize == _bfd_stringtab_size (elf_hash_table (info)->dynstr))
1201             {
1202               asection *sdyn;
1203               Elf_External_Dyn *dyncon, *dynconend;
1204
1205               /* The hash table size did not change, which means that
1206                  the dynamic object name was already entered.  If we
1207                  have already included this dynamic object in the
1208                  link, just ignore it.  There is no reason to include
1209                  a particular dynamic object more than once.  */
1210               sdyn = bfd_get_section_by_name (elf_hash_table (info)->dynobj,
1211                                               ".dynamic");
1212               BFD_ASSERT (sdyn != NULL);
1213
1214               dyncon = (Elf_External_Dyn *) sdyn->contents;
1215               dynconend = (Elf_External_Dyn *) (sdyn->contents +
1216                                                 sdyn->_raw_size);
1217               for (; dyncon < dynconend; dyncon++)
1218                 {
1219                   Elf_Internal_Dyn dyn;
1220
1221                   elf_swap_dyn_in (elf_hash_table (info)->dynobj, dyncon,
1222                                    &dyn);
1223                   if (dyn.d_tag == DT_NEEDED
1224                       && dyn.d_un.d_val == strindex)
1225                     {
1226                       if (buf != NULL)
1227                         free (buf);
1228                       if (extversym != NULL)
1229                         free (extversym);
1230                       return true;
1231                     }
1232                 }
1233             }
1234
1235           if (! elf_add_dynamic_entry (info, DT_NEEDED, strindex))
1236             goto error_return;
1237         }
1238
1239       /* Save the SONAME, if there is one, because sometimes the
1240          linker emulation code will need to know it.  */
1241       if (*name == '\0')
1242         name = bfd_get_filename (abfd);
1243       elf_dt_name (abfd) = name;
1244     }
1245
1246   if (bfd_seek (abfd,
1247                 hdr->sh_offset + extsymoff * sizeof (Elf_External_Sym),
1248                 SEEK_SET) != 0
1249       || (bfd_read ((PTR) buf, sizeof (Elf_External_Sym), extsymcount, abfd)
1250           != extsymcount * sizeof (Elf_External_Sym)))
1251     goto error_return;
1252
1253   weaks = NULL;
1254
1255   ever = extversym != NULL ? extversym + extsymoff : NULL;
1256   esymend = buf + extsymcount;
1257   for (esym = buf;
1258        esym < esymend;
1259        esym++, sym_hash++, ever = (ever != NULL ? ever + 1 : NULL))
1260     {
1261       Elf_Internal_Sym sym;
1262       int bind;
1263       bfd_vma value;
1264       asection *sec;
1265       flagword flags;
1266       const char *name;
1267       struct elf_link_hash_entry *h;
1268       boolean definition;
1269       boolean size_change_ok, type_change_ok;
1270       boolean new_weakdef;
1271       unsigned int old_alignment;
1272
1273       elf_swap_symbol_in (abfd, esym, &sym);
1274
1275       flags = BSF_NO_FLAGS;
1276       sec = NULL;
1277       value = sym.st_value;
1278       *sym_hash = NULL;
1279
1280       bind = ELF_ST_BIND (sym.st_info);
1281       if (bind == STB_LOCAL)
1282         {
1283           /* This should be impossible, since ELF requires that all
1284              global symbols follow all local symbols, and that sh_info
1285              point to the first global symbol.  Unfortunatealy, Irix 5
1286              screws this up.  */
1287           continue;
1288         }
1289       else if (bind == STB_GLOBAL)
1290         {
1291           if (sym.st_shndx != SHN_UNDEF
1292               && sym.st_shndx != SHN_COMMON)
1293             flags = BSF_GLOBAL;
1294           else
1295             flags = 0;
1296         }
1297       else if (bind == STB_WEAK)
1298         flags = BSF_WEAK;
1299       else
1300         {
1301           /* Leave it up to the processor backend.  */
1302         }
1303
1304       if (sym.st_shndx == SHN_UNDEF)
1305         sec = bfd_und_section_ptr;
1306       else if (sym.st_shndx > 0 && sym.st_shndx < SHN_LORESERVE)
1307         {
1308           sec = section_from_elf_index (abfd, sym.st_shndx);
1309           if (sec == NULL)
1310             sec = bfd_abs_section_ptr;
1311           else if ((abfd->flags & (EXEC_P | DYNAMIC)) != 0)
1312             value -= sec->vma;
1313         }
1314       else if (sym.st_shndx == SHN_ABS)
1315         sec = bfd_abs_section_ptr;
1316       else if (sym.st_shndx == SHN_COMMON)
1317         {
1318           sec = bfd_com_section_ptr;
1319           /* What ELF calls the size we call the value.  What ELF
1320              calls the value we call the alignment.  */
1321           value = sym.st_size;
1322         }
1323       else
1324         {
1325           /* Leave it up to the processor backend.  */
1326         }
1327
1328       name = bfd_elf_string_from_elf_section (abfd, hdr->sh_link, sym.st_name);
1329       if (name == (const char *) NULL)
1330         goto error_return;
1331
1332       if (add_symbol_hook)
1333         {
1334           if (! (*add_symbol_hook) (abfd, info, &sym, &name, &flags, &sec,
1335                                     &value))
1336             goto error_return;
1337
1338           /* The hook function sets the name to NULL if this symbol
1339              should be skipped for some reason.  */
1340           if (name == (const char *) NULL)
1341             continue;
1342         }
1343
1344       /* Sanity check that all possibilities were handled.  */
1345       if (sec == (asection *) NULL)
1346         {
1347           bfd_set_error (bfd_error_bad_value);
1348           goto error_return;
1349         }
1350
1351       if (bfd_is_und_section (sec)
1352           || bfd_is_com_section (sec))
1353         definition = false;
1354       else
1355         definition = true;
1356
1357       size_change_ok = false;
1358       type_change_ok = get_elf_backend_data (abfd)->type_change_ok;
1359       old_alignment = 0;
1360       if (info->hash->creator->flavour == bfd_target_elf_flavour)
1361         {
1362           Elf_Internal_Versym iver;
1363           unsigned int vernum = 0;
1364           boolean override;
1365
1366           if (ever != NULL)
1367             {
1368               _bfd_elf_swap_versym_in (abfd, ever, &iver);
1369               vernum = iver.vs_vers & VERSYM_VERSION;
1370
1371               /* If this is a hidden symbol, or if it is not version
1372                  1, we append the version name to the symbol name.
1373                  However, we do not modify a non-hidden absolute
1374                  symbol, because it might be the version symbol
1375                  itself.  FIXME: What if it isn't?  */
1376               if ((iver.vs_vers & VERSYM_HIDDEN) != 0
1377                   || (vernum > 1 && ! bfd_is_abs_section (sec)))
1378                 {
1379                   const char *verstr;
1380                   int namelen, newlen;
1381                   char *newname, *p;
1382
1383                   if (sym.st_shndx != SHN_UNDEF)
1384                     {
1385                       if (vernum > elf_tdata (abfd)->dynverdef_hdr.sh_info)
1386                         {
1387                           (*_bfd_error_handler)
1388                             (_("%s: %s: invalid version %u (max %d)"),
1389                              bfd_get_filename (abfd), name, vernum,
1390                              elf_tdata (abfd)->dynverdef_hdr.sh_info);
1391                           bfd_set_error (bfd_error_bad_value);
1392                           goto error_return;
1393                         }
1394                       else if (vernum > 1)
1395                         verstr =
1396                           elf_tdata (abfd)->verdef[vernum - 1].vd_nodename;
1397                       else
1398                         verstr = "";
1399                     }
1400                   else
1401                     {
1402                       /* We cannot simply test for the number of
1403                          entries in the VERNEED section since the
1404                          numbers for the needed versions do not start
1405                          at 0.  */
1406                       Elf_Internal_Verneed *t;
1407
1408                       verstr = NULL;
1409                       for (t = elf_tdata (abfd)->verref;
1410                            t != NULL;
1411                            t = t->vn_nextref)
1412                         {
1413                           Elf_Internal_Vernaux *a;
1414
1415                           for (a = t->vn_auxptr; a != NULL; a = a->vna_nextptr)
1416                             {
1417                               if (a->vna_other == vernum)
1418                                 {
1419                                   verstr = a->vna_nodename;
1420                                   break;
1421                                 }
1422                             }
1423                           if (a != NULL)
1424                             break;
1425                         }
1426                       if (verstr == NULL)
1427                         {
1428                           (*_bfd_error_handler)
1429                             (_("%s: %s: invalid needed version %d"),
1430                              bfd_get_filename (abfd), name, vernum);
1431                           bfd_set_error (bfd_error_bad_value);
1432                           goto error_return;
1433                         }
1434                     }
1435
1436                   namelen = strlen (name);
1437                   newlen = namelen + strlen (verstr) + 2;
1438                   if ((iver.vs_vers & VERSYM_HIDDEN) == 0)
1439                     ++newlen;
1440
1441                   newname = (char *) bfd_alloc (abfd, newlen);
1442                   if (newname == NULL)
1443                     goto error_return;
1444                   strcpy (newname, name);
1445                   p = newname + namelen;
1446                   *p++ = ELF_VER_CHR;
1447                   if ((iver.vs_vers & VERSYM_HIDDEN) == 0)
1448                     *p++ = ELF_VER_CHR;
1449                   strcpy (p, verstr);
1450
1451                   name = newname;
1452                 }
1453             }
1454
1455           if (! elf_merge_symbol (abfd, info, name, &sym, &sec, &value,
1456                                   sym_hash, &override, &type_change_ok,
1457                                   &size_change_ok))
1458             goto error_return;
1459
1460           if (override)
1461             definition = false;
1462
1463           h = *sym_hash;
1464           while (h->root.type == bfd_link_hash_indirect
1465                  || h->root.type == bfd_link_hash_warning)
1466             h = (struct elf_link_hash_entry *) h->root.u.i.link;
1467
1468           /* Remember the old alignment if this is a common symbol, so
1469              that we don't reduce the alignment later on.  We can't
1470              check later, because _bfd_generic_link_add_one_symbol
1471              will set a default for the alignment which we want to
1472              override.  */
1473           if (h->root.type == bfd_link_hash_common)
1474             old_alignment = h->root.u.c.p->alignment_power;
1475
1476           if (elf_tdata (abfd)->verdef != NULL
1477               && ! override
1478               && vernum > 1
1479               && definition)
1480             h->verinfo.verdef = &elf_tdata (abfd)->verdef[vernum - 1];
1481         }
1482
1483       if (! (_bfd_generic_link_add_one_symbol
1484              (info, abfd, name, flags, sec, value, (const char *) NULL,
1485               false, collect, (struct bfd_link_hash_entry **) sym_hash)))
1486         goto error_return;
1487
1488       h = *sym_hash;
1489       while (h->root.type == bfd_link_hash_indirect
1490              || h->root.type == bfd_link_hash_warning)
1491         h = (struct elf_link_hash_entry *) h->root.u.i.link;
1492       *sym_hash = h;
1493
1494       new_weakdef = false;
1495       if (dynamic
1496           && definition
1497           && (flags & BSF_WEAK) != 0
1498           && ELF_ST_TYPE (sym.st_info) != STT_FUNC
1499           && info->hash->creator->flavour == bfd_target_elf_flavour
1500           && h->weakdef == NULL)
1501         {
1502           /* Keep a list of all weak defined non function symbols from
1503              a dynamic object, using the weakdef field.  Later in this
1504              function we will set the weakdef field to the correct
1505              value.  We only put non-function symbols from dynamic
1506              objects on this list, because that happens to be the only
1507              time we need to know the normal symbol corresponding to a
1508              weak symbol, and the information is time consuming to
1509              figure out.  If the weakdef field is not already NULL,
1510              then this symbol was already defined by some previous
1511              dynamic object, and we will be using that previous
1512              definition anyhow.  */
1513
1514           h->weakdef = weaks;
1515           weaks = h;
1516           new_weakdef = true;
1517         }
1518
1519       /* Set the alignment of a common symbol.  */
1520       if (sym.st_shndx == SHN_COMMON
1521           && h->root.type == bfd_link_hash_common)
1522         {
1523           unsigned int align;
1524
1525           align = bfd_log2 (sym.st_value);
1526           if (align > old_alignment)
1527             h->root.u.c.p->alignment_power = align;
1528         }
1529
1530       if (info->hash->creator->flavour == bfd_target_elf_flavour)
1531         {
1532           int old_flags;
1533           boolean dynsym;
1534           int new_flag;
1535
1536           /* Remember the symbol size and type.  */
1537           if (sym.st_size != 0
1538               && (definition || h->size == 0))
1539             {
1540               if (h->size != 0 && h->size != sym.st_size && ! size_change_ok)
1541                 (*_bfd_error_handler)
1542                   (_("Warning: size of symbol `%s' changed from %lu to %lu in %s"),
1543                    name, (unsigned long) h->size, (unsigned long) sym.st_size,
1544                    bfd_get_filename (abfd));
1545
1546               h->size = sym.st_size;
1547             }
1548
1549           /* If this is a common symbol, then we always want H->SIZE
1550              to be the size of the common symbol.  The code just above
1551              won't fix the size if a common symbol becomes larger.  We
1552              don't warn about a size change here, because that is
1553              covered by --warn-common.  */
1554           if (h->root.type == bfd_link_hash_common)
1555             h->size = h->root.u.c.size;
1556
1557           if (ELF_ST_TYPE (sym.st_info) != STT_NOTYPE
1558               && (definition || h->type == STT_NOTYPE))
1559             {
1560               if (h->type != STT_NOTYPE
1561                   && h->type != ELF_ST_TYPE (sym.st_info)
1562                   && ! type_change_ok)
1563                 (*_bfd_error_handler)
1564                   (_("Warning: type of symbol `%s' changed from %d to %d in %s"),
1565                    name, h->type, ELF_ST_TYPE (sym.st_info),
1566                    bfd_get_filename (abfd));
1567
1568               h->type = ELF_ST_TYPE (sym.st_info);
1569             }
1570
1571           /* If st_other has a processor-specific meaning, specific code
1572              might be needed here.  */
1573           if (sym.st_other != 0)
1574             {
1575               /* Combine visibilities, using the most constraining one.  */
1576               unsigned char hvis   = ELF_ST_VISIBILITY (h->other);
1577               unsigned char symvis = ELF_ST_VISIBILITY (sym.st_other);
1578               
1579               if (symvis && (hvis > symvis || hvis == 0))
1580                 h->other = sym.st_other;
1581               
1582               /* If neither has visibility, use the st_other of the
1583                  definition.  This is an arbitrary choice, since the
1584                  other bits have no general meaning.  */
1585               if (!symvis && !hvis
1586                   && (definition || h->other == 0))
1587                 h->other = sym.st_other;
1588             }
1589
1590           /* Set a flag in the hash table entry indicating the type of
1591              reference or definition we just found.  Keep a count of
1592              the number of dynamic symbols we find.  A dynamic symbol
1593              is one which is referenced or defined by both a regular
1594              object and a shared object.  */
1595           old_flags = h->elf_link_hash_flags;
1596           dynsym = false;
1597           if (! dynamic)
1598             {
1599               if (! definition)
1600                 {
1601                   new_flag = ELF_LINK_HASH_REF_REGULAR;
1602                   if (bind != STB_WEAK)
1603                     new_flag |= ELF_LINK_HASH_REF_REGULAR_NONWEAK;
1604                 }
1605               else
1606                 new_flag = ELF_LINK_HASH_DEF_REGULAR;
1607               if (info->shared
1608                   || (old_flags & (ELF_LINK_HASH_DEF_DYNAMIC
1609                                    | ELF_LINK_HASH_REF_DYNAMIC)) != 0)
1610                 dynsym = true;
1611             }
1612           else
1613             {
1614               if (! definition)
1615                 new_flag = ELF_LINK_HASH_REF_DYNAMIC;
1616               else
1617                 new_flag = ELF_LINK_HASH_DEF_DYNAMIC;
1618               if ((old_flags & (ELF_LINK_HASH_DEF_REGULAR
1619                                 | ELF_LINK_HASH_REF_REGULAR)) != 0
1620                   || (h->weakdef != NULL
1621                       && ! new_weakdef
1622                       && h->weakdef->dynindx != -1))
1623                 dynsym = true;
1624             }
1625
1626           h->elf_link_hash_flags |= new_flag;
1627
1628           /* If this symbol has a version, and it is the default
1629              version, we create an indirect symbol from the default
1630              name to the fully decorated name.  This will cause
1631              external references which do not specify a version to be
1632              bound to this version of the symbol.  */
1633           if (definition)
1634             {
1635               char *p;
1636
1637               p = strchr (name, ELF_VER_CHR);
1638               if (p != NULL && p[1] == ELF_VER_CHR)
1639                 {
1640                   char *shortname;
1641                   struct elf_link_hash_entry *hi;
1642                   boolean override;
1643
1644                   shortname = bfd_hash_allocate (&info->hash->table,
1645                                                  p - name + 1);
1646                   if (shortname == NULL)
1647                     goto error_return;
1648                   strncpy (shortname, name, p - name);
1649                   shortname[p - name] = '\0';
1650
1651                   /* We are going to create a new symbol.  Merge it
1652                      with any existing symbol with this name.  For the
1653                      purposes of the merge, act as though we were
1654                      defining the symbol we just defined, although we
1655                      actually going to define an indirect symbol.  */
1656                   type_change_ok = false;
1657                   size_change_ok = false;
1658                   if (! elf_merge_symbol (abfd, info, shortname, &sym, &sec,
1659                                           &value, &hi, &override,
1660                                           &type_change_ok, &size_change_ok))
1661                     goto error_return;
1662
1663                   if (! override)
1664                     {
1665                       if (! (_bfd_generic_link_add_one_symbol
1666                              (info, abfd, shortname, BSF_INDIRECT,
1667                               bfd_ind_section_ptr, (bfd_vma) 0, name, false,
1668                               collect, (struct bfd_link_hash_entry **) &hi)))
1669                         goto error_return;
1670                     }
1671                   else
1672                     {
1673                       /* In this case the symbol named SHORTNAME is
1674                          overriding the indirect symbol we want to
1675                          add.  We were planning on making SHORTNAME an
1676                          indirect symbol referring to NAME.  SHORTNAME
1677                          is the name without a version.  NAME is the
1678                          fully versioned name, and it is the default
1679                          version.
1680
1681                          Overriding means that we already saw a
1682                          definition for the symbol SHORTNAME in a
1683                          regular object, and it is overriding the
1684                          symbol defined in the dynamic object.
1685
1686                          When this happens, we actually want to change
1687                          NAME, the symbol we just added, to refer to
1688                          SHORTNAME.  This will cause references to
1689                          NAME in the shared object to become
1690                          references to SHORTNAME in the regular
1691                          object.  This is what we expect when we
1692                          override a function in a shared object: that
1693                          the references in the shared object will be
1694                          mapped to the definition in the regular
1695                          object.  */
1696
1697                       while (hi->root.type == bfd_link_hash_indirect
1698                              || hi->root.type == bfd_link_hash_warning)
1699                         hi = (struct elf_link_hash_entry *) hi->root.u.i.link;
1700
1701                       h->root.type = bfd_link_hash_indirect;
1702                       h->root.u.i.link = (struct bfd_link_hash_entry *) hi;
1703                       if (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC)
1704                         {
1705                           h->elf_link_hash_flags &=~ ELF_LINK_HASH_DEF_DYNAMIC;
1706                           hi->elf_link_hash_flags |= ELF_LINK_HASH_REF_DYNAMIC;
1707                           if (hi->elf_link_hash_flags
1708                               & (ELF_LINK_HASH_REF_REGULAR
1709                                  | ELF_LINK_HASH_DEF_REGULAR))
1710                             {
1711                               if (! _bfd_elf_link_record_dynamic_symbol (info,
1712                                                                          hi))
1713                                 goto error_return;
1714                             }
1715                         }
1716
1717                       /* Now set HI to H, so that the following code
1718                          will set the other fields correctly.  */
1719                       hi = h;
1720                     }
1721
1722                   /* If there is a duplicate definition somewhere,
1723                      then HI may not point to an indirect symbol.  We
1724                      will have reported an error to the user in that
1725                      case.  */
1726
1727                   if (hi->root.type == bfd_link_hash_indirect)
1728                     {
1729                       struct elf_link_hash_entry *ht;
1730
1731                       /* If the symbol became indirect, then we assume
1732                          that we have not seen a definition before.  */
1733                       BFD_ASSERT ((hi->elf_link_hash_flags
1734                                    & (ELF_LINK_HASH_DEF_DYNAMIC
1735                                       | ELF_LINK_HASH_DEF_REGULAR))
1736                                   == 0);
1737
1738                       ht = (struct elf_link_hash_entry *) hi->root.u.i.link;
1739                       (*bed->elf_backend_copy_indirect_symbol) (ht, hi);
1740
1741                       /* See if the new flags lead us to realize that
1742                          the symbol must be dynamic.  */
1743                       if (! dynsym)
1744                         {
1745                           if (! dynamic)
1746                             {
1747                               if (info->shared
1748                                   || ((hi->elf_link_hash_flags
1749                                        & ELF_LINK_HASH_REF_DYNAMIC)
1750                                       != 0))
1751                                 dynsym = true;
1752                             }
1753                           else
1754                             {
1755                               if ((hi->elf_link_hash_flags
1756                                    & ELF_LINK_HASH_REF_REGULAR) != 0)
1757                                 dynsym = true;
1758                             }
1759                         }
1760                     }
1761
1762                   /* We also need to define an indirection from the
1763                      nondefault version of the symbol.  */
1764
1765                   shortname = bfd_hash_allocate (&info->hash->table,
1766                                                  strlen (name));
1767                   if (shortname == NULL)
1768                     goto error_return;
1769                   strncpy (shortname, name, p - name);
1770                   strcpy (shortname + (p - name), p + 1);
1771
1772                   /* Once again, merge with any existing symbol.  */
1773                   type_change_ok = false;
1774                   size_change_ok = false;
1775                   if (! elf_merge_symbol (abfd, info, shortname, &sym, &sec,
1776                                           &value, &hi, &override,
1777                                           &type_change_ok, &size_change_ok))
1778                     goto error_return;
1779
1780                   if (override)
1781                     {
1782                       /* Here SHORTNAME is a versioned name, so we
1783                          don't expect to see the type of override we
1784                          do in the case above.  */
1785                       (*_bfd_error_handler)
1786                         (_("%s: warning: unexpected redefinition of `%s'"),
1787                          bfd_get_filename (abfd), shortname);
1788                     }
1789                   else
1790                     {
1791                       if (! (_bfd_generic_link_add_one_symbol
1792                              (info, abfd, shortname, BSF_INDIRECT,
1793                               bfd_ind_section_ptr, (bfd_vma) 0, name, false,
1794                               collect, (struct bfd_link_hash_entry **) &hi)))
1795                         goto error_return;
1796
1797                       /* If there is a duplicate definition somewhere,
1798                          then HI may not point to an indirect symbol.
1799                          We will have reported an error to the user in
1800                          that case.  */
1801
1802                       if (hi->root.type == bfd_link_hash_indirect)
1803                         {
1804                           /* If the symbol became indirect, then we
1805                              assume that we have not seen a definition
1806                              before.  */
1807                           BFD_ASSERT ((hi->elf_link_hash_flags
1808                                        & (ELF_LINK_HASH_DEF_DYNAMIC
1809                                           | ELF_LINK_HASH_DEF_REGULAR))
1810                                       == 0);
1811
1812                           (*bed->elf_backend_copy_indirect_symbol) (h, hi);
1813
1814                           /* See if the new flags lead us to realize
1815                              that the symbol must be dynamic.  */
1816                           if (! dynsym)
1817                             {
1818                               if (! dynamic)
1819                                 {
1820                                   if (info->shared
1821                                       || ((hi->elf_link_hash_flags
1822                                            & ELF_LINK_HASH_REF_DYNAMIC)
1823                                           != 0))
1824                                     dynsym = true;
1825                                 }
1826                               else
1827                                 {
1828                                   if ((hi->elf_link_hash_flags
1829                                        & ELF_LINK_HASH_REF_REGULAR) != 0)
1830                                     dynsym = true;
1831                                 }
1832                             }
1833                         }
1834                     }
1835                 }
1836             }
1837
1838           if (dynsym && h->dynindx == -1)
1839             {
1840               if (! _bfd_elf_link_record_dynamic_symbol (info, h))
1841                 goto error_return;
1842               if (h->weakdef != NULL
1843                   && ! new_weakdef
1844                   && h->weakdef->dynindx == -1)
1845                 {
1846                   if (! _bfd_elf_link_record_dynamic_symbol (info,
1847                                                              h->weakdef))
1848                     goto error_return;
1849                 }
1850             }
1851         }
1852     }
1853
1854   /* Now set the weakdefs field correctly for all the weak defined
1855      symbols we found.  The only way to do this is to search all the
1856      symbols.  Since we only need the information for non functions in
1857      dynamic objects, that's the only time we actually put anything on
1858      the list WEAKS.  We need this information so that if a regular
1859      object refers to a symbol defined weakly in a dynamic object, the
1860      real symbol in the dynamic object is also put in the dynamic
1861      symbols; we also must arrange for both symbols to point to the
1862      same memory location.  We could handle the general case of symbol
1863      aliasing, but a general symbol alias can only be generated in
1864      assembler code, handling it correctly would be very time
1865      consuming, and other ELF linkers don't handle general aliasing
1866      either.  */
1867   while (weaks != NULL)
1868     {
1869       struct elf_link_hash_entry *hlook;
1870       asection *slook;
1871       bfd_vma vlook;
1872       struct elf_link_hash_entry **hpp;
1873       struct elf_link_hash_entry **hppend;
1874
1875       hlook = weaks;
1876       weaks = hlook->weakdef;
1877       hlook->weakdef = NULL;
1878
1879       BFD_ASSERT (hlook->root.type == bfd_link_hash_defined
1880                   || hlook->root.type == bfd_link_hash_defweak
1881                   || hlook->root.type == bfd_link_hash_common
1882                   || hlook->root.type == bfd_link_hash_indirect);
1883       slook = hlook->root.u.def.section;
1884       vlook = hlook->root.u.def.value;
1885
1886       hpp = elf_sym_hashes (abfd);
1887       hppend = hpp + extsymcount;
1888       for (; hpp < hppend; hpp++)
1889         {
1890           struct elf_link_hash_entry *h;
1891
1892           h = *hpp;
1893           if (h != NULL && h != hlook
1894               && h->root.type == bfd_link_hash_defined
1895               && h->root.u.def.section == slook
1896               && h->root.u.def.value == vlook)
1897             {
1898               hlook->weakdef = h;
1899
1900               /* If the weak definition is in the list of dynamic
1901                  symbols, make sure the real definition is put there
1902                  as well.  */
1903               if (hlook->dynindx != -1
1904                   && h->dynindx == -1)
1905                 {
1906                   if (! _bfd_elf_link_record_dynamic_symbol (info, h))
1907                     goto error_return;
1908                 }
1909
1910               /* If the real definition is in the list of dynamic
1911                  symbols, make sure the weak definition is put there
1912                  as well.  If we don't do this, then the dynamic
1913                  loader might not merge the entries for the real
1914                  definition and the weak definition.  */
1915               if (h->dynindx != -1
1916                   && hlook->dynindx == -1)
1917                 {
1918                   if (! _bfd_elf_link_record_dynamic_symbol (info, hlook))
1919                     goto error_return;
1920                 }
1921
1922               break;
1923             }
1924         }
1925     }
1926
1927   if (buf != NULL)
1928     {
1929       free (buf);
1930       buf = NULL;
1931     }
1932
1933   if (extversym != NULL)
1934     {
1935       free (extversym);
1936       extversym = NULL;
1937     }
1938
1939   /* If this object is the same format as the output object, and it is
1940      not a shared library, then let the backend look through the
1941      relocs.
1942
1943      This is required to build global offset table entries and to
1944      arrange for dynamic relocs.  It is not required for the
1945      particular common case of linking non PIC code, even when linking
1946      against shared libraries, but unfortunately there is no way of
1947      knowing whether an object file has been compiled PIC or not.
1948      Looking through the relocs is not particularly time consuming.
1949      The problem is that we must either (1) keep the relocs in memory,
1950      which causes the linker to require additional runtime memory or
1951      (2) read the relocs twice from the input file, which wastes time.
1952      This would be a good case for using mmap.
1953
1954      I have no idea how to handle linking PIC code into a file of a
1955      different format.  It probably can't be done.  */
1956   check_relocs = get_elf_backend_data (abfd)->check_relocs;
1957   if (! dynamic
1958       && abfd->xvec == info->hash->creator
1959       && check_relocs != NULL)
1960     {
1961       asection *o;
1962
1963       for (o = abfd->sections; o != NULL; o = o->next)
1964         {
1965           Elf_Internal_Rela *internal_relocs;
1966           boolean ok;
1967
1968           if ((o->flags & SEC_RELOC) == 0
1969               || o->reloc_count == 0
1970               || ((info->strip == strip_all || info->strip == strip_debugger)
1971                   && (o->flags & SEC_DEBUGGING) != 0)
1972               || bfd_is_abs_section (o->output_section))
1973             continue;
1974
1975           internal_relocs = (NAME(_bfd_elf,link_read_relocs)
1976                              (abfd, o, (PTR) NULL,
1977                               (Elf_Internal_Rela *) NULL,
1978                               info->keep_memory));
1979           if (internal_relocs == NULL)
1980             goto error_return;
1981
1982           ok = (*check_relocs) (abfd, info, o, internal_relocs);
1983
1984           if (! info->keep_memory)
1985             free (internal_relocs);
1986
1987           if (! ok)
1988             goto error_return;
1989         }
1990     }
1991
1992   /* If this is a non-traditional, non-relocateable link, try to
1993      optimize the handling of the .stab/.stabstr sections.  */
1994   if (! dynamic
1995       && ! info->relocateable
1996       && ! info->traditional_format
1997       && info->hash->creator->flavour == bfd_target_elf_flavour
1998       && (info->strip != strip_all && info->strip != strip_debugger))
1999     {
2000       asection *stab, *stabstr;
2001
2002       stab = bfd_get_section_by_name (abfd, ".stab");
2003       if (stab != NULL)
2004         {
2005           stabstr = bfd_get_section_by_name (abfd, ".stabstr");
2006
2007           if (stabstr != NULL)
2008             {
2009               struct bfd_elf_section_data *secdata;
2010
2011               secdata = elf_section_data (stab);
2012               if (! _bfd_link_section_stabs (abfd,
2013                                              &elf_hash_table (info)->stab_info,
2014                                              stab, stabstr,
2015                                              &secdata->stab_info))
2016                 goto error_return;
2017             }
2018         }
2019     }
2020
2021   return true;
2022
2023  error_return:
2024   if (buf != NULL)
2025     free (buf);
2026   if (dynbuf != NULL)
2027     free (dynbuf);
2028   if (dynver != NULL)
2029     free (dynver);
2030   if (extversym != NULL)
2031     free (extversym);
2032   return false;
2033 }
2034
2035 /* Create some sections which will be filled in with dynamic linking
2036    information.  ABFD is an input file which requires dynamic sections
2037    to be created.  The dynamic sections take up virtual memory space
2038    when the final executable is run, so we need to create them before
2039    addresses are assigned to the output sections.  We work out the
2040    actual contents and size of these sections later.  */
2041
2042 boolean
2043 elf_link_create_dynamic_sections (abfd, info)
2044      bfd *abfd;
2045      struct bfd_link_info *info;
2046 {
2047   flagword flags;
2048   register asection *s;
2049   struct elf_link_hash_entry *h;
2050   struct elf_backend_data *bed;
2051
2052   if (elf_hash_table (info)->dynamic_sections_created)
2053     return true;
2054
2055   /* Make sure that all dynamic sections use the same input BFD.  */
2056   if (elf_hash_table (info)->dynobj == NULL)
2057     elf_hash_table (info)->dynobj = abfd;
2058   else
2059     abfd = elf_hash_table (info)->dynobj;
2060
2061   /* Note that we set the SEC_IN_MEMORY flag for all of these
2062      sections.  */
2063   flags = (SEC_ALLOC | SEC_LOAD | SEC_HAS_CONTENTS
2064            | SEC_IN_MEMORY | SEC_LINKER_CREATED);
2065
2066   /* A dynamically linked executable has a .interp section, but a
2067      shared library does not.  */
2068   if (! info->shared)
2069     {
2070       s = bfd_make_section (abfd, ".interp");
2071       if (s == NULL
2072           || ! bfd_set_section_flags (abfd, s, flags | SEC_READONLY))
2073         return false;
2074     }
2075
2076   /* Create sections to hold version informations.  These are removed
2077      if they are not needed.  */
2078   s = bfd_make_section (abfd, ".gnu.version_d");
2079   if (s == NULL
2080       || ! bfd_set_section_flags (abfd, s, flags | SEC_READONLY)
2081       || ! bfd_set_section_alignment (abfd, s, LOG_FILE_ALIGN))
2082     return false;
2083
2084   s = bfd_make_section (abfd, ".gnu.version");
2085   if (s == NULL
2086       || ! bfd_set_section_flags (abfd, s, flags | SEC_READONLY)
2087       || ! bfd_set_section_alignment (abfd, s, 1))
2088     return false;
2089
2090   s = bfd_make_section (abfd, ".gnu.version_r");
2091   if (s == NULL
2092       || ! bfd_set_section_flags (abfd, s, flags | SEC_READONLY)
2093       || ! bfd_set_section_alignment (abfd, s, LOG_FILE_ALIGN))
2094     return false;
2095
2096   s = bfd_make_section (abfd, ".dynsym");
2097   if (s == NULL
2098       || ! bfd_set_section_flags (abfd, s, flags | SEC_READONLY)
2099       || ! bfd_set_section_alignment (abfd, s, LOG_FILE_ALIGN))
2100     return false;
2101
2102   s = bfd_make_section (abfd, ".dynstr");
2103   if (s == NULL
2104       || ! bfd_set_section_flags (abfd, s, flags | SEC_READONLY))
2105     return false;
2106
2107   /* Create a strtab to hold the dynamic symbol names.  */
2108   if (elf_hash_table (info)->dynstr == NULL)
2109     {
2110       elf_hash_table (info)->dynstr = elf_stringtab_init ();
2111       if (elf_hash_table (info)->dynstr == NULL)
2112         return false;
2113     }
2114
2115   s = bfd_make_section (abfd, ".dynamic");
2116   if (s == NULL
2117       || ! bfd_set_section_flags (abfd, s, flags)
2118       || ! bfd_set_section_alignment (abfd, s, LOG_FILE_ALIGN))
2119     return false;
2120
2121   /* The special symbol _DYNAMIC is always set to the start of the
2122      .dynamic section.  This call occurs before we have processed the
2123      symbols for any dynamic object, so we don't have to worry about
2124      overriding a dynamic definition.  We could set _DYNAMIC in a
2125      linker script, but we only want to define it if we are, in fact,
2126      creating a .dynamic section.  We don't want to define it if there
2127      is no .dynamic section, since on some ELF platforms the start up
2128      code examines it to decide how to initialize the process.  */
2129   h = NULL;
2130   if (! (_bfd_generic_link_add_one_symbol
2131          (info, abfd, "_DYNAMIC", BSF_GLOBAL, s, (bfd_vma) 0,
2132           (const char *) NULL, false, get_elf_backend_data (abfd)->collect,
2133           (struct bfd_link_hash_entry **) &h)))
2134     return false;
2135   h->elf_link_hash_flags |= ELF_LINK_HASH_DEF_REGULAR;
2136   h->type = STT_OBJECT;
2137
2138   if (info->shared
2139       && ! _bfd_elf_link_record_dynamic_symbol (info, h))
2140     return false;
2141
2142   bed = get_elf_backend_data (abfd);
2143
2144   s = bfd_make_section (abfd, ".hash");
2145   if (s == NULL
2146       || ! bfd_set_section_flags (abfd, s, flags | SEC_READONLY)
2147       || ! bfd_set_section_alignment (abfd, s, LOG_FILE_ALIGN))
2148     return false;
2149   elf_section_data (s)->this_hdr.sh_entsize = bed->s->sizeof_hash_entry;
2150
2151   /* Let the backend create the rest of the sections.  This lets the
2152      backend set the right flags.  The backend will normally create
2153      the .got and .plt sections.  */
2154   if (! (*bed->elf_backend_create_dynamic_sections) (abfd, info))
2155     return false;
2156
2157   elf_hash_table (info)->dynamic_sections_created = true;
2158
2159   return true;
2160 }
2161
2162 /* Add an entry to the .dynamic table.  */
2163
2164 boolean
2165 elf_add_dynamic_entry (info, tag, val)
2166      struct bfd_link_info *info;
2167      bfd_vma tag;
2168      bfd_vma val;
2169 {
2170   Elf_Internal_Dyn dyn;
2171   bfd *dynobj;
2172   asection *s;
2173   size_t newsize;
2174   bfd_byte *newcontents;
2175
2176   dynobj = elf_hash_table (info)->dynobj;
2177
2178   s = bfd_get_section_by_name (dynobj, ".dynamic");
2179   BFD_ASSERT (s != NULL);
2180
2181   newsize = s->_raw_size + sizeof (Elf_External_Dyn);
2182   newcontents = (bfd_byte *) bfd_realloc (s->contents, newsize);
2183   if (newcontents == NULL)
2184     return false;
2185
2186   dyn.d_tag = tag;
2187   dyn.d_un.d_val = val;
2188   elf_swap_dyn_out (dynobj, &dyn,
2189                     (Elf_External_Dyn *) (newcontents + s->_raw_size));
2190
2191   s->_raw_size = newsize;
2192   s->contents = newcontents;
2193
2194   return true;
2195 }
2196
2197 /* Record a new local dynamic symbol.  */
2198
2199 boolean
2200 elf_link_record_local_dynamic_symbol (info, input_bfd, input_indx)
2201      struct bfd_link_info *info;
2202      bfd *input_bfd;
2203      long input_indx;
2204 {
2205   struct elf_link_local_dynamic_entry *entry;
2206   struct elf_link_hash_table *eht;
2207   struct bfd_strtab_hash *dynstr;
2208   Elf_External_Sym esym;
2209   unsigned long dynstr_index;
2210   char *name;
2211
2212   /* See if the entry exists already.  */
2213   for (entry = elf_hash_table (info)->dynlocal; entry ; entry = entry->next)
2214     if (entry->input_bfd == input_bfd && entry->input_indx == input_indx)
2215       return true;
2216
2217   entry = (struct elf_link_local_dynamic_entry *)
2218     bfd_alloc (input_bfd, sizeof (*entry));
2219   if (entry == NULL)
2220     return false;
2221
2222   /* Go find the symbol, so that we can find it's name.  */
2223   if (bfd_seek (input_bfd,
2224                 (elf_tdata (input_bfd)->symtab_hdr.sh_offset
2225                  + input_indx * sizeof (Elf_External_Sym)),
2226                 SEEK_SET) != 0
2227       || (bfd_read (&esym, sizeof (Elf_External_Sym), 1, input_bfd)
2228           != sizeof (Elf_External_Sym)))
2229     return false;
2230   elf_swap_symbol_in (input_bfd, &esym, &entry->isym);
2231
2232   name = (bfd_elf_string_from_elf_section
2233           (input_bfd, elf_tdata (input_bfd)->symtab_hdr.sh_link,
2234            entry->isym.st_name));
2235
2236   dynstr = elf_hash_table (info)->dynstr;
2237   if (dynstr == NULL)
2238     {
2239       /* Create a strtab to hold the dynamic symbol names.  */
2240       elf_hash_table (info)->dynstr = dynstr = _bfd_elf_stringtab_init ();
2241       if (dynstr == NULL)
2242         return false;
2243     }
2244
2245   dynstr_index = _bfd_stringtab_add (dynstr, name, true, false);
2246   if (dynstr_index == (unsigned long) -1)
2247     return false;
2248   entry->isym.st_name = dynstr_index;
2249
2250   eht = elf_hash_table (info);
2251
2252   entry->next = eht->dynlocal;
2253   eht->dynlocal = entry;
2254   entry->input_bfd = input_bfd;
2255   entry->input_indx = input_indx;
2256   eht->dynsymcount++;
2257
2258   /* Whatever binding the symbol had before, it's now local.  */
2259   entry->isym.st_info
2260     = ELF_ST_INFO (STB_LOCAL, ELF_ST_TYPE (entry->isym.st_info));
2261
2262   /* The dynindx will be set at the end of size_dynamic_sections.  */
2263
2264   return true;
2265 }
2266 \f
2267
2268 /* Read and swap the relocs from the section indicated by SHDR.  This
2269    may be either a REL or a RELA section.  The relocations are
2270    translated into RELA relocations and stored in INTERNAL_RELOCS,
2271    which should have already been allocated to contain enough space.
2272    The EXTERNAL_RELOCS are a buffer where the external form of the
2273    relocations should be stored.
2274
2275    Returns false if something goes wrong.  */
2276
2277 static boolean
2278 elf_link_read_relocs_from_section (abfd, shdr, external_relocs,
2279                                    internal_relocs)
2280      bfd *abfd;
2281      Elf_Internal_Shdr *shdr;
2282      PTR external_relocs;
2283      Elf_Internal_Rela *internal_relocs;
2284 {
2285   struct elf_backend_data *bed;
2286
2287   /* If there aren't any relocations, that's OK.  */
2288   if (!shdr)
2289     return true;
2290
2291   /* Position ourselves at the start of the section.  */
2292   if (bfd_seek (abfd, shdr->sh_offset, SEEK_SET) != 0)
2293     return false;
2294
2295   /* Read the relocations.  */
2296   if (bfd_read (external_relocs, 1, shdr->sh_size, abfd)
2297       != shdr->sh_size)
2298     return false;
2299
2300   bed = get_elf_backend_data (abfd);
2301
2302   /* Convert the external relocations to the internal format.  */
2303   if (shdr->sh_entsize == sizeof (Elf_External_Rel))
2304     {
2305       Elf_External_Rel *erel;
2306       Elf_External_Rel *erelend;
2307       Elf_Internal_Rela *irela;
2308       Elf_Internal_Rel *irel;
2309
2310       erel = (Elf_External_Rel *) external_relocs;
2311       erelend = erel + shdr->sh_size / shdr->sh_entsize;
2312       irela = internal_relocs;
2313       irel = bfd_alloc (abfd, (bed->s->int_rels_per_ext_rel
2314                                * sizeof (Elf_Internal_Rel)));
2315       for (; erel < erelend; erel++, irela += bed->s->int_rels_per_ext_rel)
2316         {
2317           unsigned char i;
2318
2319           if (bed->s->swap_reloc_in)
2320             (*bed->s->swap_reloc_in) (abfd, (bfd_byte *) erel, irel);
2321           else
2322             elf_swap_reloc_in (abfd, erel, irel);
2323
2324           for (i = 0; i < bed->s->int_rels_per_ext_rel; ++i)
2325             {
2326               irela[i].r_offset = irel[i].r_offset;
2327               irela[i].r_info = irel[i].r_info;
2328               irela[i].r_addend = 0;
2329             }
2330         }
2331     }
2332   else
2333     {
2334       Elf_External_Rela *erela;
2335       Elf_External_Rela *erelaend;
2336       Elf_Internal_Rela *irela;
2337
2338       BFD_ASSERT (shdr->sh_entsize == sizeof (Elf_External_Rela));
2339
2340       erela = (Elf_External_Rela *) external_relocs;
2341       erelaend = erela + shdr->sh_size / shdr->sh_entsize;
2342       irela = internal_relocs;
2343       for (; erela < erelaend; erela++, irela += bed->s->int_rels_per_ext_rel)
2344         {
2345           if (bed->s->swap_reloca_in)
2346             (*bed->s->swap_reloca_in) (abfd, (bfd_byte *) erela, irela);
2347           else
2348             elf_swap_reloca_in (abfd, erela, irela);
2349         }
2350     }
2351
2352   return true;
2353 }
2354
2355 /* Read and swap the relocs for a section O.  They may have been
2356    cached.  If the EXTERNAL_RELOCS and INTERNAL_RELOCS arguments are
2357    not NULL, they are used as buffers to read into.  They are known to
2358    be large enough.  If the INTERNAL_RELOCS relocs argument is NULL,
2359    the return value is allocated using either malloc or bfd_alloc,
2360    according to the KEEP_MEMORY argument.  If O has two relocation
2361    sections (both REL and RELA relocations), then the REL_HDR
2362    relocations will appear first in INTERNAL_RELOCS, followed by the
2363    REL_HDR2 relocations.  */
2364
2365 Elf_Internal_Rela *
2366 NAME(_bfd_elf,link_read_relocs) (abfd, o, external_relocs, internal_relocs,
2367                                  keep_memory)
2368      bfd *abfd;
2369      asection *o;
2370      PTR external_relocs;
2371      Elf_Internal_Rela *internal_relocs;
2372      boolean keep_memory;
2373 {
2374   Elf_Internal_Shdr *rel_hdr;
2375   PTR alloc1 = NULL;
2376   Elf_Internal_Rela *alloc2 = NULL;
2377   struct elf_backend_data *bed = get_elf_backend_data (abfd);
2378
2379   if (elf_section_data (o)->relocs != NULL)
2380     return elf_section_data (o)->relocs;
2381
2382   if (o->reloc_count == 0)
2383     return NULL;
2384
2385   rel_hdr = &elf_section_data (o)->rel_hdr;
2386
2387   if (internal_relocs == NULL)
2388     {
2389       size_t size;
2390
2391       size = (o->reloc_count * bed->s->int_rels_per_ext_rel 
2392               * sizeof (Elf_Internal_Rela));
2393       if (keep_memory)
2394         internal_relocs = (Elf_Internal_Rela *) bfd_alloc (abfd, size);
2395       else
2396         internal_relocs = alloc2 = (Elf_Internal_Rela *) bfd_malloc (size);
2397       if (internal_relocs == NULL)
2398         goto error_return;
2399     }
2400
2401   if (external_relocs == NULL)
2402     {
2403       size_t size = (size_t) rel_hdr->sh_size;
2404
2405       if (elf_section_data (o)->rel_hdr2)
2406         size += (size_t) elf_section_data (o)->rel_hdr2->sh_size;
2407       alloc1 = (PTR) bfd_malloc (size);
2408       if (alloc1 == NULL)
2409         goto error_return;
2410       external_relocs = alloc1;
2411     }
2412
2413   if (!elf_link_read_relocs_from_section (abfd, rel_hdr,
2414                                           external_relocs,
2415                                           internal_relocs))
2416     goto error_return;
2417   if (!elf_link_read_relocs_from_section 
2418       (abfd, 
2419        elf_section_data (o)->rel_hdr2,
2420        ((bfd_byte *) external_relocs) + rel_hdr->sh_size,
2421        internal_relocs + (rel_hdr->sh_size / rel_hdr->sh_entsize
2422                           * bed->s->int_rels_per_ext_rel)))
2423     goto error_return;
2424
2425   /* Cache the results for next time, if we can.  */
2426   if (keep_memory)
2427     elf_section_data (o)->relocs = internal_relocs;
2428
2429   if (alloc1 != NULL)
2430     free (alloc1);
2431
2432   /* Don't free alloc2, since if it was allocated we are passing it
2433      back (under the name of internal_relocs).  */
2434
2435   return internal_relocs;
2436
2437  error_return:
2438   if (alloc1 != NULL)
2439     free (alloc1);
2440   if (alloc2 != NULL)
2441     free (alloc2);
2442   return NULL;
2443 }
2444 \f
2445
2446 /* Record an assignment to a symbol made by a linker script.  We need
2447    this in case some dynamic object refers to this symbol.  */
2448
2449 /*ARGSUSED*/
2450 boolean
2451 NAME(bfd_elf,record_link_assignment) (output_bfd, info, name, provide)
2452      bfd *output_bfd ATTRIBUTE_UNUSED;
2453      struct bfd_link_info *info;
2454      const char *name;
2455      boolean provide;
2456 {
2457   struct elf_link_hash_entry *h;
2458
2459   if (info->hash->creator->flavour != bfd_target_elf_flavour)
2460     return true;
2461
2462   h = elf_link_hash_lookup (elf_hash_table (info), name, true, true, false);
2463   if (h == NULL)
2464     return false;
2465
2466   if (h->root.type == bfd_link_hash_new)
2467     h->elf_link_hash_flags &=~ ELF_LINK_NON_ELF;
2468
2469   /* If this symbol is being provided by the linker script, and it is
2470      currently defined by a dynamic object, but not by a regular
2471      object, then mark it as undefined so that the generic linker will
2472      force the correct value.  */
2473   if (provide
2474       && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC) != 0
2475       && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) == 0)
2476     h->root.type = bfd_link_hash_undefined;
2477
2478   /* If this symbol is not being provided by the linker script, and it is
2479      currently defined by a dynamic object, but not by a regular object,
2480      then clear out any version information because the symbol will not be
2481      associated with the dynamic object any more.  */
2482   if (!provide
2483       && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC) != 0
2484       && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) == 0)
2485     h->verinfo.verdef = NULL;
2486
2487   h->elf_link_hash_flags |= ELF_LINK_HASH_DEF_REGULAR;
2488
2489   /* When possible, keep the original type of the symbol */
2490   if (h->type == STT_NOTYPE)
2491     h->type = STT_OBJECT;
2492
2493   if (((h->elf_link_hash_flags & (ELF_LINK_HASH_DEF_DYNAMIC
2494                                   | ELF_LINK_HASH_REF_DYNAMIC)) != 0
2495        || info->shared)
2496       && h->dynindx == -1)
2497     {
2498       if (! _bfd_elf_link_record_dynamic_symbol (info, h))
2499         return false;
2500
2501       /* If this is a weak defined symbol, and we know a corresponding
2502          real symbol from the same dynamic object, make sure the real
2503          symbol is also made into a dynamic symbol.  */
2504       if (h->weakdef != NULL
2505           && h->weakdef->dynindx == -1)
2506         {
2507           if (! _bfd_elf_link_record_dynamic_symbol (info, h->weakdef))
2508             return false;
2509         }
2510     }
2511
2512   return true;
2513 }
2514 \f
2515 /* This structure is used to pass information to
2516    elf_link_assign_sym_version.  */
2517
2518 struct elf_assign_sym_version_info
2519 {
2520   /* Output BFD.  */
2521   bfd *output_bfd;
2522   /* General link information.  */
2523   struct bfd_link_info *info;
2524   /* Version tree.  */
2525   struct bfd_elf_version_tree *verdefs;
2526   /* Whether we are exporting all dynamic symbols.  */
2527   boolean export_dynamic;
2528   /* Whether we had a failure.  */
2529   boolean failed;
2530 };
2531
2532 /* This structure is used to pass information to
2533    elf_link_find_version_dependencies.  */
2534
2535 struct elf_find_verdep_info
2536 {
2537   /* Output BFD.  */
2538   bfd *output_bfd;
2539   /* General link information.  */
2540   struct bfd_link_info *info;
2541   /* The number of dependencies.  */
2542   unsigned int vers;
2543   /* Whether we had a failure.  */
2544   boolean failed;
2545 };
2546
2547 /* Array used to determine the number of hash table buckets to use
2548    based on the number of symbols there are.  If there are fewer than
2549    3 symbols we use 1 bucket, fewer than 17 symbols we use 3 buckets,
2550    fewer than 37 we use 17 buckets, and so forth.  We never use more
2551    than 32771 buckets.  */
2552
2553 static const size_t elf_buckets[] =
2554 {
2555   1, 3, 17, 37, 67, 97, 131, 197, 263, 521, 1031, 2053, 4099, 8209,
2556   16411, 32771, 0
2557 };
2558
2559 /* Compute bucket count for hashing table.  We do not use a static set
2560    of possible tables sizes anymore.  Instead we determine for all
2561    possible reasonable sizes of the table the outcome (i.e., the
2562    number of collisions etc) and choose the best solution.  The
2563    weighting functions are not too simple to allow the table to grow
2564    without bounds.  Instead one of the weighting factors is the size.
2565    Therefore the result is always a good payoff between few collisions
2566    (= short chain lengths) and table size.  */
2567 static size_t
2568 compute_bucket_count (info)
2569      struct bfd_link_info *info;
2570 {
2571   size_t dynsymcount = elf_hash_table (info)->dynsymcount;
2572   size_t best_size = 0;
2573   unsigned long int *hashcodes;
2574   unsigned long int *hashcodesp;
2575   unsigned long int i;
2576
2577   /* Compute the hash values for all exported symbols.  At the same
2578      time store the values in an array so that we could use them for
2579      optimizations.  */
2580   hashcodes = (unsigned long int *) bfd_malloc (dynsymcount
2581                                                 * sizeof (unsigned long int));
2582   if (hashcodes == NULL)
2583     return 0;
2584   hashcodesp = hashcodes;
2585
2586   /* Put all hash values in HASHCODES.  */
2587   elf_link_hash_traverse (elf_hash_table (info),
2588                           elf_collect_hash_codes, &hashcodesp);
2589
2590 /* We have a problem here.  The following code to optimize the table
2591    size requires an integer type with more the 32 bits.  If
2592    BFD_HOST_U_64_BIT is set we know about such a type.  */
2593 #ifdef BFD_HOST_U_64_BIT
2594   if (info->optimize == true)
2595     {
2596       unsigned long int nsyms = hashcodesp - hashcodes;
2597       size_t minsize;
2598       size_t maxsize;
2599       BFD_HOST_U_64_BIT best_chlen = ~((BFD_HOST_U_64_BIT) 0);
2600       unsigned long int *counts ;
2601
2602       /* Possible optimization parameters: if we have NSYMS symbols we say
2603          that the hashing table must at least have NSYMS/4 and at most
2604          2*NSYMS buckets.  */
2605       minsize = nsyms / 4;
2606       if (minsize == 0)
2607         minsize = 1;
2608       best_size = maxsize = nsyms * 2;
2609
2610       /* Create array where we count the collisions in.  We must use bfd_malloc
2611          since the size could be large.  */
2612       counts = (unsigned long int *) bfd_malloc (maxsize
2613                                                  * sizeof (unsigned long int));
2614       if (counts == NULL)
2615         {
2616           free (hashcodes);
2617           return 0;
2618         }
2619
2620       /* Compute the "optimal" size for the hash table.  The criteria is a
2621          minimal chain length.  The minor criteria is (of course) the size
2622          of the table.  */
2623       for (i = minsize; i < maxsize; ++i)
2624         {
2625           /* Walk through the array of hashcodes and count the collisions.  */
2626           BFD_HOST_U_64_BIT max;
2627           unsigned long int j;
2628           unsigned long int fact;
2629
2630           memset (counts, '\0', i * sizeof (unsigned long int));
2631
2632           /* Determine how often each hash bucket is used.  */
2633           for (j = 0; j < nsyms; ++j)
2634             ++counts[hashcodes[j] % i];
2635
2636           /* For the weight function we need some information about the
2637              pagesize on the target.  This is information need not be 100%
2638              accurate.  Since this information is not available (so far) we
2639              define it here to a reasonable default value.  If it is crucial
2640              to have a better value some day simply define this value.  */
2641 # ifndef BFD_TARGET_PAGESIZE
2642 #  define BFD_TARGET_PAGESIZE   (4096)
2643 # endif
2644
2645           /* We in any case need 2 + NSYMS entries for the size values and
2646              the chains.  */
2647           max = (2 + nsyms) * (ARCH_SIZE / 8);
2648
2649 # if 1
2650           /* Variant 1: optimize for short chains.  We add the squares
2651              of all the chain lengths (which favous many small chain
2652              over a few long chains).  */
2653           for (j = 0; j < i; ++j)
2654             max += counts[j] * counts[j];
2655
2656           /* This adds penalties for the overall size of the table.  */
2657           fact = i / (BFD_TARGET_PAGESIZE / (ARCH_SIZE / 8)) + 1;
2658           max *= fact * fact;
2659 # else
2660           /* Variant 2: Optimize a lot more for small table.  Here we
2661              also add squares of the size but we also add penalties for
2662              empty slots (the +1 term).  */
2663           for (j = 0; j < i; ++j)
2664             max += (1 + counts[j]) * (1 + counts[j]);
2665
2666           /* The overall size of the table is considered, but not as
2667              strong as in variant 1, where it is squared.  */
2668           fact = i / (BFD_TARGET_PAGESIZE / (ARCH_SIZE / 8)) + 1;
2669           max *= fact;
2670 # endif
2671
2672           /* Compare with current best results.  */
2673           if (max < best_chlen)
2674             {
2675               best_chlen = max;
2676               best_size = i;
2677             }
2678         }
2679
2680       free (counts);
2681     }
2682   else
2683 #endif /* defined (BFD_HOST_U_64_BIT) */
2684     {
2685       /* This is the fallback solution if no 64bit type is available or if we
2686          are not supposed to spend much time on optimizations.  We select the
2687          bucket count using a fixed set of numbers.  */
2688       for (i = 0; elf_buckets[i] != 0; i++)
2689         {
2690           best_size = elf_buckets[i];
2691           if (dynsymcount < elf_buckets[i + 1])
2692             break;
2693         }
2694     }
2695
2696   /* Free the arrays we needed.  */
2697   free (hashcodes);
2698
2699   return best_size;
2700 }
2701
2702 /* Set up the sizes and contents of the ELF dynamic sections.  This is
2703    called by the ELF linker emulation before_allocation routine.  We
2704    must set the sizes of the sections before the linker sets the
2705    addresses of the various sections.  */
2706
2707 boolean
2708 NAME(bfd_elf,size_dynamic_sections) (output_bfd, soname, rpath,
2709                                      export_dynamic, filter_shlib,
2710                                      auxiliary_filters, info, sinterpptr,
2711                                      verdefs)
2712      bfd *output_bfd;
2713      const char *soname;
2714      const char *rpath;
2715      boolean export_dynamic;
2716      const char *filter_shlib;
2717      const char * const *auxiliary_filters;
2718      struct bfd_link_info *info;
2719      asection **sinterpptr;
2720      struct bfd_elf_version_tree *verdefs;
2721 {
2722   bfd_size_type soname_indx;
2723   bfd *dynobj;
2724   struct elf_backend_data *bed;
2725   struct elf_assign_sym_version_info asvinfo;
2726
2727   *sinterpptr = NULL;
2728
2729   soname_indx = (bfd_size_type) -1;
2730
2731   if (info->hash->creator->flavour != bfd_target_elf_flavour)
2732     return true;
2733
2734   /* The backend may have to create some sections regardless of whether
2735      we're dynamic or not.  */
2736   bed = get_elf_backend_data (output_bfd);
2737   if (bed->elf_backend_always_size_sections
2738       && ! (*bed->elf_backend_always_size_sections) (output_bfd, info))
2739     return false;
2740
2741   dynobj = elf_hash_table (info)->dynobj;
2742
2743   /* If there were no dynamic objects in the link, there is nothing to
2744      do here.  */
2745   if (dynobj == NULL)
2746     return true;
2747
2748   if (elf_hash_table (info)->dynamic_sections_created)
2749     {
2750       struct elf_info_failed eif;
2751       struct elf_link_hash_entry *h;
2752       bfd_size_type strsize;
2753
2754       *sinterpptr = bfd_get_section_by_name (dynobj, ".interp");
2755       BFD_ASSERT (*sinterpptr != NULL || info->shared);
2756
2757       if (soname != NULL)
2758         {
2759           soname_indx = _bfd_stringtab_add (elf_hash_table (info)->dynstr,
2760                                             soname, true, true);
2761           if (soname_indx == (bfd_size_type) -1
2762               || ! elf_add_dynamic_entry (info, DT_SONAME, soname_indx))
2763             return false;
2764         }
2765
2766       if (info->symbolic)
2767         {
2768           if (! elf_add_dynamic_entry (info, DT_SYMBOLIC, 0))
2769             return false;
2770         }
2771
2772       if (rpath != NULL)
2773         {
2774           bfd_size_type indx;
2775
2776           indx = _bfd_stringtab_add (elf_hash_table (info)->dynstr, rpath,
2777                                      true, true);
2778           if (indx == (bfd_size_type) -1
2779               || ! elf_add_dynamic_entry (info, DT_RPATH, indx))
2780             return false;
2781         }
2782
2783       if (filter_shlib != NULL)
2784         {
2785           bfd_size_type indx;
2786
2787           indx = _bfd_stringtab_add (elf_hash_table (info)->dynstr,
2788                                      filter_shlib, true, true);
2789           if (indx == (bfd_size_type) -1
2790               || ! elf_add_dynamic_entry (info, DT_FILTER, indx))
2791             return false;
2792         }
2793
2794       if (auxiliary_filters != NULL)
2795         {
2796           const char * const *p;
2797
2798           for (p = auxiliary_filters; *p != NULL; p++)
2799             {
2800               bfd_size_type indx;
2801
2802               indx = _bfd_stringtab_add (elf_hash_table (info)->dynstr,
2803                                          *p, true, true);
2804               if (indx == (bfd_size_type) -1
2805                   || ! elf_add_dynamic_entry (info, DT_AUXILIARY, indx))
2806                 return false;
2807             }
2808         }
2809
2810       /* If we are supposed to export all symbols into the dynamic symbol
2811          table (this is not the normal case), then do so.  */
2812       if (export_dynamic)
2813         {
2814           struct elf_info_failed eif;
2815
2816           eif.failed = false;
2817           eif.info = info;
2818           elf_link_hash_traverse (elf_hash_table (info), elf_export_symbol,
2819                                   (PTR) &eif);
2820           if (eif.failed)
2821             return false;
2822         }
2823
2824       /* Attach all the symbols to their version information.  */
2825       asvinfo.output_bfd = output_bfd;
2826       asvinfo.info = info;
2827       asvinfo.verdefs = verdefs;
2828       asvinfo.export_dynamic = export_dynamic;
2829       asvinfo.failed = false;
2830
2831       elf_link_hash_traverse (elf_hash_table (info),
2832                               elf_link_assign_sym_version,
2833                               (PTR) &asvinfo);
2834       if (asvinfo.failed)
2835         return false;
2836
2837       /* Find all symbols which were defined in a dynamic object and make
2838          the backend pick a reasonable value for them.  */
2839       eif.failed = false;
2840       eif.info = info;
2841       elf_link_hash_traverse (elf_hash_table (info),
2842                               elf_adjust_dynamic_symbol,
2843                               (PTR) &eif);
2844       if (eif.failed)
2845         return false;
2846
2847       /* Add some entries to the .dynamic section.  We fill in some of the
2848          values later, in elf_bfd_final_link, but we must add the entries
2849          now so that we know the final size of the .dynamic section.  */
2850
2851       /* If there are initialization and/or finalization functions to
2852          call then add the corresponding DT_INIT/DT_FINI entries.  */
2853       h = (info->init_function
2854            ? elf_link_hash_lookup (elf_hash_table (info), 
2855                                    info->init_function, false,
2856                                    false, false)
2857            : NULL);
2858       if (h != NULL
2859           && (h->elf_link_hash_flags & (ELF_LINK_HASH_REF_REGULAR
2860                                         | ELF_LINK_HASH_DEF_REGULAR)) != 0)
2861         {
2862           if (! elf_add_dynamic_entry (info, DT_INIT, 0))
2863             return false;
2864         }
2865       h = (info->fini_function
2866            ? elf_link_hash_lookup (elf_hash_table (info), 
2867                                    info->fini_function, false,
2868                                    false, false)
2869            : NULL);
2870       if (h != NULL
2871           && (h->elf_link_hash_flags & (ELF_LINK_HASH_REF_REGULAR
2872                                         | ELF_LINK_HASH_DEF_REGULAR)) != 0)
2873         {
2874           if (! elf_add_dynamic_entry (info, DT_FINI, 0))
2875             return false;
2876         }
2877
2878       strsize = _bfd_stringtab_size (elf_hash_table (info)->dynstr);
2879       if (! elf_add_dynamic_entry (info, DT_HASH, 0)
2880           || ! elf_add_dynamic_entry (info, DT_STRTAB, 0)
2881           || ! elf_add_dynamic_entry (info, DT_SYMTAB, 0)
2882           || ! elf_add_dynamic_entry (info, DT_STRSZ, strsize)
2883           || ! elf_add_dynamic_entry (info, DT_SYMENT,
2884                                       sizeof (Elf_External_Sym)))
2885         return false;
2886     }
2887
2888   /* The backend must work out the sizes of all the other dynamic
2889      sections.  */
2890   if (bed->elf_backend_size_dynamic_sections
2891       && ! (*bed->elf_backend_size_dynamic_sections) (output_bfd, info))
2892     return false;
2893
2894   if (elf_hash_table (info)->dynamic_sections_created)
2895     {
2896       size_t dynsymcount;
2897       asection *s;
2898       size_t bucketcount = 0;
2899       Elf_Internal_Sym isym;
2900       size_t hash_entry_size;
2901
2902       /* Set up the version definition section.  */
2903       s = bfd_get_section_by_name (dynobj, ".gnu.version_d");
2904       BFD_ASSERT (s != NULL);
2905
2906       /* We may have created additional version definitions if we are
2907          just linking a regular application.  */
2908       verdefs = asvinfo.verdefs;
2909
2910       if (verdefs == NULL)
2911         _bfd_strip_section_from_output (info, s);
2912       else
2913         {
2914           unsigned int cdefs;
2915           bfd_size_type size;
2916           struct bfd_elf_version_tree *t;
2917           bfd_byte *p;
2918           Elf_Internal_Verdef def;
2919           Elf_Internal_Verdaux defaux;
2920
2921           cdefs = 0;
2922           size = 0;
2923
2924           /* Make space for the base version.  */
2925           size += sizeof (Elf_External_Verdef);
2926           size += sizeof (Elf_External_Verdaux);
2927           ++cdefs;
2928
2929           for (t = verdefs; t != NULL; t = t->next)
2930             {
2931               struct bfd_elf_version_deps *n;
2932
2933               size += sizeof (Elf_External_Verdef);
2934               size += sizeof (Elf_External_Verdaux);
2935               ++cdefs;
2936
2937               for (n = t->deps; n != NULL; n = n->next)
2938                 size += sizeof (Elf_External_Verdaux);
2939             }
2940
2941           s->_raw_size = size;
2942           s->contents = (bfd_byte *) bfd_alloc (output_bfd, s->_raw_size);
2943           if (s->contents == NULL && s->_raw_size != 0)
2944             return false;
2945
2946           /* Fill in the version definition section.  */
2947
2948           p = s->contents;
2949
2950           def.vd_version = VER_DEF_CURRENT;
2951           def.vd_flags = VER_FLG_BASE;
2952           def.vd_ndx = 1;
2953           def.vd_cnt = 1;
2954           def.vd_aux = sizeof (Elf_External_Verdef);
2955           def.vd_next = (sizeof (Elf_External_Verdef)
2956                          + sizeof (Elf_External_Verdaux));
2957
2958           if (soname_indx != (bfd_size_type) -1)
2959             {
2960               def.vd_hash = bfd_elf_hash (soname);
2961               defaux.vda_name = soname_indx;
2962             }
2963           else
2964             {
2965               const char *name;
2966               bfd_size_type indx;
2967
2968               name = output_bfd->filename;
2969               def.vd_hash = bfd_elf_hash (name);
2970               indx = _bfd_stringtab_add (elf_hash_table (info)->dynstr,
2971                                             name, true, false);
2972               if (indx == (bfd_size_type) -1)
2973                 return false;
2974               defaux.vda_name = indx;
2975             }
2976           defaux.vda_next = 0;
2977
2978           _bfd_elf_swap_verdef_out (output_bfd, &def,
2979                                     (Elf_External_Verdef *)p);
2980           p += sizeof (Elf_External_Verdef);
2981           _bfd_elf_swap_verdaux_out (output_bfd, &defaux,
2982                                      (Elf_External_Verdaux *) p);
2983           p += sizeof (Elf_External_Verdaux);
2984
2985           for (t = verdefs; t != NULL; t = t->next)
2986             {
2987               unsigned int cdeps;
2988               struct bfd_elf_version_deps *n;
2989               struct elf_link_hash_entry *h;
2990
2991               cdeps = 0;
2992               for (n = t->deps; n != NULL; n = n->next)
2993                 ++cdeps;
2994
2995               /* Add a symbol representing this version.  */
2996               h = NULL;
2997               if (! (_bfd_generic_link_add_one_symbol
2998                      (info, dynobj, t->name, BSF_GLOBAL, bfd_abs_section_ptr,
2999                       (bfd_vma) 0, (const char *) NULL, false,
3000                       get_elf_backend_data (dynobj)->collect,
3001                       (struct bfd_link_hash_entry **) &h)))
3002                 return false;
3003               h->elf_link_hash_flags &= ~ ELF_LINK_NON_ELF;
3004               h->elf_link_hash_flags |= ELF_LINK_HASH_DEF_REGULAR;
3005               h->type = STT_OBJECT;
3006               h->verinfo.vertree = t;
3007
3008               if (! _bfd_elf_link_record_dynamic_symbol (info, h))
3009                 return false;
3010
3011               def.vd_version = VER_DEF_CURRENT;
3012               def.vd_flags = 0;
3013               if (t->globals == NULL && t->locals == NULL && ! t->used)
3014                 def.vd_flags |= VER_FLG_WEAK;
3015               def.vd_ndx = t->vernum + 1;
3016               def.vd_cnt = cdeps + 1;
3017               def.vd_hash = bfd_elf_hash (t->name);
3018               def.vd_aux = sizeof (Elf_External_Verdef);
3019               if (t->next != NULL)
3020                 def.vd_next = (sizeof (Elf_External_Verdef)
3021                                + (cdeps + 1) * sizeof (Elf_External_Verdaux));
3022               else
3023                 def.vd_next = 0;
3024
3025               _bfd_elf_swap_verdef_out (output_bfd, &def,
3026                                         (Elf_External_Verdef *) p);
3027               p += sizeof (Elf_External_Verdef);
3028
3029               defaux.vda_name = h->dynstr_index;
3030               if (t->deps == NULL)
3031                 defaux.vda_next = 0;
3032               else
3033                 defaux.vda_next = sizeof (Elf_External_Verdaux);
3034               t->name_indx = defaux.vda_name;
3035
3036               _bfd_elf_swap_verdaux_out (output_bfd, &defaux,
3037                                          (Elf_External_Verdaux *) p);
3038               p += sizeof (Elf_External_Verdaux);
3039
3040               for (n = t->deps; n != NULL; n = n->next)
3041                 {
3042                   if (n->version_needed == NULL)
3043                     {
3044                       /* This can happen if there was an error in the
3045                          version script.  */
3046                       defaux.vda_name = 0;
3047                     }
3048                   else
3049                     defaux.vda_name = n->version_needed->name_indx;
3050                   if (n->next == NULL)
3051                     defaux.vda_next = 0;
3052                   else
3053                     defaux.vda_next = sizeof (Elf_External_Verdaux);
3054
3055                   _bfd_elf_swap_verdaux_out (output_bfd, &defaux,
3056                                              (Elf_External_Verdaux *) p);
3057                   p += sizeof (Elf_External_Verdaux);
3058                 }
3059             }
3060
3061           if (! elf_add_dynamic_entry (info, DT_VERDEF, 0)
3062               || ! elf_add_dynamic_entry (info, DT_VERDEFNUM, cdefs))
3063             return false;
3064
3065           elf_tdata (output_bfd)->cverdefs = cdefs;
3066         }
3067
3068       /* Work out the size of the version reference section.  */
3069
3070       s = bfd_get_section_by_name (dynobj, ".gnu.version_r");
3071       BFD_ASSERT (s != NULL);
3072       {
3073         struct elf_find_verdep_info sinfo;
3074
3075         sinfo.output_bfd = output_bfd;
3076         sinfo.info = info;
3077         sinfo.vers = elf_tdata (output_bfd)->cverdefs;
3078         if (sinfo.vers == 0)
3079           sinfo.vers = 1;
3080         sinfo.failed = false;
3081
3082         elf_link_hash_traverse (elf_hash_table (info),
3083                                 elf_link_find_version_dependencies,
3084                                 (PTR) &sinfo);
3085
3086         if (elf_tdata (output_bfd)->verref == NULL)
3087           _bfd_strip_section_from_output (info, s);
3088         else
3089           {
3090             Elf_Internal_Verneed *t;
3091             unsigned int size;
3092             unsigned int crefs;
3093             bfd_byte *p;
3094
3095             /* Build the version definition section.  */
3096             size = 0;
3097             crefs = 0;
3098             for (t = elf_tdata (output_bfd)->verref;
3099                  t != NULL;
3100                  t = t->vn_nextref)
3101               {
3102                 Elf_Internal_Vernaux *a;
3103
3104                 size += sizeof (Elf_External_Verneed);
3105                 ++crefs;
3106                 for (a = t->vn_auxptr; a != NULL; a = a->vna_nextptr)
3107                   size += sizeof (Elf_External_Vernaux);
3108               }
3109
3110             s->_raw_size = size;
3111             s->contents = (bfd_byte *) bfd_alloc (output_bfd, size);
3112             if (s->contents == NULL)
3113               return false;
3114
3115             p = s->contents;
3116             for (t = elf_tdata (output_bfd)->verref;
3117                  t != NULL;
3118                  t = t->vn_nextref)
3119               {
3120                 unsigned int caux;
3121                 Elf_Internal_Vernaux *a;
3122                 bfd_size_type indx;
3123
3124                 caux = 0;
3125                 for (a = t->vn_auxptr; a != NULL; a = a->vna_nextptr)
3126                   ++caux;
3127
3128                 t->vn_version = VER_NEED_CURRENT;
3129                 t->vn_cnt = caux;
3130                 if (elf_dt_name (t->vn_bfd) != NULL)
3131                   indx = _bfd_stringtab_add (elf_hash_table (info)->dynstr,
3132                                              elf_dt_name (t->vn_bfd),
3133                                              true, false);
3134                 else
3135                   indx = _bfd_stringtab_add (elf_hash_table (info)->dynstr,
3136                                              t->vn_bfd->filename, true, false);
3137                 if (indx == (bfd_size_type) -1)
3138                   return false;
3139                 t->vn_file = indx;
3140                 t->vn_aux = sizeof (Elf_External_Verneed);
3141                 if (t->vn_nextref == NULL)
3142                   t->vn_next = 0;
3143                 else
3144                   t->vn_next = (sizeof (Elf_External_Verneed)
3145                                 + caux * sizeof (Elf_External_Vernaux));
3146
3147                 _bfd_elf_swap_verneed_out (output_bfd, t,
3148                                            (Elf_External_Verneed *) p);
3149                 p += sizeof (Elf_External_Verneed);
3150
3151                 for (a = t->vn_auxptr; a != NULL; a = a->vna_nextptr)
3152                   {
3153                     a->vna_hash = bfd_elf_hash (a->vna_nodename);
3154                     indx = _bfd_stringtab_add (elf_hash_table (info)->dynstr,
3155                                                a->vna_nodename, true, false);
3156                     if (indx == (bfd_size_type) -1)
3157                       return false;
3158                     a->vna_name = indx;
3159                     if (a->vna_nextptr == NULL)
3160                       a->vna_next = 0;
3161                     else
3162                       a->vna_next = sizeof (Elf_External_Vernaux);
3163
3164                     _bfd_elf_swap_vernaux_out (output_bfd, a,
3165                                                (Elf_External_Vernaux *) p);
3166                     p += sizeof (Elf_External_Vernaux);
3167                   }
3168               }
3169
3170             if (! elf_add_dynamic_entry (info, DT_VERNEED, 0)
3171                 || ! elf_add_dynamic_entry (info, DT_VERNEEDNUM, crefs))
3172               return false;
3173
3174             elf_tdata (output_bfd)->cverrefs = crefs;
3175           }
3176       }
3177
3178       /* Assign dynsym indicies.  In a shared library we generate a 
3179          section symbol for each output section, which come first.
3180          Next come all of the back-end allocated local dynamic syms,
3181          followed by the rest of the global symbols.  */
3182
3183       dynsymcount = _bfd_elf_link_renumber_dynsyms (output_bfd, info);
3184
3185       /* Work out the size of the symbol version section.  */
3186       s = bfd_get_section_by_name (dynobj, ".gnu.version");
3187       BFD_ASSERT (s != NULL);
3188       if (dynsymcount == 0
3189           || (verdefs == NULL && elf_tdata (output_bfd)->verref == NULL))
3190         {
3191           _bfd_strip_section_from_output (info, s);
3192           /* The DYNSYMCOUNT might have changed if we were going to
3193              output a dynamic symbol table entry for S.  */
3194           dynsymcount = _bfd_elf_link_renumber_dynsyms (output_bfd, info);
3195         }
3196       else
3197         {
3198           s->_raw_size = dynsymcount * sizeof (Elf_External_Versym);
3199           s->contents = (bfd_byte *) bfd_zalloc (output_bfd, s->_raw_size);
3200           if (s->contents == NULL)
3201             return false;
3202
3203           if (! elf_add_dynamic_entry (info, DT_VERSYM, 0))
3204             return false;
3205         }
3206
3207       /* Set the size of the .dynsym and .hash sections.  We counted
3208          the number of dynamic symbols in elf_link_add_object_symbols.
3209          We will build the contents of .dynsym and .hash when we build
3210          the final symbol table, because until then we do not know the
3211          correct value to give the symbols.  We built the .dynstr
3212          section as we went along in elf_link_add_object_symbols.  */
3213       s = bfd_get_section_by_name (dynobj, ".dynsym");
3214       BFD_ASSERT (s != NULL);
3215       s->_raw_size = dynsymcount * sizeof (Elf_External_Sym);
3216       s->contents = (bfd_byte *) bfd_alloc (output_bfd, s->_raw_size);
3217       if (s->contents == NULL && s->_raw_size != 0)
3218         return false;
3219
3220       /* The first entry in .dynsym is a dummy symbol.  */
3221       isym.st_value = 0;
3222       isym.st_size = 0;
3223       isym.st_name = 0;
3224       isym.st_info = 0;
3225       isym.st_other = 0;
3226       isym.st_shndx = 0;
3227       elf_swap_symbol_out (output_bfd, &isym,
3228                            (PTR) (Elf_External_Sym *) s->contents);
3229
3230       /* Compute the size of the hashing table.  As a side effect this
3231          computes the hash values for all the names we export.  */
3232       bucketcount = compute_bucket_count (info);
3233
3234       s = bfd_get_section_by_name (dynobj, ".hash");
3235       BFD_ASSERT (s != NULL);
3236       hash_entry_size = elf_section_data (s)->this_hdr.sh_entsize;
3237       s->_raw_size = ((2 + bucketcount + dynsymcount) * hash_entry_size);
3238       s->contents = (bfd_byte *) bfd_alloc (output_bfd, s->_raw_size);
3239       if (s->contents == NULL)
3240         return false;
3241       memset (s->contents, 0, (size_t) s->_raw_size);
3242
3243       bfd_put (8 * hash_entry_size, output_bfd, bucketcount, s->contents);
3244       bfd_put (8 * hash_entry_size, output_bfd, dynsymcount, 
3245                s->contents + hash_entry_size);
3246
3247       elf_hash_table (info)->bucketcount = bucketcount;
3248
3249       s = bfd_get_section_by_name (dynobj, ".dynstr");
3250       BFD_ASSERT (s != NULL);
3251       s->_raw_size = _bfd_stringtab_size (elf_hash_table (info)->dynstr);
3252
3253       if (! elf_add_dynamic_entry (info, DT_NULL, 0))
3254         return false;
3255     }
3256
3257   return true;
3258 }
3259 \f
3260 /* Fix up the flags for a symbol.  This handles various cases which
3261    can only be fixed after all the input files are seen.  This is
3262    currently called by both adjust_dynamic_symbol and
3263    assign_sym_version, which is unnecessary but perhaps more robust in
3264    the face of future changes.  */
3265
3266 static boolean
3267 elf_fix_symbol_flags (h, eif)
3268      struct elf_link_hash_entry *h;
3269      struct elf_info_failed *eif;
3270 {
3271   /* If this symbol was mentioned in a non-ELF file, try to set
3272      DEF_REGULAR and REF_REGULAR correctly.  This is the only way to
3273      permit a non-ELF file to correctly refer to a symbol defined in
3274      an ELF dynamic object.  */
3275   if ((h->elf_link_hash_flags & ELF_LINK_NON_ELF) != 0)
3276     {
3277       if (h->root.type != bfd_link_hash_defined
3278           && h->root.type != bfd_link_hash_defweak)
3279         h->elf_link_hash_flags |= (ELF_LINK_HASH_REF_REGULAR
3280                                    | ELF_LINK_HASH_REF_REGULAR_NONWEAK);
3281       else
3282         {
3283           if (h->root.u.def.section->owner != NULL
3284               && (bfd_get_flavour (h->root.u.def.section->owner)
3285                   == bfd_target_elf_flavour))
3286             h->elf_link_hash_flags |= (ELF_LINK_HASH_REF_REGULAR
3287                                        | ELF_LINK_HASH_REF_REGULAR_NONWEAK);
3288           else
3289             h->elf_link_hash_flags |= ELF_LINK_HASH_DEF_REGULAR;
3290         }
3291
3292       if (h->dynindx == -1
3293           && ((h->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC) != 0
3294               || (h->elf_link_hash_flags & ELF_LINK_HASH_REF_DYNAMIC) != 0))
3295         {
3296           if (! _bfd_elf_link_record_dynamic_symbol (eif->info, h))
3297             {
3298               eif->failed = true;
3299               return false;
3300             }
3301         }
3302     }
3303   else
3304     {
3305       /* Unfortunately, ELF_LINK_NON_ELF is only correct if the symbol
3306          was first seen in a non-ELF file.  Fortunately, if the symbol
3307          was first seen in an ELF file, we're probably OK unless the
3308          symbol was defined in a non-ELF file.  Catch that case here.
3309          FIXME: We're still in trouble if the symbol was first seen in
3310          a dynamic object, and then later in a non-ELF regular object.  */
3311       if ((h->root.type == bfd_link_hash_defined
3312            || h->root.type == bfd_link_hash_defweak)
3313           && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) == 0
3314           && (h->root.u.def.section->owner != NULL
3315               ? (bfd_get_flavour (h->root.u.def.section->owner)
3316                  != bfd_target_elf_flavour)
3317               : (bfd_is_abs_section (h->root.u.def.section)
3318                  && (h->elf_link_hash_flags
3319                      & ELF_LINK_HASH_DEF_DYNAMIC) == 0)))
3320         h->elf_link_hash_flags |= ELF_LINK_HASH_DEF_REGULAR;
3321     }
3322
3323   /* If this is a final link, and the symbol was defined as a common
3324      symbol in a regular object file, and there was no definition in
3325      any dynamic object, then the linker will have allocated space for
3326      the symbol in a common section but the ELF_LINK_HASH_DEF_REGULAR
3327      flag will not have been set.  */
3328   if (h->root.type == bfd_link_hash_defined
3329       && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) == 0
3330       && (h->elf_link_hash_flags & ELF_LINK_HASH_REF_REGULAR) != 0
3331       && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC) == 0
3332       && (h->root.u.def.section->owner->flags & DYNAMIC) == 0)
3333     h->elf_link_hash_flags |= ELF_LINK_HASH_DEF_REGULAR;
3334
3335   /* If -Bsymbolic was used (which means to bind references to global
3336      symbols to the definition within the shared object), and this
3337      symbol was defined in a regular object, then it actually doesn't
3338      need a PLT entry.  */
3339   if ((h->elf_link_hash_flags & ELF_LINK_HASH_NEEDS_PLT) != 0
3340       && eif->info->shared
3341       && eif->info->symbolic
3342       && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) != 0)
3343     {
3344       h->elf_link_hash_flags &=~ ELF_LINK_HASH_NEEDS_PLT;
3345       h->plt.offset = (bfd_vma) -1;
3346     }
3347
3348   /* If this is a weak defined symbol in a dynamic object, and we know
3349      the real definition in the dynamic object, copy interesting flags
3350      over to the real definition.  */
3351   if (h->weakdef != NULL)
3352     {
3353       struct elf_link_hash_entry *weakdef;
3354
3355       BFD_ASSERT (h->root.type == bfd_link_hash_defined
3356                   || h->root.type == bfd_link_hash_defweak);
3357       weakdef = h->weakdef;
3358       BFD_ASSERT (weakdef->root.type == bfd_link_hash_defined
3359                   || weakdef->root.type == bfd_link_hash_defweak);
3360       BFD_ASSERT (weakdef->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC);
3361
3362       /* If the real definition is defined by a regular object file,
3363          don't do anything special.  See the longer description in
3364          elf_adjust_dynamic_symbol, below.  */
3365       if ((weakdef->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) != 0)
3366         h->weakdef = NULL;
3367       else
3368         weakdef->elf_link_hash_flags |=
3369           (h->elf_link_hash_flags
3370            & (ELF_LINK_HASH_REF_REGULAR
3371               | ELF_LINK_HASH_REF_REGULAR_NONWEAK
3372               | ELF_LINK_NON_GOT_REF));
3373     }
3374
3375   return true;
3376 }
3377
3378 /* Make the backend pick a good value for a dynamic symbol.  This is
3379    called via elf_link_hash_traverse, and also calls itself
3380    recursively.  */
3381
3382 static boolean
3383 elf_adjust_dynamic_symbol (h, data)
3384      struct elf_link_hash_entry *h;
3385      PTR data;
3386 {
3387   struct elf_info_failed *eif = (struct elf_info_failed *) data;
3388   bfd *dynobj;
3389   struct elf_backend_data *bed;
3390
3391   /* Ignore indirect symbols.  These are added by the versioning code.  */
3392   if (h->root.type == bfd_link_hash_indirect)
3393     return true;
3394
3395   /* Fix the symbol flags.  */
3396   if (! elf_fix_symbol_flags (h, eif))
3397     return false;
3398
3399   /* If this symbol does not require a PLT entry, and it is not
3400      defined by a dynamic object, or is not referenced by a regular
3401      object, ignore it.  We do have to handle a weak defined symbol,
3402      even if no regular object refers to it, if we decided to add it
3403      to the dynamic symbol table.  FIXME: Do we normally need to worry
3404      about symbols which are defined by one dynamic object and
3405      referenced by another one?  */
3406   if ((h->elf_link_hash_flags & ELF_LINK_HASH_NEEDS_PLT) == 0
3407       && ((h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) != 0
3408           || (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC) == 0
3409           || ((h->elf_link_hash_flags & ELF_LINK_HASH_REF_REGULAR) == 0
3410               && (h->weakdef == NULL || h->weakdef->dynindx == -1))))
3411     {
3412       h->plt.offset = (bfd_vma) -1;
3413       return true;
3414     }
3415
3416   /* If we've already adjusted this symbol, don't do it again.  This
3417      can happen via a recursive call.  */
3418   if ((h->elf_link_hash_flags & ELF_LINK_HASH_DYNAMIC_ADJUSTED) != 0)
3419     return true;
3420
3421   /* Don't look at this symbol again.  Note that we must set this
3422      after checking the above conditions, because we may look at a
3423      symbol once, decide not to do anything, and then get called
3424      recursively later after REF_REGULAR is set below.  */
3425   h->elf_link_hash_flags |= ELF_LINK_HASH_DYNAMIC_ADJUSTED;
3426
3427   /* If this is a weak definition, and we know a real definition, and
3428      the real symbol is not itself defined by a regular object file,
3429      then get a good value for the real definition.  We handle the
3430      real symbol first, for the convenience of the backend routine.
3431
3432      Note that there is a confusing case here.  If the real definition
3433      is defined by a regular object file, we don't get the real symbol
3434      from the dynamic object, but we do get the weak symbol.  If the
3435      processor backend uses a COPY reloc, then if some routine in the
3436      dynamic object changes the real symbol, we will not see that
3437      change in the corresponding weak symbol.  This is the way other
3438      ELF linkers work as well, and seems to be a result of the shared
3439      library model.
3440
3441      I will clarify this issue.  Most SVR4 shared libraries define the
3442      variable _timezone and define timezone as a weak synonym.  The
3443      tzset call changes _timezone.  If you write
3444        extern int timezone;
3445        int _timezone = 5;
3446        int main () { tzset (); printf ("%d %d\n", timezone, _timezone); }
3447      you might expect that, since timezone is a synonym for _timezone,
3448      the same number will print both times.  However, if the processor
3449      backend uses a COPY reloc, then actually timezone will be copied
3450      into your process image, and, since you define _timezone
3451      yourself, _timezone will not.  Thus timezone and _timezone will
3452      wind up at different memory locations.  The tzset call will set
3453      _timezone, leaving timezone unchanged.  */
3454
3455   if (h->weakdef != NULL)
3456     {
3457       /* If we get to this point, we know there is an implicit
3458          reference by a regular object file via the weak symbol H.
3459          FIXME: Is this really true?  What if the traversal finds
3460          H->WEAKDEF before it finds H?  */
3461       h->weakdef->elf_link_hash_flags |= ELF_LINK_HASH_REF_REGULAR;
3462
3463       if (! elf_adjust_dynamic_symbol (h->weakdef, (PTR) eif))
3464         return false;
3465     }
3466
3467   /* If a symbol has no type and no size and does not require a PLT
3468      entry, then we are probably about to do the wrong thing here: we
3469      are probably going to create a COPY reloc for an empty object.
3470      This case can arise when a shared object is built with assembly
3471      code, and the assembly code fails to set the symbol type.  */
3472   if (h->size == 0
3473       && h->type == STT_NOTYPE
3474       && (h->elf_link_hash_flags & ELF_LINK_HASH_NEEDS_PLT) == 0)
3475     (*_bfd_error_handler)
3476       (_("warning: type and size of dynamic symbol `%s' are not defined"),
3477          h->root.root.string);
3478
3479   dynobj = elf_hash_table (eif->info)->dynobj;
3480   bed = get_elf_backend_data (dynobj);
3481   if (! (*bed->elf_backend_adjust_dynamic_symbol) (eif->info, h))
3482     {
3483       eif->failed = true;
3484       return false;
3485     }
3486
3487   return true;
3488 }
3489 \f
3490 /* This routine is used to export all defined symbols into the dynamic
3491    symbol table.  It is called via elf_link_hash_traverse.  */
3492
3493 static boolean
3494 elf_export_symbol (h, data)
3495      struct elf_link_hash_entry *h;
3496      PTR data;
3497 {
3498   struct elf_info_failed *eif = (struct elf_info_failed *) data;
3499
3500   /* Ignore indirect symbols.  These are added by the versioning code.  */
3501   if (h->root.type == bfd_link_hash_indirect)
3502     return true;
3503
3504   if (h->dynindx == -1
3505       && (h->elf_link_hash_flags
3506           & (ELF_LINK_HASH_DEF_REGULAR | ELF_LINK_HASH_REF_REGULAR)) != 0)
3507     {
3508       if (! _bfd_elf_link_record_dynamic_symbol (eif->info, h))
3509         {
3510           eif->failed = true;
3511           return false;
3512         }
3513     }
3514
3515   return true;
3516 }
3517 \f
3518 /* Look through the symbols which are defined in other shared
3519    libraries and referenced here.  Update the list of version
3520    dependencies.  This will be put into the .gnu.version_r section.
3521    This function is called via elf_link_hash_traverse.  */
3522
3523 static boolean
3524 elf_link_find_version_dependencies (h, data)
3525      struct elf_link_hash_entry *h;
3526      PTR data;
3527 {
3528   struct elf_find_verdep_info *rinfo = (struct elf_find_verdep_info *) data;
3529   Elf_Internal_Verneed *t;
3530   Elf_Internal_Vernaux *a;
3531
3532   /* We only care about symbols defined in shared objects with version
3533      information.  */
3534   if ((h->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC) == 0
3535       || (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) != 0
3536       || h->dynindx == -1
3537       || h->verinfo.verdef == NULL)
3538     return true;
3539
3540   /* See if we already know about this version.  */
3541   for (t = elf_tdata (rinfo->output_bfd)->verref; t != NULL; t = t->vn_nextref)
3542     {
3543       if (t->vn_bfd != h->verinfo.verdef->vd_bfd)
3544         continue;
3545
3546       for (a = t->vn_auxptr; a != NULL; a = a->vna_nextptr)
3547         if (a->vna_nodename == h->verinfo.verdef->vd_nodename)
3548           return true;
3549
3550       break;
3551     }
3552
3553   /* This is a new version.  Add it to tree we are building.  */
3554
3555   if (t == NULL)
3556     {
3557       t = (Elf_Internal_Verneed *) bfd_zalloc (rinfo->output_bfd, sizeof *t);
3558       if (t == NULL)
3559         {
3560           rinfo->failed = true;
3561           return false;
3562         }
3563
3564       t->vn_bfd = h->verinfo.verdef->vd_bfd;
3565       t->vn_nextref = elf_tdata (rinfo->output_bfd)->verref;
3566       elf_tdata (rinfo->output_bfd)->verref = t;
3567     }
3568
3569   a = (Elf_Internal_Vernaux *) bfd_zalloc (rinfo->output_bfd, sizeof *a);
3570
3571   /* Note that we are copying a string pointer here, and testing it
3572      above.  If bfd_elf_string_from_elf_section is ever changed to
3573      discard the string data when low in memory, this will have to be
3574      fixed.  */
3575   a->vna_nodename = h->verinfo.verdef->vd_nodename;
3576
3577   a->vna_flags = h->verinfo.verdef->vd_flags;
3578   a->vna_nextptr = t->vn_auxptr;
3579
3580   h->verinfo.verdef->vd_exp_refno = rinfo->vers;
3581   ++rinfo->vers;
3582
3583   a->vna_other = h->verinfo.verdef->vd_exp_refno + 1;
3584
3585   t->vn_auxptr = a;
3586
3587   return true;
3588 }
3589
3590 /* Figure out appropriate versions for all the symbols.  We may not
3591    have the version number script until we have read all of the input
3592    files, so until that point we don't know which symbols should be
3593    local.  This function is called via elf_link_hash_traverse.  */
3594
3595 static boolean
3596 elf_link_assign_sym_version (h, data)
3597      struct elf_link_hash_entry *h;
3598      PTR data;
3599 {
3600   struct elf_assign_sym_version_info *sinfo =
3601     (struct elf_assign_sym_version_info *) data;
3602   struct bfd_link_info *info = sinfo->info;
3603   struct elf_backend_data *bed;
3604   struct elf_info_failed eif;
3605   char *p;
3606
3607   /* Fix the symbol flags.  */
3608   eif.failed = false;
3609   eif.info = info;
3610   if (! elf_fix_symbol_flags (h, &eif))
3611     {
3612       if (eif.failed)
3613         sinfo->failed = true;
3614       return false;
3615     }
3616
3617   /* We only need version numbers for symbols defined in regular
3618      objects.  */
3619   if ((h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) == 0)
3620     return true;
3621
3622   bed = get_elf_backend_data (sinfo->output_bfd);
3623   p = strchr (h->root.root.string, ELF_VER_CHR);
3624   if (p != NULL && h->verinfo.vertree == NULL)
3625     {
3626       struct bfd_elf_version_tree *t;
3627       boolean hidden;
3628
3629       hidden = true;
3630
3631       /* There are two consecutive ELF_VER_CHR characters if this is
3632          not a hidden symbol.  */
3633       ++p;
3634       if (*p == ELF_VER_CHR)
3635         {
3636           hidden = false;
3637           ++p;
3638         }
3639
3640       /* If there is no version string, we can just return out.  */
3641       if (*p == '\0')
3642         {
3643           if (hidden)
3644             h->elf_link_hash_flags |= ELF_LINK_HIDDEN;
3645           return true;
3646         }
3647
3648       /* Look for the version.  If we find it, it is no longer weak.  */
3649       for (t = sinfo->verdefs; t != NULL; t = t->next)
3650         {
3651           if (strcmp (t->name, p) == 0)
3652             {
3653               int len;
3654               char *alc;
3655               struct bfd_elf_version_expr *d;
3656
3657               len = p - h->root.root.string;
3658               alc = bfd_alloc (sinfo->output_bfd, len);
3659               if (alc == NULL)
3660                 return false;
3661               strncpy (alc, h->root.root.string, len - 1);
3662               alc[len - 1] = '\0';
3663               if (alc[len - 2] == ELF_VER_CHR)
3664                 alc[len - 2] = '\0';
3665
3666               h->verinfo.vertree = t;
3667               t->used = true;
3668               d = NULL;
3669
3670               if (t->globals != NULL)
3671                 {
3672                   for (d = t->globals; d != NULL; d = d->next)
3673                     if ((*d->match) (d, alc))
3674                       break;
3675                 }
3676
3677               /* See if there is anything to force this symbol to
3678                  local scope.  */
3679               if (d == NULL && t->locals != NULL)
3680                 {
3681                   for (d = t->locals; d != NULL; d = d->next)
3682                     {
3683                       if ((*d->match) (d, alc))
3684                         {
3685                           if (h->dynindx != -1
3686                               && info->shared
3687                               && ! sinfo->export_dynamic)
3688                             {
3689                               h->elf_link_hash_flags |= ELF_LINK_FORCED_LOCAL;
3690                               (*bed->elf_backend_hide_symbol) (h);
3691                               /* FIXME: The name of the symbol has
3692                                  already been recorded in the dynamic
3693                                  string table section.  */
3694                             }
3695
3696                           break;
3697                         }
3698                     }
3699                 }
3700
3701               bfd_release (sinfo->output_bfd, alc);
3702               break;
3703             }
3704         }
3705
3706       /* If we are building an application, we need to create a
3707          version node for this version.  */
3708       if (t == NULL && ! info->shared)
3709         {
3710           struct bfd_elf_version_tree **pp;
3711           int version_index;
3712
3713           /* If we aren't going to export this symbol, we don't need
3714              to worry about it. */
3715           if (h->dynindx == -1)
3716             return true;
3717
3718           t = ((struct bfd_elf_version_tree *)
3719                bfd_alloc (sinfo->output_bfd, sizeof *t));
3720           if (t == NULL)
3721             {
3722               sinfo->failed = true;
3723               return false;
3724             }
3725
3726           t->next = NULL;
3727           t->name = p;
3728           t->globals = NULL;
3729           t->locals = NULL;
3730           t->deps = NULL;
3731           t->name_indx = (unsigned int) -1;
3732           t->used = true;
3733
3734           version_index = 1;
3735           for (pp = &sinfo->verdefs; *pp != NULL; pp = &(*pp)->next)
3736             ++version_index;
3737           t->vernum = version_index;
3738
3739           *pp = t;
3740
3741           h->verinfo.vertree = t;
3742         }
3743       else if (t == NULL)
3744         {
3745           /* We could not find the version for a symbol when
3746              generating a shared archive.  Return an error.  */
3747           (*_bfd_error_handler)
3748             (_("%s: undefined versioned symbol name %s"),
3749              bfd_get_filename (sinfo->output_bfd), h->root.root.string);
3750           bfd_set_error (bfd_error_bad_value);
3751           sinfo->failed = true;
3752           return false;
3753         }
3754
3755       if (hidden)
3756         h->elf_link_hash_flags |= ELF_LINK_HIDDEN;
3757     }
3758
3759   /* If we don't have a version for this symbol, see if we can find
3760      something.  */
3761   if (h->verinfo.vertree == NULL && sinfo->verdefs != NULL)
3762     {
3763       struct bfd_elf_version_tree *t;
3764       struct bfd_elf_version_tree *deflt;
3765       struct bfd_elf_version_expr *d;
3766
3767       /* See if can find what version this symbol is in.  If the
3768          symbol is supposed to be local, then don't actually register
3769          it.  */
3770       deflt = NULL;
3771       for (t = sinfo->verdefs; t != NULL; t = t->next)
3772         {
3773           if (t->globals != NULL)
3774             {
3775               for (d = t->globals; d != NULL; d = d->next)
3776                 {
3777                   if ((*d->match) (d, h->root.root.string))
3778                     {
3779                       h->verinfo.vertree = t;
3780                       break;
3781                     }
3782                 }
3783
3784               if (d != NULL)
3785                 break;
3786             }
3787
3788           if (t->locals != NULL)
3789             {
3790               for (d = t->locals; d != NULL; d = d->next)
3791                 {
3792                   if (d->pattern[0] == '*' && d->pattern[1] == '\0')
3793                     deflt = t;
3794                   else if ((*d->match) (d, h->root.root.string))
3795                     {
3796                       h->verinfo.vertree = t;
3797                       if (h->dynindx != -1
3798                           && info->shared
3799                           && ! sinfo->export_dynamic)
3800                         {
3801                           h->elf_link_hash_flags |= ELF_LINK_FORCED_LOCAL;
3802                           (*bed->elf_backend_hide_symbol) (h);
3803                           /* FIXME: The name of the symbol has already
3804                              been recorded in the dynamic string table
3805                              section.  */
3806                         }
3807                       break;
3808                     }
3809                 }
3810
3811               if (d != NULL)
3812                 break;
3813             }
3814         }
3815
3816       if (deflt != NULL && h->verinfo.vertree == NULL)
3817         {
3818           h->verinfo.vertree = deflt;
3819           if (h->dynindx != -1
3820               && info->shared
3821               && ! sinfo->export_dynamic)
3822             {
3823               h->elf_link_hash_flags |= ELF_LINK_FORCED_LOCAL;
3824               (*bed->elf_backend_hide_symbol) (h);
3825               /* FIXME: The name of the symbol has already been
3826                  recorded in the dynamic string table section.  */
3827             }
3828         }
3829     }
3830
3831   return true;
3832 }
3833 \f
3834 /* Final phase of ELF linker.  */
3835
3836 /* A structure we use to avoid passing large numbers of arguments.  */
3837
3838 struct elf_final_link_info
3839 {
3840   /* General link information.  */
3841   struct bfd_link_info *info;
3842   /* Output BFD.  */
3843   bfd *output_bfd;
3844   /* Symbol string table.  */
3845   struct bfd_strtab_hash *symstrtab;
3846   /* .dynsym section.  */
3847   asection *dynsym_sec;
3848   /* .hash section.  */
3849   asection *hash_sec;
3850   /* symbol version section (.gnu.version).  */
3851   asection *symver_sec;
3852   /* Buffer large enough to hold contents of any section.  */
3853   bfd_byte *contents;
3854   /* Buffer large enough to hold external relocs of any section.  */
3855   PTR external_relocs;
3856   /* Buffer large enough to hold internal relocs of any section.  */
3857   Elf_Internal_Rela *internal_relocs;
3858   /* Buffer large enough to hold external local symbols of any input
3859      BFD.  */
3860   Elf_External_Sym *external_syms;
3861   /* Buffer large enough to hold internal local symbols of any input
3862      BFD.  */
3863   Elf_Internal_Sym *internal_syms;
3864   /* Array large enough to hold a symbol index for each local symbol
3865      of any input BFD.  */
3866   long *indices;
3867   /* Array large enough to hold a section pointer for each local
3868      symbol of any input BFD.  */
3869   asection **sections;
3870   /* Buffer to hold swapped out symbols.  */
3871   Elf_External_Sym *symbuf;
3872   /* Number of swapped out symbols in buffer.  */
3873   size_t symbuf_count;
3874   /* Number of symbols which fit in symbuf.  */
3875   size_t symbuf_size;
3876 };
3877
3878 static boolean elf_link_output_sym
3879   PARAMS ((struct elf_final_link_info *, const char *,
3880            Elf_Internal_Sym *, asection *));
3881 static boolean elf_link_flush_output_syms
3882   PARAMS ((struct elf_final_link_info *));
3883 static boolean elf_link_output_extsym
3884   PARAMS ((struct elf_link_hash_entry *, PTR));
3885 static boolean elf_link_input_bfd
3886   PARAMS ((struct elf_final_link_info *, bfd *));
3887 static boolean elf_reloc_link_order
3888   PARAMS ((bfd *, struct bfd_link_info *, asection *,
3889            struct bfd_link_order *));
3890
3891 /* This struct is used to pass information to elf_link_output_extsym.  */
3892
3893 struct elf_outext_info
3894 {
3895   boolean failed;
3896   boolean localsyms;
3897   struct elf_final_link_info *finfo;
3898 };
3899
3900 /* Compute the size of, and allocate space for, REL_HDR which is the
3901    section header for a section containing relocations for O.  */
3902
3903 static boolean
3904 elf_link_size_reloc_section (abfd, rel_hdr, o)
3905      bfd *abfd;
3906      Elf_Internal_Shdr *rel_hdr;
3907      asection *o;
3908 {
3909   register struct elf_link_hash_entry **p, **pend;
3910   unsigned reloc_count;
3911
3912   /* Figure out how many relocations there will be.  */
3913   if (rel_hdr == &elf_section_data (o)->rel_hdr)
3914     reloc_count = elf_section_data (o)->rel_count;
3915   else
3916     reloc_count = elf_section_data (o)->rel_count2;
3917
3918   /* That allows us to calculate the size of the section.  */
3919   rel_hdr->sh_size = rel_hdr->sh_entsize * reloc_count;
3920
3921   /* The contents field must last into write_object_contents, so we
3922      allocate it with bfd_alloc rather than malloc.  */
3923   rel_hdr->contents = (PTR) bfd_alloc (abfd, rel_hdr->sh_size);
3924   if (rel_hdr->contents == NULL && rel_hdr->sh_size != 0)
3925     return false;
3926   
3927   /* We only allocate one set of hash entries, so we only do it the
3928      first time we are called.  */
3929   if (elf_section_data (o)->rel_hashes == NULL)
3930     {
3931       p = ((struct elf_link_hash_entry **)
3932            bfd_malloc (o->reloc_count
3933                        * sizeof (struct elf_link_hash_entry *)));
3934       if (p == NULL && o->reloc_count != 0)
3935         return false;
3936
3937       elf_section_data (o)->rel_hashes = p;
3938       pend = p + o->reloc_count;
3939       for (; p < pend; p++)
3940         *p = NULL;
3941     }
3942
3943   return true;
3944 }
3945
3946 /* When performing a relocateable link, the input relocations are
3947    preserved.  But, if they reference global symbols, the indices
3948    referenced must be updated.  Update all the relocations in
3949    REL_HDR (there are COUNT of them), using the data in REL_HASH.  */
3950
3951 static void
3952 elf_link_adjust_relocs (abfd, rel_hdr, count, rel_hash)
3953      bfd *abfd;
3954      Elf_Internal_Shdr *rel_hdr;
3955      unsigned int count;
3956      struct elf_link_hash_entry **rel_hash;
3957 {
3958   unsigned int i;
3959
3960   for (i = 0; i < count; i++, rel_hash++)
3961     {
3962       if (*rel_hash == NULL)
3963         continue;
3964
3965       BFD_ASSERT ((*rel_hash)->indx >= 0);
3966
3967       if (rel_hdr->sh_entsize == sizeof (Elf_External_Rel))
3968         {
3969           Elf_External_Rel *erel;
3970           Elf_Internal_Rel irel;
3971           
3972           erel = (Elf_External_Rel *) rel_hdr->contents + i;
3973           elf_swap_reloc_in (abfd, erel, &irel);
3974           irel.r_info = ELF_R_INFO ((*rel_hash)->indx,
3975                                     ELF_R_TYPE (irel.r_info));
3976           elf_swap_reloc_out (abfd, &irel, erel);
3977         }
3978       else
3979         {
3980           Elf_External_Rela *erela;
3981           Elf_Internal_Rela irela;
3982           
3983           BFD_ASSERT (rel_hdr->sh_entsize
3984                       == sizeof (Elf_External_Rela));
3985           
3986           erela = (Elf_External_Rela *) rel_hdr->contents + i;
3987           elf_swap_reloca_in (abfd, erela, &irela);
3988           irela.r_info = ELF_R_INFO ((*rel_hash)->indx,
3989                                      ELF_R_TYPE (irela.r_info));
3990           elf_swap_reloca_out (abfd, &irela, erela);
3991         }
3992     }
3993 }
3994
3995 /* Do the final step of an ELF link.  */
3996
3997 boolean
3998 elf_bfd_final_link (abfd, info)
3999      bfd *abfd;
4000      struct bfd_link_info *info;
4001 {
4002   boolean dynamic;
4003   bfd *dynobj;
4004   struct elf_final_link_info finfo;
4005   register asection *o;
4006   register struct bfd_link_order *p;
4007   register bfd *sub;
4008   size_t max_contents_size;
4009   size_t max_external_reloc_size;
4010   size_t max_internal_reloc_count;
4011   size_t max_sym_count;
4012   file_ptr off;
4013   Elf_Internal_Sym elfsym;
4014   unsigned int i;
4015   Elf_Internal_Shdr *symtab_hdr;
4016   Elf_Internal_Shdr *symstrtab_hdr;
4017   struct elf_backend_data *bed = get_elf_backend_data (abfd);
4018   struct elf_outext_info eoinfo;
4019
4020   if (info->shared)
4021     abfd->flags |= DYNAMIC;
4022
4023   dynamic = elf_hash_table (info)->dynamic_sections_created;
4024   dynobj = elf_hash_table (info)->dynobj;
4025
4026   finfo.info = info;
4027   finfo.output_bfd = abfd;
4028   finfo.symstrtab = elf_stringtab_init ();
4029   if (finfo.symstrtab == NULL)
4030     return false;
4031
4032   if (! dynamic)
4033     {
4034       finfo.dynsym_sec = NULL;
4035       finfo.hash_sec = NULL;
4036       finfo.symver_sec = NULL;
4037     }
4038   else
4039     {
4040       finfo.dynsym_sec = bfd_get_section_by_name (dynobj, ".dynsym");
4041       finfo.hash_sec = bfd_get_section_by_name (dynobj, ".hash");
4042       BFD_ASSERT (finfo.dynsym_sec != NULL && finfo.hash_sec != NULL);
4043       finfo.symver_sec = bfd_get_section_by_name (dynobj, ".gnu.version");
4044       /* Note that it is OK if symver_sec is NULL.  */
4045     }
4046
4047   finfo.contents = NULL;
4048   finfo.external_relocs = NULL;
4049   finfo.internal_relocs = NULL;
4050   finfo.external_syms = NULL;
4051   finfo.internal_syms = NULL;
4052   finfo.indices = NULL;
4053   finfo.sections = NULL;
4054   finfo.symbuf = NULL;
4055   finfo.symbuf_count = 0;
4056
4057   /* Count up the number of relocations we will output for each output
4058      section, so that we know the sizes of the reloc sections.  We
4059      also figure out some maximum sizes.  */
4060   max_contents_size = 0;
4061   max_external_reloc_size = 0;
4062   max_internal_reloc_count = 0;
4063   max_sym_count = 0;
4064   for (o = abfd->sections; o != (asection *) NULL; o = o->next)
4065     {
4066       o->reloc_count = 0;
4067
4068       for (p = o->link_order_head; p != NULL; p = p->next)
4069         {
4070           if (p->type == bfd_section_reloc_link_order
4071               || p->type == bfd_symbol_reloc_link_order)
4072             ++o->reloc_count;
4073           else if (p->type == bfd_indirect_link_order)
4074             {
4075               asection *sec;
4076
4077               sec = p->u.indirect.section;
4078
4079               /* Mark all sections which are to be included in the
4080                  link.  This will normally be every section.  We need
4081                  to do this so that we can identify any sections which
4082                  the linker has decided to not include.  */
4083               sec->linker_mark = true;
4084
4085               if (info->relocateable)
4086                 o->reloc_count += sec->reloc_count;
4087
4088               if (sec->_raw_size > max_contents_size)
4089                 max_contents_size = sec->_raw_size;
4090               if (sec->_cooked_size > max_contents_size)
4091                 max_contents_size = sec->_cooked_size;
4092
4093               /* We are interested in just local symbols, not all
4094                  symbols.  */
4095               if (bfd_get_flavour (sec->owner) == bfd_target_elf_flavour
4096                   && (sec->owner->flags & DYNAMIC) == 0)
4097                 {
4098                   size_t sym_count;
4099
4100                   if (elf_bad_symtab (sec->owner))
4101                     sym_count = (elf_tdata (sec->owner)->symtab_hdr.sh_size
4102                                  / sizeof (Elf_External_Sym));
4103                   else
4104                     sym_count = elf_tdata (sec->owner)->symtab_hdr.sh_info;
4105
4106                   if (sym_count > max_sym_count)
4107                     max_sym_count = sym_count;
4108
4109                   if ((sec->flags & SEC_RELOC) != 0)
4110                     {
4111                       size_t ext_size;
4112
4113                       ext_size = elf_section_data (sec)->rel_hdr.sh_size;
4114                       if (ext_size > max_external_reloc_size)
4115                         max_external_reloc_size = ext_size;
4116                       if (sec->reloc_count > max_internal_reloc_count)
4117                         max_internal_reloc_count = sec->reloc_count;
4118                     }
4119                 }
4120             }
4121         }
4122
4123       if (o->reloc_count > 0)
4124         o->flags |= SEC_RELOC;
4125       else
4126         {
4127           /* Explicitly clear the SEC_RELOC flag.  The linker tends to
4128              set it (this is probably a bug) and if it is set
4129              assign_section_numbers will create a reloc section.  */
4130           o->flags &=~ SEC_RELOC;
4131         }
4132
4133       /* If the SEC_ALLOC flag is not set, force the section VMA to
4134          zero.  This is done in elf_fake_sections as well, but forcing
4135          the VMA to 0 here will ensure that relocs against these
4136          sections are handled correctly.  */
4137       if ((o->flags & SEC_ALLOC) == 0
4138           && ! o->user_set_vma)
4139         o->vma = 0;
4140     }
4141
4142   /* Figure out the file positions for everything but the symbol table
4143      and the relocs.  We set symcount to force assign_section_numbers
4144      to create a symbol table.  */
4145   bfd_get_symcount (abfd) = info->strip == strip_all ? 0 : 1;
4146   BFD_ASSERT (! abfd->output_has_begun);
4147   if (! _bfd_elf_compute_section_file_positions (abfd, info))
4148     goto error_return;
4149
4150   /* Figure out how many relocations we will have in each section.
4151      Just using RELOC_COUNT isn't good enough since that doesn't
4152      maintain a separate value for REL vs. RELA relocations.  */
4153   if (info->relocateable)
4154     for (sub = info->input_bfds; sub != NULL; sub = sub->link_next)
4155       for (o = sub->sections; o != NULL; o = o->next)
4156         {
4157           asection *output_section;
4158
4159           if (! o->linker_mark)
4160             {
4161               /* This section was omitted from the link.  */
4162               continue;
4163             }
4164
4165           output_section = o->output_section;
4166
4167           if (output_section != NULL
4168               && (o->flags & SEC_RELOC) != 0)
4169             {
4170               struct bfd_elf_section_data *esdi 
4171                 = elf_section_data (o);
4172               struct bfd_elf_section_data *esdo 
4173                 = elf_section_data (output_section);
4174               unsigned int *rel_count;
4175               unsigned int *rel_count2;
4176
4177               /* We must be careful to add the relocation froms the
4178                  input section to the right output count.  */
4179               if (esdi->rel_hdr.sh_entsize == esdo->rel_hdr.sh_entsize)
4180                 {
4181                   rel_count = &esdo->rel_count;
4182                   rel_count2 = &esdo->rel_count2;
4183                 }
4184               else
4185                 {
4186                   rel_count = &esdo->rel_count2;
4187                   rel_count2 = &esdo->rel_count;
4188                 }
4189               
4190               *rel_count += (esdi->rel_hdr.sh_size 
4191                              / esdi->rel_hdr.sh_entsize);
4192               if (esdi->rel_hdr2)
4193                 *rel_count2 += (esdi->rel_hdr2->sh_size 
4194                                 / esdi->rel_hdr2->sh_entsize);
4195             }
4196         }
4197
4198   /* That created the reloc sections.  Set their sizes, and assign
4199      them file positions, and allocate some buffers.  */
4200   for (o = abfd->sections; o != NULL; o = o->next)
4201     {
4202       if ((o->flags & SEC_RELOC) != 0)
4203         {
4204           if (!elf_link_size_reloc_section (abfd,
4205                                             &elf_section_data (o)->rel_hdr,
4206                                             o))
4207             goto error_return;
4208
4209           if (elf_section_data (o)->rel_hdr2
4210               && !elf_link_size_reloc_section (abfd,
4211                                                elf_section_data (o)->rel_hdr2,
4212                                                o))
4213             goto error_return;
4214         }
4215
4216       /* Now, reset REL_COUNT and REL_COUNT2 so that we can use them
4217          to count upwards while actually outputting the relocations. */
4218       elf_section_data (o)->rel_count = 0;
4219       elf_section_data (o)->rel_count2 = 0;
4220     }
4221
4222   _bfd_elf_assign_file_positions_for_relocs (abfd);
4223
4224   /* We have now assigned file positions for all the sections except
4225      .symtab and .strtab.  We start the .symtab section at the current
4226      file position, and write directly to it.  We build the .strtab
4227      section in memory.  */
4228   bfd_get_symcount (abfd) = 0;
4229   symtab_hdr = &elf_tdata (abfd)->symtab_hdr;
4230   /* sh_name is set in prep_headers.  */
4231   symtab_hdr->sh_type = SHT_SYMTAB;
4232   symtab_hdr->sh_flags = 0;
4233   symtab_hdr->sh_addr = 0;
4234   symtab_hdr->sh_size = 0;
4235   symtab_hdr->sh_entsize = sizeof (Elf_External_Sym);
4236   /* sh_link is set in assign_section_numbers.  */
4237   /* sh_info is set below.  */
4238   /* sh_offset is set just below.  */
4239   symtab_hdr->sh_addralign = 4;  /* FIXME: system dependent?  */
4240
4241   off = elf_tdata (abfd)->next_file_pos;
4242   off = _bfd_elf_assign_file_position_for_section (symtab_hdr, off, true);
4243
4244   /* Note that at this point elf_tdata (abfd)->next_file_pos is
4245      incorrect.  We do not yet know the size of the .symtab section.
4246      We correct next_file_pos below, after we do know the size.  */
4247
4248   /* Allocate a buffer to hold swapped out symbols.  This is to avoid
4249      continuously seeking to the right position in the file.  */
4250   if (! info->keep_memory || max_sym_count < 20)
4251     finfo.symbuf_size = 20;
4252   else
4253     finfo.symbuf_size = max_sym_count;
4254   finfo.symbuf = ((Elf_External_Sym *)
4255                   bfd_malloc (finfo.symbuf_size * sizeof (Elf_External_Sym)));
4256   if (finfo.symbuf == NULL)
4257     goto error_return;
4258
4259   /* Start writing out the symbol table.  The first symbol is always a
4260      dummy symbol.  */
4261   if (info->strip != strip_all || info->relocateable)
4262     {
4263       elfsym.st_value = 0;
4264       elfsym.st_size = 0;
4265       elfsym.st_info = 0;
4266       elfsym.st_other = 0;
4267       elfsym.st_shndx = SHN_UNDEF;
4268       if (! elf_link_output_sym (&finfo, (const char *) NULL,
4269                                  &elfsym, bfd_und_section_ptr))
4270         goto error_return;
4271     }
4272
4273 #if 0
4274   /* Some standard ELF linkers do this, but we don't because it causes
4275      bootstrap comparison failures.  */
4276   /* Output a file symbol for the output file as the second symbol.
4277      We output this even if we are discarding local symbols, although
4278      I'm not sure if this is correct.  */
4279   elfsym.st_value = 0;
4280   elfsym.st_size = 0;
4281   elfsym.st_info = ELF_ST_INFO (STB_LOCAL, STT_FILE);
4282   elfsym.st_other = 0;
4283   elfsym.st_shndx = SHN_ABS;
4284   if (! elf_link_output_sym (&finfo, bfd_get_filename (abfd),
4285                              &elfsym, bfd_abs_section_ptr))
4286     goto error_return;
4287 #endif
4288
4289   /* Output a symbol for each section.  We output these even if we are
4290      discarding local symbols, since they are used for relocs.  These
4291      symbols have no names.  We store the index of each one in the
4292      index field of the section, so that we can find it again when
4293      outputting relocs.  */
4294   if (info->strip != strip_all || info->relocateable)
4295     {
4296       elfsym.st_size = 0;
4297       elfsym.st_info = ELF_ST_INFO (STB_LOCAL, STT_SECTION);
4298       elfsym.st_other = 0;
4299       for (i = 1; i < elf_elfheader (abfd)->e_shnum; i++)
4300         {
4301           o = section_from_elf_index (abfd, i);
4302           if (o != NULL)
4303             o->target_index = bfd_get_symcount (abfd);
4304           elfsym.st_shndx = i;
4305           if (info->relocateable || o == NULL)
4306             elfsym.st_value = 0;
4307           else
4308             elfsym.st_value = o->vma;
4309           if (! elf_link_output_sym (&finfo, (const char *) NULL,
4310                                      &elfsym, o))
4311             goto error_return;
4312         }
4313     }
4314
4315   /* Allocate some memory to hold information read in from the input
4316      files.  */
4317   finfo.contents = (bfd_byte *) bfd_malloc (max_contents_size);
4318   finfo.external_relocs = (PTR) bfd_malloc (max_external_reloc_size);
4319   finfo.internal_relocs = ((Elf_Internal_Rela *)
4320                            bfd_malloc (max_internal_reloc_count
4321                                        * sizeof (Elf_Internal_Rela)
4322                                        * bed->s->int_rels_per_ext_rel));
4323   finfo.external_syms = ((Elf_External_Sym *)
4324                          bfd_malloc (max_sym_count
4325                                      * sizeof (Elf_External_Sym)));
4326   finfo.internal_syms = ((Elf_Internal_Sym *)
4327                          bfd_malloc (max_sym_count
4328                                      * sizeof (Elf_Internal_Sym)));
4329   finfo.indices = (long *) bfd_malloc (max_sym_count * sizeof (long));
4330   finfo.sections = ((asection **)
4331                     bfd_malloc (max_sym_count * sizeof (asection *)));
4332   if ((finfo.contents == NULL && max_contents_size != 0)
4333       || (finfo.external_relocs == NULL && max_external_reloc_size != 0)
4334       || (finfo.internal_relocs == NULL && max_internal_reloc_count != 0)
4335       || (finfo.external_syms == NULL && max_sym_count != 0)
4336       || (finfo.internal_syms == NULL && max_sym_count != 0)
4337       || (finfo.indices == NULL && max_sym_count != 0)
4338       || (finfo.sections == NULL && max_sym_count != 0))
4339     goto error_return;
4340
4341   /* Since ELF permits relocations to be against local symbols, we
4342      must have the local symbols available when we do the relocations.
4343      Since we would rather only read the local symbols once, and we
4344      would rather not keep them in memory, we handle all the
4345      relocations for a single input file at the same time.
4346
4347      Unfortunately, there is no way to know the total number of local
4348      symbols until we have seen all of them, and the local symbol
4349      indices precede the global symbol indices.  This means that when
4350      we are generating relocateable output, and we see a reloc against
4351      a global symbol, we can not know the symbol index until we have
4352      finished examining all the local symbols to see which ones we are
4353      going to output.  To deal with this, we keep the relocations in
4354      memory, and don't output them until the end of the link.  This is
4355      an unfortunate waste of memory, but I don't see a good way around
4356      it.  Fortunately, it only happens when performing a relocateable
4357      link, which is not the common case.  FIXME: If keep_memory is set
4358      we could write the relocs out and then read them again; I don't
4359      know how bad the memory loss will be.  */
4360
4361   for (sub = info->input_bfds; sub != NULL; sub = sub->link_next)
4362     sub->output_has_begun = false;
4363   for (o = abfd->sections; o != NULL; o = o->next)
4364     {
4365       for (p = o->link_order_head; p != NULL; p = p->next)
4366         {
4367           if (p->type == bfd_indirect_link_order
4368               && (bfd_get_flavour (p->u.indirect.section->owner)
4369                   == bfd_target_elf_flavour))
4370             {
4371               sub = p->u.indirect.section->owner;
4372               if (! sub->output_has_begun)
4373                 {
4374                   if (! elf_link_input_bfd (&finfo, sub))
4375                     goto error_return;
4376                   sub->output_has_begun = true;
4377                 }
4378             }
4379           else if (p->type == bfd_section_reloc_link_order
4380                    || p->type == bfd_symbol_reloc_link_order)
4381             {
4382               if (! elf_reloc_link_order (abfd, info, o, p))
4383                 goto error_return;
4384             }
4385           else
4386             {
4387               if (! _bfd_default_link_order (abfd, info, o, p))
4388                 goto error_return;
4389             }
4390         }
4391     }
4392
4393   /* That wrote out all the local symbols.  Finish up the symbol table
4394      with the global symbols.  */
4395
4396   if (info->strip != strip_all && info->shared)
4397     {
4398       /* Output any global symbols that got converted to local in a
4399          version script.  We do this in a separate step since ELF
4400          requires all local symbols to appear prior to any global
4401          symbols.  FIXME: We should only do this if some global
4402          symbols were, in fact, converted to become local.  FIXME:
4403          Will this work correctly with the Irix 5 linker?  */
4404       eoinfo.failed = false;
4405       eoinfo.finfo = &finfo;
4406       eoinfo.localsyms = true;
4407       elf_link_hash_traverse (elf_hash_table (info), elf_link_output_extsym,
4408                               (PTR) &eoinfo);
4409       if (eoinfo.failed)
4410         return false;
4411     }
4412
4413   /* The sh_info field records the index of the first non local symbol.  */
4414   symtab_hdr->sh_info = bfd_get_symcount (abfd);
4415
4416   if (dynamic)
4417     {
4418       Elf_Internal_Sym sym;
4419       Elf_External_Sym *dynsym =
4420         (Elf_External_Sym *)finfo.dynsym_sec->contents;
4421       long last_local = 0;
4422
4423       /* Write out the section symbols for the output sections.  */
4424       if (info->shared)
4425         {
4426           asection *s;
4427
4428           sym.st_size = 0;
4429           sym.st_name = 0;
4430           sym.st_info = ELF_ST_INFO (STB_LOCAL, STT_SECTION);
4431           sym.st_other = 0;
4432
4433           for (s = abfd->sections; s != NULL; s = s->next)
4434             {
4435               int indx;
4436               indx = elf_section_data (s)->this_idx;
4437               BFD_ASSERT (indx > 0);
4438               sym.st_shndx = indx;
4439               sym.st_value = s->vma;
4440
4441               elf_swap_symbol_out (abfd, &sym,
4442                                    dynsym + elf_section_data (s)->dynindx);
4443             }
4444
4445           last_local = bfd_count_sections (abfd);
4446         }
4447
4448       /* Write out the local dynsyms.  */
4449       if (elf_hash_table (info)->dynlocal)
4450         {
4451           struct elf_link_local_dynamic_entry *e;
4452           for (e = elf_hash_table (info)->dynlocal; e ; e = e->next)
4453             {
4454               asection *s;
4455
4456               sym.st_size = e->isym.st_size;
4457               sym.st_other = e->isym.st_other;
4458
4459               /* Copy the internal symbol as is.
4460                  Note that we saved a word of storage and overwrote
4461                  the original st_name with the dynstr_index.  */
4462               sym = e->isym;
4463
4464               if (e->isym.st_shndx > 0 && e->isym.st_shndx < SHN_LORESERVE)
4465                 {
4466                   s = bfd_section_from_elf_index (e->input_bfd,
4467                                                   e->isym.st_shndx);
4468
4469                   sym.st_shndx =
4470                     elf_section_data (s->output_section)->this_idx;
4471                   sym.st_value = (s->output_section->vma
4472                                   + s->output_offset
4473                                   + e->isym.st_value);
4474                 }
4475
4476               if (last_local < e->dynindx)
4477                 last_local = e->dynindx;
4478
4479               elf_swap_symbol_out (abfd, &sym, dynsym + e->dynindx);
4480             }
4481         }
4482
4483       elf_section_data (finfo.dynsym_sec->output_section)->this_hdr.sh_info =
4484         last_local + 1;
4485     }
4486
4487   /* We get the global symbols from the hash table.  */
4488   eoinfo.failed = false;
4489   eoinfo.localsyms = false;
4490   eoinfo.finfo = &finfo;
4491   elf_link_hash_traverse (elf_hash_table (info), elf_link_output_extsym,
4492                           (PTR) &eoinfo);
4493   if (eoinfo.failed)
4494     return false;
4495
4496   /* If backend needs to output some symbols not present in the hash
4497      table, do it now.  */
4498   if (bed->elf_backend_output_arch_syms)
4499     {
4500       if (! (*bed->elf_backend_output_arch_syms)
4501               (abfd, info, (PTR) &finfo,
4502                (boolean (*) PARAMS ((PTR, const char *,
4503                             Elf_Internal_Sym *, asection *)))
4504                elf_link_output_sym))
4505         return false;
4506     }      
4507
4508   /* Flush all symbols to the file.  */
4509   if (! elf_link_flush_output_syms (&finfo))
4510     return false;
4511
4512   /* Now we know the size of the symtab section.  */
4513   off += symtab_hdr->sh_size;
4514
4515   /* Finish up and write out the symbol string table (.strtab)
4516      section.  */
4517   symstrtab_hdr = &elf_tdata (abfd)->strtab_hdr;
4518   /* sh_name was set in prep_headers.  */
4519   symstrtab_hdr->sh_type = SHT_STRTAB;
4520   symstrtab_hdr->sh_flags = 0;
4521   symstrtab_hdr->sh_addr = 0;
4522   symstrtab_hdr->sh_size = _bfd_stringtab_size (finfo.symstrtab);
4523   symstrtab_hdr->sh_entsize = 0;
4524   symstrtab_hdr->sh_link = 0;
4525   symstrtab_hdr->sh_info = 0;
4526   /* sh_offset is set just below.  */
4527   symstrtab_hdr->sh_addralign = 1;
4528
4529   off = _bfd_elf_assign_file_position_for_section (symstrtab_hdr, off, true);
4530   elf_tdata (abfd)->next_file_pos = off;
4531
4532   if (bfd_get_symcount (abfd) > 0)
4533     {
4534       if (bfd_seek (abfd, symstrtab_hdr->sh_offset, SEEK_SET) != 0
4535           || ! _bfd_stringtab_emit (abfd, finfo.symstrtab))
4536         return false;
4537     }
4538
4539   /* Adjust the relocs to have the correct symbol indices.  */
4540   for (o = abfd->sections; o != NULL; o = o->next)
4541     {
4542       if ((o->flags & SEC_RELOC) == 0)
4543         continue;
4544
4545       elf_link_adjust_relocs (abfd, &elf_section_data (o)->rel_hdr, 
4546                               elf_section_data (o)->rel_count,
4547                               elf_section_data (o)->rel_hashes);
4548       if (elf_section_data (o)->rel_hdr2 != NULL)
4549         elf_link_adjust_relocs (abfd, elf_section_data (o)->rel_hdr2,
4550                                 elf_section_data (o)->rel_count2,
4551                                 (elf_section_data (o)->rel_hashes 
4552                                  + elf_section_data (o)->rel_count));
4553
4554       /* Set the reloc_count field to 0 to prevent write_relocs from
4555          trying to swap the relocs out itself.  */
4556       o->reloc_count = 0;
4557     }
4558
4559   /* If we are linking against a dynamic object, or generating a
4560      shared library, finish up the dynamic linking information.  */
4561   if (dynamic)
4562     {
4563       Elf_External_Dyn *dyncon, *dynconend;
4564
4565       /* Fix up .dynamic entries.  */
4566       o = bfd_get_section_by_name (dynobj, ".dynamic");
4567       BFD_ASSERT (o != NULL);
4568
4569       dyncon = (Elf_External_Dyn *) o->contents;
4570       dynconend = (Elf_External_Dyn *) (o->contents + o->_raw_size);
4571       for (; dyncon < dynconend; dyncon++)
4572         {
4573           Elf_Internal_Dyn dyn;
4574           const char *name;
4575           unsigned int type;
4576
4577           elf_swap_dyn_in (dynobj, dyncon, &dyn);
4578
4579           switch (dyn.d_tag)
4580             {
4581             default:
4582               break;
4583             case DT_INIT:
4584               name = info->init_function;
4585               goto get_sym;
4586             case DT_FINI:
4587               name = info->fini_function;
4588             get_sym:
4589               {
4590                 struct elf_link_hash_entry *h;
4591
4592                 h = elf_link_hash_lookup (elf_hash_table (info), name,
4593                                           false, false, true);
4594                 if (h != NULL
4595                     && (h->root.type == bfd_link_hash_defined
4596                         || h->root.type == bfd_link_hash_defweak))
4597                   {
4598                     dyn.d_un.d_val = h->root.u.def.value;
4599                     o = h->root.u.def.section;
4600                     if (o->output_section != NULL)
4601                       dyn.d_un.d_val += (o->output_section->vma
4602                                          + o->output_offset);
4603                     else
4604                       {
4605                         /* The symbol is imported from another shared
4606                            library and does not apply to this one.  */
4607                         dyn.d_un.d_val = 0;
4608                       }
4609
4610                     elf_swap_dyn_out (dynobj, &dyn, dyncon);
4611                   }
4612               }
4613               break;
4614
4615             case DT_HASH:
4616               name = ".hash";
4617               goto get_vma;
4618             case DT_STRTAB:
4619               name = ".dynstr";
4620               goto get_vma;
4621             case DT_SYMTAB:
4622               name = ".dynsym";
4623               goto get_vma;
4624             case DT_VERDEF:
4625               name = ".gnu.version_d";
4626               goto get_vma;
4627             case DT_VERNEED:
4628               name = ".gnu.version_r";
4629               goto get_vma;
4630             case DT_VERSYM:
4631               name = ".gnu.version";
4632             get_vma:
4633               o = bfd_get_section_by_name (abfd, name);
4634               BFD_ASSERT (o != NULL);
4635               dyn.d_un.d_ptr = o->vma;
4636               elf_swap_dyn_out (dynobj, &dyn, dyncon);
4637               break;
4638
4639             case DT_REL:
4640             case DT_RELA:
4641             case DT_RELSZ:
4642             case DT_RELASZ:
4643               if (dyn.d_tag == DT_REL || dyn.d_tag == DT_RELSZ)
4644                 type = SHT_REL;
4645               else
4646                 type = SHT_RELA;
4647               dyn.d_un.d_val = 0;
4648               for (i = 1; i < elf_elfheader (abfd)->e_shnum; i++)
4649                 {
4650                   Elf_Internal_Shdr *hdr;
4651
4652                   hdr = elf_elfsections (abfd)[i];
4653                   if (hdr->sh_type == type
4654                       && (hdr->sh_flags & SHF_ALLOC) != 0)
4655                     {
4656                       if (dyn.d_tag == DT_RELSZ || dyn.d_tag == DT_RELASZ)
4657                         dyn.d_un.d_val += hdr->sh_size;
4658                       else
4659                         {
4660                           if (dyn.d_un.d_val == 0
4661                               || hdr->sh_addr < dyn.d_un.d_val)
4662                             dyn.d_un.d_val = hdr->sh_addr;
4663                         }
4664                     }
4665                 }
4666               elf_swap_dyn_out (dynobj, &dyn, dyncon);
4667               break;
4668             }
4669         }
4670     }
4671
4672   /* If we have created any dynamic sections, then output them.  */
4673   if (dynobj != NULL)
4674     {
4675       if (! (*bed->elf_backend_finish_dynamic_sections) (abfd, info))
4676         goto error_return;
4677
4678       for (o = dynobj->sections; o != NULL; o = o->next)
4679         {
4680           if ((o->flags & SEC_HAS_CONTENTS) == 0
4681               || o->_raw_size == 0)
4682             continue;
4683           if ((o->flags & SEC_LINKER_CREATED) == 0)
4684             {
4685               /* At this point, we are only interested in sections
4686                  created by elf_link_create_dynamic_sections.  */
4687               continue;
4688             }
4689           if ((elf_section_data (o->output_section)->this_hdr.sh_type
4690                != SHT_STRTAB)
4691               || strcmp (bfd_get_section_name (abfd, o), ".dynstr") != 0)
4692             {
4693               if (! bfd_set_section_contents (abfd, o->output_section,
4694                                               o->contents, o->output_offset,
4695                                               o->_raw_size))
4696                 goto error_return;
4697             }
4698           else
4699             {
4700               file_ptr off;
4701
4702               /* The contents of the .dynstr section are actually in a
4703                  stringtab.  */
4704               off = elf_section_data (o->output_section)->this_hdr.sh_offset;
4705               if (bfd_seek (abfd, off, SEEK_SET) != 0
4706                   || ! _bfd_stringtab_emit (abfd,
4707                                             elf_hash_table (info)->dynstr))
4708                 goto error_return;
4709             }
4710         }
4711     }
4712
4713   /* If we have optimized stabs strings, output them.  */
4714   if (elf_hash_table (info)->stab_info != NULL)
4715     {
4716       if (! _bfd_write_stab_strings (abfd, &elf_hash_table (info)->stab_info))
4717         goto error_return;
4718     }
4719
4720   if (finfo.symstrtab != NULL)
4721     _bfd_stringtab_free (finfo.symstrtab);
4722   if (finfo.contents != NULL)
4723     free (finfo.contents);
4724   if (finfo.external_relocs != NULL)
4725     free (finfo.external_relocs);
4726   if (finfo.internal_relocs != NULL)
4727     free (finfo.internal_relocs);
4728   if (finfo.external_syms != NULL)
4729     free (finfo.external_syms);
4730   if (finfo.internal_syms != NULL)
4731     free (finfo.internal_syms);
4732   if (finfo.indices != NULL)
4733     free (finfo.indices);
4734   if (finfo.sections != NULL)
4735     free (finfo.sections);
4736   if (finfo.symbuf != NULL)
4737     free (finfo.symbuf);
4738   for (o = abfd->sections; o != NULL; o = o->next)
4739     {
4740       if ((o->flags & SEC_RELOC) != 0
4741           && elf_section_data (o)->rel_hashes != NULL)
4742         free (elf_section_data (o)->rel_hashes);
4743     }
4744
4745   elf_tdata (abfd)->linker = true;
4746
4747   return true;
4748
4749  error_return:
4750   if (finfo.symstrtab != NULL)
4751     _bfd_stringtab_free (finfo.symstrtab);
4752   if (finfo.contents != NULL)
4753     free (finfo.contents);
4754   if (finfo.external_relocs != NULL)
4755     free (finfo.external_relocs);
4756   if (finfo.internal_relocs != NULL)
4757     free (finfo.internal_relocs);
4758   if (finfo.external_syms != NULL)
4759     free (finfo.external_syms);
4760   if (finfo.internal_syms != NULL)
4761     free (finfo.internal_syms);
4762   if (finfo.indices != NULL)
4763     free (finfo.indices);
4764   if (finfo.sections != NULL)
4765     free (finfo.sections);
4766   if (finfo.symbuf != NULL)
4767     free (finfo.symbuf);
4768   for (o = abfd->sections; o != NULL; o = o->next)
4769     {
4770       if ((o->flags & SEC_RELOC) != 0
4771           && elf_section_data (o)->rel_hashes != NULL)
4772         free (elf_section_data (o)->rel_hashes);
4773     }
4774
4775   return false;
4776 }
4777
4778 /* Add a symbol to the output symbol table.  */
4779
4780 static boolean
4781 elf_link_output_sym (finfo, name, elfsym, input_sec)
4782      struct elf_final_link_info *finfo;
4783      const char *name;
4784      Elf_Internal_Sym *elfsym;
4785      asection *input_sec;
4786 {
4787   boolean (*output_symbol_hook) PARAMS ((bfd *,
4788                                          struct bfd_link_info *info,
4789                                          const char *,
4790                                          Elf_Internal_Sym *,
4791                                          asection *));
4792
4793   output_symbol_hook = get_elf_backend_data (finfo->output_bfd)->
4794     elf_backend_link_output_symbol_hook;
4795   if (output_symbol_hook != NULL)
4796     {
4797       if (! ((*output_symbol_hook)
4798              (finfo->output_bfd, finfo->info, name, elfsym, input_sec)))
4799         return false;
4800     }
4801
4802   if (name == (const char *) NULL || *name == '\0')
4803     elfsym->st_name = 0;
4804   else if (input_sec->flags & SEC_EXCLUDE)
4805     elfsym->st_name = 0;
4806   else
4807     {
4808       elfsym->st_name = (unsigned long) _bfd_stringtab_add (finfo->symstrtab,
4809                                                             name, true,
4810                                                             false);
4811       if (elfsym->st_name == (unsigned long) -1)
4812         return false;
4813     }
4814
4815   if (finfo->symbuf_count >= finfo->symbuf_size)
4816     {
4817       if (! elf_link_flush_output_syms (finfo))
4818         return false;
4819     }
4820
4821   elf_swap_symbol_out (finfo->output_bfd, elfsym,
4822                        (PTR) (finfo->symbuf + finfo->symbuf_count));
4823   ++finfo->symbuf_count;
4824
4825   ++ bfd_get_symcount (finfo->output_bfd);
4826
4827   return true;
4828 }
4829
4830 /* Flush the output symbols to the file.  */
4831
4832 static boolean
4833 elf_link_flush_output_syms (finfo)
4834      struct elf_final_link_info *finfo;
4835 {
4836   if (finfo->symbuf_count > 0)
4837     {
4838       Elf_Internal_Shdr *symtab;
4839
4840       symtab = &elf_tdata (finfo->output_bfd)->symtab_hdr;
4841
4842       if (bfd_seek (finfo->output_bfd, symtab->sh_offset + symtab->sh_size,
4843                     SEEK_SET) != 0
4844           || (bfd_write ((PTR) finfo->symbuf, finfo->symbuf_count,
4845                          sizeof (Elf_External_Sym), finfo->output_bfd)
4846               != finfo->symbuf_count * sizeof (Elf_External_Sym)))
4847         return false;
4848
4849       symtab->sh_size += finfo->symbuf_count * sizeof (Elf_External_Sym);
4850
4851       finfo->symbuf_count = 0;
4852     }
4853
4854   return true;
4855 }
4856
4857 /* Add an external symbol to the symbol table.  This is called from
4858    the hash table traversal routine.  When generating a shared object,
4859    we go through the symbol table twice.  The first time we output
4860    anything that might have been forced to local scope in a version
4861    script.  The second time we output the symbols that are still
4862    global symbols.  */
4863
4864 static boolean
4865 elf_link_output_extsym (h, data)
4866      struct elf_link_hash_entry *h;
4867      PTR data;
4868 {
4869   struct elf_outext_info *eoinfo = (struct elf_outext_info *) data;
4870   struct elf_final_link_info *finfo = eoinfo->finfo;
4871   boolean strip;
4872   Elf_Internal_Sym sym;
4873   asection *input_sec;
4874
4875   /* Decide whether to output this symbol in this pass.  */
4876   if (eoinfo->localsyms)
4877     {
4878       if ((h->elf_link_hash_flags & ELF_LINK_FORCED_LOCAL) == 0)
4879         return true;
4880     }
4881   else
4882     {
4883       if ((h->elf_link_hash_flags & ELF_LINK_FORCED_LOCAL) != 0)
4884         return true;
4885     }
4886
4887   /* If we are not creating a shared library, and this symbol is
4888      referenced by a shared library but is not defined anywhere, then
4889      warn that it is undefined.  If we do not do this, the runtime
4890      linker will complain that the symbol is undefined when the
4891      program is run.  We don't have to worry about symbols that are
4892      referenced by regular files, because we will already have issued
4893      warnings for them.  */
4894   if (! finfo->info->relocateable
4895       && ! (finfo->info->shared
4896             && !finfo->info->no_undefined)
4897       && h->root.type == bfd_link_hash_undefined
4898       && (h->elf_link_hash_flags & ELF_LINK_HASH_REF_DYNAMIC) != 0
4899       && (h->elf_link_hash_flags & ELF_LINK_HASH_REF_REGULAR) == 0)
4900     {
4901       if (! ((*finfo->info->callbacks->undefined_symbol)
4902              (finfo->info, h->root.root.string, h->root.u.undef.abfd,
4903               (asection *) NULL, 0)))
4904         {
4905           eoinfo->failed = true;
4906           return false;
4907         }
4908     }
4909
4910   /* We don't want to output symbols that have never been mentioned by
4911      a regular file, or that we have been told to strip.  However, if
4912      h->indx is set to -2, the symbol is used by a reloc and we must
4913      output it.  */
4914   if (h->indx == -2)
4915     strip = false;
4916   else if (((h->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC) != 0
4917             || (h->elf_link_hash_flags & ELF_LINK_HASH_REF_DYNAMIC) != 0)
4918            && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) == 0
4919            && (h->elf_link_hash_flags & ELF_LINK_HASH_REF_REGULAR) == 0)
4920     strip = true;
4921   else if (finfo->info->strip == strip_all
4922            || (finfo->info->strip == strip_some
4923                && bfd_hash_lookup (finfo->info->keep_hash,
4924                                    h->root.root.string,
4925                                    false, false) == NULL))
4926     strip = true;
4927   else
4928     strip = false;
4929
4930   /* If we're stripping it, and it's not a dynamic symbol, there's
4931      nothing else to do.  */
4932   if (strip && h->dynindx == -1)
4933     return true;
4934
4935   sym.st_value = 0;
4936   sym.st_size = h->size;
4937   sym.st_other = h->other;
4938   if ((h->elf_link_hash_flags & ELF_LINK_FORCED_LOCAL) != 0)
4939     sym.st_info = ELF_ST_INFO (STB_LOCAL, h->type);
4940   else if (h->root.type == bfd_link_hash_undefweak
4941            || h->root.type == bfd_link_hash_defweak)
4942     sym.st_info = ELF_ST_INFO (STB_WEAK, h->type);
4943   else
4944     sym.st_info = ELF_ST_INFO (STB_GLOBAL, h->type);
4945
4946   switch (h->root.type)
4947     {
4948     default:
4949     case bfd_link_hash_new:
4950       abort ();
4951       return false;
4952
4953     case bfd_link_hash_undefined:
4954       input_sec = bfd_und_section_ptr;
4955       sym.st_shndx = SHN_UNDEF;
4956       break;
4957
4958     case bfd_link_hash_undefweak:
4959       input_sec = bfd_und_section_ptr;
4960       sym.st_shndx = SHN_UNDEF;
4961       break;
4962
4963     case bfd_link_hash_defined:
4964     case bfd_link_hash_defweak:
4965       {
4966         input_sec = h->root.u.def.section;
4967         if (input_sec->output_section != NULL)
4968           {
4969             sym.st_shndx =
4970               _bfd_elf_section_from_bfd_section (finfo->output_bfd,
4971                                                  input_sec->output_section);
4972             if (sym.st_shndx == (unsigned short) -1)
4973               {
4974                 (*_bfd_error_handler)
4975                   (_("%s: could not find output section %s for input section %s"),
4976                    bfd_get_filename (finfo->output_bfd),
4977                    input_sec->output_section->name,
4978                    input_sec->name);
4979                 eoinfo->failed = true;
4980                 return false;
4981               }
4982
4983             /* ELF symbols in relocateable files are section relative,
4984                but in nonrelocateable files they are virtual
4985                addresses.  */
4986             sym.st_value = h->root.u.def.value + input_sec->output_offset;
4987             if (! finfo->info->relocateable)
4988               sym.st_value += input_sec->output_section->vma;
4989           }
4990         else
4991           {
4992             BFD_ASSERT (input_sec->owner == NULL
4993                         || (input_sec->owner->flags & DYNAMIC) != 0);
4994             sym.st_shndx = SHN_UNDEF;
4995             input_sec = bfd_und_section_ptr;
4996           }
4997       }
4998       break;
4999
5000     case bfd_link_hash_common:
5001       input_sec = h->root.u.c.p->section;
5002       sym.st_shndx = SHN_COMMON;
5003       sym.st_value = 1 << h->root.u.c.p->alignment_power;
5004       break;
5005
5006     case bfd_link_hash_indirect:
5007       /* These symbols are created by symbol versioning.  They point
5008          to the decorated version of the name.  For example, if the
5009          symbol foo@@GNU_1.2 is the default, which should be used when
5010          foo is used with no version, then we add an indirect symbol
5011          foo which points to foo@@GNU_1.2.  We ignore these symbols,
5012          since the indirected symbol is already in the hash table.  If
5013          the indirect symbol is non-ELF, fall through and output it.  */
5014       if ((h->elf_link_hash_flags & ELF_LINK_NON_ELF) == 0)
5015         return true;
5016
5017       /* Fall through.  */
5018     case bfd_link_hash_warning:
5019       /* We can't represent these symbols in ELF, although a warning
5020          symbol may have come from a .gnu.warning.SYMBOL section.  We
5021          just put the target symbol in the hash table.  If the target
5022          symbol does not really exist, don't do anything.  */
5023       if (h->root.u.i.link->type == bfd_link_hash_new)
5024         return true;
5025       return (elf_link_output_extsym
5026               ((struct elf_link_hash_entry *) h->root.u.i.link, data));
5027     }
5028
5029   /* Give the processor backend a chance to tweak the symbol value,
5030      and also to finish up anything that needs to be done for this
5031      symbol.  */
5032   if ((h->dynindx != -1
5033        || (h->elf_link_hash_flags & ELF_LINK_FORCED_LOCAL) != 0)
5034       && elf_hash_table (finfo->info)->dynamic_sections_created)
5035     {
5036       struct elf_backend_data *bed;
5037
5038       bed = get_elf_backend_data (finfo->output_bfd);
5039       if (! ((*bed->elf_backend_finish_dynamic_symbol)
5040              (finfo->output_bfd, finfo->info, h, &sym)))
5041         {
5042           eoinfo->failed = true;
5043           return false;
5044         }
5045     }
5046
5047   /* If we are marking the symbol as undefined, and there are no
5048      non-weak references to this symbol from a regular object, then
5049      mark the symbol as weak undefined; if there are non-weak
5050      references, mark the symbol as strong.  We can't do this earlier,
5051      because it might not be marked as undefined until the
5052      finish_dynamic_symbol routine gets through with it.  */
5053   if (sym.st_shndx == SHN_UNDEF
5054       && (h->elf_link_hash_flags & ELF_LINK_HASH_REF_REGULAR) != 0
5055       && (ELF_ST_BIND(sym.st_info) == STB_GLOBAL
5056           || ELF_ST_BIND(sym.st_info) == STB_WEAK))
5057     {
5058       int bindtype;
5059
5060       if ((h->elf_link_hash_flags & ELF_LINK_HASH_REF_REGULAR_NONWEAK) != 0)
5061         bindtype = STB_GLOBAL;
5062       else
5063         bindtype = STB_WEAK;
5064       sym.st_info = ELF_ST_INFO (bindtype, ELF_ST_TYPE (sym.st_info));
5065     }
5066
5067   /* If this symbol should be put in the .dynsym section, then put it
5068      there now.  We have already know the symbol index.  We also fill
5069      in the entry in the .hash section.  */
5070   if (h->dynindx != -1
5071       && elf_hash_table (finfo->info)->dynamic_sections_created)
5072     {
5073       size_t bucketcount;
5074       size_t bucket;
5075       size_t hash_entry_size;
5076       bfd_byte *bucketpos;
5077       bfd_vma chain;
5078
5079       sym.st_name = h->dynstr_index;
5080
5081       elf_swap_symbol_out (finfo->output_bfd, &sym,
5082                            (PTR) (((Elf_External_Sym *)
5083                                    finfo->dynsym_sec->contents)
5084                                   + h->dynindx));
5085
5086       bucketcount = elf_hash_table (finfo->info)->bucketcount;
5087       bucket = h->elf_hash_value % bucketcount;
5088       hash_entry_size 
5089         = elf_section_data (finfo->hash_sec)->this_hdr.sh_entsize;
5090       bucketpos = ((bfd_byte *) finfo->hash_sec->contents
5091                    + (bucket + 2) * hash_entry_size);
5092       chain = bfd_get (8 * hash_entry_size, finfo->output_bfd, bucketpos);
5093       bfd_put (8 * hash_entry_size, finfo->output_bfd, h->dynindx, bucketpos);
5094       bfd_put (8 * hash_entry_size, finfo->output_bfd, chain,
5095                ((bfd_byte *) finfo->hash_sec->contents
5096                 + (bucketcount + 2 + h->dynindx) * hash_entry_size));
5097
5098       if (finfo->symver_sec != NULL && finfo->symver_sec->contents != NULL)
5099         {
5100           Elf_Internal_Versym iversym;
5101
5102           if ((h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) == 0)
5103             {
5104               if (h->verinfo.verdef == NULL)
5105                 iversym.vs_vers = 0;
5106               else
5107                 iversym.vs_vers = h->verinfo.verdef->vd_exp_refno + 1;
5108             }
5109           else
5110             {
5111               if (h->verinfo.vertree == NULL)
5112                 iversym.vs_vers = 1;
5113               else
5114                 iversym.vs_vers = h->verinfo.vertree->vernum + 1;
5115             }
5116
5117           if ((h->elf_link_hash_flags & ELF_LINK_HIDDEN) != 0)
5118             iversym.vs_vers |= VERSYM_HIDDEN;
5119
5120           _bfd_elf_swap_versym_out (finfo->output_bfd, &iversym,
5121                                     (((Elf_External_Versym *)
5122                                       finfo->symver_sec->contents)
5123                                      + h->dynindx));
5124         }
5125     }
5126
5127   /* If we're stripping it, then it was just a dynamic symbol, and
5128      there's nothing else to do.  */
5129   if (strip)
5130     return true;
5131
5132   h->indx = bfd_get_symcount (finfo->output_bfd);
5133
5134   if (! elf_link_output_sym (finfo, h->root.root.string, &sym, input_sec))
5135     {
5136       eoinfo->failed = true;
5137       return false;
5138     }
5139
5140   return true;
5141 }
5142
5143 /* Copy the relocations indicated by the INTERNAL_RELOCS (which
5144    originated from the section given by INPUT_REL_HDR) to the
5145    OUTPUT_BFD.  */
5146
5147 static void
5148 elf_link_output_relocs (output_bfd, input_section, input_rel_hdr, 
5149                         internal_relocs)
5150      bfd *output_bfd;
5151      asection *input_section;
5152      Elf_Internal_Shdr *input_rel_hdr;
5153      Elf_Internal_Rela *internal_relocs;
5154 {
5155   Elf_Internal_Rela *irela;
5156   Elf_Internal_Rela *irelaend;
5157   Elf_Internal_Shdr *output_rel_hdr;
5158   asection *output_section;
5159   unsigned int *rel_countp = NULL;
5160
5161   output_section = input_section->output_section;
5162   output_rel_hdr = NULL;
5163
5164   if (elf_section_data (output_section)->rel_hdr.sh_entsize 
5165       == input_rel_hdr->sh_entsize)
5166     {
5167       output_rel_hdr = &elf_section_data (output_section)->rel_hdr;
5168       rel_countp = &elf_section_data (output_section)->rel_count;
5169     }
5170   else if (elf_section_data (output_section)->rel_hdr2
5171            && (elf_section_data (output_section)->rel_hdr2->sh_entsize
5172                == input_rel_hdr->sh_entsize))
5173     {
5174       output_rel_hdr = elf_section_data (output_section)->rel_hdr2;
5175       rel_countp = &elf_section_data (output_section)->rel_count2;
5176     }
5177
5178   BFD_ASSERT (output_rel_hdr != NULL);
5179   
5180   irela = internal_relocs;
5181   irelaend = irela + input_rel_hdr->sh_size / input_rel_hdr->sh_entsize;
5182   if (input_rel_hdr->sh_entsize == sizeof (Elf_External_Rel))
5183     {
5184       Elf_External_Rel *erel;
5185
5186       erel = ((Elf_External_Rel *) output_rel_hdr->contents + *rel_countp);
5187       for (; irela < irelaend; irela++, erel++)
5188         {
5189           Elf_Internal_Rel irel;
5190
5191           irel.r_offset = irela->r_offset;
5192           irel.r_info = irela->r_info;
5193           BFD_ASSERT (irela->r_addend == 0);
5194           elf_swap_reloc_out (output_bfd, &irel, erel);
5195         }
5196     }
5197   else
5198     {
5199       Elf_External_Rela *erela;
5200
5201       BFD_ASSERT (input_rel_hdr->sh_entsize
5202                   == sizeof (Elf_External_Rela));
5203       erela = ((Elf_External_Rela *) output_rel_hdr->contents + *rel_countp);
5204       for (; irela < irelaend; irela++, erela++)
5205         elf_swap_reloca_out (output_bfd, irela, erela);
5206     }
5207
5208   /* Bump the counter, so that we know where to add the next set of
5209      relocations.  */
5210   *rel_countp += input_rel_hdr->sh_size / input_rel_hdr->sh_entsize;
5211 }
5212
5213 /* Link an input file into the linker output file.  This function
5214    handles all the sections and relocations of the input file at once.
5215    This is so that we only have to read the local symbols once, and
5216    don't have to keep them in memory.  */
5217
5218 static boolean
5219 elf_link_input_bfd (finfo, input_bfd)
5220      struct elf_final_link_info *finfo;
5221      bfd *input_bfd;
5222 {
5223   boolean (*relocate_section) PARAMS ((bfd *, struct bfd_link_info *,
5224                                        bfd *, asection *, bfd_byte *,
5225                                        Elf_Internal_Rela *,
5226                                        Elf_Internal_Sym *, asection **));
5227   bfd *output_bfd;
5228   Elf_Internal_Shdr *symtab_hdr;
5229   size_t locsymcount;
5230   size_t extsymoff;
5231   Elf_External_Sym *external_syms;
5232   Elf_External_Sym *esym;
5233   Elf_External_Sym *esymend;
5234   Elf_Internal_Sym *isym;
5235   long *pindex;
5236   asection **ppsection;
5237   asection *o;
5238   struct elf_backend_data *bed;
5239
5240   output_bfd = finfo->output_bfd;
5241   bed = get_elf_backend_data (output_bfd);
5242   relocate_section = bed->elf_backend_relocate_section;
5243
5244   /* If this is a dynamic object, we don't want to do anything here:
5245      we don't want the local symbols, and we don't want the section
5246      contents.  */
5247   if ((input_bfd->flags & DYNAMIC) != 0)
5248     return true;
5249
5250   symtab_hdr = &elf_tdata (input_bfd)->symtab_hdr;
5251   if (elf_bad_symtab (input_bfd))
5252     {
5253       locsymcount = symtab_hdr->sh_size / sizeof (Elf_External_Sym);
5254       extsymoff = 0;
5255     }
5256   else
5257     {
5258       locsymcount = symtab_hdr->sh_info;
5259       extsymoff = symtab_hdr->sh_info;
5260     }
5261
5262   /* Read the local symbols.  */
5263   if (symtab_hdr->contents != NULL)
5264     external_syms = (Elf_External_Sym *) symtab_hdr->contents;
5265   else if (locsymcount == 0)
5266     external_syms = NULL;
5267   else
5268     {
5269       external_syms = finfo->external_syms;
5270       if (bfd_seek (input_bfd, symtab_hdr->sh_offset, SEEK_SET) != 0
5271           || (bfd_read (external_syms, sizeof (Elf_External_Sym),
5272                         locsymcount, input_bfd)
5273               != locsymcount * sizeof (Elf_External_Sym)))
5274         return false;
5275     }
5276
5277   /* Swap in the local symbols and write out the ones which we know
5278      are going into the output file.  */
5279   esym = external_syms;
5280   esymend = esym + locsymcount;
5281   isym = finfo->internal_syms;
5282   pindex = finfo->indices;
5283   ppsection = finfo->sections;
5284   for (; esym < esymend; esym++, isym++, pindex++, ppsection++)
5285     {
5286       asection *isec;
5287       const char *name;
5288       Elf_Internal_Sym osym;
5289
5290       elf_swap_symbol_in (input_bfd, esym, isym);
5291       *pindex = -1;
5292
5293       if (elf_bad_symtab (input_bfd))
5294         {
5295           if (ELF_ST_BIND (isym->st_info) != STB_LOCAL)
5296             {
5297               *ppsection = NULL;
5298               continue;
5299             }
5300         }
5301
5302       if (isym->st_shndx == SHN_UNDEF)
5303         isec = bfd_und_section_ptr;
5304       else if (isym->st_shndx > 0 && isym->st_shndx < SHN_LORESERVE)
5305         isec = section_from_elf_index (input_bfd, isym->st_shndx);
5306       else if (isym->st_shndx == SHN_ABS)
5307         isec = bfd_abs_section_ptr;
5308       else if (isym->st_shndx == SHN_COMMON)
5309         isec = bfd_com_section_ptr;
5310       else
5311         {
5312           /* Who knows?  */
5313           isec = NULL;
5314         }
5315
5316       *ppsection = isec;
5317
5318       /* Don't output the first, undefined, symbol.  */
5319       if (esym == external_syms)
5320         continue;
5321
5322       /* If we are stripping all symbols, we don't want to output this
5323          one.  */
5324       if (finfo->info->strip == strip_all)
5325         continue;
5326
5327       /* We never output section symbols.  Instead, we use the section
5328          symbol of the corresponding section in the output file.  */
5329       if (ELF_ST_TYPE (isym->st_info) == STT_SECTION)
5330         continue;
5331
5332       /* If we are discarding all local symbols, we don't want to
5333          output this one.  If we are generating a relocateable output
5334          file, then some of the local symbols may be required by
5335          relocs; we output them below as we discover that they are
5336          needed.  */
5337       if (finfo->info->discard == discard_all)
5338         continue;
5339
5340       /* If this symbol is defined in a section which we are
5341          discarding, we don't need to keep it, but note that
5342          linker_mark is only reliable for sections that have contents.
5343          For the benefit of the MIPS ELF linker, we check SEC_EXCLUDE
5344          as well as linker_mark.  */
5345       if (isym->st_shndx > 0
5346           && isym->st_shndx < SHN_LORESERVE
5347           && isec != NULL
5348           && ((! isec->linker_mark && (isec->flags & SEC_HAS_CONTENTS) != 0)
5349               || (! finfo->info->relocateable
5350                   && (isec->flags & SEC_EXCLUDE) != 0)))
5351         continue;
5352
5353       /* Get the name of the symbol.  */
5354       name = bfd_elf_string_from_elf_section (input_bfd, symtab_hdr->sh_link,
5355                                               isym->st_name);
5356       if (name == NULL)
5357         return false;
5358
5359       /* See if we are discarding symbols with this name.  */
5360       if ((finfo->info->strip == strip_some
5361            && (bfd_hash_lookup (finfo->info->keep_hash, name, false, false)
5362                == NULL))
5363           || (finfo->info->discard == discard_l
5364               && bfd_is_local_label_name (input_bfd, name)))
5365         continue;
5366
5367       /* If we get here, we are going to output this symbol.  */
5368
5369       osym = *isym;
5370
5371       /* Adjust the section index for the output file.  */
5372       osym.st_shndx = _bfd_elf_section_from_bfd_section (output_bfd,
5373                                                          isec->output_section);
5374       if (osym.st_shndx == (unsigned short) -1)
5375         return false;
5376
5377       *pindex = bfd_get_symcount (output_bfd);
5378
5379       /* ELF symbols in relocateable files are section relative, but
5380          in executable files they are virtual addresses.  Note that
5381          this code assumes that all ELF sections have an associated
5382          BFD section with a reasonable value for output_offset; below
5383          we assume that they also have a reasonable value for
5384          output_section.  Any special sections must be set up to meet
5385          these requirements.  */
5386       osym.st_value += isec->output_offset;
5387       if (! finfo->info->relocateable)
5388         osym.st_value += isec->output_section->vma;
5389
5390       if (! elf_link_output_sym (finfo, name, &osym, isec))
5391         return false;
5392     }
5393
5394   /* Relocate the contents of each section.  */
5395   for (o = input_bfd->sections; o != NULL; o = o->next)
5396     {
5397       bfd_byte *contents;
5398
5399       if (! o->linker_mark)
5400         {
5401           /* This section was omitted from the link.  */
5402           continue;
5403         }
5404
5405       if ((o->flags & SEC_HAS_CONTENTS) == 0
5406           || (o->_raw_size == 0 && (o->flags & SEC_RELOC) == 0))
5407         continue;
5408
5409       if ((o->flags & SEC_LINKER_CREATED) != 0)
5410         {
5411           /* Section was created by elf_link_create_dynamic_sections
5412              or somesuch.  */
5413           continue;
5414         }
5415
5416       /* Get the contents of the section.  They have been cached by a
5417          relaxation routine.  Note that o is a section in an input
5418          file, so the contents field will not have been set by any of
5419          the routines which work on output files.  */
5420       if (elf_section_data (o)->this_hdr.contents != NULL)
5421         contents = elf_section_data (o)->this_hdr.contents;
5422       else
5423         {
5424           contents = finfo->contents;
5425           if (! bfd_get_section_contents (input_bfd, o, contents,
5426                                           (file_ptr) 0, o->_raw_size))
5427             return false;
5428         }
5429
5430       if ((o->flags & SEC_RELOC) != 0)
5431         {
5432           Elf_Internal_Rela *internal_relocs;
5433
5434           /* Get the swapped relocs.  */
5435           internal_relocs = (NAME(_bfd_elf,link_read_relocs)
5436                              (input_bfd, o, finfo->external_relocs,
5437                               finfo->internal_relocs, false));
5438           if (internal_relocs == NULL
5439               && o->reloc_count > 0)
5440             return false;
5441
5442           /* Relocate the section by invoking a back end routine.
5443
5444              The back end routine is responsible for adjusting the
5445              section contents as necessary, and (if using Rela relocs
5446              and generating a relocateable output file) adjusting the
5447              reloc addend as necessary.
5448
5449              The back end routine does not have to worry about setting
5450              the reloc address or the reloc symbol index.
5451
5452              The back end routine is given a pointer to the swapped in
5453              internal symbols, and can access the hash table entries
5454              for the external symbols via elf_sym_hashes (input_bfd).
5455
5456              When generating relocateable output, the back end routine
5457              must handle STB_LOCAL/STT_SECTION symbols specially.  The
5458              output symbol is going to be a section symbol
5459              corresponding to the output section, which will require
5460              the addend to be adjusted.  */
5461
5462           if (! (*relocate_section) (output_bfd, finfo->info,
5463                                      input_bfd, o, contents,
5464                                      internal_relocs,
5465                                      finfo->internal_syms,
5466                                      finfo->sections))
5467             return false;
5468
5469           if (finfo->info->relocateable)
5470             {
5471               Elf_Internal_Rela *irela;
5472               Elf_Internal_Rela *irelaend;
5473               struct elf_link_hash_entry **rel_hash;
5474               Elf_Internal_Shdr *input_rel_hdr;
5475
5476               /* Adjust the reloc addresses and symbol indices.  */
5477
5478               irela = internal_relocs;
5479               irelaend = 
5480                 irela + o->reloc_count * bed->s->int_rels_per_ext_rel;
5481               rel_hash = (elf_section_data (o->output_section)->rel_hashes
5482                           + elf_section_data (o->output_section)->rel_count
5483                           + elf_section_data (o->output_section)->rel_count2);
5484               for (; irela < irelaend; irela++, rel_hash++)
5485                 {
5486                   unsigned long r_symndx;
5487                   Elf_Internal_Sym *isym;
5488                   asection *sec;
5489
5490                   irela->r_offset += o->output_offset;
5491
5492                   r_symndx = ELF_R_SYM (irela->r_info);
5493
5494                   if (r_symndx == 0)
5495                     continue;
5496
5497                   if (r_symndx >= locsymcount
5498                       || (elf_bad_symtab (input_bfd)
5499                           && finfo->sections[r_symndx] == NULL))
5500                     {
5501                       struct elf_link_hash_entry *rh;
5502                       long indx;
5503
5504                       /* This is a reloc against a global symbol.  We
5505                          have not yet output all the local symbols, so
5506                          we do not know the symbol index of any global
5507                          symbol.  We set the rel_hash entry for this
5508                          reloc to point to the global hash table entry
5509                          for this symbol.  The symbol index is then
5510                          set at the end of elf_bfd_final_link.  */
5511                       indx = r_symndx - extsymoff;
5512                       rh = elf_sym_hashes (input_bfd)[indx];
5513                       while (rh->root.type == bfd_link_hash_indirect
5514                              || rh->root.type == bfd_link_hash_warning)
5515                         rh = (struct elf_link_hash_entry *) rh->root.u.i.link;
5516
5517                       /* Setting the index to -2 tells
5518                          elf_link_output_extsym that this symbol is
5519                          used by a reloc.  */
5520                       BFD_ASSERT (rh->indx < 0);
5521                       rh->indx = -2;
5522
5523                       *rel_hash = rh;
5524
5525                       continue;
5526                     }
5527
5528                   /* This is a reloc against a local symbol. */
5529
5530                   *rel_hash = NULL;
5531                   isym = finfo->internal_syms + r_symndx;
5532                   sec = finfo->sections[r_symndx];
5533                   if (ELF_ST_TYPE (isym->st_info) == STT_SECTION)
5534                     {
5535                       /* I suppose the backend ought to fill in the
5536                          section of any STT_SECTION symbol against a
5537                          processor specific section.  If we have
5538                          discarded a section, the output_section will
5539                          be the absolute section.  */
5540                       if (sec != NULL
5541                           && (bfd_is_abs_section (sec)
5542                               || (sec->output_section != NULL
5543                                   && bfd_is_abs_section (sec->output_section))))
5544                         r_symndx = 0;
5545                       else if (sec == NULL || sec->owner == NULL)
5546                         {
5547                           bfd_set_error (bfd_error_bad_value);
5548                           return false;
5549                         }
5550                       else
5551                         {
5552                           r_symndx = sec->output_section->target_index;
5553                           BFD_ASSERT (r_symndx != 0);
5554                         }
5555                     }
5556                   else
5557                     {
5558                       if (finfo->indices[r_symndx] == -1)
5559                         {
5560                           unsigned long link;
5561                           const char *name;
5562                           asection *osec;
5563
5564                           if (finfo->info->strip == strip_all)
5565                             {
5566                               /* You can't do ld -r -s.  */
5567                               bfd_set_error (bfd_error_invalid_operation);
5568                               return false;
5569                             }
5570
5571                           /* This symbol was skipped earlier, but
5572                              since it is needed by a reloc, we
5573                              must output it now.  */
5574                           link = symtab_hdr->sh_link;
5575                           name = bfd_elf_string_from_elf_section (input_bfd,
5576                                                                   link,
5577                                                                   isym->st_name);
5578                           if (name == NULL)
5579                             return false;
5580
5581                           osec = sec->output_section;
5582                           isym->st_shndx =
5583                             _bfd_elf_section_from_bfd_section (output_bfd,
5584                                                                osec);
5585                           if (isym->st_shndx == (unsigned short) -1)
5586                             return false;
5587
5588                           isym->st_value += sec->output_offset;
5589                           if (! finfo->info->relocateable)
5590                             isym->st_value += osec->vma;
5591
5592                           finfo->indices[r_symndx] = bfd_get_symcount (output_bfd);
5593
5594                           if (! elf_link_output_sym (finfo, name, isym, sec))
5595                             return false;
5596                         }
5597
5598                       r_symndx = finfo->indices[r_symndx];
5599                     }
5600
5601                   irela->r_info = ELF_R_INFO (r_symndx,
5602                                               ELF_R_TYPE (irela->r_info));
5603                 }
5604
5605               /* Swap out the relocs.  */
5606               input_rel_hdr = &elf_section_data (o)->rel_hdr;
5607               elf_link_output_relocs (output_bfd, o, 
5608                                       input_rel_hdr,
5609                                       internal_relocs);
5610               internal_relocs 
5611                 += input_rel_hdr->sh_size / input_rel_hdr->sh_entsize;
5612               input_rel_hdr = elf_section_data (o)->rel_hdr2;
5613               if (input_rel_hdr)
5614                 elf_link_output_relocs (output_bfd, o, 
5615                                         input_rel_hdr,
5616                                         internal_relocs);
5617             }
5618         }
5619
5620       /* Write out the modified section contents.  */
5621       if (elf_section_data (o)->stab_info == NULL)
5622         {
5623           if (! (o->flags & SEC_EXCLUDE) &&
5624               ! bfd_set_section_contents (output_bfd, o->output_section,
5625                                           contents, o->output_offset,
5626                                           (o->_cooked_size != 0
5627                                            ? o->_cooked_size
5628                                            : o->_raw_size)))
5629             return false;
5630         }
5631       else
5632         {
5633           if (! (_bfd_write_section_stabs
5634                  (output_bfd, &elf_hash_table (finfo->info)->stab_info,
5635                   o, &elf_section_data (o)->stab_info, contents)))
5636             return false;
5637         }
5638     }
5639
5640   return true;
5641 }
5642
5643 /* Generate a reloc when linking an ELF file.  This is a reloc
5644    requested by the linker, and does come from any input file.  This
5645    is used to build constructor and destructor tables when linking
5646    with -Ur.  */
5647
5648 static boolean
5649 elf_reloc_link_order (output_bfd, info, output_section, link_order)
5650      bfd *output_bfd;
5651      struct bfd_link_info *info;
5652      asection *output_section;
5653      struct bfd_link_order *link_order;
5654 {
5655   reloc_howto_type *howto;
5656   long indx;
5657   bfd_vma offset;
5658   bfd_vma addend;
5659   struct elf_link_hash_entry **rel_hash_ptr;
5660   Elf_Internal_Shdr *rel_hdr;
5661
5662   howto = bfd_reloc_type_lookup (output_bfd, link_order->u.reloc.p->reloc);
5663   if (howto == NULL)
5664     {
5665       bfd_set_error (bfd_error_bad_value);
5666       return false;
5667     }
5668
5669   addend = link_order->u.reloc.p->addend;
5670
5671   /* Figure out the symbol index.  */
5672   rel_hash_ptr = (elf_section_data (output_section)->rel_hashes
5673                   + elf_section_data (output_section)->rel_count
5674                   + elf_section_data (output_section)->rel_count2);
5675   if (link_order->type == bfd_section_reloc_link_order)
5676     {
5677       indx = link_order->u.reloc.p->u.section->target_index;
5678       BFD_ASSERT (indx != 0);
5679       *rel_hash_ptr = NULL;
5680     }
5681   else
5682     {
5683       struct elf_link_hash_entry *h;
5684
5685       /* Treat a reloc against a defined symbol as though it were
5686          actually against the section.  */
5687       h = ((struct elf_link_hash_entry *)
5688            bfd_wrapped_link_hash_lookup (output_bfd, info,
5689                                          link_order->u.reloc.p->u.name,
5690                                          false, false, true));
5691       if (h != NULL
5692           && (h->root.type == bfd_link_hash_defined
5693               || h->root.type == bfd_link_hash_defweak))
5694         {
5695           asection *section;
5696
5697           section = h->root.u.def.section;
5698           indx = section->output_section->target_index;
5699           *rel_hash_ptr = NULL;
5700           /* It seems that we ought to add the symbol value to the
5701              addend here, but in practice it has already been added
5702              because it was passed to constructor_callback.  */
5703           addend += section->output_section->vma + section->output_offset;
5704         }
5705       else if (h != NULL)
5706         {
5707           /* Setting the index to -2 tells elf_link_output_extsym that
5708              this symbol is used by a reloc.  */
5709           h->indx = -2;
5710           *rel_hash_ptr = h;
5711           indx = 0;
5712         }
5713       else
5714         {
5715           if (! ((*info->callbacks->unattached_reloc)
5716                  (info, link_order->u.reloc.p->u.name, (bfd *) NULL,
5717                   (asection *) NULL, (bfd_vma) 0)))
5718             return false;
5719           indx = 0;
5720         }
5721     }
5722
5723   /* If this is an inplace reloc, we must write the addend into the
5724      object file.  */
5725   if (howto->partial_inplace && addend != 0)
5726     {
5727       bfd_size_type size;
5728       bfd_reloc_status_type rstat;
5729       bfd_byte *buf;
5730       boolean ok;
5731
5732       size = bfd_get_reloc_size (howto);
5733       buf = (bfd_byte *) bfd_zmalloc (size);
5734       if (buf == (bfd_byte *) NULL)
5735         return false;
5736       rstat = _bfd_relocate_contents (howto, output_bfd, addend, buf);
5737       switch (rstat)
5738         {
5739         case bfd_reloc_ok:
5740           break;
5741         default:
5742         case bfd_reloc_outofrange:
5743           abort ();
5744         case bfd_reloc_overflow:
5745           if (! ((*info->callbacks->reloc_overflow)
5746                  (info,
5747                   (link_order->type == bfd_section_reloc_link_order
5748                    ? bfd_section_name (output_bfd,
5749                                        link_order->u.reloc.p->u.section)
5750                    : link_order->u.reloc.p->u.name),
5751                   howto->name, addend, (bfd *) NULL, (asection *) NULL,
5752                   (bfd_vma) 0)))
5753             {
5754               free (buf);
5755               return false;
5756             }
5757           break;
5758         }
5759       ok = bfd_set_section_contents (output_bfd, output_section, (PTR) buf,
5760                                      (file_ptr) link_order->offset, size);
5761       free (buf);
5762       if (! ok)
5763         return false;
5764     }
5765
5766   /* The address of a reloc is relative to the section in a
5767      relocateable file, and is a virtual address in an executable
5768      file.  */
5769   offset = link_order->offset;
5770   if (! info->relocateable)
5771     offset += output_section->vma;
5772
5773   rel_hdr = &elf_section_data (output_section)->rel_hdr;
5774
5775   if (rel_hdr->sh_type == SHT_REL)
5776     {
5777       Elf_Internal_Rel irel;
5778       Elf_External_Rel *erel;
5779
5780       irel.r_offset = offset;
5781       irel.r_info = ELF_R_INFO (indx, howto->type);
5782       erel = ((Elf_External_Rel *) rel_hdr->contents
5783               + elf_section_data (output_section)->rel_count);
5784       elf_swap_reloc_out (output_bfd, &irel, erel);
5785     }
5786   else
5787     {
5788       Elf_Internal_Rela irela;
5789       Elf_External_Rela *erela;
5790
5791       irela.r_offset = offset;
5792       irela.r_info = ELF_R_INFO (indx, howto->type);
5793       irela.r_addend = addend;
5794       erela = ((Elf_External_Rela *) rel_hdr->contents
5795                + elf_section_data (output_section)->rel_count);
5796       elf_swap_reloca_out (output_bfd, &irela, erela);
5797     }
5798
5799   ++elf_section_data (output_section)->rel_count;
5800
5801   return true;
5802 }
5803
5804 \f
5805 /* Allocate a pointer to live in a linker created section.  */
5806
5807 boolean
5808 elf_create_pointer_linker_section (abfd, info, lsect, h, rel)
5809      bfd *abfd;
5810      struct bfd_link_info *info;
5811      elf_linker_section_t *lsect;
5812      struct elf_link_hash_entry *h;
5813      const Elf_Internal_Rela *rel;
5814 {
5815   elf_linker_section_pointers_t **ptr_linker_section_ptr = NULL;
5816   elf_linker_section_pointers_t *linker_section_ptr;
5817   unsigned long r_symndx = ELF_R_SYM (rel->r_info);;
5818
5819   BFD_ASSERT (lsect != NULL);
5820
5821   /* Is this a global symbol? */
5822   if (h != NULL)
5823     {
5824       /* Has this symbol already been allocated, if so, our work is done */
5825       if (_bfd_elf_find_pointer_linker_section (h->linker_section_pointer,
5826                                                 rel->r_addend,
5827                                                 lsect->which))
5828         return true;
5829
5830       ptr_linker_section_ptr = &h->linker_section_pointer;
5831       /* Make sure this symbol is output as a dynamic symbol.  */
5832       if (h->dynindx == -1)
5833         {
5834           if (! elf_link_record_dynamic_symbol (info, h))
5835             return false;
5836         }
5837
5838       if (lsect->rel_section)
5839         lsect->rel_section->_raw_size += sizeof (Elf_External_Rela);
5840     }
5841
5842   else  /* Allocation of a pointer to a local symbol */
5843     {
5844       elf_linker_section_pointers_t **ptr = elf_local_ptr_offsets (abfd);
5845
5846       /* Allocate a table to hold the local symbols if first time */
5847       if (!ptr)
5848         {
5849           unsigned int num_symbols = elf_tdata (abfd)->symtab_hdr.sh_info;
5850           register unsigned int i;
5851
5852           ptr = (elf_linker_section_pointers_t **)
5853             bfd_alloc (abfd, num_symbols * sizeof (elf_linker_section_pointers_t *));
5854
5855           if (!ptr)
5856             return false;
5857
5858           elf_local_ptr_offsets (abfd) = ptr;
5859           for (i = 0; i < num_symbols; i++)
5860             ptr[i] = (elf_linker_section_pointers_t *)0;
5861         }
5862
5863       /* Has this symbol already been allocated, if so, our work is done */
5864       if (_bfd_elf_find_pointer_linker_section (ptr[r_symndx],
5865                                                 rel->r_addend,
5866                                                 lsect->which))
5867         return true;
5868
5869       ptr_linker_section_ptr = &ptr[r_symndx];
5870
5871       if (info->shared)
5872         {
5873           /* If we are generating a shared object, we need to
5874              output a R_<xxx>_RELATIVE reloc so that the
5875              dynamic linker can adjust this GOT entry.  */
5876           BFD_ASSERT (lsect->rel_section != NULL);
5877           lsect->rel_section->_raw_size += sizeof (Elf_External_Rela);
5878         }
5879     }
5880
5881   /* Allocate space for a pointer in the linker section, and allocate a new pointer record
5882      from internal memory.  */
5883   BFD_ASSERT (ptr_linker_section_ptr != NULL);
5884   linker_section_ptr = (elf_linker_section_pointers_t *)
5885     bfd_alloc (abfd, sizeof (elf_linker_section_pointers_t));
5886
5887   if (!linker_section_ptr)
5888     return false;
5889
5890   linker_section_ptr->next = *ptr_linker_section_ptr;
5891   linker_section_ptr->addend = rel->r_addend;
5892   linker_section_ptr->which = lsect->which;
5893   linker_section_ptr->written_address_p = false;
5894   *ptr_linker_section_ptr = linker_section_ptr;
5895
5896 #if 0
5897   if (lsect->hole_size && lsect->hole_offset < lsect->max_hole_offset)
5898     {
5899       linker_section_ptr->offset = lsect->section->_raw_size - lsect->hole_size + (ARCH_SIZE / 8);
5900       lsect->hole_offset += ARCH_SIZE / 8;
5901       lsect->sym_offset  += ARCH_SIZE / 8;
5902       if (lsect->sym_hash)      /* Bump up symbol value if needed */
5903         {
5904           lsect->sym_hash->root.u.def.value += ARCH_SIZE / 8;
5905 #ifdef DEBUG
5906           fprintf (stderr, "Bump up %s by %ld, current value = %ld\n",
5907                    lsect->sym_hash->root.root.string,
5908                    (long)ARCH_SIZE / 8,
5909                    (long)lsect->sym_hash->root.u.def.value);
5910 #endif
5911         }
5912     }
5913   else
5914 #endif
5915     linker_section_ptr->offset = lsect->section->_raw_size;
5916
5917   lsect->section->_raw_size += ARCH_SIZE / 8;
5918
5919 #ifdef DEBUG
5920   fprintf (stderr, "Create pointer in linker section %s, offset = %ld, section size = %ld\n",
5921            lsect->name, (long)linker_section_ptr->offset, (long)lsect->section->_raw_size);
5922 #endif
5923
5924   return true;
5925 }
5926
5927 \f
5928 #if ARCH_SIZE==64
5929 #define bfd_put_ptr(BFD,VAL,ADDR) bfd_put_64 (BFD, VAL, ADDR)
5930 #endif
5931 #if ARCH_SIZE==32
5932 #define bfd_put_ptr(BFD,VAL,ADDR) bfd_put_32 (BFD, VAL, ADDR)
5933 #endif
5934
5935 /* Fill in the address for a pointer generated in alinker section.  */
5936
5937 bfd_vma
5938 elf_finish_pointer_linker_section (output_bfd, input_bfd, info, lsect, h, relocation, rel, relative_reloc)
5939      bfd *output_bfd;
5940      bfd *input_bfd;
5941      struct bfd_link_info *info;
5942      elf_linker_section_t *lsect;
5943      struct elf_link_hash_entry *h;
5944      bfd_vma relocation;
5945      const Elf_Internal_Rela *rel;
5946      int relative_reloc;
5947 {
5948   elf_linker_section_pointers_t *linker_section_ptr;
5949
5950   BFD_ASSERT (lsect != NULL);
5951
5952   if (h != NULL)                /* global symbol */
5953     {
5954       linker_section_ptr = _bfd_elf_find_pointer_linker_section (h->linker_section_pointer,
5955                                                                  rel->r_addend,
5956                                                                  lsect->which);
5957
5958       BFD_ASSERT (linker_section_ptr != NULL);
5959
5960       if (! elf_hash_table (info)->dynamic_sections_created
5961           || (info->shared
5962               && info->symbolic
5963               && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR)))
5964         {
5965           /* This is actually a static link, or it is a
5966              -Bsymbolic link and the symbol is defined
5967              locally.  We must initialize this entry in the
5968              global section.
5969
5970              When doing a dynamic link, we create a .rela.<xxx>
5971              relocation entry to initialize the value.  This
5972              is done in the finish_dynamic_symbol routine.  */
5973           if (!linker_section_ptr->written_address_p)
5974             {
5975               linker_section_ptr->written_address_p = true;
5976               bfd_put_ptr (output_bfd, relocation + linker_section_ptr->addend,
5977                           lsect->section->contents + linker_section_ptr->offset);
5978             }
5979         }
5980     }
5981   else                          /* local symbol */
5982     {
5983       unsigned long r_symndx = ELF_R_SYM (rel->r_info);
5984       BFD_ASSERT (elf_local_ptr_offsets (input_bfd) != NULL);
5985       BFD_ASSERT (elf_local_ptr_offsets (input_bfd)[r_symndx] != NULL);
5986       linker_section_ptr = _bfd_elf_find_pointer_linker_section (elf_local_ptr_offsets (input_bfd)[r_symndx],
5987                                                                  rel->r_addend,
5988                                                                  lsect->which);
5989
5990       BFD_ASSERT (linker_section_ptr != NULL);
5991
5992       /* Write out pointer if it hasn't been rewritten out before */
5993       if (!linker_section_ptr->written_address_p)
5994         {
5995           linker_section_ptr->written_address_p = true;
5996           bfd_put_ptr (output_bfd, relocation + linker_section_ptr->addend,
5997                        lsect->section->contents + linker_section_ptr->offset);
5998
5999           if (info->shared)
6000             {
6001               asection *srel = lsect->rel_section;
6002               Elf_Internal_Rela outrel;
6003
6004               /* We need to generate a relative reloc for the dynamic linker.  */
6005               if (!srel)
6006                 lsect->rel_section = srel = bfd_get_section_by_name (elf_hash_table (info)->dynobj,
6007                                                                      lsect->rel_name);
6008
6009               BFD_ASSERT (srel != NULL);
6010
6011               outrel.r_offset = (lsect->section->output_section->vma
6012                                  + lsect->section->output_offset
6013                                  + linker_section_ptr->offset);
6014               outrel.r_info = ELF_R_INFO (0, relative_reloc);
6015               outrel.r_addend = 0;
6016               elf_swap_reloca_out (output_bfd, &outrel,
6017                                    (((Elf_External_Rela *)
6018                                      lsect->section->contents)
6019                                     + elf_section_data (lsect->section)->rel_count));
6020               ++elf_section_data (lsect->section)->rel_count;
6021             }
6022         }
6023     }
6024
6025   relocation = (lsect->section->output_offset
6026                 + linker_section_ptr->offset
6027                 - lsect->hole_offset
6028                 - lsect->sym_offset);
6029
6030 #ifdef DEBUG
6031   fprintf (stderr, "Finish pointer in linker section %s, offset = %ld (0x%lx)\n",
6032            lsect->name, (long)relocation, (long)relocation);
6033 #endif
6034
6035   /* Subtract out the addend, because it will get added back in by the normal
6036      processing.  */
6037   return relocation - linker_section_ptr->addend;
6038 }
6039 \f
6040 /* Garbage collect unused sections.  */
6041
6042 static boolean elf_gc_mark
6043   PARAMS ((struct bfd_link_info *info, asection *sec,
6044            asection * (*gc_mark_hook)
6045              PARAMS ((bfd *, struct bfd_link_info *, Elf_Internal_Rela *,
6046                       struct elf_link_hash_entry *, Elf_Internal_Sym *))));
6047
6048 static boolean elf_gc_sweep
6049   PARAMS ((struct bfd_link_info *info,
6050            boolean (*gc_sweep_hook)
6051              PARAMS ((bfd *abfd, struct bfd_link_info *info, asection *o,
6052                       const Elf_Internal_Rela *relocs))));
6053
6054 static boolean elf_gc_sweep_symbol
6055   PARAMS ((struct elf_link_hash_entry *h, PTR idxptr));
6056
6057 static boolean elf_gc_allocate_got_offsets
6058   PARAMS ((struct elf_link_hash_entry *h, PTR offarg));
6059
6060 static boolean elf_gc_propagate_vtable_entries_used
6061   PARAMS ((struct elf_link_hash_entry *h, PTR dummy));
6062
6063 static boolean elf_gc_smash_unused_vtentry_relocs
6064   PARAMS ((struct elf_link_hash_entry *h, PTR dummy));
6065
6066 /* The mark phase of garbage collection.  For a given section, mark
6067    it, and all the sections which define symbols to which it refers.  */
6068
6069 static boolean
6070 elf_gc_mark (info, sec, gc_mark_hook)
6071      struct bfd_link_info *info;
6072      asection *sec;
6073      asection * (*gc_mark_hook)
6074        PARAMS ((bfd *, struct bfd_link_info *, Elf_Internal_Rela *,
6075                 struct elf_link_hash_entry *, Elf_Internal_Sym *));
6076 {
6077   boolean ret = true;
6078
6079   sec->gc_mark = 1;
6080
6081   /* Look through the section relocs.  */
6082
6083   if ((sec->flags & SEC_RELOC) != 0 && sec->reloc_count > 0)
6084     {
6085       Elf_Internal_Rela *relstart, *rel, *relend;
6086       Elf_Internal_Shdr *symtab_hdr;
6087       struct elf_link_hash_entry **sym_hashes;
6088       size_t nlocsyms;
6089       size_t extsymoff;
6090       Elf_External_Sym *locsyms, *freesyms = NULL;
6091       bfd *input_bfd = sec->owner;
6092       struct elf_backend_data *bed = get_elf_backend_data (input_bfd);
6093
6094       /* GCFIXME: how to arrange so that relocs and symbols are not
6095          reread continually?  */
6096
6097       symtab_hdr = &elf_tdata (input_bfd)->symtab_hdr;
6098       sym_hashes = elf_sym_hashes (input_bfd);
6099
6100       /* Read the local symbols.  */
6101       if (elf_bad_symtab (input_bfd))
6102         {
6103           nlocsyms = symtab_hdr->sh_size / sizeof (Elf_External_Sym);
6104           extsymoff = 0;
6105         }
6106       else
6107         extsymoff = nlocsyms = symtab_hdr->sh_info;
6108       if (symtab_hdr->contents)
6109         locsyms = (Elf_External_Sym *) symtab_hdr->contents;
6110       else if (nlocsyms == 0)
6111         locsyms = NULL;
6112       else
6113         {
6114           locsyms = freesyms =
6115             bfd_malloc (nlocsyms * sizeof (Elf_External_Sym));
6116           if (freesyms == NULL
6117               || bfd_seek (input_bfd, symtab_hdr->sh_offset, SEEK_SET) != 0
6118               || (bfd_read (locsyms, sizeof (Elf_External_Sym),
6119                             nlocsyms, input_bfd)
6120                   != nlocsyms * sizeof (Elf_External_Sym)))
6121             {
6122               ret = false;
6123               goto out1;
6124             }
6125         }
6126
6127       /* Read the relocations.  */
6128       relstart = (NAME(_bfd_elf,link_read_relocs)
6129                   (sec->owner, sec, NULL, (Elf_Internal_Rela *) NULL,
6130                    info->keep_memory));
6131       if (relstart == NULL)
6132         {
6133           ret = false;
6134           goto out1;
6135         }
6136       relend = relstart + sec->reloc_count * bed->s->int_rels_per_ext_rel;
6137
6138       for (rel = relstart; rel < relend; rel++)
6139         {
6140           unsigned long r_symndx;
6141           asection *rsec;
6142           struct elf_link_hash_entry *h;
6143           Elf_Internal_Sym s;
6144
6145           r_symndx = ELF_R_SYM (rel->r_info);
6146           if (r_symndx == 0)
6147             continue;
6148
6149           if (elf_bad_symtab (sec->owner))
6150             {
6151               elf_swap_symbol_in (input_bfd, &locsyms[r_symndx], &s);
6152               if (ELF_ST_BIND (s.st_info) == STB_LOCAL)
6153                 rsec = (*gc_mark_hook)(sec->owner, info, rel, NULL, &s);
6154               else
6155                 {
6156                   h = sym_hashes[r_symndx - extsymoff];
6157                   rsec = (*gc_mark_hook)(sec->owner, info, rel, h, NULL);
6158                 }
6159             }
6160           else if (r_symndx >= nlocsyms)
6161             {
6162               h = sym_hashes[r_symndx - extsymoff];
6163               rsec = (*gc_mark_hook)(sec->owner, info, rel, h, NULL);
6164             }
6165           else
6166             {
6167               elf_swap_symbol_in (input_bfd, &locsyms[r_symndx], &s);
6168               rsec = (*gc_mark_hook)(sec->owner, info, rel, NULL, &s);
6169             }
6170
6171           if (rsec && !rsec->gc_mark)
6172             if (!elf_gc_mark (info, rsec, gc_mark_hook))
6173               {
6174                 ret = false;
6175                 goto out2;
6176               }
6177         }
6178
6179     out2:
6180       if (!info->keep_memory)
6181         free (relstart);
6182     out1:
6183       if (freesyms)
6184         free (freesyms);
6185     }
6186
6187   return ret;
6188 }
6189
6190 /* The sweep phase of garbage collection.  Remove all garbage sections.  */
6191
6192 static boolean
6193 elf_gc_sweep (info, gc_sweep_hook)
6194      struct bfd_link_info *info;
6195      boolean (*gc_sweep_hook)
6196        PARAMS ((bfd *abfd, struct bfd_link_info *info, asection *o,
6197                 const Elf_Internal_Rela *relocs));
6198 {
6199   bfd *sub;
6200
6201   for (sub = info->input_bfds; sub != NULL; sub = sub->link_next)
6202     {
6203       asection *o;
6204
6205       if (bfd_get_flavour (sub) != bfd_target_elf_flavour)
6206         continue;
6207
6208       for (o = sub->sections; o != NULL; o = o->next)
6209         {
6210           /* Keep special sections.  Keep .debug sections.  */
6211           if ((o->flags & SEC_LINKER_CREATED)
6212               || (o->flags & SEC_DEBUGGING))
6213             o->gc_mark = 1;
6214
6215           if (o->gc_mark)
6216             continue;
6217
6218           /* Skip sweeping sections already excluded.  */
6219           if (o->flags & SEC_EXCLUDE)
6220             continue;
6221
6222           /* Since this is early in the link process, it is simple
6223              to remove a section from the output.  */
6224           o->flags |= SEC_EXCLUDE;
6225
6226           /* But we also have to update some of the relocation
6227              info we collected before.  */
6228           if (gc_sweep_hook
6229               && (o->flags & SEC_RELOC) && o->reloc_count > 0)
6230             {
6231               Elf_Internal_Rela *internal_relocs;
6232               boolean r;
6233
6234               internal_relocs = (NAME(_bfd_elf,link_read_relocs)
6235                                  (o->owner, o, NULL, NULL, info->keep_memory));
6236               if (internal_relocs == NULL)
6237                 return false;
6238
6239               r = (*gc_sweep_hook)(o->owner, info, o, internal_relocs);
6240
6241               if (!info->keep_memory)
6242                 free (internal_relocs);
6243
6244               if (!r)
6245                 return false;
6246             }
6247         }
6248     }
6249
6250   /* Remove the symbols that were in the swept sections from the dynamic
6251      symbol table.  GCFIXME: Anyone know how to get them out of the
6252      static symbol table as well?  */
6253   {
6254     int i = 0;
6255
6256     elf_link_hash_traverse (elf_hash_table (info),
6257                             elf_gc_sweep_symbol,
6258                             (PTR) &i);
6259
6260     elf_hash_table (info)->dynsymcount = i;
6261   }
6262
6263   return true;
6264 }
6265
6266 /* Sweep symbols in swept sections.  Called via elf_link_hash_traverse.  */
6267
6268 static boolean
6269 elf_gc_sweep_symbol (h, idxptr)
6270      struct elf_link_hash_entry *h;
6271      PTR idxptr;
6272 {
6273   int *idx = (int *) idxptr;
6274
6275   if (h->dynindx != -1
6276       && ((h->root.type != bfd_link_hash_defined
6277            && h->root.type != bfd_link_hash_defweak)
6278           || h->root.u.def.section->gc_mark))
6279     h->dynindx = (*idx)++;
6280
6281   return true;
6282 }
6283
6284 /* Propogate collected vtable information.  This is called through
6285    elf_link_hash_traverse.  */
6286
6287 static boolean
6288 elf_gc_propagate_vtable_entries_used (h, okp)
6289      struct elf_link_hash_entry *h;
6290      PTR okp;
6291 {
6292   /* Those that are not vtables. */
6293   if (h->vtable_parent == NULL)
6294     return true;
6295
6296   /* Those vtables that do not have parents, we cannot merge.  */
6297   if (h->vtable_parent == (struct elf_link_hash_entry *) -1)
6298     return true;
6299
6300   /* If we've already been done, exit.  */
6301   if (h->vtable_entries_used && h->vtable_entries_used[-1])
6302     return true;
6303
6304   /* Make sure the parent's table is up to date.  */
6305   elf_gc_propagate_vtable_entries_used (h->vtable_parent, okp);
6306
6307   if (h->vtable_entries_used == NULL)
6308     {
6309       /* None of this table's entries were referenced.  Re-use the
6310          parent's table.  */
6311       h->vtable_entries_used = h->vtable_parent->vtable_entries_used;
6312       h->vtable_entries_size = h->vtable_parent->vtable_entries_size;
6313     }
6314   else
6315     {
6316       size_t n;
6317       boolean *cu, *pu;
6318
6319       /* Or the parent's entries into ours.  */
6320       cu = h->vtable_entries_used;
6321       cu[-1] = true;
6322       pu = h->vtable_parent->vtable_entries_used;
6323       if (pu != NULL)
6324         {
6325           n = h->vtable_parent->vtable_entries_size / FILE_ALIGN;
6326           while (--n != 0)
6327             {
6328               if (*pu) *cu = true;
6329               pu++, cu++;
6330             }
6331         }
6332     }
6333
6334   return true;
6335 }
6336
6337 static boolean
6338 elf_gc_smash_unused_vtentry_relocs (h, okp)
6339      struct elf_link_hash_entry *h;
6340      PTR okp;
6341 {
6342   asection *sec;
6343   bfd_vma hstart, hend;
6344   Elf_Internal_Rela *relstart, *relend, *rel;
6345   struct elf_backend_data *bed;
6346
6347   /* Take care of both those symbols that do not describe vtables as
6348      well as those that are not loaded.  */
6349   if (h->vtable_parent == NULL)
6350     return true;
6351
6352   BFD_ASSERT (h->root.type == bfd_link_hash_defined
6353               || h->root.type == bfd_link_hash_defweak);
6354
6355   sec = h->root.u.def.section;
6356   hstart = h->root.u.def.value;
6357   hend = hstart + h->size;
6358
6359   relstart = (NAME(_bfd_elf,link_read_relocs)
6360               (sec->owner, sec, NULL, (Elf_Internal_Rela *) NULL, true));
6361   if (!relstart)
6362     return *(boolean *)okp = false;
6363   bed = get_elf_backend_data (sec->owner);
6364   relend = relstart + sec->reloc_count * bed->s->int_rels_per_ext_rel;
6365
6366   for (rel = relstart; rel < relend; ++rel)
6367     if (rel->r_offset >= hstart && rel->r_offset < hend)
6368       {
6369         /* If the entry is in use, do nothing.  */
6370         if (h->vtable_entries_used
6371             && (rel->r_offset - hstart) < h->vtable_entries_size)
6372           {
6373             bfd_vma entry = (rel->r_offset - hstart) / FILE_ALIGN;
6374             if (h->vtable_entries_used[entry])
6375               continue;
6376           }
6377         /* Otherwise, kill it.  */
6378         rel->r_offset = rel->r_info = rel->r_addend = 0;
6379       }
6380
6381   return true;
6382 }
6383
6384 /* Do mark and sweep of unused sections.  */
6385
6386 boolean
6387 elf_gc_sections (abfd, info)
6388      bfd *abfd;
6389      struct bfd_link_info *info;
6390 {
6391   boolean ok = true;
6392   bfd *sub;
6393   asection * (*gc_mark_hook)
6394     PARAMS ((bfd *abfd, struct bfd_link_info *, Elf_Internal_Rela *,
6395              struct elf_link_hash_entry *h, Elf_Internal_Sym *));
6396
6397   if (!get_elf_backend_data (abfd)->can_gc_sections
6398       || info->relocateable
6399       || elf_hash_table (info)->dynamic_sections_created)
6400     return true;
6401
6402   /* Apply transitive closure to the vtable entry usage info.  */
6403   elf_link_hash_traverse (elf_hash_table (info),
6404                           elf_gc_propagate_vtable_entries_used,
6405                           (PTR) &ok);
6406   if (!ok)
6407     return false;
6408
6409   /* Kill the vtable relocations that were not used.  */
6410   elf_link_hash_traverse (elf_hash_table (info),
6411                           elf_gc_smash_unused_vtentry_relocs,
6412                           (PTR) &ok);
6413   if (!ok)
6414     return false;
6415
6416   /* Grovel through relocs to find out who stays ...  */
6417
6418   gc_mark_hook = get_elf_backend_data (abfd)->gc_mark_hook;
6419   for (sub = info->input_bfds; sub != NULL; sub = sub->link_next)
6420     {
6421       asection *o;
6422
6423       if (bfd_get_flavour (sub) != bfd_target_elf_flavour)
6424         continue;
6425
6426       for (o = sub->sections; o != NULL; o = o->next)
6427         {
6428           if (o->flags & SEC_KEEP)
6429             if (!elf_gc_mark (info, o, gc_mark_hook))
6430               return false;
6431         }
6432     }
6433
6434   /* ... and mark SEC_EXCLUDE for those that go.  */
6435   if (!elf_gc_sweep(info, get_elf_backend_data (abfd)->gc_sweep_hook))
6436     return false;
6437
6438   return true;
6439 }
6440 \f
6441 /* Called from check_relocs to record the existance of a VTINHERIT reloc.  */
6442
6443 boolean
6444 elf_gc_record_vtinherit (abfd, sec, h, offset)
6445      bfd *abfd;
6446      asection *sec;
6447      struct elf_link_hash_entry *h;
6448      bfd_vma offset;
6449 {
6450   struct elf_link_hash_entry **sym_hashes, **sym_hashes_end;
6451   struct elf_link_hash_entry **search, *child;
6452   bfd_size_type extsymcount;
6453
6454   /* The sh_info field of the symtab header tells us where the
6455      external symbols start.  We don't care about the local symbols at
6456      this point.  */
6457   extsymcount = elf_tdata (abfd)->symtab_hdr.sh_size/sizeof (Elf_External_Sym);
6458   if (!elf_bad_symtab (abfd))
6459     extsymcount -= elf_tdata (abfd)->symtab_hdr.sh_info;
6460
6461   sym_hashes = elf_sym_hashes (abfd);
6462   sym_hashes_end = sym_hashes + extsymcount;
6463
6464   /* Hunt down the child symbol, which is in this section at the same
6465      offset as the relocation.  */
6466   for (search = sym_hashes; search != sym_hashes_end; ++search)
6467     {
6468       if ((child = *search) != NULL
6469           && (child->root.type == bfd_link_hash_defined
6470               || child->root.type == bfd_link_hash_defweak)
6471           && child->root.u.def.section == sec
6472           && child->root.u.def.value == offset)
6473         goto win;
6474     }
6475
6476   (*_bfd_error_handler) ("%s: %s+%lu: No symbol found for INHERIT",
6477                          bfd_get_filename (abfd), sec->name,
6478                          (unsigned long)offset);
6479   bfd_set_error (bfd_error_invalid_operation);
6480   return false;
6481
6482 win:
6483   if (!h)
6484     {
6485       /* This *should* only be the absolute section.  It could potentially
6486          be that someone has defined a non-global vtable though, which
6487          would be bad.  It isn't worth paging in the local symbols to be
6488          sure though; that case should simply be handled by the assembler.  */
6489
6490       child->vtable_parent = (struct elf_link_hash_entry *) -1;
6491     }
6492   else
6493     child->vtable_parent = h;
6494
6495   return true;
6496 }
6497
6498 /* Called from check_relocs to record the existance of a VTENTRY reloc.  */
6499
6500 boolean
6501 elf_gc_record_vtentry (abfd, sec, h, addend)
6502      bfd *abfd ATTRIBUTE_UNUSED;
6503      asection *sec ATTRIBUTE_UNUSED;
6504      struct elf_link_hash_entry *h;
6505      bfd_vma addend;
6506 {
6507   if (addend >= h->vtable_entries_size)
6508     {
6509       size_t size, bytes;
6510       boolean *ptr = h->vtable_entries_used;
6511
6512       /* While the symbol is undefined, we have to be prepared to handle
6513          a zero size.  */
6514       if (h->root.type == bfd_link_hash_undefined)
6515         size = addend;
6516       else
6517         {
6518           size = h->size;
6519           if (size < addend)
6520             {
6521               /* Oops!  We've got a reference past the defined end of
6522                  the table.  This is probably a bug -- shall we warn?  */
6523               size = addend;
6524             }
6525         }
6526
6527       /* Allocate one extra entry for use as a "done" flag for the
6528          consolidation pass.  */
6529       bytes = (size / FILE_ALIGN + 1) * sizeof (boolean);
6530
6531       if (ptr)
6532         {
6533           ptr = bfd_realloc (ptr - 1, bytes);
6534           
6535           if (ptr != NULL)
6536             {
6537               size_t oldbytes;
6538
6539               oldbytes = (h->vtable_entries_size/FILE_ALIGN + 1) * sizeof (boolean);
6540               memset (((char *)ptr) + oldbytes, 0, bytes - oldbytes);
6541             }
6542         }
6543       else
6544         ptr = bfd_zmalloc (bytes);
6545
6546       if (ptr == NULL)
6547         return false;
6548       
6549       /* And arrange for that done flag to be at index -1.  */
6550       h->vtable_entries_used = ptr + 1;
6551       h->vtable_entries_size = size;
6552     }
6553   
6554   h->vtable_entries_used[addend / FILE_ALIGN] = true;
6555
6556   return true;
6557 }
6558
6559 /* And an accompanying bit to work out final got entry offsets once
6560    we're done.  Should be called from final_link.  */
6561
6562 boolean
6563 elf_gc_common_finalize_got_offsets (abfd, info)
6564      bfd *abfd;
6565      struct bfd_link_info *info;
6566 {
6567   bfd *i;
6568   struct elf_backend_data *bed = get_elf_backend_data (abfd);
6569   bfd_vma gotoff;
6570
6571   /* The GOT offset is relative to the .got section, but the GOT header is
6572      put into the .got.plt section, if the backend uses it.  */
6573   if (bed->want_got_plt)
6574     gotoff = 0;
6575   else
6576     gotoff = bed->got_header_size;
6577
6578   /* Do the local .got entries first.  */
6579   for (i = info->input_bfds; i; i = i->link_next)
6580     {
6581       bfd_signed_vma *local_got;
6582       bfd_size_type j, locsymcount;
6583       Elf_Internal_Shdr *symtab_hdr;
6584
6585       if (bfd_get_flavour (i) != bfd_target_elf_flavour)
6586         continue;
6587
6588       local_got = elf_local_got_refcounts (i);
6589       if (!local_got)
6590         continue;
6591
6592       symtab_hdr = &elf_tdata (i)->symtab_hdr;
6593       if (elf_bad_symtab (i))
6594         locsymcount = symtab_hdr->sh_size / sizeof (Elf_External_Sym);
6595       else
6596         locsymcount = symtab_hdr->sh_info;
6597
6598       for (j = 0; j < locsymcount; ++j)
6599         {
6600           if (local_got[j] > 0)
6601             {
6602               local_got[j] = gotoff;
6603               gotoff += ARCH_SIZE / 8;
6604             }
6605           else
6606             local_got[j] = (bfd_vma) -1;
6607         }
6608     }
6609
6610   /* Then the global .got and .plt entries.  */
6611   elf_link_hash_traverse (elf_hash_table (info),
6612                           elf_gc_allocate_got_offsets,
6613                           (PTR) &gotoff);
6614   return true;
6615 }
6616
6617 /* We need a special top-level link routine to convert got reference counts
6618    to real got offsets.  */
6619
6620 static boolean
6621 elf_gc_allocate_got_offsets (h, offarg)
6622      struct elf_link_hash_entry *h;
6623      PTR offarg;
6624 {
6625   bfd_vma *off = (bfd_vma *) offarg;
6626
6627   if (h->got.refcount > 0)
6628     {
6629       h->got.offset = off[0];
6630       off[0] += ARCH_SIZE / 8;
6631     }
6632   else
6633     h->got.offset = (bfd_vma) -1;
6634
6635   return true;
6636 }
6637
6638 /* Many folk need no more in the way of final link than this, once
6639    got entry reference counting is enabled.  */
6640
6641 boolean
6642 elf_gc_common_final_link (abfd, info)
6643      bfd *abfd;
6644      struct bfd_link_info *info;
6645 {
6646   if (!elf_gc_common_finalize_got_offsets (abfd, info))
6647     return false;
6648
6649   /* Invoke the regular ELF backend linker to do all the work.  */
6650   return elf_bfd_final_link (abfd, info);
6651 }
6652
6653 /* This function will be called though elf_link_hash_traverse to store
6654    all hash value of the exported symbols in an array.  */
6655
6656 static boolean
6657 elf_collect_hash_codes (h, data)
6658      struct elf_link_hash_entry *h;
6659      PTR data;
6660 {
6661   unsigned long **valuep = (unsigned long **) data;
6662   const char *name;
6663   char *p;
6664   unsigned long ha;
6665   char *alc = NULL;
6666
6667   /* Ignore indirect symbols.  These are added by the versioning code.  */
6668   if (h->dynindx == -1)
6669     return true;
6670
6671   name = h->root.root.string;
6672   p = strchr (name, ELF_VER_CHR);
6673   if (p != NULL)
6674     {
6675       alc = bfd_malloc (p - name + 1);
6676       memcpy (alc, name, p - name);
6677       alc[p - name] = '\0';
6678       name = alc;
6679     }
6680
6681   /* Compute the hash value.  */
6682   ha = bfd_elf_hash (name);
6683
6684   /* Store the found hash value in the array given as the argument.  */
6685   *(*valuep)++ = ha;
6686
6687   /* And store it in the struct so that we can put it in the hash table
6688      later.  */
6689   h->elf_hash_value = ha;
6690
6691   if (alc != NULL)
6692     free (alc);
6693
6694   return true;
6695 }