2 Copyright 1995, 1996, 1997 Free Software Foundation, Inc.
4 This file is part of BFD, the Binary File Descriptor library.
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.
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.
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. */
20 /* ELF linker code. */
22 static boolean elf_link_add_object_symbols
23 PARAMS ((bfd *, struct bfd_link_info *));
24 static boolean elf_link_add_archive_symbols
25 PARAMS ((bfd *, struct bfd_link_info *));
26 static boolean elf_export_symbol
27 PARAMS ((struct elf_link_hash_entry *, PTR));
28 static boolean elf_adjust_dynamic_symbol
29 PARAMS ((struct elf_link_hash_entry *, PTR));
30 static boolean elf_link_find_version_dependencies
31 PARAMS ((struct elf_link_hash_entry *, PTR));
32 static boolean elf_link_find_version_dependencies
33 PARAMS ((struct elf_link_hash_entry *, PTR));
34 static boolean elf_link_assign_sym_version
35 PARAMS ((struct elf_link_hash_entry *, PTR));
36 static boolean elf_link_renumber_dynsyms
37 PARAMS ((struct elf_link_hash_entry *, PTR));
39 /* This struct is used to pass information to routines called via
40 elf_link_hash_traverse which must return failure. */
42 struct elf_info_failed
45 struct bfd_link_info *info;
48 /* Given an ELF BFD, add symbols to the global hash table as
52 elf_bfd_link_add_symbols (abfd, info)
54 struct bfd_link_info *info;
56 switch (bfd_get_format (abfd))
59 return elf_link_add_object_symbols (abfd, info);
61 return elf_link_add_archive_symbols (abfd, info);
63 bfd_set_error (bfd_error_wrong_format);
69 /* Add symbols from an ELF archive file to the linker hash table. We
70 don't use _bfd_generic_link_add_archive_symbols because of a
71 problem which arises on UnixWare. The UnixWare libc.so is an
72 archive which includes an entry libc.so.1 which defines a bunch of
73 symbols. The libc.so archive also includes a number of other
74 object files, which also define symbols, some of which are the same
75 as those defined in libc.so.1. Correct linking requires that we
76 consider each object file in turn, and include it if it defines any
77 symbols we need. _bfd_generic_link_add_archive_symbols does not do
78 this; it looks through the list of undefined symbols, and includes
79 any object file which defines them. When this algorithm is used on
80 UnixWare, it winds up pulling in libc.so.1 early and defining a
81 bunch of symbols. This means that some of the other objects in the
82 archive are not included in the link, which is incorrect since they
83 precede libc.so.1 in the archive.
85 Fortunately, ELF archive handling is simpler than that done by
86 _bfd_generic_link_add_archive_symbols, which has to allow for a.out
87 oddities. In ELF, if we find a symbol in the archive map, and the
88 symbol is currently undefined, we know that we must pull in that
91 Unfortunately, we do have to make multiple passes over the symbol
92 table until nothing further is resolved. */
95 elf_link_add_archive_symbols (abfd, info)
97 struct bfd_link_info *info;
100 boolean *defined = NULL;
101 boolean *included = NULL;
105 if (! bfd_has_map (abfd))
107 /* An empty archive is a special case. */
108 if (bfd_openr_next_archived_file (abfd, (bfd *) NULL) == NULL)
110 bfd_set_error (bfd_error_no_armap);
114 /* Keep track of all symbols we know to be already defined, and all
115 files we know to be already included. This is to speed up the
116 second and subsequent passes. */
117 c = bfd_ardata (abfd)->symdef_count;
120 defined = (boolean *) bfd_malloc (c * sizeof (boolean));
121 included = (boolean *) bfd_malloc (c * sizeof (boolean));
122 if (defined == (boolean *) NULL || included == (boolean *) NULL)
124 memset (defined, 0, c * sizeof (boolean));
125 memset (included, 0, c * sizeof (boolean));
127 symdefs = bfd_ardata (abfd)->symdefs;
140 symdefend = symdef + c;
141 for (i = 0; symdef < symdefend; symdef++, i++)
143 struct elf_link_hash_entry *h;
145 struct bfd_link_hash_entry *undefs_tail;
148 if (defined[i] || included[i])
150 if (symdef->file_offset == last)
156 h = elf_link_hash_lookup (elf_hash_table (info), symdef->name,
157 false, false, false);
163 /* If this is a default version (the name contains @@),
164 look up the symbol again without the version. The
165 effect is that references to the symbol without the
166 version will be matched by the default symbol in the
169 p = strchr (symdef->name, ELF_VER_CHR);
170 if (p == NULL || p[1] != ELF_VER_CHR)
173 copy = bfd_alloc (abfd, p - symdef->name + 1);
176 memcpy (copy, symdef->name, p - symdef->name);
177 copy[p - symdef->name] = '\0';
179 h = elf_link_hash_lookup (elf_hash_table (info), copy,
180 false, false, false);
182 bfd_release (abfd, copy);
188 if (h->root.type != bfd_link_hash_undefined)
190 if (h->root.type != bfd_link_hash_undefweak)
195 /* We need to include this archive member. */
197 element = _bfd_get_elt_at_filepos (abfd, symdef->file_offset);
198 if (element == (bfd *) NULL)
201 if (! bfd_check_format (element, bfd_object))
204 /* Doublecheck that we have not included this object
205 already--it should be impossible, but there may be
206 something wrong with the archive. */
207 if (element->archive_pass != 0)
209 bfd_set_error (bfd_error_bad_value);
212 element->archive_pass = 1;
214 undefs_tail = info->hash->undefs_tail;
216 if (! (*info->callbacks->add_archive_element) (info, element,
219 if (! elf_link_add_object_symbols (element, info))
222 /* If there are any new undefined symbols, we need to make
223 another pass through the archive in order to see whether
224 they can be defined. FIXME: This isn't perfect, because
225 common symbols wind up on undefs_tail and because an
226 undefined symbol which is defined later on in this pass
227 does not require another pass. This isn't a bug, but it
228 does make the code less efficient than it could be. */
229 if (undefs_tail != info->hash->undefs_tail)
232 /* Look backward to mark all symbols from this object file
233 which we have already seen in this pass. */
237 included[mark] = true;
242 while (symdefs[mark].file_offset == symdef->file_offset);
244 /* We mark subsequent symbols from this object file as we go
245 on through the loop. */
246 last = symdef->file_offset;
257 if (defined != (boolean *) NULL)
259 if (included != (boolean *) NULL)
264 /* Add symbols from an ELF object file to the linker hash table. */
267 elf_link_add_object_symbols (abfd, info)
269 struct bfd_link_info *info;
271 boolean (*add_symbol_hook) PARAMS ((bfd *, struct bfd_link_info *,
272 const Elf_Internal_Sym *,
273 const char **, flagword *,
274 asection **, bfd_vma *));
275 boolean (*check_relocs) PARAMS ((bfd *, struct bfd_link_info *,
276 asection *, const Elf_Internal_Rela *));
278 Elf_Internal_Shdr *hdr;
282 Elf_External_Sym *buf = NULL;
283 struct elf_link_hash_entry **sym_hash;
285 bfd_byte *dynver = NULL;
286 Elf_External_Versym *extversym = NULL;
287 Elf_External_Versym *ever;
288 Elf_External_Dyn *dynbuf = NULL;
289 struct elf_link_hash_entry *weaks;
290 Elf_External_Sym *esym;
291 Elf_External_Sym *esymend;
293 add_symbol_hook = get_elf_backend_data (abfd)->elf_add_symbol_hook;
294 collect = get_elf_backend_data (abfd)->collect;
296 if ((abfd->flags & DYNAMIC) == 0)
302 /* You can't use -r against a dynamic object. Also, there's no
303 hope of using a dynamic object which does not exactly match
304 the format of the output file. */
305 if (info->relocateable || info->hash->creator != abfd->xvec)
307 bfd_set_error (bfd_error_invalid_operation);
312 /* As a GNU extension, any input sections which are named
313 .gnu.warning.SYMBOL are treated as warning symbols for the given
314 symbol. This differs from .gnu.warning sections, which generate
315 warnings when they are included in an output file. */
320 for (s = abfd->sections; s != NULL; s = s->next)
324 name = bfd_get_section_name (abfd, s);
325 if (strncmp (name, ".gnu.warning.", sizeof ".gnu.warning." - 1) == 0)
330 name += sizeof ".gnu.warning." - 1;
332 /* If this is a shared object, then look up the symbol
333 in the hash table. If it is there, and it is already
334 been defined, then we will not be using the entry
335 from this shared object, so we don't need to warn.
336 FIXME: If we see the definition in a regular object
337 later on, we will warn, but we shouldn't. The only
338 fix is to keep track of what warnings we are supposed
339 to emit, and then handle them all at the end of the
341 if (dynamic && abfd->xvec == info->hash->creator)
343 struct elf_link_hash_entry *h;
345 h = elf_link_hash_lookup (elf_hash_table (info), name,
348 /* FIXME: What about bfd_link_hash_common? */
350 && (h->root.type == bfd_link_hash_defined
351 || h->root.type == bfd_link_hash_defweak))
353 /* We don't want to issue this warning. Clobber
354 the section size so that the warning does not
355 get copied into the output file. */
361 sz = bfd_section_size (abfd, s);
362 msg = (char *) bfd_alloc (abfd, sz);
366 if (! bfd_get_section_contents (abfd, s, msg, (file_ptr) 0, sz))
369 if (! (_bfd_generic_link_add_one_symbol
370 (info, abfd, name, BSF_WARNING, s, (bfd_vma) 0, msg,
371 false, collect, (struct bfd_link_hash_entry **) NULL)))
374 if (! info->relocateable)
376 /* Clobber the section size so that the warning does
377 not get copied into the output file. */
384 /* If this is a dynamic object, we always link against the .dynsym
385 symbol table, not the .symtab symbol table. The dynamic linker
386 will only see the .dynsym symbol table, so there is no reason to
387 look at .symtab for a dynamic object. */
389 if (! dynamic || elf_dynsymtab (abfd) == 0)
390 hdr = &elf_tdata (abfd)->symtab_hdr;
392 hdr = &elf_tdata (abfd)->dynsymtab_hdr;
396 /* Read in any version definitions. */
398 if (elf_dynverdef (abfd) != 0)
400 Elf_Internal_Shdr *verdefhdr;
403 const Elf_External_Verdef *extverdef;
404 Elf_Internal_Verdef *intverdef;
406 verdefhdr = &elf_tdata (abfd)->dynverdef_hdr;
407 elf_tdata (abfd)->verdef =
408 ((Elf_Internal_Verdef *)
410 verdefhdr->sh_info * sizeof (Elf_Internal_Verdef)));
411 if (elf_tdata (abfd)->verdef == NULL)
414 dynver = (bfd_byte *) bfd_malloc (verdefhdr->sh_size);
418 if (bfd_seek (abfd, verdefhdr->sh_offset, SEEK_SET) != 0
419 || (bfd_read ((PTR) dynver, 1, verdefhdr->sh_size, abfd)
420 != verdefhdr->sh_size))
423 extverdef = (const Elf_External_Verdef *) dynver;
424 intverdef = elf_tdata (abfd)->verdef;
425 for (i = 0; i < verdefhdr->sh_info; i++, intverdef++)
427 const Elf_External_Verdaux *extverdaux;
428 Elf_Internal_Verdaux intverdaux;
430 _bfd_elf_swap_verdef_in (abfd, extverdef, intverdef);
432 /* Pick up the name of the version. */
433 extverdaux = ((const Elf_External_Verdaux *)
434 ((bfd_byte *) extverdef + intverdef->vd_aux));
435 _bfd_elf_swap_verdaux_in (abfd, extverdaux, &intverdaux);
437 intverdef->vd_bfd = abfd;
438 intverdef->vd_nodename =
439 bfd_elf_string_from_elf_section (abfd, verdefhdr->sh_link,
440 intverdaux.vda_name);
442 extverdef = ((const Elf_External_Verdef *)
443 ((bfd_byte *) extverdef + intverdef->vd_next));
450 /* Read in the symbol versions, but don't bother to convert them
451 to internal format. */
452 if (elf_dynversym (abfd) != 0)
454 Elf_Internal_Shdr *versymhdr;
456 versymhdr = &elf_tdata (abfd)->dynversym_hdr;
457 extversym = (Elf_External_Versym *) bfd_malloc (hdr->sh_size);
458 if (extversym == NULL)
460 if (bfd_seek (abfd, versymhdr->sh_offset, SEEK_SET) != 0
461 || (bfd_read ((PTR) extversym, 1, versymhdr->sh_size, abfd)
462 != versymhdr->sh_size))
467 symcount = hdr->sh_size / sizeof (Elf_External_Sym);
469 /* The sh_info field of the symtab header tells us where the
470 external symbols start. We don't care about the local symbols at
472 if (elf_bad_symtab (abfd))
474 extsymcount = symcount;
479 extsymcount = symcount - hdr->sh_info;
480 extsymoff = hdr->sh_info;
483 buf = ((Elf_External_Sym *)
484 bfd_malloc (extsymcount * sizeof (Elf_External_Sym)));
485 if (buf == NULL && extsymcount != 0)
488 /* We store a pointer to the hash table entry for each external
490 sym_hash = ((struct elf_link_hash_entry **)
492 extsymcount * sizeof (struct elf_link_hash_entry *)));
493 if (sym_hash == NULL)
495 elf_sym_hashes (abfd) = sym_hash;
499 /* If we are creating a shared library, create all the dynamic
500 sections immediately. We need to attach them to something,
501 so we attach them to this BFD, provided it is the right
502 format. FIXME: If there are no input BFD's of the same
503 format as the output, we can't make a shared library. */
505 && ! elf_hash_table (info)->dynamic_sections_created
506 && abfd->xvec == info->hash->creator)
508 if (! elf_link_create_dynamic_sections (abfd, info))
517 bfd_size_type oldsize;
518 bfd_size_type strindex;
520 /* Find the name to use in a DT_NEEDED entry that refers to this
521 object. If the object has a DT_SONAME entry, we use it.
522 Otherwise, if the generic linker stuck something in
523 elf_dt_name, we use that. Otherwise, we just use the file
524 name. If the generic linker put a null string into
525 elf_dt_name, we don't make a DT_NEEDED entry at all, even if
526 there is a DT_SONAME entry. */
528 name = bfd_get_filename (abfd);
529 if (elf_dt_name (abfd) != NULL)
531 name = elf_dt_name (abfd);
535 s = bfd_get_section_by_name (abfd, ".dynamic");
538 Elf_External_Dyn *extdyn;
539 Elf_External_Dyn *extdynend;
543 dynbuf = (Elf_External_Dyn *) bfd_malloc ((size_t) s->_raw_size);
547 if (! bfd_get_section_contents (abfd, s, (PTR) dynbuf,
548 (file_ptr) 0, s->_raw_size))
551 elfsec = _bfd_elf_section_from_bfd_section (abfd, s);
554 link = elf_elfsections (abfd)[elfsec]->sh_link;
557 extdynend = extdyn + s->_raw_size / sizeof (Elf_External_Dyn);
558 for (; extdyn < extdynend; extdyn++)
560 Elf_Internal_Dyn dyn;
562 elf_swap_dyn_in (abfd, extdyn, &dyn);
563 if (dyn.d_tag == DT_SONAME)
565 name = bfd_elf_string_from_elf_section (abfd, link,
570 if (dyn.d_tag == DT_NEEDED)
572 struct bfd_link_needed_list *n, **pn;
575 n = ((struct bfd_link_needed_list *)
576 bfd_alloc (abfd, sizeof (struct bfd_link_needed_list)));
577 fnm = bfd_elf_string_from_elf_section (abfd, link,
579 if (n == NULL || fnm == NULL)
581 anm = bfd_alloc (abfd, strlen (fnm) + 1);
588 for (pn = &elf_hash_table (info)->needed;
600 /* We do not want to include any of the sections in a dynamic
601 object in the output file. We hack by simply clobbering the
602 list of sections in the BFD. This could be handled more
603 cleanly by, say, a new section flag; the existing
604 SEC_NEVER_LOAD flag is not the one we want, because that one
605 still implies that the section takes up space in the output
607 abfd->sections = NULL;
608 abfd->section_count = 0;
610 /* If this is the first dynamic object found in the link, create
611 the special sections required for dynamic linking. */
612 if (! elf_hash_table (info)->dynamic_sections_created)
614 if (! elf_link_create_dynamic_sections (abfd, info))
620 /* Add a DT_NEEDED entry for this dynamic object. */
621 oldsize = _bfd_stringtab_size (elf_hash_table (info)->dynstr);
622 strindex = _bfd_stringtab_add (elf_hash_table (info)->dynstr, name,
624 if (strindex == (bfd_size_type) -1)
627 if (oldsize == _bfd_stringtab_size (elf_hash_table (info)->dynstr))
630 Elf_External_Dyn *dyncon, *dynconend;
632 /* The hash table size did not change, which means that
633 the dynamic object name was already entered. If we
634 have already included this dynamic object in the
635 link, just ignore it. There is no reason to include
636 a particular dynamic object more than once. */
637 sdyn = bfd_get_section_by_name (elf_hash_table (info)->dynobj,
639 BFD_ASSERT (sdyn != NULL);
641 dyncon = (Elf_External_Dyn *) sdyn->contents;
642 dynconend = (Elf_External_Dyn *) (sdyn->contents +
644 for (; dyncon < dynconend; dyncon++)
646 Elf_Internal_Dyn dyn;
648 elf_swap_dyn_in (elf_hash_table (info)->dynobj, dyncon,
650 if (dyn.d_tag == DT_NEEDED
651 && dyn.d_un.d_val == strindex)
655 if (extversym != NULL)
662 if (! elf_add_dynamic_entry (info, DT_NEEDED, strindex))
666 /* Save the SONAME, if there is one, because sometimes the
667 linker emulation code will need to know it. */
669 name = bfd_get_filename (abfd);
670 elf_dt_name (abfd) = name;
674 hdr->sh_offset + extsymoff * sizeof (Elf_External_Sym),
676 || (bfd_read ((PTR) buf, sizeof (Elf_External_Sym), extsymcount, abfd)
677 != extsymcount * sizeof (Elf_External_Sym)))
682 ever = extversym != NULL ? extversym + extsymoff : NULL;
683 esymend = buf + extsymcount;
686 esym++, sym_hash++, ever = (ever != NULL ? ever + 1 : NULL))
688 Elf_Internal_Sym sym;
694 struct elf_link_hash_entry *h;
696 boolean size_change_ok, type_change_ok;
699 elf_swap_symbol_in (abfd, esym, &sym);
701 flags = BSF_NO_FLAGS;
703 value = sym.st_value;
706 bind = ELF_ST_BIND (sym.st_info);
707 if (bind == STB_LOCAL)
709 /* This should be impossible, since ELF requires that all
710 global symbols follow all local symbols, and that sh_info
711 point to the first global symbol. Unfortunatealy, Irix 5
715 else if (bind == STB_GLOBAL)
717 if (sym.st_shndx != SHN_UNDEF
718 && sym.st_shndx != SHN_COMMON)
723 else if (bind == STB_WEAK)
727 /* Leave it up to the processor backend. */
730 if (sym.st_shndx == SHN_UNDEF)
731 sec = bfd_und_section_ptr;
732 else if (sym.st_shndx > 0 && sym.st_shndx < SHN_LORESERVE)
734 sec = section_from_elf_index (abfd, sym.st_shndx);
738 sec = bfd_abs_section_ptr;
740 else if (sym.st_shndx == SHN_ABS)
741 sec = bfd_abs_section_ptr;
742 else if (sym.st_shndx == SHN_COMMON)
744 sec = bfd_com_section_ptr;
745 /* What ELF calls the size we call the value. What ELF
746 calls the value we call the alignment. */
751 /* Leave it up to the processor backend. */
754 name = bfd_elf_string_from_elf_section (abfd, hdr->sh_link, sym.st_name);
755 if (name == (const char *) NULL)
760 if (! (*add_symbol_hook) (abfd, info, &sym, &name, &flags, &sec,
764 /* The hook function sets the name to NULL if this symbol
765 should be skipped for some reason. */
766 if (name == (const char *) NULL)
770 /* Sanity check that all possibilities were handled. */
771 if (sec == (asection *) NULL)
773 bfd_set_error (bfd_error_bad_value);
777 if (bfd_is_und_section (sec)
778 || bfd_is_com_section (sec))
783 size_change_ok = false;
784 type_change_ok = get_elf_backend_data (abfd)->type_change_ok;
785 if (info->hash->creator->flavour == bfd_target_elf_flavour)
787 Elf_Internal_Versym iver;
793 _bfd_elf_swap_versym_in (abfd, ever, &iver);
794 vernum = iver.vs_vers & VERSYM_VERSION;
796 /* If this is a hidden symbol, or if it is not version
797 1, we append the version name to the symbol name.
798 However, we do not modify a non-hidden absolute
799 symbol, because it might be the version symbol
800 itself. FIXME: What if it isn't? */
801 if ((iver.vs_vers & VERSYM_HIDDEN) != 0
802 || (vernum > 1 && ! bfd_is_abs_section (sec)))
808 if (vernum > elf_tdata (abfd)->dynverdef_hdr.sh_info)
810 (*_bfd_error_handler)
811 ("%s: %s: invalid version %d (max %d)",
812 abfd->filename, name, vernum,
813 elf_tdata (abfd)->dynverdef_hdr.sh_info);
814 bfd_set_error (bfd_error_bad_value);
818 verstr = elf_tdata (abfd)->verdef[vernum - 1].vd_nodename;
822 namelen = strlen (name);
823 newlen = namelen + strlen (verstr) + 2;
824 if ((iver.vs_vers & VERSYM_HIDDEN) == 0)
827 newname = (char *) bfd_alloc (abfd, newlen);
830 strcpy (newname, name);
831 p = newname + namelen;
833 if ((iver.vs_vers & VERSYM_HIDDEN) == 0)
841 /* We need to look up the symbol now in order to get some of
842 the dynamic object handling right. We pass the hash
843 table entry in to _bfd_generic_link_add_one_symbol so
844 that it does not have to look it up again. */
845 if (! bfd_is_und_section (sec))
846 h = elf_link_hash_lookup (elf_hash_table (info), name,
849 h = ((struct elf_link_hash_entry *)
850 bfd_wrapped_link_hash_lookup (abfd, info, name, true,
856 if (h->root.type == bfd_link_hash_new)
857 h->elf_link_hash_flags &=~ ELF_LINK_NON_ELF;
859 while (h->root.type == bfd_link_hash_indirect
860 || h->root.type == bfd_link_hash_warning)
861 h = (struct elf_link_hash_entry *) h->root.u.i.link;
863 /* It's OK to change the type if it used to be a weak
864 definition, or if the current definition is weak (and
865 hence might be ignored). */
866 if (h->root.type == bfd_link_hash_defweak
867 || h->root.type == bfd_link_hash_undefweak
869 type_change_ok = true;
871 /* It's OK to change the size if it used to be a weak
872 definition, or if it used to be undefined, or if we will
873 be overriding an old definition. */
875 || h->root.type == bfd_link_hash_undefined)
876 size_change_ok = true;
880 /* If we are looking at a dynamic object, and this is a
881 definition, we need to see if it has already been defined
882 by some other object. If it has, we want to use the
883 existing definition, and we do not want to report a
884 multiple symbol definition error; we do this by
885 clobbering sec to be bfd_und_section_ptr. We treat a
886 common symbol as a definition if the symbol in the shared
887 library is a function, since common symbols always
888 represent variables; this can cause confusion in
889 principle, but any such confusion would seem to indicate
890 an erroneous program or shared library. */
891 if (dynamic && definition)
893 if (h->root.type == bfd_link_hash_defined
894 || h->root.type == bfd_link_hash_defweak
895 || (h->root.type == bfd_link_hash_common
897 || ELF_ST_TYPE (sym.st_info) == STT_FUNC)))
900 sec = bfd_und_section_ptr;
902 size_change_ok = true;
903 if (h->root.type == bfd_link_hash_common)
904 type_change_ok = true;
908 /* Similarly, if we are not looking at a dynamic object, and
909 we have a definition, we want to override any definition
910 we may have from a dynamic object. Symbols from regular
911 files always take precedence over symbols from dynamic
912 objects, even if they are defined after the dynamic
913 object in the link. */
916 || (bfd_is_com_section (sec)
917 && (h->root.type == bfd_link_hash_defweak
918 || h->type == STT_FUNC)))
919 && (h->root.type == bfd_link_hash_defined
920 || h->root.type == bfd_link_hash_defweak)
921 && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC) != 0
922 && (h->root.u.def.section->owner->flags & DYNAMIC) != 0)
925 /* Change the hash table entry to undefined, and let
926 _bfd_generic_link_add_one_symbol do the right thing
927 with the new definition. */
928 h->root.type = bfd_link_hash_undefined;
929 h->root.u.undef.abfd = h->root.u.def.section->owner;
930 size_change_ok = true;
931 if (bfd_is_com_section (sec))
932 type_change_ok = true;
934 /* This union may have been set to be non-NULL when this
935 symbol was seen in a dynamic object. We must force
936 the union to be NULL, so that it is correct for a
938 h->verinfo.vertree = NULL;
944 && (h->verinfo.verdef == NULL || definition))
945 h->verinfo.verdef = &elf_tdata (abfd)->verdef[vernum - 1];
948 if (! (_bfd_generic_link_add_one_symbol
949 (info, abfd, name, flags, sec, value, (const char *) NULL,
950 false, collect, (struct bfd_link_hash_entry **) sym_hash)))
954 while (h->root.type == bfd_link_hash_indirect
955 || h->root.type == bfd_link_hash_warning)
956 h = (struct elf_link_hash_entry *) h->root.u.i.link;
962 && (flags & BSF_WEAK) != 0
963 && ELF_ST_TYPE (sym.st_info) != STT_FUNC
964 && info->hash->creator->flavour == bfd_target_elf_flavour
965 && h->weakdef == NULL)
967 /* Keep a list of all weak defined non function symbols from
968 a dynamic object, using the weakdef field. Later in this
969 function we will set the weakdef field to the correct
970 value. We only put non-function symbols from dynamic
971 objects on this list, because that happens to be the only
972 time we need to know the normal symbol corresponding to a
973 weak symbol, and the information is time consuming to
974 figure out. If the weakdef field is not already NULL,
975 then this symbol was already defined by some previous
976 dynamic object, and we will be using that previous
977 definition anyhow. */
984 /* Get the alignment of a common symbol. */
985 if (sym.st_shndx == SHN_COMMON
986 && h->root.type == bfd_link_hash_common)
987 h->root.u.c.p->alignment_power = bfd_log2 (sym.st_value);
989 if (info->hash->creator->flavour == bfd_target_elf_flavour)
995 /* Remember the symbol size and type. */
997 && (definition || h->size == 0))
999 if (h->size != 0 && h->size != sym.st_size && ! size_change_ok)
1000 (*_bfd_error_handler)
1001 ("Warning: size of symbol `%s' changed from %lu to %lu in %s",
1002 name, (unsigned long) h->size, (unsigned long) sym.st_size,
1003 bfd_get_filename (abfd));
1005 h->size = sym.st_size;
1007 if (ELF_ST_TYPE (sym.st_info) != STT_NOTYPE
1008 && (definition || h->type == STT_NOTYPE))
1010 if (h->type != STT_NOTYPE
1011 && h->type != ELF_ST_TYPE (sym.st_info)
1012 && ! type_change_ok)
1013 (*_bfd_error_handler)
1014 ("Warning: type of symbol `%s' changed from %d to %d in %s",
1015 name, h->type, ELF_ST_TYPE (sym.st_info),
1016 bfd_get_filename (abfd));
1018 h->type = ELF_ST_TYPE (sym.st_info);
1021 if (sym.st_other != 0
1022 && (definition || h->other == 0))
1023 h->other = sym.st_other;
1025 /* Set a flag in the hash table entry indicating the type of
1026 reference or definition we just found. Keep a count of
1027 the number of dynamic symbols we find. A dynamic symbol
1028 is one which is referenced or defined by both a regular
1029 object and a shared object. */
1030 old_flags = h->elf_link_hash_flags;
1035 new_flag = ELF_LINK_HASH_REF_REGULAR;
1037 new_flag = ELF_LINK_HASH_DEF_REGULAR;
1039 || (old_flags & (ELF_LINK_HASH_DEF_DYNAMIC
1040 | ELF_LINK_HASH_REF_DYNAMIC)) != 0)
1046 new_flag = ELF_LINK_HASH_REF_DYNAMIC;
1048 new_flag = ELF_LINK_HASH_DEF_DYNAMIC;
1049 if ((old_flags & (ELF_LINK_HASH_DEF_REGULAR
1050 | ELF_LINK_HASH_REF_REGULAR)) != 0
1051 || (h->weakdef != NULL
1053 && h->weakdef->dynindx != -1))
1057 h->elf_link_hash_flags |= new_flag;
1059 /* If this symbol has a version, and it is the default
1060 version, we create an indirect symbol from the default
1061 name to the fully decorated name. This will cause
1062 external references which do not specify a version to be
1063 bound to this version of the symbol. */
1068 p = strchr (name, ELF_VER_CHR);
1069 if (p != NULL && p[1] == ELF_VER_CHR)
1072 struct elf_link_hash_entry *hold;
1074 shortname = bfd_hash_allocate (&info->hash->table,
1076 if (shortname == NULL)
1078 strncpy (shortname, name, p - name);
1079 shortname[p - name] = '\0';
1081 /* First look to see if we have an existing symbol
1083 hold = elf_link_hash_lookup (elf_hash_table (info),
1084 shortname, false, false,
1087 /* If we are looking at a normal object, and the
1088 symbol was seen in a shared object, clobber the
1089 definition in the shared object. */
1092 && (hold->root.type == bfd_link_hash_defined
1093 || hold->root.type == bfd_link_hash_defweak)
1094 && (hold->elf_link_hash_flags
1095 & ELF_LINK_HASH_DEF_DYNAMIC) != 0
1096 && ((hold->root.u.def.section->owner->flags & DYNAMIC)
1099 /* Change the hash table entry to undefined, so
1100 that _bfd_generic_link_add_one_symbol will do
1102 hold->root.type = bfd_link_hash_undefined;
1103 hold->root.u.undef.abfd =
1104 hold->root.u.def.section->owner;
1105 hold->verinfo.vertree = NULL;
1109 /* If we are looking at a shared object, and we have
1110 already seen this symbol defined elsewhere, then
1111 don't try to define it again. */
1114 && (hold->root.type == bfd_link_hash_defined
1115 || hold->root.type == bfd_link_hash_defweak
1116 || hold->root.type == bfd_link_hash_indirect
1117 || (hold->root.type == bfd_link_hash_common
1118 && (bind == STB_WEAK
1119 || ELF_ST_TYPE (sym.st_info) == STT_FUNC))))
1121 /* Don't add an indirect symbol. */
1125 struct elf_link_hash_entry *hi;
1128 if (! (_bfd_generic_link_add_one_symbol
1129 (info, abfd, shortname, BSF_INDIRECT,
1130 bfd_ind_section_ptr, (bfd_vma) 0, name, false,
1131 collect, (struct bfd_link_hash_entry **) &hi)))
1134 /* If there is a duplicate definition somewhere,
1135 then HI may not point to an indirect symbol.
1136 We will have reported an error to the user in
1139 if (hi->root.type == bfd_link_hash_indirect)
1141 hi->elf_link_hash_flags &= ~ ELF_LINK_NON_ELF;
1143 /* If the symbol became indirect, then we
1144 assume that we have not seen a definition
1146 BFD_ASSERT ((hi->elf_link_hash_flags
1147 & (ELF_LINK_HASH_DEF_DYNAMIC
1148 | ELF_LINK_HASH_DEF_REGULAR))
1151 /* Copy down any references that we may have
1152 already seen to the symbol which just
1154 h->elf_link_hash_flags |=
1155 (hi->elf_link_hash_flags
1156 & (ELF_LINK_HASH_REF_DYNAMIC
1157 | ELF_LINK_HASH_REF_REGULAR));
1159 /* Copy over the global table offset entry.
1160 This may have been already set up by a
1161 check_relocs routine. */
1162 if (h->got_offset == (bfd_vma) -1)
1164 h->got_offset = hi->got_offset;
1165 hi->got_offset = (bfd_vma) -1;
1167 BFD_ASSERT (hi->got_offset == (bfd_vma) -1);
1169 if (h->dynindx == -1)
1171 h->dynindx = hi->dynindx;
1172 h->dynstr_index = hi->dynstr_index;
1174 hi->dynstr_index = 0;
1176 BFD_ASSERT (hi->dynindx == -1);
1178 /* FIXME: There may be other information to
1179 copy over for particular targets. */
1181 /* See if the new flags lead us to realize
1182 that the symbol must be dynamic. */
1188 || ((hi->elf_link_hash_flags
1189 & ELF_LINK_HASH_REF_DYNAMIC)
1195 if ((hi->elf_link_hash_flags
1196 & ELF_LINK_HASH_REF_REGULAR) != 0)
1203 /* We also need to define an indirection from the
1204 nondefault version of the symbol. */
1206 shortname = bfd_hash_allocate (&info->hash->table,
1208 if (shortname == NULL)
1210 strncpy (shortname, name, p - name);
1211 strcpy (shortname + (p - name), p + 1);
1213 /* First look to see if we have an existing symbol
1215 hold = elf_link_hash_lookup (elf_hash_table (info),
1216 shortname, false, false,
1219 /* If we are looking at a normal object, and the
1220 symbol was seen in a shared object, clobber the
1221 definition in the shared object. */
1224 && (hold->root.type == bfd_link_hash_defined
1225 || hold->root.type == bfd_link_hash_defweak)
1226 && (hold->elf_link_hash_flags
1227 & ELF_LINK_HASH_DEF_DYNAMIC) != 0
1228 && ((hold->root.u.def.section->owner->flags & DYNAMIC)
1231 /* Change the hash table entry to undefined, so
1232 that _bfd_generic_link_add_one_symbol will do
1234 hold->root.type = bfd_link_hash_undefined;
1235 hold->root.u.undef.abfd =
1236 hold->root.u.def.section->owner;
1237 hold->verinfo.vertree = NULL;
1241 /* If we are looking at a shared object, and we have
1242 already seen this symbol defined elsewhere, then
1243 don't try to define it again. */
1246 && (hold->root.type == bfd_link_hash_defined
1247 || hold->root.type == bfd_link_hash_defweak
1248 || hold->root.type == bfd_link_hash_indirect
1249 || (hold->root.type == bfd_link_hash_common
1250 && (bind == STB_WEAK
1251 || ELF_ST_TYPE (sym.st_info) == STT_FUNC))))
1253 /* Don't add an indirect symbol. */
1257 struct elf_link_hash_entry *hi;
1260 if (! (_bfd_generic_link_add_one_symbol
1261 (info, abfd, shortname, BSF_INDIRECT,
1262 bfd_ind_section_ptr, (bfd_vma) 0, name, false,
1263 collect, (struct bfd_link_hash_entry **) &hi)))
1266 /* If there is a duplicate definition somewhere,
1267 then HI may not point to an indirect symbol.
1268 We will have reported an error to the user in
1271 if (hi->root.type == bfd_link_hash_indirect)
1273 hi->elf_link_hash_flags &= ~ ELF_LINK_NON_ELF;
1275 /* If the symbol became indirect, then we
1276 assume that we have not seen a definition
1278 BFD_ASSERT ((hi->elf_link_hash_flags
1279 & (ELF_LINK_HASH_DEF_DYNAMIC
1280 | ELF_LINK_HASH_DEF_REGULAR))
1283 /* Copy down any references that we may have
1284 already seen to the symbol which just
1286 h->elf_link_hash_flags |=
1287 (hi->elf_link_hash_flags
1288 & (ELF_LINK_HASH_REF_DYNAMIC
1289 | ELF_LINK_HASH_REF_REGULAR));
1291 /* Copy over the global table offset entry.
1292 This may have been already set up by a
1293 check_relocs routine. */
1294 if (h->got_offset == (bfd_vma) -1)
1296 h->got_offset = hi->got_offset;
1297 hi->got_offset = (bfd_vma) -1;
1299 BFD_ASSERT (hi->got_offset == (bfd_vma) -1);
1301 if (h->dynindx == -1)
1303 h->dynindx = hi->dynindx;
1304 h->dynstr_index = hi->dynstr_index;
1306 hi->dynstr_index = 0;
1308 BFD_ASSERT (hi->dynindx == -1);
1310 /* FIXME: There may be other information to
1311 copy over for particular targets. */
1313 /* See if the new flags lead us to realize
1314 that the symbol must be dynamic. */
1320 || ((hi->elf_link_hash_flags
1321 & ELF_LINK_HASH_REF_DYNAMIC)
1327 if ((hi->elf_link_hash_flags
1328 & ELF_LINK_HASH_REF_REGULAR) != 0)
1337 if (dynsym && h->dynindx == -1)
1339 if (! _bfd_elf_link_record_dynamic_symbol (info, h))
1341 if (h->weakdef != NULL
1343 && h->weakdef->dynindx == -1)
1345 if (! _bfd_elf_link_record_dynamic_symbol (info,
1353 /* Now set the weakdefs field correctly for all the weak defined
1354 symbols we found. The only way to do this is to search all the
1355 symbols. Since we only need the information for non functions in
1356 dynamic objects, that's the only time we actually put anything on
1357 the list WEAKS. We need this information so that if a regular
1358 object refers to a symbol defined weakly in a dynamic object, the
1359 real symbol in the dynamic object is also put in the dynamic
1360 symbols; we also must arrange for both symbols to point to the
1361 same memory location. We could handle the general case of symbol
1362 aliasing, but a general symbol alias can only be generated in
1363 assembler code, handling it correctly would be very time
1364 consuming, and other ELF linkers don't handle general aliasing
1366 while (weaks != NULL)
1368 struct elf_link_hash_entry *hlook;
1371 struct elf_link_hash_entry **hpp;
1372 struct elf_link_hash_entry **hppend;
1375 weaks = hlook->weakdef;
1376 hlook->weakdef = NULL;
1378 BFD_ASSERT (hlook->root.type == bfd_link_hash_defined
1379 || hlook->root.type == bfd_link_hash_defweak
1380 || hlook->root.type == bfd_link_hash_common
1381 || hlook->root.type == bfd_link_hash_indirect);
1382 slook = hlook->root.u.def.section;
1383 vlook = hlook->root.u.def.value;
1385 hpp = elf_sym_hashes (abfd);
1386 hppend = hpp + extsymcount;
1387 for (; hpp < hppend; hpp++)
1389 struct elf_link_hash_entry *h;
1392 if (h != NULL && h != hlook
1393 && h->root.type == bfd_link_hash_defined
1394 && h->root.u.def.section == slook
1395 && h->root.u.def.value == vlook)
1399 /* If the weak definition is in the list of dynamic
1400 symbols, make sure the real definition is put there
1402 if (hlook->dynindx != -1
1403 && h->dynindx == -1)
1405 if (! _bfd_elf_link_record_dynamic_symbol (info, h))
1409 /* If the real definition is in the list of dynamic
1410 symbols, make sure the weak definition is put there
1411 as well. If we don't do this, then the dynamic
1412 loader might not merge the entries for the real
1413 definition and the weak definition. */
1414 if (h->dynindx != -1
1415 && hlook->dynindx == -1)
1417 if (! _bfd_elf_link_record_dynamic_symbol (info, hlook))
1432 if (extversym != NULL)
1438 /* If this object is the same format as the output object, and it is
1439 not a shared library, then let the backend look through the
1442 This is required to build global offset table entries and to
1443 arrange for dynamic relocs. It is not required for the
1444 particular common case of linking non PIC code, even when linking
1445 against shared libraries, but unfortunately there is no way of
1446 knowing whether an object file has been compiled PIC or not.
1447 Looking through the relocs is not particularly time consuming.
1448 The problem is that we must either (1) keep the relocs in memory,
1449 which causes the linker to require additional runtime memory or
1450 (2) read the relocs twice from the input file, which wastes time.
1451 This would be a good case for using mmap.
1453 I have no idea how to handle linking PIC code into a file of a
1454 different format. It probably can't be done. */
1455 check_relocs = get_elf_backend_data (abfd)->check_relocs;
1457 && abfd->xvec == info->hash->creator
1458 && check_relocs != NULL)
1462 for (o = abfd->sections; o != NULL; o = o->next)
1464 Elf_Internal_Rela *internal_relocs;
1467 if ((o->flags & SEC_RELOC) == 0
1468 || o->reloc_count == 0)
1471 internal_relocs = (NAME(_bfd_elf,link_read_relocs)
1472 (abfd, o, (PTR) NULL,
1473 (Elf_Internal_Rela *) NULL,
1474 info->keep_memory));
1475 if (internal_relocs == NULL)
1478 ok = (*check_relocs) (abfd, info, o, internal_relocs);
1480 if (! info->keep_memory)
1481 free (internal_relocs);
1488 /* If this is a non-traditional, non-relocateable link, try to
1489 optimize the handling of the .stab/.stabstr sections. */
1491 && ! info->relocateable
1492 && ! info->traditional_format
1493 && info->hash->creator->flavour == bfd_target_elf_flavour
1494 && (info->strip != strip_all && info->strip != strip_debugger))
1496 asection *stab, *stabstr;
1498 stab = bfd_get_section_by_name (abfd, ".stab");
1501 stabstr = bfd_get_section_by_name (abfd, ".stabstr");
1503 if (stabstr != NULL)
1505 struct bfd_elf_section_data *secdata;
1507 secdata = elf_section_data (stab);
1508 if (! _bfd_link_section_stabs (abfd,
1509 &elf_hash_table (info)->stab_info,
1511 &secdata->stab_info))
1526 if (extversym != NULL)
1531 /* Create some sections which will be filled in with dynamic linking
1532 information. ABFD is an input file which requires dynamic sections
1533 to be created. The dynamic sections take up virtual memory space
1534 when the final executable is run, so we need to create them before
1535 addresses are assigned to the output sections. We work out the
1536 actual contents and size of these sections later. */
1539 elf_link_create_dynamic_sections (abfd, info)
1541 struct bfd_link_info *info;
1544 register asection *s;
1545 struct elf_link_hash_entry *h;
1546 struct elf_backend_data *bed;
1548 if (elf_hash_table (info)->dynamic_sections_created)
1551 /* Make sure that all dynamic sections use the same input BFD. */
1552 if (elf_hash_table (info)->dynobj == NULL)
1553 elf_hash_table (info)->dynobj = abfd;
1555 abfd = elf_hash_table (info)->dynobj;
1557 /* Note that we set the SEC_IN_MEMORY flag for all of these
1559 flags = (SEC_ALLOC | SEC_LOAD | SEC_HAS_CONTENTS
1560 | SEC_IN_MEMORY | SEC_LINKER_CREATED);
1562 /* A dynamically linked executable has a .interp section, but a
1563 shared library does not. */
1566 s = bfd_make_section (abfd, ".interp");
1568 || ! bfd_set_section_flags (abfd, s, flags | SEC_READONLY))
1572 /* Create sections to hold version informations. These are removed
1573 if they are not needed. */
1574 s = bfd_make_section (abfd, ".gnu.version_d");
1576 || ! bfd_set_section_flags (abfd, s, flags | SEC_READONLY)
1577 || ! bfd_set_section_alignment (abfd, s, 2))
1580 s = bfd_make_section (abfd, ".gnu.version");
1582 || ! bfd_set_section_flags (abfd, s, flags | SEC_READONLY)
1583 || ! bfd_set_section_alignment (abfd, s, 1))
1586 s = bfd_make_section (abfd, ".gnu.version_r");
1588 || ! bfd_set_section_flags (abfd, s, flags | SEC_READONLY)
1589 || ! bfd_set_section_alignment (abfd, s, 2))
1592 s = bfd_make_section (abfd, ".dynsym");
1594 || ! bfd_set_section_flags (abfd, s, flags | SEC_READONLY)
1595 || ! bfd_set_section_alignment (abfd, s, LOG_FILE_ALIGN))
1598 s = bfd_make_section (abfd, ".dynstr");
1600 || ! bfd_set_section_flags (abfd, s, flags | SEC_READONLY))
1603 /* Create a strtab to hold the dynamic symbol names. */
1604 if (elf_hash_table (info)->dynstr == NULL)
1606 elf_hash_table (info)->dynstr = elf_stringtab_init ();
1607 if (elf_hash_table (info)->dynstr == NULL)
1611 s = bfd_make_section (abfd, ".dynamic");
1613 || ! bfd_set_section_flags (abfd, s, flags)
1614 || ! bfd_set_section_alignment (abfd, s, LOG_FILE_ALIGN))
1617 /* The special symbol _DYNAMIC is always set to the start of the
1618 .dynamic section. This call occurs before we have processed the
1619 symbols for any dynamic object, so we don't have to worry about
1620 overriding a dynamic definition. We could set _DYNAMIC in a
1621 linker script, but we only want to define it if we are, in fact,
1622 creating a .dynamic section. We don't want to define it if there
1623 is no .dynamic section, since on some ELF platforms the start up
1624 code examines it to decide how to initialize the process. */
1626 if (! (_bfd_generic_link_add_one_symbol
1627 (info, abfd, "_DYNAMIC", BSF_GLOBAL, s, (bfd_vma) 0,
1628 (const char *) NULL, false, get_elf_backend_data (abfd)->collect,
1629 (struct bfd_link_hash_entry **) &h)))
1631 h->elf_link_hash_flags |= ELF_LINK_HASH_DEF_REGULAR;
1632 h->type = STT_OBJECT;
1635 && ! _bfd_elf_link_record_dynamic_symbol (info, h))
1638 s = bfd_make_section (abfd, ".hash");
1640 || ! bfd_set_section_flags (abfd, s, flags | SEC_READONLY)
1641 || ! bfd_set_section_alignment (abfd, s, LOG_FILE_ALIGN))
1644 /* Let the backend create the rest of the sections. This lets the
1645 backend set the right flags. The backend will normally create
1646 the .got and .plt sections. */
1647 bed = get_elf_backend_data (abfd);
1648 if (! (*bed->elf_backend_create_dynamic_sections) (abfd, info))
1651 elf_hash_table (info)->dynamic_sections_created = true;
1656 /* Add an entry to the .dynamic table. */
1659 elf_add_dynamic_entry (info, tag, val)
1660 struct bfd_link_info *info;
1664 Elf_Internal_Dyn dyn;
1668 bfd_byte *newcontents;
1670 dynobj = elf_hash_table (info)->dynobj;
1672 s = bfd_get_section_by_name (dynobj, ".dynamic");
1673 BFD_ASSERT (s != NULL);
1675 newsize = s->_raw_size + sizeof (Elf_External_Dyn);
1676 newcontents = (bfd_byte *) bfd_realloc (s->contents, newsize);
1677 if (newcontents == NULL)
1681 dyn.d_un.d_val = val;
1682 elf_swap_dyn_out (dynobj, &dyn,
1683 (Elf_External_Dyn *) (newcontents + s->_raw_size));
1685 s->_raw_size = newsize;
1686 s->contents = newcontents;
1692 /* Read and swap the relocs for a section. They may have been cached.
1693 If the EXTERNAL_RELOCS and INTERNAL_RELOCS arguments are not NULL,
1694 they are used as buffers to read into. They are known to be large
1695 enough. If the INTERNAL_RELOCS relocs argument is NULL, the return
1696 value is allocated using either malloc or bfd_alloc, according to
1697 the KEEP_MEMORY argument. */
1700 NAME(_bfd_elf,link_read_relocs) (abfd, o, external_relocs, internal_relocs,
1704 PTR external_relocs;
1705 Elf_Internal_Rela *internal_relocs;
1706 boolean keep_memory;
1708 Elf_Internal_Shdr *rel_hdr;
1710 Elf_Internal_Rela *alloc2 = NULL;
1712 if (elf_section_data (o)->relocs != NULL)
1713 return elf_section_data (o)->relocs;
1715 if (o->reloc_count == 0)
1718 rel_hdr = &elf_section_data (o)->rel_hdr;
1720 if (internal_relocs == NULL)
1724 size = o->reloc_count * sizeof (Elf_Internal_Rela);
1726 internal_relocs = (Elf_Internal_Rela *) bfd_alloc (abfd, size);
1728 internal_relocs = alloc2 = (Elf_Internal_Rela *) bfd_malloc (size);
1729 if (internal_relocs == NULL)
1733 if (external_relocs == NULL)
1735 alloc1 = (PTR) bfd_malloc ((size_t) rel_hdr->sh_size);
1738 external_relocs = alloc1;
1741 if ((bfd_seek (abfd, rel_hdr->sh_offset, SEEK_SET) != 0)
1742 || (bfd_read (external_relocs, 1, rel_hdr->sh_size, abfd)
1743 != rel_hdr->sh_size))
1746 /* Swap in the relocs. For convenience, we always produce an
1747 Elf_Internal_Rela array; if the relocs are Rel, we set the addend
1749 if (rel_hdr->sh_entsize == sizeof (Elf_External_Rel))
1751 Elf_External_Rel *erel;
1752 Elf_External_Rel *erelend;
1753 Elf_Internal_Rela *irela;
1755 erel = (Elf_External_Rel *) external_relocs;
1756 erelend = erel + o->reloc_count;
1757 irela = internal_relocs;
1758 for (; erel < erelend; erel++, irela++)
1760 Elf_Internal_Rel irel;
1762 elf_swap_reloc_in (abfd, erel, &irel);
1763 irela->r_offset = irel.r_offset;
1764 irela->r_info = irel.r_info;
1765 irela->r_addend = 0;
1770 Elf_External_Rela *erela;
1771 Elf_External_Rela *erelaend;
1772 Elf_Internal_Rela *irela;
1774 BFD_ASSERT (rel_hdr->sh_entsize == sizeof (Elf_External_Rela));
1776 erela = (Elf_External_Rela *) external_relocs;
1777 erelaend = erela + o->reloc_count;
1778 irela = internal_relocs;
1779 for (; erela < erelaend; erela++, irela++)
1780 elf_swap_reloca_in (abfd, erela, irela);
1783 /* Cache the results for next time, if we can. */
1785 elf_section_data (o)->relocs = internal_relocs;
1790 /* Don't free alloc2, since if it was allocated we are passing it
1791 back (under the name of internal_relocs). */
1793 return internal_relocs;
1804 /* Record an assignment to a symbol made by a linker script. We need
1805 this in case some dynamic object refers to this symbol. */
1809 NAME(bfd_elf,record_link_assignment) (output_bfd, info, name, provide)
1811 struct bfd_link_info *info;
1815 struct elf_link_hash_entry *h;
1817 if (info->hash->creator->flavour != bfd_target_elf_flavour)
1820 h = elf_link_hash_lookup (elf_hash_table (info), name, true, true, false);
1824 if (h->root.type == bfd_link_hash_new)
1825 h->elf_link_hash_flags &=~ ELF_LINK_NON_ELF;
1827 /* If this symbol is being provided by the linker script, and it is
1828 currently defined by a dynamic object, but not by a regular
1829 object, then mark it as undefined so that the generic linker will
1830 force the correct value. */
1832 && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC) != 0
1833 && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) == 0)
1834 h->root.type = bfd_link_hash_undefined;
1836 h->elf_link_hash_flags |= ELF_LINK_HASH_DEF_REGULAR;
1837 h->type = STT_OBJECT;
1839 if (((h->elf_link_hash_flags & (ELF_LINK_HASH_DEF_DYNAMIC
1840 | ELF_LINK_HASH_REF_DYNAMIC)) != 0
1842 && h->dynindx == -1)
1844 if (! _bfd_elf_link_record_dynamic_symbol (info, h))
1847 /* If this is a weak defined symbol, and we know a corresponding
1848 real symbol from the same dynamic object, make sure the real
1849 symbol is also made into a dynamic symbol. */
1850 if (h->weakdef != NULL
1851 && h->weakdef->dynindx == -1)
1853 if (! _bfd_elf_link_record_dynamic_symbol (info, h->weakdef))
1861 /* This structure is used to pass information to
1862 elf_link_assign_sym_version. */
1864 struct elf_assign_sym_version_info
1868 /* General link information. */
1869 struct bfd_link_info *info;
1871 struct bfd_elf_version_tree *verdefs;
1872 /* Whether we are exporting all dynamic symbols. */
1873 boolean export_dynamic;
1874 /* Whether we removed any symbols from the dynamic symbol table. */
1875 boolean removed_dynamic;
1876 /* Whether we had a failure. */
1880 /* This structure is used to pass information to
1881 elf_link_find_version_dependencies. */
1883 struct elf_find_verdep_info
1887 /* General link information. */
1888 struct bfd_link_info *info;
1889 /* The number of dependencies. */
1891 /* Whether we had a failure. */
1895 /* Array used to determine the number of hash table buckets to use
1896 based on the number of symbols there are. If there are fewer than
1897 3 symbols we use 1 bucket, fewer than 17 symbols we use 3 buckets,
1898 fewer than 37 we use 17 buckets, and so forth. We never use more
1899 than 32771 buckets. */
1901 static const size_t elf_buckets[] =
1903 1, 3, 17, 37, 67, 97, 131, 197, 263, 521, 1031, 2053, 4099, 8209,
1907 /* Set up the sizes and contents of the ELF dynamic sections. This is
1908 called by the ELF linker emulation before_allocation routine. We
1909 must set the sizes of the sections before the linker sets the
1910 addresses of the various sections. */
1913 NAME(bfd_elf,size_dynamic_sections) (output_bfd, soname, rpath,
1914 export_dynamic, filter_shlib,
1915 auxiliary_filters, info, sinterpptr,
1920 boolean export_dynamic;
1921 const char *filter_shlib;
1922 const char * const *auxiliary_filters;
1923 struct bfd_link_info *info;
1924 asection **sinterpptr;
1925 struct bfd_elf_version_tree *verdefs;
1927 bfd_size_type soname_indx;
1929 struct elf_backend_data *bed;
1930 bfd_size_type old_dynsymcount;
1936 if (info->hash->creator->flavour != bfd_target_elf_flavour)
1939 /* The backend may have to create some sections regardless of whether
1940 we're dynamic or not. */
1941 bed = get_elf_backend_data (output_bfd);
1942 if (bed->elf_backend_always_size_sections
1943 && ! (*bed->elf_backend_always_size_sections) (output_bfd, info))
1946 dynobj = elf_hash_table (info)->dynobj;
1948 /* If there were no dynamic objects in the link, there is nothing to
1953 /* If we are supposed to export all symbols into the dynamic symbol
1954 table (this is not the normal case), then do so. */
1957 struct elf_info_failed eif;
1961 elf_link_hash_traverse (elf_hash_table (info), elf_export_symbol,
1967 if (elf_hash_table (info)->dynamic_sections_created)
1969 struct elf_info_failed eif;
1970 struct elf_link_hash_entry *h;
1971 bfd_size_type strsize;
1973 *sinterpptr = bfd_get_section_by_name (dynobj, ".interp");
1974 BFD_ASSERT (*sinterpptr != NULL || info->shared);
1978 soname_indx = _bfd_stringtab_add (elf_hash_table (info)->dynstr,
1979 soname, true, true);
1980 if (soname_indx == (bfd_size_type) -1
1981 || ! elf_add_dynamic_entry (info, DT_SONAME, soname_indx))
1987 if (! elf_add_dynamic_entry (info, DT_SYMBOLIC, 0))
1995 indx = _bfd_stringtab_add (elf_hash_table (info)->dynstr, rpath,
1997 if (indx == (bfd_size_type) -1
1998 || ! elf_add_dynamic_entry (info, DT_RPATH, indx))
2002 if (filter_shlib != NULL)
2006 indx = _bfd_stringtab_add (elf_hash_table (info)->dynstr,
2007 filter_shlib, true, true);
2008 if (indx == (bfd_size_type) -1
2009 || ! elf_add_dynamic_entry (info, DT_FILTER, indx))
2013 if (auxiliary_filters != NULL)
2015 const char * const *p;
2017 for (p = auxiliary_filters; *p != NULL; p++)
2021 indx = _bfd_stringtab_add (elf_hash_table (info)->dynstr,
2023 if (indx == (bfd_size_type) -1
2024 || ! elf_add_dynamic_entry (info, DT_AUXILIARY, indx))
2029 /* Find all symbols which were defined in a dynamic object and make
2030 the backend pick a reasonable value for them. */
2033 elf_link_hash_traverse (elf_hash_table (info),
2034 elf_adjust_dynamic_symbol,
2039 /* Add some entries to the .dynamic section. We fill in some of the
2040 values later, in elf_bfd_final_link, but we must add the entries
2041 now so that we know the final size of the .dynamic section. */
2042 h = elf_link_hash_lookup (elf_hash_table (info), "_init", false,
2045 && (h->elf_link_hash_flags & (ELF_LINK_HASH_REF_REGULAR
2046 | ELF_LINK_HASH_DEF_REGULAR)) != 0)
2048 if (! elf_add_dynamic_entry (info, DT_INIT, 0))
2051 h = elf_link_hash_lookup (elf_hash_table (info), "_fini", false,
2054 && (h->elf_link_hash_flags & (ELF_LINK_HASH_REF_REGULAR
2055 | ELF_LINK_HASH_DEF_REGULAR)) != 0)
2057 if (! elf_add_dynamic_entry (info, DT_FINI, 0))
2060 strsize = _bfd_stringtab_size (elf_hash_table (info)->dynstr);
2061 if (! elf_add_dynamic_entry (info, DT_HASH, 0)
2062 || ! elf_add_dynamic_entry (info, DT_STRTAB, 0)
2063 || ! elf_add_dynamic_entry (info, DT_SYMTAB, 0)
2064 || ! elf_add_dynamic_entry (info, DT_STRSZ, strsize)
2065 || ! elf_add_dynamic_entry (info, DT_SYMENT,
2066 sizeof (Elf_External_Sym)))
2070 /* The backend must work out the sizes of all the other dynamic
2072 old_dynsymcount = elf_hash_table (info)->dynsymcount;
2073 if (! (*bed->elf_backend_size_dynamic_sections) (output_bfd, info))
2076 if (elf_hash_table (info)->dynamic_sections_created)
2081 size_t bucketcount = 0;
2082 Elf_Internal_Sym isym;
2083 struct elf_assign_sym_version_info sinfo;
2085 /* Set up the version definition section. */
2086 s = bfd_get_section_by_name (dynobj, ".gnu.version_d");
2087 BFD_ASSERT (s != NULL);
2089 /* Attach all the symbols to their version information. This
2090 may cause some symbols to be unexported. */
2091 sinfo.output_bfd = output_bfd;
2093 sinfo.verdefs = verdefs;
2094 sinfo.export_dynamic = export_dynamic;
2095 sinfo.removed_dynamic = false;
2096 sinfo.failed = false;
2098 elf_link_hash_traverse (elf_hash_table (info),
2099 elf_link_assign_sym_version,
2104 /* We may have created additional version definitions if we are
2105 just linking a regular application. */
2106 verdefs = sinfo.verdefs;
2108 if (verdefs == NULL)
2112 /* Don't include this section in the output file. */
2113 for (spp = &output_bfd->sections;
2114 *spp != s->output_section;
2115 spp = &(*spp)->next)
2117 *spp = s->output_section->next;
2118 --output_bfd->section_count;
2124 struct bfd_elf_version_tree *t;
2126 Elf_Internal_Verdef def;
2127 Elf_Internal_Verdaux defaux;
2129 if (sinfo.removed_dynamic)
2131 /* Some dynamic symbols were changed to be local
2132 symbols. In this case, we renumber all of the
2133 dynamic symbols, so that we don't have a hole. If
2134 the backend changed dynsymcount, then assume that the
2135 new symbols are at the start. This is the case on
2136 the MIPS. FIXME: The names of the removed symbols
2137 will still be in the dynamic string table, wasting
2139 elf_hash_table (info)->dynsymcount =
2140 1 + (elf_hash_table (info)->dynsymcount - old_dynsymcount);
2141 elf_link_hash_traverse (elf_hash_table (info),
2142 elf_link_renumber_dynsyms,
2149 /* Make space for the base version. */
2150 size += sizeof (Elf_External_Verdef);
2151 size += sizeof (Elf_External_Verdaux);
2154 for (t = verdefs; t != NULL; t = t->next)
2156 struct bfd_elf_version_deps *n;
2158 size += sizeof (Elf_External_Verdef);
2159 size += sizeof (Elf_External_Verdaux);
2162 for (n = t->deps; n != NULL; n = n->next)
2163 size += sizeof (Elf_External_Verdaux);
2166 s->_raw_size = size;
2167 s->contents = (bfd_byte *) bfd_alloc (output_bfd, s->_raw_size);
2168 if (s->contents == NULL && s->_raw_size != 0)
2171 /* Fill in the version definition section. */
2175 def.vd_version = VER_DEF_CURRENT;
2176 def.vd_flags = VER_FLG_BASE;
2179 def.vd_aux = sizeof (Elf_External_Verdef);
2180 def.vd_next = (sizeof (Elf_External_Verdef)
2181 + sizeof (Elf_External_Verdaux));
2183 if (soname_indx != -1)
2185 def.vd_hash = bfd_elf_hash ((const unsigned char *) soname);
2186 defaux.vda_name = soname_indx;
2193 name = output_bfd->filename;
2194 def.vd_hash = bfd_elf_hash ((const unsigned char *) name);
2195 indx = _bfd_stringtab_add (elf_hash_table (info)->dynstr,
2197 if (indx == (bfd_size_type) -1)
2199 defaux.vda_name = indx;
2201 defaux.vda_next = 0;
2203 _bfd_elf_swap_verdef_out (output_bfd, &def,
2204 (Elf_External_Verdef *)p);
2205 p += sizeof (Elf_External_Verdef);
2206 _bfd_elf_swap_verdaux_out (output_bfd, &defaux,
2207 (Elf_External_Verdaux *) p);
2208 p += sizeof (Elf_External_Verdaux);
2210 for (t = verdefs; t != NULL; t = t->next)
2213 struct bfd_elf_version_deps *n;
2214 struct elf_link_hash_entry *h;
2217 for (n = t->deps; n != NULL; n = n->next)
2220 /* Add a symbol representing this version. */
2222 if (! (_bfd_generic_link_add_one_symbol
2223 (info, dynobj, t->name, BSF_GLOBAL, bfd_abs_section_ptr,
2224 (bfd_vma) 0, (const char *) NULL, false,
2225 get_elf_backend_data (dynobj)->collect,
2226 (struct bfd_link_hash_entry **) &h)))
2228 h->elf_link_hash_flags &= ~ ELF_LINK_NON_ELF;
2229 h->elf_link_hash_flags |= ELF_LINK_HASH_DEF_REGULAR;
2230 h->type = STT_OBJECT;
2231 h->verinfo.vertree = t;
2233 if (! _bfd_elf_link_record_dynamic_symbol (info, h))
2236 def.vd_version = VER_DEF_CURRENT;
2238 if (t->globals == NULL && t->locals == NULL && ! t->used)
2239 def.vd_flags |= VER_FLG_WEAK;
2240 def.vd_ndx = t->vernum + 1;
2241 def.vd_cnt = cdeps + 1;
2242 def.vd_hash = bfd_elf_hash ((const unsigned char *) t->name);
2243 def.vd_aux = sizeof (Elf_External_Verdef);
2244 if (t->next != NULL)
2245 def.vd_next = (sizeof (Elf_External_Verdef)
2246 + (cdeps + 1) * sizeof (Elf_External_Verdaux));
2250 _bfd_elf_swap_verdef_out (output_bfd, &def,
2251 (Elf_External_Verdef *) p);
2252 p += sizeof (Elf_External_Verdef);
2254 defaux.vda_name = h->dynstr_index;
2255 if (t->deps == NULL)
2256 defaux.vda_next = 0;
2258 defaux.vda_next = sizeof (Elf_External_Verdaux);
2259 t->name_indx = defaux.vda_name;
2261 _bfd_elf_swap_verdaux_out (output_bfd, &defaux,
2262 (Elf_External_Verdaux *) p);
2263 p += sizeof (Elf_External_Verdaux);
2265 for (n = t->deps; n != NULL; n = n->next)
2267 defaux.vda_name = n->version_needed->name_indx;
2268 if (n->next == NULL)
2269 defaux.vda_next = 0;
2271 defaux.vda_next = sizeof (Elf_External_Verdaux);
2273 _bfd_elf_swap_verdaux_out (output_bfd, &defaux,
2274 (Elf_External_Verdaux *) p);
2275 p += sizeof (Elf_External_Verdaux);
2279 if (! elf_add_dynamic_entry (info, DT_VERDEF, 0)
2280 || ! elf_add_dynamic_entry (info, DT_VERDEFNUM, cdefs))
2283 elf_tdata (output_bfd)->cverdefs = cdefs;
2286 /* Work out the size of the version reference section. */
2288 s = bfd_get_section_by_name (dynobj, ".gnu.version_r");
2289 BFD_ASSERT (s != NULL);
2291 struct elf_find_verdep_info sinfo;
2293 sinfo.output_bfd = output_bfd;
2295 sinfo.vers = elf_tdata (output_bfd)->cverdefs;
2296 if (sinfo.vers == 0)
2298 sinfo.failed = false;
2300 elf_link_hash_traverse (elf_hash_table (info),
2301 elf_link_find_version_dependencies,
2304 if (elf_tdata (output_bfd)->verref == NULL)
2308 /* We don't have any version definitions, so we can just
2309 remove the section. */
2311 for (spp = &output_bfd->sections;
2312 *spp != s->output_section;
2313 spp = &(*spp)->next)
2315 *spp = s->output_section->next;
2316 --output_bfd->section_count;
2320 Elf_Internal_Verneed *t;
2325 /* Build the version definition section. */
2328 for (t = elf_tdata (output_bfd)->verref;
2332 Elf_Internal_Vernaux *a;
2334 size += sizeof (Elf_External_Verneed);
2336 for (a = t->vn_auxptr; a != NULL; a = a->vna_nextptr)
2337 size += sizeof (Elf_External_Vernaux);
2340 s->_raw_size = size;
2341 s->contents = (bfd_byte *) bfd_alloc (output_bfd, size);
2342 if (s->contents == NULL)
2346 for (t = elf_tdata (output_bfd)->verref;
2351 Elf_Internal_Vernaux *a;
2355 for (a = t->vn_auxptr; a != NULL; a = a->vna_nextptr)
2358 t->vn_version = VER_NEED_CURRENT;
2360 indx = _bfd_stringtab_add (elf_hash_table (info)->dynstr,
2361 t->vn_bfd->filename, true, false);
2362 if (indx == (bfd_size_type) -1)
2365 t->vn_aux = sizeof (Elf_External_Verneed);
2366 if (t->vn_nextref == NULL)
2369 t->vn_next = (sizeof (Elf_External_Verneed)
2370 + caux * sizeof (Elf_External_Vernaux));
2372 _bfd_elf_swap_verneed_out (output_bfd, t,
2373 (Elf_External_Verneed *) p);
2374 p += sizeof (Elf_External_Verneed);
2376 for (a = t->vn_auxptr; a != NULL; a = a->vna_nextptr)
2378 a->vna_hash = bfd_elf_hash ((const unsigned char *)
2380 indx = _bfd_stringtab_add (elf_hash_table (info)->dynstr,
2381 a->vna_nodename, true, false);
2382 if (indx == (bfd_size_type) -1)
2385 if (a->vna_nextptr == NULL)
2388 a->vna_next = sizeof (Elf_External_Vernaux);
2390 _bfd_elf_swap_vernaux_out (output_bfd, a,
2391 (Elf_External_Vernaux *) p);
2392 p += sizeof (Elf_External_Vernaux);
2396 if (! elf_add_dynamic_entry (info, DT_VERNEED, 0)
2397 || ! elf_add_dynamic_entry (info, DT_VERNEEDNUM, crefs))
2400 elf_tdata (output_bfd)->cverrefs = crefs;
2404 dynsymcount = elf_hash_table (info)->dynsymcount;
2406 /* Work out the size of the symbol version section. */
2407 s = bfd_get_section_by_name (dynobj, ".gnu.version");
2408 BFD_ASSERT (s != NULL);
2409 if (dynsymcount == 0
2410 || (verdefs == NULL && elf_tdata (output_bfd)->verref == NULL))
2414 /* We don't need any symbol versions; just discard the
2416 for (spp = &output_bfd->sections;
2417 *spp != s->output_section;
2418 spp = &(*spp)->next)
2420 *spp = s->output_section->next;
2421 --output_bfd->section_count;
2425 s->_raw_size = dynsymcount * sizeof (Elf_External_Versym);
2426 s->contents = (bfd_byte *) bfd_zalloc (output_bfd, s->_raw_size);
2427 if (s->contents == NULL)
2430 if (! elf_add_dynamic_entry (info, DT_VERSYM, 0))
2434 /* Set the size of the .dynsym and .hash sections. We counted
2435 the number of dynamic symbols in elf_link_add_object_symbols.
2436 We will build the contents of .dynsym and .hash when we build
2437 the final symbol table, because until then we do not know the
2438 correct value to give the symbols. We built the .dynstr
2439 section as we went along in elf_link_add_object_symbols. */
2440 s = bfd_get_section_by_name (dynobj, ".dynsym");
2441 BFD_ASSERT (s != NULL);
2442 s->_raw_size = dynsymcount * sizeof (Elf_External_Sym);
2443 s->contents = (bfd_byte *) bfd_alloc (output_bfd, s->_raw_size);
2444 if (s->contents == NULL && s->_raw_size != 0)
2447 /* The first entry in .dynsym is a dummy symbol. */
2454 elf_swap_symbol_out (output_bfd, &isym,
2455 (PTR) (Elf_External_Sym *) s->contents);
2457 for (i = 0; elf_buckets[i] != 0; i++)
2459 bucketcount = elf_buckets[i];
2460 if (dynsymcount < elf_buckets[i + 1])
2464 s = bfd_get_section_by_name (dynobj, ".hash");
2465 BFD_ASSERT (s != NULL);
2466 s->_raw_size = (2 + bucketcount + dynsymcount) * (ARCH_SIZE / 8);
2467 s->contents = (bfd_byte *) bfd_alloc (output_bfd, s->_raw_size);
2468 if (s->contents == NULL)
2470 memset (s->contents, 0, (size_t) s->_raw_size);
2472 put_word (output_bfd, bucketcount, s->contents);
2473 put_word (output_bfd, dynsymcount, s->contents + (ARCH_SIZE / 8));
2475 elf_hash_table (info)->bucketcount = bucketcount;
2477 s = bfd_get_section_by_name (dynobj, ".dynstr");
2478 BFD_ASSERT (s != NULL);
2479 s->_raw_size = _bfd_stringtab_size (elf_hash_table (info)->dynstr);
2481 if (! elf_add_dynamic_entry (info, DT_NULL, 0))
2488 /* Make the backend pick a good value for a dynamic symbol. This is
2489 called via elf_link_hash_traverse, and also calls itself
2493 elf_adjust_dynamic_symbol (h, data)
2494 struct elf_link_hash_entry *h;
2497 struct elf_info_failed *eif = (struct elf_info_failed *) data;
2499 struct elf_backend_data *bed;
2501 /* Ignore indirect symbols. These are added by the versioning code. */
2502 if (h->root.type == bfd_link_hash_indirect)
2505 /* If this symbol was mentioned in a non-ELF file, try to set
2506 DEF_REGULAR and REF_REGULAR correctly. This is the only way to
2507 permit a non-ELF file to correctly refer to a symbol defined in
2508 an ELF dynamic object. */
2509 if ((h->elf_link_hash_flags & ELF_LINK_NON_ELF) != 0)
2511 if (h->root.type != bfd_link_hash_defined
2512 && h->root.type != bfd_link_hash_defweak)
2513 h->elf_link_hash_flags |= ELF_LINK_HASH_REF_REGULAR;
2516 if (h->root.u.def.section->owner != NULL
2517 && (bfd_get_flavour (h->root.u.def.section->owner)
2518 == bfd_target_elf_flavour))
2519 h->elf_link_hash_flags |= ELF_LINK_HASH_REF_REGULAR;
2521 h->elf_link_hash_flags |= ELF_LINK_HASH_DEF_REGULAR;
2524 if ((h->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC) != 0
2525 || (h->elf_link_hash_flags & ELF_LINK_HASH_REF_DYNAMIC) != 0)
2527 if (! _bfd_elf_link_record_dynamic_symbol (eif->info, h))
2535 /* If this is a final link, and the symbol was defined as a common
2536 symbol in a regular object file, and there was no definition in
2537 any dynamic object, then the linker will have allocated space for
2538 the symbol in a common section but the ELF_LINK_HASH_DEF_REGULAR
2539 flag will not have been set. */
2540 if (h->root.type == bfd_link_hash_defined
2541 && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) == 0
2542 && (h->elf_link_hash_flags & ELF_LINK_HASH_REF_REGULAR) != 0
2543 && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC) == 0
2544 && (h->root.u.def.section->owner->flags & DYNAMIC) == 0)
2545 h->elf_link_hash_flags |= ELF_LINK_HASH_DEF_REGULAR;
2547 /* If -Bsymbolic was used (which means to bind references to global
2548 symbols to the definition within the shared object), and this
2549 symbol was defined in a regular object, then it actually doesn't
2550 need a PLT entry. */
2551 if ((h->elf_link_hash_flags & ELF_LINK_HASH_NEEDS_PLT) != 0
2552 && eif->info->shared
2553 && eif->info->symbolic
2554 && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) != 0)
2555 h->elf_link_hash_flags &=~ ELF_LINK_HASH_NEEDS_PLT;
2557 /* If this symbol does not require a PLT entry, and it is not
2558 defined by a dynamic object, or is not referenced by a regular
2559 object, ignore it. We do have to handle a weak defined symbol,
2560 even if no regular object refers to it, if we decided to add it
2561 to the dynamic symbol table. FIXME: Do we normally need to worry
2562 about symbols which are defined by one dynamic object and
2563 referenced by another one? */
2564 if ((h->elf_link_hash_flags & ELF_LINK_HASH_NEEDS_PLT) == 0
2565 && ((h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) != 0
2566 || (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC) == 0
2567 || ((h->elf_link_hash_flags & ELF_LINK_HASH_REF_REGULAR) == 0
2568 && (h->weakdef == NULL || h->weakdef->dynindx == -1))))
2571 /* If we've already adjusted this symbol, don't do it again. This
2572 can happen via a recursive call. */
2573 if ((h->elf_link_hash_flags & ELF_LINK_HASH_DYNAMIC_ADJUSTED) != 0)
2576 /* Don't look at this symbol again. Note that we must set this
2577 after checking the above conditions, because we may look at a
2578 symbol once, decide not to do anything, and then get called
2579 recursively later after REF_REGULAR is set below. */
2580 h->elf_link_hash_flags |= ELF_LINK_HASH_DYNAMIC_ADJUSTED;
2582 /* If this is a weak definition, and we know a real definition, and
2583 the real symbol is not itself defined by a regular object file,
2584 then get a good value for the real definition. We handle the
2585 real symbol first, for the convenience of the backend routine.
2587 Note that there is a confusing case here. If the real definition
2588 is defined by a regular object file, we don't get the real symbol
2589 from the dynamic object, but we do get the weak symbol. If the
2590 processor backend uses a COPY reloc, then if some routine in the
2591 dynamic object changes the real symbol, we will not see that
2592 change in the corresponding weak symbol. This is the way other
2593 ELF linkers work as well, and seems to be a result of the shared
2596 I will clarify this issue. Most SVR4 shared libraries define the
2597 variable _timezone and define timezone as a weak synonym. The
2598 tzset call changes _timezone. If you write
2599 extern int timezone;
2601 int main () { tzset (); printf ("%d %d\n", timezone, _timezone); }
2602 you might expect that, since timezone is a synonym for _timezone,
2603 the same number will print both times. However, if the processor
2604 backend uses a COPY reloc, then actually timezone will be copied
2605 into your process image, and, since you define _timezone
2606 yourself, _timezone will not. Thus timezone and _timezone will
2607 wind up at different memory locations. The tzset call will set
2608 _timezone, leaving timezone unchanged. */
2610 if (h->weakdef != NULL)
2612 struct elf_link_hash_entry *weakdef;
2614 BFD_ASSERT (h->root.type == bfd_link_hash_defined
2615 || h->root.type == bfd_link_hash_defweak);
2616 weakdef = h->weakdef;
2617 BFD_ASSERT (weakdef->root.type == bfd_link_hash_defined
2618 || weakdef->root.type == bfd_link_hash_defweak);
2619 BFD_ASSERT (weakdef->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC);
2620 if ((weakdef->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) != 0)
2622 /* This symbol is defined by a regular object file, so we
2623 will not do anything special. Clear weakdef for the
2624 convenience of the processor backend. */
2629 /* There is an implicit reference by a regular object file
2630 via the weak symbol. */
2631 weakdef->elf_link_hash_flags |= ELF_LINK_HASH_REF_REGULAR;
2632 if (! elf_adjust_dynamic_symbol (weakdef, (PTR) eif))
2637 dynobj = elf_hash_table (eif->info)->dynobj;
2638 bed = get_elf_backend_data (dynobj);
2639 if (! (*bed->elf_backend_adjust_dynamic_symbol) (eif->info, h))
2648 /* This routine is used to export all defined symbols into the dynamic
2649 symbol table. It is called via elf_link_hash_traverse. */
2652 elf_export_symbol (h, data)
2653 struct elf_link_hash_entry *h;
2656 struct elf_info_failed *eif = (struct elf_info_failed *) data;
2658 /* Ignore indirect symbols. These are added by the versioning code. */
2659 if (h->root.type == bfd_link_hash_indirect)
2662 if (h->dynindx == -1
2663 && (h->elf_link_hash_flags
2664 & (ELF_LINK_HASH_DEF_REGULAR | ELF_LINK_HASH_REF_REGULAR)) != 0)
2666 if (! _bfd_elf_link_record_dynamic_symbol (eif->info, h))
2676 /* Look through the symbols which are defined in other shared
2677 libraries and referenced here. Update the list of version
2678 dependencies. This will be put into the .gnu.version_r section.
2679 This function is called via elf_link_hash_traverse. */
2682 elf_link_find_version_dependencies (h, data)
2683 struct elf_link_hash_entry *h;
2686 struct elf_find_verdep_info *rinfo = (struct elf_find_verdep_info *) data;
2687 Elf_Internal_Verneed *t;
2688 Elf_Internal_Vernaux *a;
2690 /* We only care about symbols defined in shared objects with version
2692 if ((h->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC) == 0
2693 || (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) != 0
2695 || h->verinfo.verdef == NULL)
2698 /* See if we already know about this version. */
2699 for (t = elf_tdata (rinfo->output_bfd)->verref; t != NULL; t = t->vn_nextref)
2701 if (t->vn_bfd == h->verinfo.verdef->vd_bfd)
2704 for (a = t->vn_auxptr; a != NULL; a = a->vna_nextptr)
2705 if (a->vna_nodename == h->verinfo.verdef->vd_nodename)
2711 /* This is a new version. Add it to tree we are building. */
2715 t = (Elf_Internal_Verneed *) bfd_zalloc (rinfo->output_bfd, sizeof *t);
2718 rinfo->failed = true;
2722 t->vn_bfd = h->verinfo.verdef->vd_bfd;
2723 t->vn_nextref = elf_tdata (rinfo->output_bfd)->verref;
2724 elf_tdata (rinfo->output_bfd)->verref = t;
2727 a = (Elf_Internal_Vernaux *) bfd_zalloc (rinfo->output_bfd, sizeof *a);
2729 /* Note that we are copying a string pointer here, and testing it
2730 above. If bfd_elf_string_from_elf_section is ever changed to
2731 discard the string data when low in memory, this will have to be
2733 a->vna_nodename = h->verinfo.verdef->vd_nodename;
2735 a->vna_flags = h->verinfo.verdef->vd_flags;
2736 a->vna_nextptr = t->vn_auxptr;
2738 h->verinfo.verdef->vd_exp_refno = rinfo->vers;
2741 a->vna_other = h->verinfo.verdef->vd_exp_refno + 1;
2748 /* Figure out appropriate versions for all the symbols. We may not
2749 have the version number script until we have read all of the input
2750 files, so until that point we don't know which symbols should be
2751 local. This function is called via elf_link_hash_traverse. */
2754 elf_link_assign_sym_version (h, data)
2755 struct elf_link_hash_entry *h;
2758 struct elf_assign_sym_version_info *sinfo =
2759 (struct elf_assign_sym_version_info *) data;
2760 struct bfd_link_info *info = sinfo->info;
2763 /* We only need version numbers for symbols defined in regular
2765 if ((h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) == 0)
2768 p = strchr (h->root.root.string, ELF_VER_CHR);
2769 if (p != NULL && h->verinfo.vertree == NULL)
2771 struct bfd_elf_version_tree *t;
2776 /* There are two consecutive ELF_VER_CHR characters if this is
2777 not a hidden symbol. */
2779 if (*p == ELF_VER_CHR)
2785 /* If there is no version string, we can just return out. */
2789 h->elf_link_hash_flags |= ELF_LINK_HIDDEN;
2793 /* Look for the version. If we find it, it is no longer weak. */
2794 for (t = sinfo->verdefs; t != NULL; t = t->next)
2796 if (strcmp (t->name, p) == 0)
2798 h->verinfo.vertree = t;
2801 /* See if there is anything to force this symbol to
2803 if (t->locals != NULL)
2807 struct bfd_elf_version_expr *d;
2809 len = p - h->root.root.string;
2810 alc = bfd_alloc (sinfo->output_bfd, len);
2813 strncpy (alc, h->root.root.string, len - 1);
2814 alc[len - 1] = '\0';
2815 if (alc[len - 2] == ELF_VER_CHR)
2816 alc[len - 2] = '\0';
2818 for (d = t->locals; d != NULL; d = d->next)
2820 if ((d->match[0] == '*' && d->match[1] == '\0')
2821 || fnmatch (d->match, alc, 0) == 0)
2823 if (h->dynindx != -1
2825 && ! sinfo->export_dynamic
2826 && (h->elf_link_hash_flags
2827 & ELF_LINK_HASH_NEEDS_PLT) == 0)
2829 sinfo->removed_dynamic = true;
2830 h->elf_link_hash_flags |= ELF_LINK_FORCED_LOCAL;
2832 /* FIXME: The name of the symbol has
2833 already been recorded in the dynamic
2834 string table section. */
2841 bfd_release (sinfo->output_bfd, alc);
2848 /* If we are building an application, we need to create a
2849 version node for this version. */
2850 if (t == NULL && ! info->shared)
2852 struct bfd_elf_version_tree **pp;
2855 /* If we aren't going to export this symbol, we don't need
2856 to worry about it. */
2857 if (h->dynindx == -1)
2860 t = ((struct bfd_elf_version_tree *)
2861 bfd_alloc (sinfo->output_bfd, sizeof *t));
2864 sinfo->failed = true;
2873 t->name_indx = (unsigned int) -1;
2877 for (pp = &sinfo->verdefs; *pp != NULL; pp = &(*pp)->next)
2879 t->vernum = version_index;
2883 h->verinfo.vertree = t;
2887 /* We could not find the version for a symbol when
2888 generating a shared archive. Return an error. */
2889 (*_bfd_error_handler)
2890 ("%s: undefined version name %s",
2891 bfd_get_filename (sinfo->output_bfd), h->root.root.string);
2892 bfd_set_error (bfd_error_bad_value);
2893 sinfo->failed = true;
2898 h->elf_link_hash_flags |= ELF_LINK_HIDDEN;
2901 /* If we don't have a version for this symbol, see if we can find
2903 if (h->verinfo.vertree == NULL && sinfo->verdefs != NULL)
2905 struct bfd_elf_version_tree *t;
2906 struct bfd_elf_version_tree *deflt;
2907 struct bfd_elf_version_expr *d;
2909 /* See if can find what version this symbol is in. If the
2910 symbol is supposed to eb local, then don't actually register
2913 for (t = sinfo->verdefs; t != NULL; t = t->next)
2915 if (t->globals != NULL)
2917 for (d = t->globals; d != NULL; d = d->next)
2919 if (fnmatch (d->match, h->root.root.string, 0) == 0)
2921 h->verinfo.vertree = t;
2930 if (t->locals != NULL)
2932 for (d = t->locals; d != NULL; d = d->next)
2934 if (d->match[0] == '*' && d->match[1] == '\0')
2936 else if (fnmatch (d->match, h->root.root.string, 0) == 0)
2938 h->verinfo.vertree = t;
2939 if (h->dynindx != -1
2941 && ! sinfo->export_dynamic
2942 && (h->elf_link_hash_flags
2943 & ELF_LINK_HASH_NEEDS_PLT) == 0)
2945 sinfo->removed_dynamic = true;
2946 h->elf_link_hash_flags |= ELF_LINK_FORCED_LOCAL;
2948 /* FIXME: The name of the symbol has already
2949 been recorded in the dynamic string table
2961 if (deflt != NULL && h->verinfo.vertree == NULL)
2963 h->verinfo.vertree = deflt;
2964 if (h->dynindx != -1
2966 && ! sinfo->export_dynamic
2967 && (h->elf_link_hash_flags & ELF_LINK_HASH_NEEDS_PLT) == 0)
2969 sinfo->removed_dynamic = true;
2970 h->elf_link_hash_flags |= ELF_LINK_FORCED_LOCAL;
2972 /* FIXME: The name of the symbol has already been
2973 recorded in the dynamic string table section. */
2981 /* This function is used to renumber the dynamic symbols, if some of
2982 them are removed because they are marked as local. This is called
2983 via elf_link_hash_traverse. */
2986 elf_link_renumber_dynsyms (h, data)
2987 struct elf_link_hash_entry *h;
2990 struct bfd_link_info *info = (struct bfd_link_info *) data;
2992 if (h->dynindx != -1)
2994 h->dynindx = elf_hash_table (info)->dynsymcount;
2995 ++elf_hash_table (info)->dynsymcount;
3001 /* Final phase of ELF linker. */
3003 /* A structure we use to avoid passing large numbers of arguments. */
3005 struct elf_final_link_info
3007 /* General link information. */
3008 struct bfd_link_info *info;
3011 /* Symbol string table. */
3012 struct bfd_strtab_hash *symstrtab;
3013 /* .dynsym section. */
3014 asection *dynsym_sec;
3015 /* .hash section. */
3017 /* symbol version section (.gnu.version). */
3018 asection *symver_sec;
3019 /* Buffer large enough to hold contents of any section. */
3021 /* Buffer large enough to hold external relocs of any section. */
3022 PTR external_relocs;
3023 /* Buffer large enough to hold internal relocs of any section. */
3024 Elf_Internal_Rela *internal_relocs;
3025 /* Buffer large enough to hold external local symbols of any input
3027 Elf_External_Sym *external_syms;
3028 /* Buffer large enough to hold internal local symbols of any input
3030 Elf_Internal_Sym *internal_syms;
3031 /* Array large enough to hold a symbol index for each local symbol
3032 of any input BFD. */
3034 /* Array large enough to hold a section pointer for each local
3035 symbol of any input BFD. */
3036 asection **sections;
3037 /* Buffer to hold swapped out symbols. */
3038 Elf_External_Sym *symbuf;
3039 /* Number of swapped out symbols in buffer. */
3040 size_t symbuf_count;
3041 /* Number of symbols which fit in symbuf. */
3045 static boolean elf_link_output_sym
3046 PARAMS ((struct elf_final_link_info *, const char *,
3047 Elf_Internal_Sym *, asection *));
3048 static boolean elf_link_flush_output_syms
3049 PARAMS ((struct elf_final_link_info *));
3050 static boolean elf_link_output_extsym
3051 PARAMS ((struct elf_link_hash_entry *, PTR));
3052 static boolean elf_link_input_bfd
3053 PARAMS ((struct elf_final_link_info *, bfd *));
3054 static boolean elf_reloc_link_order
3055 PARAMS ((bfd *, struct bfd_link_info *, asection *,
3056 struct bfd_link_order *));
3058 /* This struct is used to pass information to elf_link_output_extsym. */
3060 struct elf_outext_info
3064 struct elf_final_link_info *finfo;
3067 /* Do the final step of an ELF link. */
3070 elf_bfd_final_link (abfd, info)
3072 struct bfd_link_info *info;
3076 struct elf_final_link_info finfo;
3077 register asection *o;
3078 register struct bfd_link_order *p;
3080 size_t max_contents_size;
3081 size_t max_external_reloc_size;
3082 size_t max_internal_reloc_count;
3083 size_t max_sym_count;
3085 Elf_Internal_Sym elfsym;
3087 Elf_Internal_Shdr *symtab_hdr;
3088 Elf_Internal_Shdr *symstrtab_hdr;
3089 struct elf_backend_data *bed = get_elf_backend_data (abfd);
3090 struct elf_outext_info eoinfo;
3093 abfd->flags |= DYNAMIC;
3095 dynamic = elf_hash_table (info)->dynamic_sections_created;
3096 dynobj = elf_hash_table (info)->dynobj;
3099 finfo.output_bfd = abfd;
3100 finfo.symstrtab = elf_stringtab_init ();
3101 if (finfo.symstrtab == NULL)
3106 finfo.dynsym_sec = NULL;
3107 finfo.hash_sec = NULL;
3108 finfo.symver_sec = NULL;
3112 finfo.dynsym_sec = bfd_get_section_by_name (dynobj, ".dynsym");
3113 finfo.hash_sec = bfd_get_section_by_name (dynobj, ".hash");
3114 BFD_ASSERT (finfo.dynsym_sec != NULL && finfo.hash_sec != NULL);
3115 finfo.symver_sec = bfd_get_section_by_name (dynobj, ".gnu.version");
3116 /* Note that it is OK if symver_sec is NULL. */
3119 finfo.contents = NULL;
3120 finfo.external_relocs = NULL;
3121 finfo.internal_relocs = NULL;
3122 finfo.external_syms = NULL;
3123 finfo.internal_syms = NULL;
3124 finfo.indices = NULL;
3125 finfo.sections = NULL;
3126 finfo.symbuf = NULL;
3127 finfo.symbuf_count = 0;
3129 /* Count up the number of relocations we will output for each output
3130 section, so that we know the sizes of the reloc sections. We
3131 also figure out some maximum sizes. */
3132 max_contents_size = 0;
3133 max_external_reloc_size = 0;
3134 max_internal_reloc_count = 0;
3136 for (o = abfd->sections; o != (asection *) NULL; o = o->next)
3140 for (p = o->link_order_head; p != NULL; p = p->next)
3142 if (p->type == bfd_section_reloc_link_order
3143 || p->type == bfd_symbol_reloc_link_order)
3145 else if (p->type == bfd_indirect_link_order)
3149 sec = p->u.indirect.section;
3151 /* Mark all sections which are to be included in the
3152 link. This will normally be every section. We need
3153 to do this so that we can identify any sections which
3154 the linker has decided to not include. */
3155 sec->linker_mark = true;
3157 if (info->relocateable)
3158 o->reloc_count += sec->reloc_count;
3160 if (sec->_raw_size > max_contents_size)
3161 max_contents_size = sec->_raw_size;
3162 if (sec->_cooked_size > max_contents_size)
3163 max_contents_size = sec->_cooked_size;
3165 /* We are interested in just local symbols, not all
3167 if (bfd_get_flavour (sec->owner) == bfd_target_elf_flavour
3168 && (sec->owner->flags & DYNAMIC) == 0)
3172 if (elf_bad_symtab (sec->owner))
3173 sym_count = (elf_tdata (sec->owner)->symtab_hdr.sh_size
3174 / sizeof (Elf_External_Sym));
3176 sym_count = elf_tdata (sec->owner)->symtab_hdr.sh_info;
3178 if (sym_count > max_sym_count)
3179 max_sym_count = sym_count;
3181 if ((sec->flags & SEC_RELOC) != 0)
3185 ext_size = elf_section_data (sec)->rel_hdr.sh_size;
3186 if (ext_size > max_external_reloc_size)
3187 max_external_reloc_size = ext_size;
3188 if (sec->reloc_count > max_internal_reloc_count)
3189 max_internal_reloc_count = sec->reloc_count;
3195 if (o->reloc_count > 0)
3196 o->flags |= SEC_RELOC;
3199 /* Explicitly clear the SEC_RELOC flag. The linker tends to
3200 set it (this is probably a bug) and if it is set
3201 assign_section_numbers will create a reloc section. */
3202 o->flags &=~ SEC_RELOC;
3205 /* If the SEC_ALLOC flag is not set, force the section VMA to
3206 zero. This is done in elf_fake_sections as well, but forcing
3207 the VMA to 0 here will ensure that relocs against these
3208 sections are handled correctly. */
3209 if ((o->flags & SEC_ALLOC) == 0
3210 && ! o->user_set_vma)
3214 /* Figure out the file positions for everything but the symbol table
3215 and the relocs. We set symcount to force assign_section_numbers
3216 to create a symbol table. */
3217 abfd->symcount = info->strip == strip_all ? 0 : 1;
3218 BFD_ASSERT (! abfd->output_has_begun);
3219 if (! _bfd_elf_compute_section_file_positions (abfd, info))
3222 /* That created the reloc sections. Set their sizes, and assign
3223 them file positions, and allocate some buffers. */
3224 for (o = abfd->sections; o != NULL; o = o->next)
3226 if ((o->flags & SEC_RELOC) != 0)
3228 Elf_Internal_Shdr *rel_hdr;
3229 register struct elf_link_hash_entry **p, **pend;
3231 rel_hdr = &elf_section_data (o)->rel_hdr;
3233 rel_hdr->sh_size = rel_hdr->sh_entsize * o->reloc_count;
3235 /* The contents field must last into write_object_contents,
3236 so we allocate it with bfd_alloc rather than malloc. */
3237 rel_hdr->contents = (PTR) bfd_alloc (abfd, rel_hdr->sh_size);
3238 if (rel_hdr->contents == NULL && rel_hdr->sh_size != 0)
3241 p = ((struct elf_link_hash_entry **)
3242 bfd_malloc (o->reloc_count
3243 * sizeof (struct elf_link_hash_entry *)));
3244 if (p == NULL && o->reloc_count != 0)
3246 elf_section_data (o)->rel_hashes = p;
3247 pend = p + o->reloc_count;
3248 for (; p < pend; p++)
3251 /* Use the reloc_count field as an index when outputting the
3257 _bfd_elf_assign_file_positions_for_relocs (abfd);
3259 /* We have now assigned file positions for all the sections except
3260 .symtab and .strtab. We start the .symtab section at the current
3261 file position, and write directly to it. We build the .strtab
3262 section in memory. */
3264 symtab_hdr = &elf_tdata (abfd)->symtab_hdr;
3265 /* sh_name is set in prep_headers. */
3266 symtab_hdr->sh_type = SHT_SYMTAB;
3267 symtab_hdr->sh_flags = 0;
3268 symtab_hdr->sh_addr = 0;
3269 symtab_hdr->sh_size = 0;
3270 symtab_hdr->sh_entsize = sizeof (Elf_External_Sym);
3271 /* sh_link is set in assign_section_numbers. */
3272 /* sh_info is set below. */
3273 /* sh_offset is set just below. */
3274 symtab_hdr->sh_addralign = 4; /* FIXME: system dependent? */
3276 off = elf_tdata (abfd)->next_file_pos;
3277 off = _bfd_elf_assign_file_position_for_section (symtab_hdr, off, true);
3279 /* Note that at this point elf_tdata (abfd)->next_file_pos is
3280 incorrect. We do not yet know the size of the .symtab section.
3281 We correct next_file_pos below, after we do know the size. */
3283 /* Allocate a buffer to hold swapped out symbols. This is to avoid
3284 continuously seeking to the right position in the file. */
3285 if (! info->keep_memory || max_sym_count < 20)
3286 finfo.symbuf_size = 20;
3288 finfo.symbuf_size = max_sym_count;
3289 finfo.symbuf = ((Elf_External_Sym *)
3290 bfd_malloc (finfo.symbuf_size * sizeof (Elf_External_Sym)));
3291 if (finfo.symbuf == NULL)
3294 /* Start writing out the symbol table. The first symbol is always a
3296 if (info->strip != strip_all || info->relocateable)
3298 elfsym.st_value = 0;
3301 elfsym.st_other = 0;
3302 elfsym.st_shndx = SHN_UNDEF;
3303 if (! elf_link_output_sym (&finfo, (const char *) NULL,
3304 &elfsym, bfd_und_section_ptr))
3309 /* Some standard ELF linkers do this, but we don't because it causes
3310 bootstrap comparison failures. */
3311 /* Output a file symbol for the output file as the second symbol.
3312 We output this even if we are discarding local symbols, although
3313 I'm not sure if this is correct. */
3314 elfsym.st_value = 0;
3316 elfsym.st_info = ELF_ST_INFO (STB_LOCAL, STT_FILE);
3317 elfsym.st_other = 0;
3318 elfsym.st_shndx = SHN_ABS;
3319 if (! elf_link_output_sym (&finfo, bfd_get_filename (abfd),
3320 &elfsym, bfd_abs_section_ptr))
3324 /* Output a symbol for each section. We output these even if we are
3325 discarding local symbols, since they are used for relocs. These
3326 symbols have no names. We store the index of each one in the
3327 index field of the section, so that we can find it again when
3328 outputting relocs. */
3329 if (info->strip != strip_all || info->relocateable)
3332 elfsym.st_info = ELF_ST_INFO (STB_LOCAL, STT_SECTION);
3333 elfsym.st_other = 0;
3334 for (i = 1; i < elf_elfheader (abfd)->e_shnum; i++)
3336 o = section_from_elf_index (abfd, i);
3338 o->target_index = abfd->symcount;
3339 elfsym.st_shndx = i;
3340 if (info->relocateable || o == NULL)
3341 elfsym.st_value = 0;
3343 elfsym.st_value = o->vma;
3344 if (! elf_link_output_sym (&finfo, (const char *) NULL,
3350 /* Allocate some memory to hold information read in from the input
3352 finfo.contents = (bfd_byte *) bfd_malloc (max_contents_size);
3353 finfo.external_relocs = (PTR) bfd_malloc (max_external_reloc_size);
3354 finfo.internal_relocs = ((Elf_Internal_Rela *)
3355 bfd_malloc (max_internal_reloc_count
3356 * sizeof (Elf_Internal_Rela)));
3357 finfo.external_syms = ((Elf_External_Sym *)
3358 bfd_malloc (max_sym_count
3359 * sizeof (Elf_External_Sym)));
3360 finfo.internal_syms = ((Elf_Internal_Sym *)
3361 bfd_malloc (max_sym_count
3362 * sizeof (Elf_Internal_Sym)));
3363 finfo.indices = (long *) bfd_malloc (max_sym_count * sizeof (long));
3364 finfo.sections = ((asection **)
3365 bfd_malloc (max_sym_count * sizeof (asection *)));
3366 if ((finfo.contents == NULL && max_contents_size != 0)
3367 || (finfo.external_relocs == NULL && max_external_reloc_size != 0)
3368 || (finfo.internal_relocs == NULL && max_internal_reloc_count != 0)
3369 || (finfo.external_syms == NULL && max_sym_count != 0)
3370 || (finfo.internal_syms == NULL && max_sym_count != 0)
3371 || (finfo.indices == NULL && max_sym_count != 0)
3372 || (finfo.sections == NULL && max_sym_count != 0))
3375 /* Since ELF permits relocations to be against local symbols, we
3376 must have the local symbols available when we do the relocations.
3377 Since we would rather only read the local symbols once, and we
3378 would rather not keep them in memory, we handle all the
3379 relocations for a single input file at the same time.
3381 Unfortunately, there is no way to know the total number of local
3382 symbols until we have seen all of them, and the local symbol
3383 indices precede the global symbol indices. This means that when
3384 we are generating relocateable output, and we see a reloc against
3385 a global symbol, we can not know the symbol index until we have
3386 finished examining all the local symbols to see which ones we are
3387 going to output. To deal with this, we keep the relocations in
3388 memory, and don't output them until the end of the link. This is
3389 an unfortunate waste of memory, but I don't see a good way around
3390 it. Fortunately, it only happens when performing a relocateable
3391 link, which is not the common case. FIXME: If keep_memory is set
3392 we could write the relocs out and then read them again; I don't
3393 know how bad the memory loss will be. */
3395 for (sub = info->input_bfds; sub != NULL; sub = sub->next)
3396 sub->output_has_begun = false;
3397 for (o = abfd->sections; o != NULL; o = o->next)
3399 for (p = o->link_order_head; p != NULL; p = p->next)
3401 if (p->type == bfd_indirect_link_order
3402 && (bfd_get_flavour (p->u.indirect.section->owner)
3403 == bfd_target_elf_flavour))
3405 sub = p->u.indirect.section->owner;
3406 if (! sub->output_has_begun)
3408 if (! elf_link_input_bfd (&finfo, sub))
3410 sub->output_has_begun = true;
3413 else if (p->type == bfd_section_reloc_link_order
3414 || p->type == bfd_symbol_reloc_link_order)
3416 if (! elf_reloc_link_order (abfd, info, o, p))
3421 if (! _bfd_default_link_order (abfd, info, o, p))
3427 /* That wrote out all the local symbols. Finish up the symbol table
3428 with the global symbols. */
3430 if (info->strip != strip_all && info->shared)
3432 /* Output any global symbols that got converted to local in a
3433 version script. We do this in a separate step since ELF
3434 requires all local symbols to appear prior to any global
3435 symbols. FIXME: We should only do this if some global
3436 symbols were, in fact, converted to become local. FIXME:
3437 Will this work correctly with the Irix 5 linker? */
3438 eoinfo.failed = false;
3439 eoinfo.finfo = &finfo;
3440 eoinfo.localsyms = true;
3441 elf_link_hash_traverse (elf_hash_table (info), elf_link_output_extsym,
3447 /* The sh_info field records the index of the first non local
3449 symtab_hdr->sh_info = abfd->symcount;
3451 elf_section_data (finfo.dynsym_sec->output_section)->this_hdr.sh_info = 1;
3453 /* We get the global symbols from the hash table. */
3454 eoinfo.failed = false;
3455 eoinfo.localsyms = false;
3456 eoinfo.finfo = &finfo;
3457 elf_link_hash_traverse (elf_hash_table (info), elf_link_output_extsym,
3462 /* Flush all symbols to the file. */
3463 if (! elf_link_flush_output_syms (&finfo))
3466 /* Now we know the size of the symtab section. */
3467 off += symtab_hdr->sh_size;
3469 /* Finish up and write out the symbol string table (.strtab)
3471 symstrtab_hdr = &elf_tdata (abfd)->strtab_hdr;
3472 /* sh_name was set in prep_headers. */
3473 symstrtab_hdr->sh_type = SHT_STRTAB;
3474 symstrtab_hdr->sh_flags = 0;
3475 symstrtab_hdr->sh_addr = 0;
3476 symstrtab_hdr->sh_size = _bfd_stringtab_size (finfo.symstrtab);
3477 symstrtab_hdr->sh_entsize = 0;
3478 symstrtab_hdr->sh_link = 0;
3479 symstrtab_hdr->sh_info = 0;
3480 /* sh_offset is set just below. */
3481 symstrtab_hdr->sh_addralign = 1;
3483 off = _bfd_elf_assign_file_position_for_section (symstrtab_hdr, off, true);
3484 elf_tdata (abfd)->next_file_pos = off;
3486 if (abfd->symcount > 0)
3488 if (bfd_seek (abfd, symstrtab_hdr->sh_offset, SEEK_SET) != 0
3489 || ! _bfd_stringtab_emit (abfd, finfo.symstrtab))
3493 /* Adjust the relocs to have the correct symbol indices. */
3494 for (o = abfd->sections; o != NULL; o = o->next)
3496 struct elf_link_hash_entry **rel_hash;
3497 Elf_Internal_Shdr *rel_hdr;
3499 if ((o->flags & SEC_RELOC) == 0)
3502 rel_hash = elf_section_data (o)->rel_hashes;
3503 rel_hdr = &elf_section_data (o)->rel_hdr;
3504 for (i = 0; i < o->reloc_count; i++, rel_hash++)
3506 if (*rel_hash == NULL)
3509 BFD_ASSERT ((*rel_hash)->indx >= 0);
3511 if (rel_hdr->sh_entsize == sizeof (Elf_External_Rel))
3513 Elf_External_Rel *erel;
3514 Elf_Internal_Rel irel;
3516 erel = (Elf_External_Rel *) rel_hdr->contents + i;
3517 elf_swap_reloc_in (abfd, erel, &irel);
3518 irel.r_info = ELF_R_INFO ((*rel_hash)->indx,
3519 ELF_R_TYPE (irel.r_info));
3520 elf_swap_reloc_out (abfd, &irel, erel);
3524 Elf_External_Rela *erela;
3525 Elf_Internal_Rela irela;
3527 BFD_ASSERT (rel_hdr->sh_entsize
3528 == sizeof (Elf_External_Rela));
3530 erela = (Elf_External_Rela *) rel_hdr->contents + i;
3531 elf_swap_reloca_in (abfd, erela, &irela);
3532 irela.r_info = ELF_R_INFO ((*rel_hash)->indx,
3533 ELF_R_TYPE (irela.r_info));
3534 elf_swap_reloca_out (abfd, &irela, erela);
3538 /* Set the reloc_count field to 0 to prevent write_relocs from
3539 trying to swap the relocs out itself. */
3543 /* If we are linking against a dynamic object, or generating a
3544 shared library, finish up the dynamic linking information. */
3547 Elf_External_Dyn *dyncon, *dynconend;
3549 /* Fix up .dynamic entries. */
3550 o = bfd_get_section_by_name (dynobj, ".dynamic");
3551 BFD_ASSERT (o != NULL);
3553 dyncon = (Elf_External_Dyn *) o->contents;
3554 dynconend = (Elf_External_Dyn *) (o->contents + o->_raw_size);
3555 for (; dyncon < dynconend; dyncon++)
3557 Elf_Internal_Dyn dyn;
3561 elf_swap_dyn_in (dynobj, dyncon, &dyn);
3568 /* SVR4 linkers seem to set DT_INIT and DT_FINI based on
3569 magic _init and _fini symbols. This is pretty ugly,
3570 but we are compatible. */
3578 struct elf_link_hash_entry *h;
3580 h = elf_link_hash_lookup (elf_hash_table (info), name,
3581 false, false, true);
3583 && (h->root.type == bfd_link_hash_defined
3584 || h->root.type == bfd_link_hash_defweak))
3586 dyn.d_un.d_val = h->root.u.def.value;
3587 o = h->root.u.def.section;
3588 if (o->output_section != NULL)
3589 dyn.d_un.d_val += (o->output_section->vma
3590 + o->output_offset);
3593 /* The symbol is imported from another shared
3594 library and does not apply to this one. */
3598 elf_swap_dyn_out (dynobj, &dyn, dyncon);
3613 name = ".gnu.version_d";
3616 name = ".gnu.version_r";
3619 name = ".gnu.version";
3621 o = bfd_get_section_by_name (abfd, name);
3622 BFD_ASSERT (o != NULL);
3623 dyn.d_un.d_ptr = o->vma;
3624 elf_swap_dyn_out (dynobj, &dyn, dyncon);
3631 if (dyn.d_tag == DT_REL || dyn.d_tag == DT_RELSZ)
3636 for (i = 1; i < elf_elfheader (abfd)->e_shnum; i++)
3638 Elf_Internal_Shdr *hdr;
3640 hdr = elf_elfsections (abfd)[i];
3641 if (hdr->sh_type == type
3642 && (hdr->sh_flags & SHF_ALLOC) != 0)
3644 if (dyn.d_tag == DT_RELSZ || dyn.d_tag == DT_RELASZ)
3645 dyn.d_un.d_val += hdr->sh_size;
3648 if (dyn.d_un.d_val == 0
3649 || hdr->sh_addr < dyn.d_un.d_val)
3650 dyn.d_un.d_val = hdr->sh_addr;
3654 elf_swap_dyn_out (dynobj, &dyn, dyncon);
3660 /* If we have created any dynamic sections, then output them. */
3663 if (! (*bed->elf_backend_finish_dynamic_sections) (abfd, info))
3666 for (o = dynobj->sections; o != NULL; o = o->next)
3668 if ((o->flags & SEC_HAS_CONTENTS) == 0
3669 || o->_raw_size == 0)
3671 if ((o->flags & SEC_LINKER_CREATED) == 0)
3673 /* At this point, we are only interested in sections
3674 created by elf_link_create_dynamic_sections. */
3677 if ((elf_section_data (o->output_section)->this_hdr.sh_type
3679 || strcmp (bfd_get_section_name (abfd, o), ".dynstr") != 0)
3681 if (! bfd_set_section_contents (abfd, o->output_section,
3682 o->contents, o->output_offset,
3690 /* The contents of the .dynstr section are actually in a
3692 off = elf_section_data (o->output_section)->this_hdr.sh_offset;
3693 if (bfd_seek (abfd, off, SEEK_SET) != 0
3694 || ! _bfd_stringtab_emit (abfd,
3695 elf_hash_table (info)->dynstr))
3701 /* If we have optimized stabs strings, output them. */
3702 if (elf_hash_table (info)->stab_info != NULL)
3704 if (! _bfd_write_stab_strings (abfd, &elf_hash_table (info)->stab_info))
3708 if (finfo.symstrtab != NULL)
3709 _bfd_stringtab_free (finfo.symstrtab);
3710 if (finfo.contents != NULL)
3711 free (finfo.contents);
3712 if (finfo.external_relocs != NULL)
3713 free (finfo.external_relocs);
3714 if (finfo.internal_relocs != NULL)
3715 free (finfo.internal_relocs);
3716 if (finfo.external_syms != NULL)
3717 free (finfo.external_syms);
3718 if (finfo.internal_syms != NULL)
3719 free (finfo.internal_syms);
3720 if (finfo.indices != NULL)
3721 free (finfo.indices);
3722 if (finfo.sections != NULL)
3723 free (finfo.sections);
3724 if (finfo.symbuf != NULL)
3725 free (finfo.symbuf);
3726 for (o = abfd->sections; o != NULL; o = o->next)
3728 if ((o->flags & SEC_RELOC) != 0
3729 && elf_section_data (o)->rel_hashes != NULL)
3730 free (elf_section_data (o)->rel_hashes);
3733 elf_tdata (abfd)->linker = true;
3738 if (finfo.symstrtab != NULL)
3739 _bfd_stringtab_free (finfo.symstrtab);
3740 if (finfo.contents != NULL)
3741 free (finfo.contents);
3742 if (finfo.external_relocs != NULL)
3743 free (finfo.external_relocs);
3744 if (finfo.internal_relocs != NULL)
3745 free (finfo.internal_relocs);
3746 if (finfo.external_syms != NULL)
3747 free (finfo.external_syms);
3748 if (finfo.internal_syms != NULL)
3749 free (finfo.internal_syms);
3750 if (finfo.indices != NULL)
3751 free (finfo.indices);
3752 if (finfo.sections != NULL)
3753 free (finfo.sections);
3754 if (finfo.symbuf != NULL)
3755 free (finfo.symbuf);
3756 for (o = abfd->sections; o != NULL; o = o->next)
3758 if ((o->flags & SEC_RELOC) != 0
3759 && elf_section_data (o)->rel_hashes != NULL)
3760 free (elf_section_data (o)->rel_hashes);
3766 /* Add a symbol to the output symbol table. */
3769 elf_link_output_sym (finfo, name, elfsym, input_sec)
3770 struct elf_final_link_info *finfo;
3772 Elf_Internal_Sym *elfsym;
3773 asection *input_sec;
3775 boolean (*output_symbol_hook) PARAMS ((bfd *,
3776 struct bfd_link_info *info,
3781 output_symbol_hook = get_elf_backend_data (finfo->output_bfd)->
3782 elf_backend_link_output_symbol_hook;
3783 if (output_symbol_hook != NULL)
3785 if (! ((*output_symbol_hook)
3786 (finfo->output_bfd, finfo->info, name, elfsym, input_sec)))
3790 if (name == (const char *) NULL || *name == '\0')
3791 elfsym->st_name = 0;
3794 elfsym->st_name = (unsigned long) _bfd_stringtab_add (finfo->symstrtab,
3797 if (elfsym->st_name == (unsigned long) -1)
3801 if (finfo->symbuf_count >= finfo->symbuf_size)
3803 if (! elf_link_flush_output_syms (finfo))
3807 elf_swap_symbol_out (finfo->output_bfd, elfsym,
3808 (PTR) (finfo->symbuf + finfo->symbuf_count));
3809 ++finfo->symbuf_count;
3811 ++finfo->output_bfd->symcount;
3816 /* Flush the output symbols to the file. */
3819 elf_link_flush_output_syms (finfo)
3820 struct elf_final_link_info *finfo;
3822 if (finfo->symbuf_count > 0)
3824 Elf_Internal_Shdr *symtab;
3826 symtab = &elf_tdata (finfo->output_bfd)->symtab_hdr;
3828 if (bfd_seek (finfo->output_bfd, symtab->sh_offset + symtab->sh_size,
3830 || (bfd_write ((PTR) finfo->symbuf, finfo->symbuf_count,
3831 sizeof (Elf_External_Sym), finfo->output_bfd)
3832 != finfo->symbuf_count * sizeof (Elf_External_Sym)))
3835 symtab->sh_size += finfo->symbuf_count * sizeof (Elf_External_Sym);
3837 finfo->symbuf_count = 0;
3843 /* Add an external symbol to the symbol table. This is called from
3844 the hash table traversal routine. When generating a shared object,
3845 we go through the symbol table twice. The first time we output
3846 anything that might have been forced to local scope in a version
3847 script. The second time we output the symbols that are still
3851 elf_link_output_extsym (h, data)
3852 struct elf_link_hash_entry *h;
3855 struct elf_outext_info *eoinfo = (struct elf_outext_info *) data;
3856 struct elf_final_link_info *finfo = eoinfo->finfo;
3858 Elf_Internal_Sym sym;
3859 asection *input_sec;
3861 /* Decide whether to output this symbol in this pass. */
3862 if (eoinfo->localsyms)
3864 if ((h->elf_link_hash_flags & ELF_LINK_FORCED_LOCAL) == 0)
3869 if ((h->elf_link_hash_flags & ELF_LINK_FORCED_LOCAL) != 0)
3873 /* If we are not creating a shared library, and this symbol is
3874 referenced by a shared library but is not defined anywhere, then
3875 warn that it is undefined. If we do not do this, the runtime
3876 linker will complain that the symbol is undefined when the
3877 program is run. We don't have to worry about symbols that are
3878 referenced by regular files, because we will already have issued
3879 warnings for them. */
3880 if (! finfo->info->relocateable
3881 && ! finfo->info->shared
3882 && h->root.type == bfd_link_hash_undefined
3883 && (h->elf_link_hash_flags & ELF_LINK_HASH_REF_DYNAMIC) != 0
3884 && (h->elf_link_hash_flags & ELF_LINK_HASH_REF_REGULAR) == 0)
3886 if (! ((*finfo->info->callbacks->undefined_symbol)
3887 (finfo->info, h->root.root.string, h->root.u.undef.abfd,
3888 (asection *) NULL, 0)))
3890 eoinfo->failed = true;
3895 /* We don't want to output symbols that have never been mentioned by
3896 a regular file, or that we have been told to strip. However, if
3897 h->indx is set to -2, the symbol is used by a reloc and we must
3901 else if (((h->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC) != 0
3902 || (h->elf_link_hash_flags & ELF_LINK_HASH_REF_DYNAMIC) != 0)
3903 && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) == 0
3904 && (h->elf_link_hash_flags & ELF_LINK_HASH_REF_REGULAR) == 0)
3906 else if (finfo->info->strip == strip_all
3907 || (finfo->info->strip == strip_some
3908 && bfd_hash_lookup (finfo->info->keep_hash,
3909 h->root.root.string,
3910 false, false) == NULL))
3915 /* If we're stripping it, and it's not a dynamic symbol, there's
3916 nothing else to do. */
3917 if (strip && h->dynindx == -1)
3921 sym.st_size = h->size;
3922 sym.st_other = h->other;
3923 if ((h->elf_link_hash_flags & ELF_LINK_FORCED_LOCAL) != 0)
3924 sym.st_info = ELF_ST_INFO (STB_LOCAL, h->type);
3925 else if (h->root.type == bfd_link_hash_undefweak
3926 || h->root.type == bfd_link_hash_defweak)
3927 sym.st_info = ELF_ST_INFO (STB_WEAK, h->type);
3929 sym.st_info = ELF_ST_INFO (STB_GLOBAL, h->type);
3931 switch (h->root.type)
3934 case bfd_link_hash_new:
3938 case bfd_link_hash_undefined:
3939 input_sec = bfd_und_section_ptr;
3940 sym.st_shndx = SHN_UNDEF;
3943 case bfd_link_hash_undefweak:
3944 input_sec = bfd_und_section_ptr;
3945 sym.st_shndx = SHN_UNDEF;
3948 case bfd_link_hash_defined:
3949 case bfd_link_hash_defweak:
3951 input_sec = h->root.u.def.section;
3952 if (input_sec->output_section != NULL)
3955 _bfd_elf_section_from_bfd_section (finfo->output_bfd,
3956 input_sec->output_section);
3957 if (sym.st_shndx == (unsigned short) -1)
3959 eoinfo->failed = true;
3963 /* ELF symbols in relocateable files are section relative,
3964 but in nonrelocateable files they are virtual
3966 sym.st_value = h->root.u.def.value + input_sec->output_offset;
3967 if (! finfo->info->relocateable)
3968 sym.st_value += input_sec->output_section->vma;
3972 BFD_ASSERT (input_sec->owner == NULL
3973 || (input_sec->owner->flags & DYNAMIC) != 0);
3974 sym.st_shndx = SHN_UNDEF;
3975 input_sec = bfd_und_section_ptr;
3980 case bfd_link_hash_common:
3981 input_sec = bfd_com_section_ptr;
3982 sym.st_shndx = SHN_COMMON;
3983 sym.st_value = 1 << h->root.u.c.p->alignment_power;
3986 case bfd_link_hash_indirect:
3987 /* These symbols are created by symbol versioning. They point
3988 to the decorated version of the name. For example, if the
3989 symbol foo@@GNU_1.2 is the default, which should be used when
3990 foo is used with no version, then we add an indirect symbol
3991 foo which points to foo@@GNU_1.2. We ignore these symbols,
3992 since the indirected symbol is already in the hash table. If
3993 the indirect symbol is non-ELF, fall through and output it. */
3994 if ((h->elf_link_hash_flags & ELF_LINK_NON_ELF) == 0)
3998 case bfd_link_hash_warning:
3999 /* We can't represent these symbols in ELF, although a warning
4000 symbol may have come from a .gnu.warning.SYMBOL section. We
4001 just put the target symbol in the hash table. If the target
4002 symbol does not really exist, don't do anything. */
4003 if (h->root.u.i.link->type == bfd_link_hash_new)
4005 return (elf_link_output_extsym
4006 ((struct elf_link_hash_entry *) h->root.u.i.link, data));
4009 /* If this symbol should be put in the .dynsym section, then put it
4010 there now. We have already know the symbol index. We also fill
4011 in the entry in the .hash section. */
4012 if (h->dynindx != -1
4013 && elf_hash_table (finfo->info)->dynamic_sections_created)
4015 struct elf_backend_data *bed;
4020 bfd_byte *bucketpos;
4023 sym.st_name = h->dynstr_index;
4025 /* Give the processor backend a chance to tweak the symbol
4026 value, and also to finish up anything that needs to be done
4028 bed = get_elf_backend_data (finfo->output_bfd);
4029 if (! ((*bed->elf_backend_finish_dynamic_symbol)
4030 (finfo->output_bfd, finfo->info, h, &sym)))
4032 eoinfo->failed = true;
4036 elf_swap_symbol_out (finfo->output_bfd, &sym,
4037 (PTR) (((Elf_External_Sym *)
4038 finfo->dynsym_sec->contents)
4041 /* We didn't include the version string in the dynamic string
4042 table, so we must not consider it in the hash table. */
4043 name = h->root.root.string;
4044 p = strchr (name, ELF_VER_CHR);
4049 copy = bfd_alloc (finfo->output_bfd, p - name + 1);
4050 strncpy (copy, name, p - name);
4051 copy[p - name] = '\0';
4055 bucketcount = elf_hash_table (finfo->info)->bucketcount;
4056 bucket = bfd_elf_hash ((const unsigned char *) name) % bucketcount;
4057 bucketpos = ((bfd_byte *) finfo->hash_sec->contents
4058 + (bucket + 2) * (ARCH_SIZE / 8));
4059 chain = get_word (finfo->output_bfd, bucketpos);
4060 put_word (finfo->output_bfd, h->dynindx, bucketpos);
4061 put_word (finfo->output_bfd, chain,
4062 ((bfd_byte *) finfo->hash_sec->contents
4063 + (bucketcount + 2 + h->dynindx) * (ARCH_SIZE / 8)));
4066 bfd_release (finfo->output_bfd, copy);
4068 if (finfo->symver_sec != NULL && finfo->symver_sec->contents != NULL)
4070 Elf_Internal_Versym iversym;
4072 if ((h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) == 0)
4074 if (h->verinfo.verdef == NULL)
4075 iversym.vs_vers = 0;
4077 iversym.vs_vers = h->verinfo.verdef->vd_exp_refno + 1;
4081 if (h->verinfo.vertree == NULL)
4082 iversym.vs_vers = 1;
4084 iversym.vs_vers = h->verinfo.vertree->vernum + 1;
4087 if ((h->elf_link_hash_flags & ELF_LINK_HIDDEN) != 0)
4088 iversym.vs_vers |= VERSYM_HIDDEN;
4090 _bfd_elf_swap_versym_out (finfo->output_bfd, &iversym,
4091 (((Elf_External_Versym *)
4092 finfo->symver_sec->contents)
4097 /* If we're stripping it, then it was just a dynamic symbol, and
4098 there's nothing else to do. */
4102 h->indx = finfo->output_bfd->symcount;
4104 if (! elf_link_output_sym (finfo, h->root.root.string, &sym, input_sec))
4106 eoinfo->failed = true;
4113 /* Link an input file into the linker output file. This function
4114 handles all the sections and relocations of the input file at once.
4115 This is so that we only have to read the local symbols once, and
4116 don't have to keep them in memory. */
4119 elf_link_input_bfd (finfo, input_bfd)
4120 struct elf_final_link_info *finfo;
4123 boolean (*relocate_section) PARAMS ((bfd *, struct bfd_link_info *,
4124 bfd *, asection *, bfd_byte *,
4125 Elf_Internal_Rela *,
4126 Elf_Internal_Sym *, asection **));
4128 Elf_Internal_Shdr *symtab_hdr;
4131 Elf_External_Sym *external_syms;
4132 Elf_External_Sym *esym;
4133 Elf_External_Sym *esymend;
4134 Elf_Internal_Sym *isym;
4136 asection **ppsection;
4139 output_bfd = finfo->output_bfd;
4141 get_elf_backend_data (output_bfd)->elf_backend_relocate_section;
4143 /* If this is a dynamic object, we don't want to do anything here:
4144 we don't want the local symbols, and we don't want the section
4146 if ((input_bfd->flags & DYNAMIC) != 0)
4149 symtab_hdr = &elf_tdata (input_bfd)->symtab_hdr;
4150 if (elf_bad_symtab (input_bfd))
4152 locsymcount = symtab_hdr->sh_size / sizeof (Elf_External_Sym);
4157 locsymcount = symtab_hdr->sh_info;
4158 extsymoff = symtab_hdr->sh_info;
4161 /* Read the local symbols. */
4162 if (symtab_hdr->contents != NULL)
4163 external_syms = (Elf_External_Sym *) symtab_hdr->contents;
4164 else if (locsymcount == 0)
4165 external_syms = NULL;
4168 external_syms = finfo->external_syms;
4169 if (bfd_seek (input_bfd, symtab_hdr->sh_offset, SEEK_SET) != 0
4170 || (bfd_read (external_syms, sizeof (Elf_External_Sym),
4171 locsymcount, input_bfd)
4172 != locsymcount * sizeof (Elf_External_Sym)))
4176 /* Swap in the local symbols and write out the ones which we know
4177 are going into the output file. */
4178 esym = external_syms;
4179 esymend = esym + locsymcount;
4180 isym = finfo->internal_syms;
4181 pindex = finfo->indices;
4182 ppsection = finfo->sections;
4183 for (; esym < esymend; esym++, isym++, pindex++, ppsection++)
4187 Elf_Internal_Sym osym;
4189 elf_swap_symbol_in (input_bfd, esym, isym);
4192 if (elf_bad_symtab (input_bfd))
4194 if (ELF_ST_BIND (isym->st_info) != STB_LOCAL)
4201 if (isym->st_shndx == SHN_UNDEF)
4202 isec = bfd_und_section_ptr;
4203 else if (isym->st_shndx > 0 && isym->st_shndx < SHN_LORESERVE)
4204 isec = section_from_elf_index (input_bfd, isym->st_shndx);
4205 else if (isym->st_shndx == SHN_ABS)
4206 isec = bfd_abs_section_ptr;
4207 else if (isym->st_shndx == SHN_COMMON)
4208 isec = bfd_com_section_ptr;
4217 /* Don't output the first, undefined, symbol. */
4218 if (esym == external_syms)
4221 /* If we are stripping all symbols, we don't want to output this
4223 if (finfo->info->strip == strip_all)
4226 /* We never output section symbols. Instead, we use the section
4227 symbol of the corresponding section in the output file. */
4228 if (ELF_ST_TYPE (isym->st_info) == STT_SECTION)
4231 /* If we are discarding all local symbols, we don't want to
4232 output this one. If we are generating a relocateable output
4233 file, then some of the local symbols may be required by
4234 relocs; we output them below as we discover that they are
4236 if (finfo->info->discard == discard_all)
4239 /* If this symbol is defined in a section which we are
4240 discarding, we don't need to keep it, but note that
4241 linker_mark is only reliable for sections that have contents.
4242 For the benefit of the MIPS ELF linker, we check SEC_EXCLUDE
4243 as well as linker_mark. */
4244 if (isym->st_shndx > 0
4245 && isym->st_shndx < SHN_LORESERVE
4247 && ((! isec->linker_mark && (isec->flags & SEC_HAS_CONTENTS) != 0)
4248 || (! finfo->info->relocateable
4249 && (isec->flags & SEC_EXCLUDE) != 0)))
4252 /* Get the name of the symbol. */
4253 name = bfd_elf_string_from_elf_section (input_bfd, symtab_hdr->sh_link,
4258 /* See if we are discarding symbols with this name. */
4259 if ((finfo->info->strip == strip_some
4260 && (bfd_hash_lookup (finfo->info->keep_hash, name, false, false)
4262 || (finfo->info->discard == discard_l
4263 && bfd_is_local_label_name (input_bfd, name)))
4266 /* If we get here, we are going to output this symbol. */
4270 /* Adjust the section index for the output file. */
4271 osym.st_shndx = _bfd_elf_section_from_bfd_section (output_bfd,
4272 isec->output_section);
4273 if (osym.st_shndx == (unsigned short) -1)
4276 *pindex = output_bfd->symcount;
4278 /* ELF symbols in relocateable files are section relative, but
4279 in executable files they are virtual addresses. Note that
4280 this code assumes that all ELF sections have an associated
4281 BFD section with a reasonable value for output_offset; below
4282 we assume that they also have a reasonable value for
4283 output_section. Any special sections must be set up to meet
4284 these requirements. */
4285 osym.st_value += isec->output_offset;
4286 if (! finfo->info->relocateable)
4287 osym.st_value += isec->output_section->vma;
4289 if (! elf_link_output_sym (finfo, name, &osym, isec))
4293 /* Relocate the contents of each section. */
4294 for (o = input_bfd->sections; o != NULL; o = o->next)
4298 if (! o->linker_mark)
4300 /* This section was omitted from the link. */
4304 if ((o->flags & SEC_HAS_CONTENTS) == 0
4305 || (o->_raw_size == 0 && (o->flags & SEC_RELOC) == 0))
4308 if ((o->flags & SEC_LINKER_CREATED) != 0)
4310 /* Section was created by elf_link_create_dynamic_sections
4315 /* Get the contents of the section. They have been cached by a
4316 relaxation routine. Note that o is a section in an input
4317 file, so the contents field will not have been set by any of
4318 the routines which work on output files. */
4319 if (elf_section_data (o)->this_hdr.contents != NULL)
4320 contents = elf_section_data (o)->this_hdr.contents;
4323 contents = finfo->contents;
4324 if (! bfd_get_section_contents (input_bfd, o, contents,
4325 (file_ptr) 0, o->_raw_size))
4329 if ((o->flags & SEC_RELOC) != 0)
4331 Elf_Internal_Rela *internal_relocs;
4333 /* Get the swapped relocs. */
4334 internal_relocs = (NAME(_bfd_elf,link_read_relocs)
4335 (input_bfd, o, finfo->external_relocs,
4336 finfo->internal_relocs, false));
4337 if (internal_relocs == NULL
4338 && o->reloc_count > 0)
4341 /* Relocate the section by invoking a back end routine.
4343 The back end routine is responsible for adjusting the
4344 section contents as necessary, and (if using Rela relocs
4345 and generating a relocateable output file) adjusting the
4346 reloc addend as necessary.
4348 The back end routine does not have to worry about setting
4349 the reloc address or the reloc symbol index.
4351 The back end routine is given a pointer to the swapped in
4352 internal symbols, and can access the hash table entries
4353 for the external symbols via elf_sym_hashes (input_bfd).
4355 When generating relocateable output, the back end routine
4356 must handle STB_LOCAL/STT_SECTION symbols specially. The
4357 output symbol is going to be a section symbol
4358 corresponding to the output section, which will require
4359 the addend to be adjusted. */
4361 if (! (*relocate_section) (output_bfd, finfo->info,
4362 input_bfd, o, contents,
4364 finfo->internal_syms,
4368 if (finfo->info->relocateable)
4370 Elf_Internal_Rela *irela;
4371 Elf_Internal_Rela *irelaend;
4372 struct elf_link_hash_entry **rel_hash;
4373 Elf_Internal_Shdr *input_rel_hdr;
4374 Elf_Internal_Shdr *output_rel_hdr;
4376 /* Adjust the reloc addresses and symbol indices. */
4378 irela = internal_relocs;
4379 irelaend = irela + o->reloc_count;
4380 rel_hash = (elf_section_data (o->output_section)->rel_hashes
4381 + o->output_section->reloc_count);
4382 for (; irela < irelaend; irela++, rel_hash++)
4384 unsigned long r_symndx;
4385 Elf_Internal_Sym *isym;
4388 irela->r_offset += o->output_offset;
4390 r_symndx = ELF_R_SYM (irela->r_info);
4395 if (r_symndx >= locsymcount
4396 || (elf_bad_symtab (input_bfd)
4397 && finfo->sections[r_symndx] == NULL))
4401 /* This is a reloc against a global symbol. We
4402 have not yet output all the local symbols, so
4403 we do not know the symbol index of any global
4404 symbol. We set the rel_hash entry for this
4405 reloc to point to the global hash table entry
4406 for this symbol. The symbol index is then
4407 set at the end of elf_bfd_final_link. */
4408 indx = r_symndx - extsymoff;
4409 *rel_hash = elf_sym_hashes (input_bfd)[indx];
4411 /* Setting the index to -2 tells
4412 elf_link_output_extsym that this symbol is
4414 BFD_ASSERT ((*rel_hash)->indx < 0);
4415 (*rel_hash)->indx = -2;
4420 /* This is a reloc against a local symbol. */
4423 isym = finfo->internal_syms + r_symndx;
4424 sec = finfo->sections[r_symndx];
4425 if (ELF_ST_TYPE (isym->st_info) == STT_SECTION)
4427 /* I suppose the backend ought to fill in the
4428 section of any STT_SECTION symbol against a
4429 processor specific section. If we have
4430 discarded a section, the output_section will
4431 be the absolute section. */
4433 && (bfd_is_abs_section (sec)
4434 || (sec->output_section != NULL
4435 && bfd_is_abs_section (sec->output_section))))
4437 else if (sec == NULL || sec->owner == NULL)
4439 bfd_set_error (bfd_error_bad_value);
4444 r_symndx = sec->output_section->target_index;
4445 BFD_ASSERT (r_symndx != 0);
4450 if (finfo->indices[r_symndx] == -1)
4456 if (finfo->info->strip == strip_all)
4458 /* You can't do ld -r -s. */
4459 bfd_set_error (bfd_error_invalid_operation);
4463 /* This symbol was skipped earlier, but
4464 since it is needed by a reloc, we
4465 must output it now. */
4466 link = symtab_hdr->sh_link;
4467 name = bfd_elf_string_from_elf_section (input_bfd,
4473 osec = sec->output_section;
4475 _bfd_elf_section_from_bfd_section (output_bfd,
4477 if (isym->st_shndx == (unsigned short) -1)
4480 isym->st_value += sec->output_offset;
4481 if (! finfo->info->relocateable)
4482 isym->st_value += osec->vma;
4484 finfo->indices[r_symndx] = output_bfd->symcount;
4486 if (! elf_link_output_sym (finfo, name, isym, sec))
4490 r_symndx = finfo->indices[r_symndx];
4493 irela->r_info = ELF_R_INFO (r_symndx,
4494 ELF_R_TYPE (irela->r_info));
4497 /* Swap out the relocs. */
4498 input_rel_hdr = &elf_section_data (o)->rel_hdr;
4499 output_rel_hdr = &elf_section_data (o->output_section)->rel_hdr;
4500 BFD_ASSERT (output_rel_hdr->sh_entsize
4501 == input_rel_hdr->sh_entsize);
4502 irela = internal_relocs;
4503 irelaend = irela + o->reloc_count;
4504 if (input_rel_hdr->sh_entsize == sizeof (Elf_External_Rel))
4506 Elf_External_Rel *erel;
4508 erel = ((Elf_External_Rel *) output_rel_hdr->contents
4509 + o->output_section->reloc_count);
4510 for (; irela < irelaend; irela++, erel++)
4512 Elf_Internal_Rel irel;
4514 irel.r_offset = irela->r_offset;
4515 irel.r_info = irela->r_info;
4516 BFD_ASSERT (irela->r_addend == 0);
4517 elf_swap_reloc_out (output_bfd, &irel, erel);
4522 Elf_External_Rela *erela;
4524 BFD_ASSERT (input_rel_hdr->sh_entsize
4525 == sizeof (Elf_External_Rela));
4526 erela = ((Elf_External_Rela *) output_rel_hdr->contents
4527 + o->output_section->reloc_count);
4528 for (; irela < irelaend; irela++, erela++)
4529 elf_swap_reloca_out (output_bfd, irela, erela);
4532 o->output_section->reloc_count += o->reloc_count;
4536 /* Write out the modified section contents. */
4537 if (elf_section_data (o)->stab_info == NULL)
4539 if (! bfd_set_section_contents (output_bfd, o->output_section,
4540 contents, o->output_offset,
4541 (o->_cooked_size != 0
4548 if (! (_bfd_write_section_stabs
4549 (output_bfd, &elf_hash_table (finfo->info)->stab_info,
4550 o, &elf_section_data (o)->stab_info, contents)))
4558 /* Generate a reloc when linking an ELF file. This is a reloc
4559 requested by the linker, and does come from any input file. This
4560 is used to build constructor and destructor tables when linking
4564 elf_reloc_link_order (output_bfd, info, output_section, link_order)
4566 struct bfd_link_info *info;
4567 asection *output_section;
4568 struct bfd_link_order *link_order;
4570 reloc_howto_type *howto;
4574 struct elf_link_hash_entry **rel_hash_ptr;
4575 Elf_Internal_Shdr *rel_hdr;
4577 howto = bfd_reloc_type_lookup (output_bfd, link_order->u.reloc.p->reloc);
4580 bfd_set_error (bfd_error_bad_value);
4584 addend = link_order->u.reloc.p->addend;
4586 /* Figure out the symbol index. */
4587 rel_hash_ptr = (elf_section_data (output_section)->rel_hashes
4588 + output_section->reloc_count);
4589 if (link_order->type == bfd_section_reloc_link_order)
4591 indx = link_order->u.reloc.p->u.section->target_index;
4592 BFD_ASSERT (indx != 0);
4593 *rel_hash_ptr = NULL;
4597 struct elf_link_hash_entry *h;
4599 /* Treat a reloc against a defined symbol as though it were
4600 actually against the section. */
4601 h = ((struct elf_link_hash_entry *)
4602 bfd_wrapped_link_hash_lookup (output_bfd, info,
4603 link_order->u.reloc.p->u.name,
4604 false, false, true));
4606 && (h->root.type == bfd_link_hash_defined
4607 || h->root.type == bfd_link_hash_defweak))
4611 section = h->root.u.def.section;
4612 indx = section->output_section->target_index;
4613 *rel_hash_ptr = NULL;
4614 /* It seems that we ought to add the symbol value to the
4615 addend here, but in practice it has already been added
4616 because it was passed to constructor_callback. */
4617 addend += section->output_section->vma + section->output_offset;
4621 /* Setting the index to -2 tells elf_link_output_extsym that
4622 this symbol is used by a reloc. */
4629 if (! ((*info->callbacks->unattached_reloc)
4630 (info, link_order->u.reloc.p->u.name, (bfd *) NULL,
4631 (asection *) NULL, (bfd_vma) 0)))
4637 /* If this is an inplace reloc, we must write the addend into the
4639 if (howto->partial_inplace && addend != 0)
4642 bfd_reloc_status_type rstat;
4646 size = bfd_get_reloc_size (howto);
4647 buf = (bfd_byte *) bfd_zmalloc (size);
4648 if (buf == (bfd_byte *) NULL)
4650 rstat = _bfd_relocate_contents (howto, output_bfd, addend, buf);
4656 case bfd_reloc_outofrange:
4658 case bfd_reloc_overflow:
4659 if (! ((*info->callbacks->reloc_overflow)
4661 (link_order->type == bfd_section_reloc_link_order
4662 ? bfd_section_name (output_bfd,
4663 link_order->u.reloc.p->u.section)
4664 : link_order->u.reloc.p->u.name),
4665 howto->name, addend, (bfd *) NULL, (asection *) NULL,
4673 ok = bfd_set_section_contents (output_bfd, output_section, (PTR) buf,
4674 (file_ptr) link_order->offset, size);
4680 /* The address of a reloc is relative to the section in a
4681 relocateable file, and is a virtual address in an executable
4683 offset = link_order->offset;
4684 if (! info->relocateable)
4685 offset += output_section->vma;
4687 rel_hdr = &elf_section_data (output_section)->rel_hdr;
4689 if (rel_hdr->sh_type == SHT_REL)
4691 Elf_Internal_Rel irel;
4692 Elf_External_Rel *erel;
4694 irel.r_offset = offset;
4695 irel.r_info = ELF_R_INFO (indx, howto->type);
4696 erel = ((Elf_External_Rel *) rel_hdr->contents
4697 + output_section->reloc_count);
4698 elf_swap_reloc_out (output_bfd, &irel, erel);
4702 Elf_Internal_Rela irela;
4703 Elf_External_Rela *erela;
4705 irela.r_offset = offset;
4706 irela.r_info = ELF_R_INFO (indx, howto->type);
4707 irela.r_addend = addend;
4708 erela = ((Elf_External_Rela *) rel_hdr->contents
4709 + output_section->reloc_count);
4710 elf_swap_reloca_out (output_bfd, &irela, erela);
4713 ++output_section->reloc_count;
4719 /* Allocate a pointer to live in a linker created section. */
4722 elf_create_pointer_linker_section (abfd, info, lsect, h, rel)
4724 struct bfd_link_info *info;
4725 elf_linker_section_t *lsect;
4726 struct elf_link_hash_entry *h;
4727 const Elf_Internal_Rela *rel;
4729 elf_linker_section_pointers_t **ptr_linker_section_ptr = NULL;
4730 elf_linker_section_pointers_t *linker_section_ptr;
4731 unsigned long r_symndx = ELF_R_SYM (rel->r_info);;
4733 BFD_ASSERT (lsect != NULL);
4735 /* Is this a global symbol? */
4738 /* Has this symbol already been allocated, if so, our work is done */
4739 if (_bfd_elf_find_pointer_linker_section (h->linker_section_pointer,
4744 ptr_linker_section_ptr = &h->linker_section_pointer;
4745 /* Make sure this symbol is output as a dynamic symbol. */
4746 if (h->dynindx == -1)
4748 if (! elf_link_record_dynamic_symbol (info, h))
4752 if (lsect->rel_section)
4753 lsect->rel_section->_raw_size += sizeof (Elf_External_Rela);
4756 else /* Allocation of a pointer to a local symbol */
4758 elf_linker_section_pointers_t **ptr = elf_local_ptr_offsets (abfd);
4760 /* Allocate a table to hold the local symbols if first time */
4763 int num_symbols = elf_tdata (abfd)->symtab_hdr.sh_info;
4764 register unsigned int i;
4766 ptr = (elf_linker_section_pointers_t **)
4767 bfd_alloc (abfd, num_symbols * sizeof (elf_linker_section_pointers_t *));
4772 elf_local_ptr_offsets (abfd) = ptr;
4773 for (i = 0; i < num_symbols; i++)
4774 ptr[i] = (elf_linker_section_pointers_t *)0;
4777 /* Has this symbol already been allocated, if so, our work is done */
4778 if (_bfd_elf_find_pointer_linker_section (ptr[r_symndx],
4783 ptr_linker_section_ptr = &ptr[r_symndx];
4787 /* If we are generating a shared object, we need to
4788 output a R_<xxx>_RELATIVE reloc so that the
4789 dynamic linker can adjust this GOT entry. */
4790 BFD_ASSERT (lsect->rel_section != NULL);
4791 lsect->rel_section->_raw_size += sizeof (Elf_External_Rela);
4795 /* Allocate space for a pointer in the linker section, and allocate a new pointer record
4796 from internal memory. */
4797 BFD_ASSERT (ptr_linker_section_ptr != NULL);
4798 linker_section_ptr = (elf_linker_section_pointers_t *)
4799 bfd_alloc (abfd, sizeof (elf_linker_section_pointers_t));
4801 if (!linker_section_ptr)
4804 linker_section_ptr->next = *ptr_linker_section_ptr;
4805 linker_section_ptr->addend = rel->r_addend;
4806 linker_section_ptr->which = lsect->which;
4807 linker_section_ptr->written_address_p = false;
4808 *ptr_linker_section_ptr = linker_section_ptr;
4811 if (lsect->hole_size && lsect->hole_offset < lsect->max_hole_offset)
4813 linker_section_ptr->offset = lsect->section->_raw_size - lsect->hole_size + (ARCH_SIZE / 8);
4814 lsect->hole_offset += ARCH_SIZE / 8;
4815 lsect->sym_offset += ARCH_SIZE / 8;
4816 if (lsect->sym_hash) /* Bump up symbol value if needed */
4818 lsect->sym_hash->root.u.def.value += ARCH_SIZE / 8;
4820 fprintf (stderr, "Bump up %s by %ld, current value = %ld\n",
4821 lsect->sym_hash->root.root.string,
4822 (long)ARCH_SIZE / 8,
4823 (long)lsect->sym_hash->root.u.def.value);
4829 linker_section_ptr->offset = lsect->section->_raw_size;
4831 lsect->section->_raw_size += ARCH_SIZE / 8;
4834 fprintf (stderr, "Create pointer in linker section %s, offset = %ld, section size = %ld\n",
4835 lsect->name, (long)linker_section_ptr->offset, (long)lsect->section->_raw_size);
4843 #define bfd_put_ptr(BFD,VAL,ADDR) bfd_put_64 (BFD, VAL, ADDR)
4846 #define bfd_put_ptr(BFD,VAL,ADDR) bfd_put_32 (BFD, VAL, ADDR)
4849 /* Fill in the address for a pointer generated in alinker section. */
4852 elf_finish_pointer_linker_section (output_bfd, input_bfd, info, lsect, h, relocation, rel, relative_reloc)
4855 struct bfd_link_info *info;
4856 elf_linker_section_t *lsect;
4857 struct elf_link_hash_entry *h;
4859 const Elf_Internal_Rela *rel;
4862 elf_linker_section_pointers_t *linker_section_ptr;
4864 BFD_ASSERT (lsect != NULL);
4866 if (h != NULL) /* global symbol */
4868 linker_section_ptr = _bfd_elf_find_pointer_linker_section (h->linker_section_pointer,
4872 BFD_ASSERT (linker_section_ptr != NULL);
4874 if (! elf_hash_table (info)->dynamic_sections_created
4877 && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR)))
4879 /* This is actually a static link, or it is a
4880 -Bsymbolic link and the symbol is defined
4881 locally. We must initialize this entry in the
4884 When doing a dynamic link, we create a .rela.<xxx>
4885 relocation entry to initialize the value. This
4886 is done in the finish_dynamic_symbol routine. */
4887 if (!linker_section_ptr->written_address_p)
4889 linker_section_ptr->written_address_p = true;
4890 bfd_put_ptr (output_bfd, relocation + linker_section_ptr->addend,
4891 lsect->section->contents + linker_section_ptr->offset);
4895 else /* local symbol */
4897 unsigned long r_symndx = ELF_R_SYM (rel->r_info);
4898 BFD_ASSERT (elf_local_ptr_offsets (input_bfd) != NULL);
4899 BFD_ASSERT (elf_local_ptr_offsets (input_bfd)[r_symndx] != NULL);
4900 linker_section_ptr = _bfd_elf_find_pointer_linker_section (elf_local_ptr_offsets (input_bfd)[r_symndx],
4904 BFD_ASSERT (linker_section_ptr != NULL);
4906 /* Write out pointer if it hasn't been rewritten out before */
4907 if (!linker_section_ptr->written_address_p)
4909 linker_section_ptr->written_address_p = true;
4910 bfd_put_ptr (output_bfd, relocation + linker_section_ptr->addend,
4911 lsect->section->contents + linker_section_ptr->offset);
4915 asection *srel = lsect->rel_section;
4916 Elf_Internal_Rela outrel;
4918 /* We need to generate a relative reloc for the dynamic linker. */
4920 lsect->rel_section = srel = bfd_get_section_by_name (elf_hash_table (info)->dynobj,
4923 BFD_ASSERT (srel != NULL);
4925 outrel.r_offset = (lsect->section->output_section->vma
4926 + lsect->section->output_offset
4927 + linker_section_ptr->offset);
4928 outrel.r_info = ELF_R_INFO (0, relative_reloc);
4929 outrel.r_addend = 0;
4930 elf_swap_reloca_out (output_bfd, &outrel,
4931 (((Elf_External_Rela *)
4932 lsect->section->contents)
4933 + lsect->section->reloc_count));
4934 ++lsect->section->reloc_count;
4939 relocation = (lsect->section->output_offset
4940 + linker_section_ptr->offset
4941 - lsect->hole_offset
4942 - lsect->sym_offset);
4945 fprintf (stderr, "Finish pointer in linker section %s, offset = %ld (0x%lx)\n",
4946 lsect->name, (long)relocation, (long)relocation);
4949 /* Subtract out the addend, because it will get added back in by the normal
4951 return relocation - linker_section_ptr->addend;