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