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