* aoutx.h (NAME(aout,slurp_reloc_table)): Cast argument to size_t
[external/binutils.git] / bfd / elflink.h
1 /* ELF linker support.
2    Copyright 1995 Free Software Foundation, Inc.
3
4 This file is part of BFD, the Binary File Descriptor library.
5
6 This program is free software; you can redistribute it and/or modify
7 it under the terms of the GNU General Public License as published by
8 the Free Software Foundation; either version 2 of the License, or
9 (at your option) any later version.
10
11 This program is distributed in the hope that it will be useful,
12 but WITHOUT ANY WARRANTY; without even the implied warranty of
13 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14 GNU General Public License for more details.
15
16 You should have received a copy of the GNU General Public License
17 along with this program; if not, write to the Free Software
18 Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.  */
19 /* ELF linker code.  */
20
21 static boolean elf_link_add_object_symbols
22   PARAMS ((bfd *, struct bfd_link_info *));
23 static boolean elf_link_add_archive_symbols
24   PARAMS ((bfd *, struct bfd_link_info *));
25 static Elf_Internal_Rela *elf_link_read_relocs
26   PARAMS ((bfd *, asection *, PTR, Elf_Internal_Rela *, boolean));
27 static boolean elf_export_symbol
28   PARAMS ((struct elf_link_hash_entry *, PTR));
29 static boolean elf_adjust_dynamic_symbol
30   PARAMS ((struct elf_link_hash_entry *, PTR));
31
32 /* This struct is used to pass information to routines called via
33    elf_link_hash_traverse which must return failure.  */
34
35 struct elf_info_failed
36 {
37   boolean failed;
38   struct bfd_link_info *info;
39 };  
40
41 /* Given an ELF BFD, add symbols to the global hash table as
42    appropriate.  */
43
44 boolean
45 elf_bfd_link_add_symbols (abfd, info)
46      bfd *abfd;
47      struct bfd_link_info *info;
48 {
49   switch (bfd_get_format (abfd))
50     {
51     case bfd_object:
52       return elf_link_add_object_symbols (abfd, info);
53     case bfd_archive:
54       return elf_link_add_archive_symbols (abfd, info);
55     default:
56       bfd_set_error (bfd_error_wrong_format);
57       return false;
58     }
59 }
60
61 /* Add symbols from an ELF archive file to the linker hash table.  We
62    don't use _bfd_generic_link_add_archive_symbols because of a
63    problem which arises on UnixWare.  The UnixWare libc.so is an
64    archive which includes an entry libc.so.1 which defines a bunch of
65    symbols.  The libc.so archive also includes a number of other
66    object files, which also define symbols, some of which are the same
67    as those defined in libc.so.1.  Correct linking requires that we
68    consider each object file in turn, and include it if it defines any
69    symbols we need.  _bfd_generic_link_add_archive_symbols does not do
70    this; it looks through the list of undefined symbols, and includes
71    any object file which defines them.  When this algorithm is used on
72    UnixWare, it winds up pulling in libc.so.1 early and defining a
73    bunch of symbols.  This means that some of the other objects in the
74    archive are not included in the link, which is incorrect since they
75    precede libc.so.1 in the archive.
76
77    Fortunately, ELF archive handling is simpler than that done by
78    _bfd_generic_link_add_archive_symbols, which has to allow for a.out
79    oddities.  In ELF, if we find a symbol in the archive map, and the
80    symbol is currently undefined, we know that we must pull in that
81    object file.
82
83    Unfortunately, we do have to make multiple passes over the symbol
84    table until nothing further is resolved.  */
85
86 static boolean
87 elf_link_add_archive_symbols (abfd, info)
88      bfd *abfd;
89      struct bfd_link_info *info;
90 {
91   symindex c;
92   boolean *defined = NULL;
93   boolean *included = NULL;
94   carsym *symdefs;
95   boolean loop;
96
97   if (! bfd_has_map (abfd))
98     {
99       /* An empty archive is a special case.  */
100       if (bfd_openr_next_archived_file (abfd, (bfd *) NULL) == NULL)
101         return true;
102       bfd_set_error (bfd_error_no_armap);
103       return false;
104     }
105
106   /* Keep track of all symbols we know to be already defined, and all
107      files we know to be already included.  This is to speed up the
108      second and subsequent passes.  */
109   c = bfd_ardata (abfd)->symdef_count;
110   if (c == 0)
111     return true;
112   defined = (boolean *) malloc (c * sizeof (boolean));
113   included = (boolean *) malloc (c * sizeof (boolean));
114   if (defined == (boolean *) NULL || included == (boolean *) NULL)
115     {
116       bfd_set_error (bfd_error_no_memory);
117       goto error_return;
118     }
119   memset (defined, 0, c * sizeof (boolean));
120   memset (included, 0, c * sizeof (boolean));
121
122   symdefs = bfd_ardata (abfd)->symdefs;
123
124   do
125     {
126       file_ptr last;
127       symindex i;
128       carsym *symdef;
129       carsym *symdefend;
130
131       loop = false;
132       last = -1;
133
134       symdef = symdefs;
135       symdefend = symdef + c;
136       for (i = 0; symdef < symdefend; symdef++, i++)
137         {
138           struct elf_link_hash_entry *h;
139           bfd *element;
140           struct bfd_link_hash_entry *undefs_tail;
141           symindex mark;
142
143           if (defined[i] || included[i])
144             continue;
145           if (symdef->file_offset == last)
146             {
147               included[i] = true;
148               continue;
149             }
150
151           h = elf_link_hash_lookup (elf_hash_table (info), symdef->name,
152                                     false, false, false);
153           if (h == (struct elf_link_hash_entry *) NULL)
154             continue;
155           if (h->root.type != bfd_link_hash_undefined)
156             {
157               defined[i] = true;
158               continue;
159             }
160
161           /* We need to include this archive member.  */
162
163           element = _bfd_get_elt_at_filepos (abfd, symdef->file_offset);
164           if (element == (bfd *) NULL)
165             goto error_return;
166
167           if (! bfd_check_format (element, bfd_object))
168             goto error_return;
169
170           /* Doublecheck that we have not included this object
171              already--it should be impossible, but there may be
172              something wrong with the archive.  */
173           if (element->archive_pass != 0)
174             {
175               bfd_set_error (bfd_error_bad_value);
176               goto error_return;
177             }
178           element->archive_pass = 1;
179
180           undefs_tail = info->hash->undefs_tail;
181
182           if (! (*info->callbacks->add_archive_element) (info, element,
183                                                          symdef->name))
184             goto error_return;
185           if (! elf_link_add_object_symbols (element, info))
186             goto error_return;
187
188           /* If there are any new undefined symbols, we need to make
189              another pass through the archive in order to see whether
190              they can be defined.  FIXME: This isn't perfect, because
191              common symbols wind up on undefs_tail and because an
192              undefined symbol which is defined later on in this pass
193              does not require another pass.  This isn't a bug, but it
194              does make the code less efficient than it could be.  */
195           if (undefs_tail != info->hash->undefs_tail)
196             loop = true;
197
198           /* Look backward to mark all symbols from this object file
199              which we have already seen in this pass.  */
200           mark = i;
201           do
202             {
203               included[mark] = true;
204               if (mark == 0)
205                 break;
206               --mark;
207             }
208           while (symdefs[mark].file_offset == symdef->file_offset);
209
210           /* We mark subsequent symbols from this object file as we go
211              on through the loop.  */
212           last = symdef->file_offset;
213         }
214     }
215   while (loop);
216
217   free (defined);
218   free (included);
219
220   return true;
221
222  error_return:
223   if (defined != (boolean *) NULL)
224     free (defined);
225   if (included != (boolean *) NULL)
226     free (included);
227   return false;
228 }
229
230 /* Add symbols from an ELF object file to the linker hash table.  */
231
232 static boolean
233 elf_link_add_object_symbols (abfd, info)
234      bfd *abfd;
235      struct bfd_link_info *info;
236 {
237   boolean (*add_symbol_hook) PARAMS ((bfd *, struct bfd_link_info *,
238                                       const Elf_Internal_Sym *,
239                                       const char **, flagword *,
240                                       asection **, bfd_vma *));
241   boolean (*check_relocs) PARAMS ((bfd *, struct bfd_link_info *,
242                                    asection *, const Elf_Internal_Rela *));
243   boolean collect;
244   Elf_Internal_Shdr *hdr;
245   size_t symcount;
246   size_t extsymcount;
247   size_t extsymoff;
248   Elf_External_Sym *buf = NULL;
249   struct elf_link_hash_entry **sym_hash;
250   boolean dynamic;
251   Elf_External_Dyn *dynbuf = NULL;
252   struct elf_link_hash_entry *weaks;
253   Elf_External_Sym *esym;
254   Elf_External_Sym *esymend;
255
256   add_symbol_hook = get_elf_backend_data (abfd)->elf_add_symbol_hook;
257   collect = get_elf_backend_data (abfd)->collect;
258
259   /* A stripped shared library might only have a dynamic symbol table,
260      not a regular symbol table.  In that case we can still go ahead
261      and link using the dynamic symbol table.  */
262   if (elf_onesymtab (abfd) == 0
263       && elf_dynsymtab (abfd) != 0)
264     {
265       elf_onesymtab (abfd) = elf_dynsymtab (abfd);
266       elf_tdata (abfd)->symtab_hdr = elf_tdata (abfd)->dynsymtab_hdr;
267     }
268
269   hdr = &elf_tdata (abfd)->symtab_hdr;
270   symcount = hdr->sh_size / sizeof (Elf_External_Sym);
271
272   /* The sh_info field of the symtab header tells us where the
273      external symbols start.  We don't care about the local symbols at
274      this point.  */
275   if (elf_bad_symtab (abfd))
276     {
277       extsymcount = symcount;
278       extsymoff = 0;
279     }
280   else
281     {
282       extsymcount = symcount - hdr->sh_info;
283       extsymoff = hdr->sh_info;
284     }
285
286   buf = (Elf_External_Sym *) malloc (extsymcount * sizeof (Elf_External_Sym));
287   if (buf == NULL && extsymcount != 0)
288     {
289       bfd_set_error (bfd_error_no_memory);
290       goto error_return;
291     }
292
293   /* We store a pointer to the hash table entry for each external
294      symbol.  */
295   sym_hash = ((struct elf_link_hash_entry **)
296               bfd_alloc (abfd,
297                          extsymcount * sizeof (struct elf_link_hash_entry *)));
298   if (sym_hash == NULL)
299     {
300       bfd_set_error (bfd_error_no_memory);
301       goto error_return;
302     }
303   elf_sym_hashes (abfd) = sym_hash;
304
305   if (elf_elfheader (abfd)->e_type != ET_DYN)
306     {
307       dynamic = false;
308
309       /* If we are creating a shared library, create all the dynamic
310          sections immediately.  We need to attach them to something,
311          so we attach them to this BFD, provided it is the right
312          format.  FIXME: If there are no input BFD's of the same
313          format as the output, we can't make a shared library.  */
314       if (info->shared
315           && ! elf_hash_table (info)->dynamic_sections_created
316           && abfd->xvec == info->hash->creator)
317         {
318           if (! elf_link_create_dynamic_sections (abfd, info))
319             goto error_return;
320         }
321     }
322   else
323     {
324       asection *s;
325       boolean add_needed;
326       const char *name;
327       bfd_size_type oldsize;
328       bfd_size_type strindex;
329
330       dynamic = true;
331
332       /* You can't use -r against a dynamic object.  Also, there's no
333          hope of using a dynamic object which does not exactly match
334          the format of the output file.  */
335       if (info->relocateable
336           || info->hash->creator != abfd->xvec)
337         {
338           bfd_set_error (bfd_error_invalid_operation);
339           goto error_return;
340         }
341
342       /* Find the name to use in a DT_NEEDED entry that refers to this
343          object.  If the object has a DT_SONAME entry, we use it.
344          Otherwise, if the generic linker stuck something in
345          elf_dt_needed_name, we use that.  Otherwise, we just use the
346          file name.  If the generic linker put a null string into
347          elf_dt_needed_name, we don't make a DT_NEEDED entry at all,
348          even if there is a DT_SONAME entry.  */
349       add_needed = true;
350       name = bfd_get_filename (abfd);
351       if (elf_dt_needed_name (abfd) != NULL)
352         {
353           name = elf_dt_needed_name (abfd);
354           if (*name == '\0')
355             add_needed = false;
356         }
357       s = bfd_get_section_by_name (abfd, ".dynamic");
358       if (s != NULL)
359         {
360           Elf_External_Dyn *extdyn;
361           Elf_External_Dyn *extdynend;
362           int elfsec;
363           unsigned long link;
364
365           dynbuf = (Elf_External_Dyn *) malloc ((size_t) s->_raw_size);
366           if (dynbuf == NULL)
367             {
368               bfd_set_error (bfd_error_no_memory);
369               goto error_return;
370             }
371
372           if (! bfd_get_section_contents (abfd, s, (PTR) dynbuf,
373                                           (file_ptr) 0, s->_raw_size))
374             goto error_return;
375
376           elfsec = _bfd_elf_section_from_bfd_section (abfd, s);
377           if (elfsec == -1)
378             goto error_return;
379           link = elf_elfsections (abfd)[elfsec]->sh_link;
380
381           extdyn = dynbuf;
382           extdynend = extdyn + s->_raw_size / sizeof (Elf_External_Dyn);
383           for (; extdyn < extdynend; extdyn++)
384             {
385               Elf_Internal_Dyn dyn;
386
387               elf_swap_dyn_in (abfd, extdyn, &dyn);
388               if (add_needed && dyn.d_tag == DT_SONAME)
389                 {
390                   name = bfd_elf_string_from_elf_section (abfd, link,
391                                                           dyn.d_un.d_val);
392                   if (name == NULL)
393                     goto error_return;
394                 }
395               if (dyn.d_tag == DT_NEEDED)
396                 {
397                   struct bfd_elf_link_needed_list *n, **pn;
398                   char *fnm, *anm;
399
400                   n = (struct bfd_elf_link_needed_list *)
401                     bfd_alloc (abfd,
402                                sizeof (struct bfd_elf_link_needed_list));
403                   fnm = bfd_elf_string_from_elf_section (abfd, link,
404                                                          dyn.d_un.d_val);
405                   if (n == NULL || fnm == NULL)
406                     goto error_return;
407                   anm = bfd_alloc (abfd, strlen (fnm) + 1);
408                   if (anm == NULL)
409                     goto error_return;
410                   strcpy (anm, fnm);
411                   n->name = anm;
412                   n->by = abfd;
413                   n->next = NULL;
414                   for (pn = &elf_hash_table (info)->needed;
415                        *pn != NULL;
416                        pn = &(*pn)->next)
417                     ;
418                   *pn = n;
419                 }
420             }
421
422           free (dynbuf);
423           dynbuf = NULL;
424         }
425
426       /* We do not want to include any of the sections in a dynamic
427          object in the output file.  We hack by simply clobbering the
428          list of sections in the BFD.  This could be handled more
429          cleanly by, say, a new section flag; the existing
430          SEC_NEVER_LOAD flag is not the one we want, because that one
431          still implies that the section takes up space in the output
432          file.  */
433       abfd->sections = NULL;
434
435       /* If this is the first dynamic object found in the link, create
436          the special sections required for dynamic linking.  */
437       if (! elf_hash_table (info)->dynamic_sections_created)
438         {
439           if (! elf_link_create_dynamic_sections (abfd, info))
440             goto error_return;
441         }
442
443       if (add_needed)
444         {
445           /* Add a DT_NEEDED entry for this dynamic object.  */
446           oldsize = _bfd_stringtab_size (elf_hash_table (info)->dynstr);
447           strindex = _bfd_stringtab_add (elf_hash_table (info)->dynstr, name,
448                                          true, false);
449           if (strindex == (bfd_size_type) -1)
450             goto error_return;
451
452           if (oldsize == _bfd_stringtab_size (elf_hash_table (info)->dynstr))
453             {
454               asection *sdyn;
455               Elf_External_Dyn *dyncon, *dynconend;
456
457               /* The hash table size did not change, which means that
458                  the dynamic object name was already entered.  If we
459                  have already included this dynamic object in the
460                  link, just ignore it.  There is no reason to include
461                  a particular dynamic object more than once.  */
462               sdyn = bfd_get_section_by_name (elf_hash_table (info)->dynobj,
463                                               ".dynamic");
464               BFD_ASSERT (sdyn != NULL);
465
466               dyncon = (Elf_External_Dyn *) sdyn->contents;
467               dynconend = (Elf_External_Dyn *) (sdyn->contents +
468                                                 sdyn->_raw_size);
469               for (; dyncon < dynconend; dyncon++)
470                 {
471                   Elf_Internal_Dyn dyn;
472
473                   elf_swap_dyn_in (elf_hash_table (info)->dynobj, dyncon,
474                                    &dyn);
475                   if (dyn.d_tag == DT_NEEDED
476                       && dyn.d_un.d_val == strindex)
477                     {
478                       if (buf != NULL)
479                         free (buf);
480                       return true;
481                     }
482                 }
483             }
484
485           if (! elf_add_dynamic_entry (info, DT_NEEDED, strindex))
486             goto error_return;
487         }
488     }
489
490   if (bfd_seek (abfd,
491                 hdr->sh_offset + extsymoff * sizeof (Elf_External_Sym),
492                 SEEK_SET) != 0
493       || (bfd_read ((PTR) buf, sizeof (Elf_External_Sym), extsymcount, abfd)
494           != extsymcount * sizeof (Elf_External_Sym)))
495     goto error_return;
496
497   weaks = NULL;
498
499   esymend = buf + extsymcount;
500   for (esym = buf; esym < esymend; esym++, sym_hash++)
501     {
502       Elf_Internal_Sym sym;
503       int bind;
504       bfd_vma value;
505       asection *sec;
506       flagword flags;
507       const char *name;
508       struct elf_link_hash_entry *h = NULL;
509       boolean definition;
510
511       elf_swap_symbol_in (abfd, esym, &sym);
512
513       flags = BSF_NO_FLAGS;
514       sec = NULL;
515       value = sym.st_value;
516       *sym_hash = NULL;
517
518       bind = ELF_ST_BIND (sym.st_info);
519       if (bind == STB_LOCAL)
520         {
521           /* This should be impossible, since ELF requires that all
522              global symbols follow all local symbols, and that sh_info
523              point to the first global symbol.  Unfortunatealy, Irix 5
524              screws this up.  */
525           continue;
526         }
527       else if (bind == STB_GLOBAL)
528         {
529           if (sym.st_shndx != SHN_UNDEF
530               && sym.st_shndx != SHN_COMMON)
531             flags = BSF_GLOBAL;
532           else
533             flags = 0;
534         }
535       else if (bind == STB_WEAK)
536         flags = BSF_WEAK;
537       else
538         {
539           /* Leave it up to the processor backend.  */
540         }
541
542       if (sym.st_shndx == SHN_UNDEF)
543         sec = bfd_und_section_ptr;
544       else if (sym.st_shndx > 0 && sym.st_shndx < SHN_LORESERVE)
545         {
546           sec = section_from_elf_index (abfd, sym.st_shndx);
547           if (sec != NULL)
548             value -= sec->vma;
549           else
550             sec = bfd_abs_section_ptr;
551         }
552       else if (sym.st_shndx == SHN_ABS)
553         sec = bfd_abs_section_ptr;
554       else if (sym.st_shndx == SHN_COMMON)
555         {
556           sec = bfd_com_section_ptr;
557           /* What ELF calls the size we call the value.  What ELF
558              calls the value we call the alignment.  */
559           value = sym.st_size;
560         }
561       else
562         {
563           /* Leave it up to the processor backend.  */
564         }
565
566       name = bfd_elf_string_from_elf_section (abfd, hdr->sh_link, sym.st_name);
567       if (name == (const char *) NULL)
568         goto error_return;
569
570       if (add_symbol_hook)
571         {
572           if (! (*add_symbol_hook) (abfd, info, &sym, &name, &flags, &sec,
573                                     &value))
574             goto error_return;
575
576           /* The hook function sets the name to NULL if this symbol
577              should be skipped for some reason.  */
578           if (name == (const char *) NULL)
579             continue;
580         }
581
582       /* Sanity check that all possibilities were handled.  */
583       if (sec == (asection *) NULL)
584         {
585           bfd_set_error (bfd_error_bad_value);
586           goto error_return;
587         }
588
589       if (bfd_is_und_section (sec)
590           || bfd_is_com_section (sec))
591         definition = false;
592       else
593         definition = true;
594
595       if (info->hash->creator->flavour == bfd_target_elf_flavour)
596         {
597           /* We need to look up the symbol now in order to get some of
598              the dynamic object handling right.  We pass the hash
599              table entry in to _bfd_generic_link_add_one_symbol so
600              that it does not have to look it up again.  */
601           h = elf_link_hash_lookup (elf_hash_table (info), name,
602                                     true, false, false);
603           if (h == NULL)
604             goto error_return;
605           *sym_hash = h;
606
607           /* If we are looking at a dynamic object, and this is a
608              definition, we need to see if it has already been defined
609              by some other object.  If it has, we want to use the
610              existing definition, and we do not want to report a
611              multiple symbol definition error; we do this by
612              clobbering sec to be bfd_und_section_ptr.  */
613           if (dynamic && definition)
614             {
615               if (h->root.type == bfd_link_hash_defined
616                   || h->root.type == bfd_link_hash_defweak)
617                 sec = bfd_und_section_ptr;
618             }
619
620           /* Similarly, if we are not looking at a dynamic object, and
621              we have a definition, we want to override any definition
622              we may have from a dynamic object.  Symbols from regular
623              files always take precedence over symbols from dynamic
624              objects, even if they are defined after the dynamic
625              object in the link.  */
626           if (! dynamic
627               && definition
628               && (h->root.type == bfd_link_hash_defined
629                   || h->root.type == bfd_link_hash_defweak)
630               && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC) != 0
631               && (bfd_get_flavour (h->root.u.def.section->owner)
632                   == bfd_target_elf_flavour)
633               && (elf_elfheader (h->root.u.def.section->owner)->e_type
634                   == ET_DYN))
635             {
636               /* Change the hash table entry to undefined, and let
637                  _bfd_generic_link_add_one_symbol do the right thing
638                  with the new definition.  */
639               h->root.type = bfd_link_hash_undefined;
640               h->root.u.undef.abfd = h->root.u.def.section->owner;
641             }
642         }
643
644       if (! (_bfd_generic_link_add_one_symbol
645              (info, abfd, name, flags, sec, value, (const char *) NULL,
646               false, collect, (struct bfd_link_hash_entry **) sym_hash)))
647         goto error_return;
648
649       if (dynamic
650           && definition
651           && (flags & BSF_WEAK) != 0
652           && ELF_ST_TYPE (sym.st_info) != STT_FUNC
653           && info->hash->creator->flavour == bfd_target_elf_flavour
654           && (*sym_hash)->weakdef == NULL)
655         {
656           /* Keep a list of all weak defined non function symbols from
657              a dynamic object, using the weakdef field.  Later in this
658              function we will set the weakdef field to the correct
659              value.  We only put non-function symbols from dynamic
660              objects on this list, because that happens to be the only
661              time we need to know the normal symbol corresponding to a
662              weak symbol, and the information is time consuming to
663              figure out.  If the weakdef field is not already NULL,
664              then this symbol was already defined by some previous
665              dynamic object, and we will be using that previous
666              definition anyhow.  */
667
668           (*sym_hash)->weakdef = weaks;
669           weaks = *sym_hash;
670         }
671
672       /* Get the alignment of a common symbol.  */
673       if (sym.st_shndx == SHN_COMMON
674           && (*sym_hash)->root.type == bfd_link_hash_common)
675         (*sym_hash)->root.u.c.p->alignment_power = bfd_log2 (sym.st_value);
676
677       if (info->hash->creator->flavour == bfd_target_elf_flavour)
678         {
679           int old_flags;
680           boolean dynsym;
681           int new_flag;
682
683           /* Remember the symbol size and type.  */
684           if (sym.st_size != 0)
685             {
686               /* FIXME: We should probably somehow give a warning if
687                  the symbol size changes.  */
688               h->size = sym.st_size;
689             }
690           if (ELF_ST_TYPE (sym.st_info) != STT_NOTYPE)
691             {
692               /* FIXME: We should probably somehow give a warning if
693                  the symbol type changes.  */
694               h->type = ELF_ST_TYPE (sym.st_info);
695             }
696
697           /* Set a flag in the hash table entry indicating the type of
698              reference or definition we just found.  Keep a count of
699              the number of dynamic symbols we find.  A dynamic symbol
700              is one which is referenced or defined by both a regular
701              object and a shared object, or one which is referenced or
702              defined by more than one shared object.  */
703           old_flags = h->elf_link_hash_flags;
704           dynsym = false;
705           if (! dynamic)
706             {
707               if (! definition)
708                 new_flag = ELF_LINK_HASH_REF_REGULAR;
709               else
710                 new_flag = ELF_LINK_HASH_DEF_REGULAR;
711               if (info->shared
712                   || (old_flags & (ELF_LINK_HASH_DEF_DYNAMIC
713                                    | ELF_LINK_HASH_REF_DYNAMIC)) != 0)
714                 dynsym = true;
715             }
716           else
717             {
718               if (! definition)
719                 new_flag = ELF_LINK_HASH_REF_DYNAMIC;
720               else
721                 new_flag = ELF_LINK_HASH_DEF_DYNAMIC;
722               if ((old_flags & new_flag) != 0
723                   || (old_flags & (ELF_LINK_HASH_DEF_REGULAR
724                                    | ELF_LINK_HASH_REF_REGULAR)) != 0)
725                 dynsym = true;
726             }
727
728           h->elf_link_hash_flags |= new_flag;
729           if (dynsym && h->dynindx == -1)
730             {
731               if (! _bfd_elf_link_record_dynamic_symbol (info, h))
732                 goto error_return;
733             }
734         }
735     }
736
737   /* Now set the weakdefs field correctly for all the weak defined
738      symbols we found.  The only way to do this is to search all the
739      symbols.  Since we only need the information for non functions in
740      dynamic objects, that's the only time we actually put anything on
741      the list WEAKS.  We need this information so that if a regular
742      object refers to a symbol defined weakly in a dynamic object, the
743      real symbol in the dynamic object is also put in the dynamic
744      symbols; we also must arrange for both symbols to point to the
745      same memory location.  We could handle the general case of symbol
746      aliasing, but a general symbol alias can only be generated in
747      assembler code, handling it correctly would be very time
748      consuming, and other ELF linkers don't handle general aliasing
749      either.  */
750   while (weaks != NULL)
751     {
752       struct elf_link_hash_entry *hlook;
753       asection *slook;
754       bfd_vma vlook;
755       struct elf_link_hash_entry **hpp;
756       struct elf_link_hash_entry **hppend;
757
758       hlook = weaks;
759       weaks = hlook->weakdef;
760       hlook->weakdef = NULL;
761
762       BFD_ASSERT (hlook->root.type == bfd_link_hash_defined
763                   || hlook->root.type == bfd_link_hash_defweak
764                   || hlook->root.type == bfd_link_hash_common
765                   || hlook->root.type == bfd_link_hash_indirect);
766       slook = hlook->root.u.def.section;
767       vlook = hlook->root.u.def.value;
768
769       hpp = elf_sym_hashes (abfd);
770       hppend = hpp + extsymcount;
771       for (; hpp < hppend; hpp++)
772         {
773           struct elf_link_hash_entry *h;
774
775           h = *hpp;
776           if (h != NULL && h != hlook
777               && (h->root.type == bfd_link_hash_defined
778                   || h->root.type == bfd_link_hash_defweak)
779               && h->root.u.def.section == slook
780               && h->root.u.def.value == vlook)
781             {
782               hlook->weakdef = h;
783
784               /* If the weak definition is in the list of dynamic
785                  symbols, make sure the real definition is put there
786                  as well.  */
787               if (hlook->dynindx != -1
788                   && h->dynindx == -1)
789                 {
790                   if (! _bfd_elf_link_record_dynamic_symbol (info, h))
791                     goto error_return;
792                 }
793
794               break;
795             }
796         }
797     }
798
799   if (buf != NULL)
800     {
801       free (buf);
802       buf = NULL;
803     }
804
805   /* If this object is the same format as the output object, and it is
806      not a shared library, then let the backend look through the
807      relocs.
808
809      This is required to build global offset table entries and to
810      arrange for dynamic relocs.  It is not required for the
811      particular common case of linking non PIC code, even when linking
812      against shared libraries, but unfortunately there is no way of
813      knowing whether an object file has been compiled PIC or not.
814      Looking through the relocs is not particularly time consuming.
815      The problem is that we must either (1) keep the relocs in memory,
816      which causes the linker to require additional runtime memory or
817      (2) read the relocs twice from the input file, which wastes time.
818      This would be a good case for using mmap.
819
820      I have no idea how to handle linking PIC code into a file of a
821      different format.  It probably can't be done.  */
822   check_relocs = get_elf_backend_data (abfd)->check_relocs;
823   if (! dynamic
824       && abfd->xvec == info->hash->creator
825       && check_relocs != NULL)
826     {
827       asection *o;
828
829       for (o = abfd->sections; o != NULL; o = o->next)
830         {
831           Elf_Internal_Rela *internal_relocs;
832           boolean ok;
833
834           if ((o->flags & SEC_RELOC) == 0
835               || o->reloc_count == 0)
836             continue;
837
838           /* I believe we can ignore the relocs for any section which
839              does not form part of the final process image, such as a
840              debugging section.  */
841           if ((o->flags & SEC_ALLOC) == 0)
842             continue;
843
844           internal_relocs = elf_link_read_relocs (abfd, o, (PTR) NULL,
845                                                   (Elf_Internal_Rela *) NULL,
846                                                   info->keep_memory);
847           if (internal_relocs == NULL)
848             goto error_return;
849
850           ok = (*check_relocs) (abfd, info, o, internal_relocs);
851
852           if (! info->keep_memory)
853             free (internal_relocs);
854
855           if (! ok)
856             goto error_return;
857         }
858     }
859
860   return true;
861
862  error_return:
863   if (buf != NULL)
864     free (buf);
865   if (dynbuf != NULL)
866     free (dynbuf);
867   return false;
868 }
869
870 /* Create some sections which will be filled in with dynamic linking
871    information.  ABFD is an input file which requires dynamic sections
872    to be created.  The dynamic sections take up virtual memory space
873    when the final executable is run, so we need to create them before
874    addresses are assigned to the output sections.  We work out the
875    actual contents and size of these sections later.  */
876
877 boolean
878 elf_link_create_dynamic_sections (abfd, info)
879      bfd *abfd;
880      struct bfd_link_info *info;
881 {
882   flagword flags;
883   register asection *s;
884   struct elf_link_hash_entry *h;
885   struct elf_backend_data *bed;
886
887   if (elf_hash_table (info)->dynamic_sections_created)
888     return true;
889
890   /* Make sure that all dynamic sections use the same input BFD.  */
891   if (elf_hash_table (info)->dynobj == NULL)
892     elf_hash_table (info)->dynobj = abfd;
893   else
894     abfd = elf_hash_table (info)->dynobj;
895
896   /* Note that we set the SEC_IN_MEMORY flag for all of these
897      sections.  */
898   flags = SEC_ALLOC | SEC_LOAD | SEC_HAS_CONTENTS | SEC_IN_MEMORY;
899
900   /* A dynamically linked executable has a .interp section, but a
901      shared library does not.  */
902   if (! info->shared)
903     {
904       s = bfd_make_section (abfd, ".interp");
905       if (s == NULL
906           || ! bfd_set_section_flags (abfd, s, flags | SEC_READONLY))
907         return false;
908     }
909
910   s = bfd_make_section (abfd, ".dynsym");
911   if (s == NULL
912       || ! bfd_set_section_flags (abfd, s, flags | SEC_READONLY)
913       || ! bfd_set_section_alignment (abfd, s, LOG_FILE_ALIGN))
914     return false;
915
916   s = bfd_make_section (abfd, ".dynstr");
917   if (s == NULL
918       || ! bfd_set_section_flags (abfd, s, flags | SEC_READONLY))
919     return false;
920
921   /* Create a strtab to hold the dynamic symbol names.  */
922   if (elf_hash_table (info)->dynstr == NULL)
923     {
924       elf_hash_table (info)->dynstr = elf_stringtab_init ();
925       if (elf_hash_table (info)->dynstr == NULL)
926         return false;
927     }
928
929   s = bfd_make_section (abfd, ".dynamic");
930   if (s == NULL
931       || ! bfd_set_section_flags (abfd, s, flags)
932       || ! bfd_set_section_alignment (abfd, s, LOG_FILE_ALIGN))
933     return false;
934
935   /* The special symbol _DYNAMIC is always set to the start of the
936      .dynamic section.  This call occurs before we have processed the
937      symbols for any dynamic object, so we don't have to worry about
938      overriding a dynamic definition.  We could set _DYNAMIC in a
939      linker script, but we only want to define it if we are, in fact,
940      creating a .dynamic section.  We don't want to define it if there
941      is no .dynamic section, since on some ELF platforms the start up
942      code examines it to decide how to initialize the process.  */
943   h = NULL;
944   if (! (_bfd_generic_link_add_one_symbol
945          (info, abfd, "_DYNAMIC", BSF_GLOBAL, s, (bfd_vma) 0,
946           (const char *) NULL, false, get_elf_backend_data (abfd)->collect,
947           (struct bfd_link_hash_entry **) &h)))
948     return false;
949   h->elf_link_hash_flags |= ELF_LINK_HASH_DEF_REGULAR;
950   h->type = STT_OBJECT;
951
952   if (info->shared
953       && ! _bfd_elf_link_record_dynamic_symbol (info, h))
954     return false;
955
956   s = bfd_make_section (abfd, ".hash");
957   if (s == NULL
958       || ! bfd_set_section_flags (abfd, s, flags | SEC_READONLY)
959       || ! bfd_set_section_alignment (abfd, s, LOG_FILE_ALIGN))
960     return false;
961
962   /* Let the backend create the rest of the sections.  This lets the
963      backend set the right flags.  The backend will normally create
964      the .got and .plt sections.  */
965   bed = get_elf_backend_data (abfd);
966   if (! (*bed->elf_backend_create_dynamic_sections) (abfd, info))
967     return false;
968
969   elf_hash_table (info)->dynamic_sections_created = true;
970
971   return true;
972 }
973
974 /* Add an entry to the .dynamic table.  */
975
976 boolean
977 elf_add_dynamic_entry (info, tag, val)
978      struct bfd_link_info *info;
979      bfd_vma tag;
980      bfd_vma val;
981 {
982   Elf_Internal_Dyn dyn;
983   bfd *dynobj;
984   asection *s;
985   size_t newsize;
986   bfd_byte *newcontents;
987
988   dynobj = elf_hash_table (info)->dynobj;
989
990   s = bfd_get_section_by_name (dynobj, ".dynamic");
991   BFD_ASSERT (s != NULL);
992
993   newsize = s->_raw_size + sizeof (Elf_External_Dyn);
994   if (s->contents == NULL)
995     newcontents = (bfd_byte *) malloc (newsize);
996   else
997     newcontents = (bfd_byte *) realloc (s->contents, newsize);
998   if (newcontents == NULL)
999     {
1000       bfd_set_error (bfd_error_no_memory);
1001       return false;
1002     }
1003
1004   dyn.d_tag = tag;
1005   dyn.d_un.d_val = val;
1006   elf_swap_dyn_out (dynobj, &dyn,
1007                     (Elf_External_Dyn *) (newcontents + s->_raw_size));
1008
1009   s->_raw_size = newsize;
1010   s->contents = newcontents;
1011
1012   return true;
1013 }
1014
1015 /* Read and swap the relocs for a section.  They may have been cached.
1016    If the EXTERNAL_RELOCS and INTERNAL_RELOCS arguments are not NULL,
1017    they are used as buffers to read into.  They are known to be large
1018    enough.  If the INTERNAL_RELOCS relocs argument is NULL, the return
1019    value is allocated using either malloc or bfd_alloc, according to
1020    the KEEP_MEMORY argument.  */
1021
1022 static Elf_Internal_Rela *
1023 elf_link_read_relocs (abfd, o, external_relocs, internal_relocs, keep_memory)
1024      bfd *abfd;
1025      asection *o;
1026      PTR external_relocs;
1027      Elf_Internal_Rela *internal_relocs;
1028      boolean keep_memory;
1029 {
1030   Elf_Internal_Shdr *rel_hdr;
1031   PTR alloc1 = NULL;
1032   Elf_Internal_Rela *alloc2 = NULL;
1033
1034   if (elf_section_data (o)->relocs != NULL)
1035     return elf_section_data (o)->relocs;
1036
1037   if (o->reloc_count == 0)
1038     return NULL;
1039
1040   rel_hdr = &elf_section_data (o)->rel_hdr;
1041
1042   if (internal_relocs == NULL)
1043     {
1044       size_t size;
1045
1046       size = o->reloc_count * sizeof (Elf_Internal_Rela);
1047       if (keep_memory)
1048         internal_relocs = (Elf_Internal_Rela *) bfd_alloc (abfd, size);
1049       else
1050         internal_relocs = alloc2 = (Elf_Internal_Rela *) malloc (size);
1051       if (internal_relocs == NULL)
1052         {
1053           bfd_set_error (bfd_error_no_memory);
1054           goto error_return;
1055         }
1056     }
1057
1058   if (external_relocs == NULL)
1059     {
1060       alloc1 = (PTR) malloc ((size_t) rel_hdr->sh_size);
1061       if (alloc1 == NULL)
1062         {
1063           bfd_set_error (bfd_error_no_memory);
1064           goto error_return;
1065         }
1066       external_relocs = alloc1;
1067     }
1068
1069   if ((bfd_seek (abfd, rel_hdr->sh_offset, SEEK_SET) != 0)
1070       || (bfd_read (external_relocs, 1, rel_hdr->sh_size, abfd)
1071           != rel_hdr->sh_size))
1072     goto error_return;
1073
1074   /* Swap in the relocs.  For convenience, we always produce an
1075      Elf_Internal_Rela array; if the relocs are Rel, we set the addend
1076      to 0.  */
1077   if (rel_hdr->sh_entsize == sizeof (Elf_External_Rel))
1078     {
1079       Elf_External_Rel *erel;
1080       Elf_External_Rel *erelend;
1081       Elf_Internal_Rela *irela;
1082
1083       erel = (Elf_External_Rel *) external_relocs;
1084       erelend = erel + o->reloc_count;
1085       irela = internal_relocs;
1086       for (; erel < erelend; erel++, irela++)
1087         {
1088           Elf_Internal_Rel irel;
1089
1090           elf_swap_reloc_in (abfd, erel, &irel);
1091           irela->r_offset = irel.r_offset;
1092           irela->r_info = irel.r_info;
1093           irela->r_addend = 0;
1094         }
1095     }
1096   else
1097     {
1098       Elf_External_Rela *erela;
1099       Elf_External_Rela *erelaend;
1100       Elf_Internal_Rela *irela;
1101
1102       BFD_ASSERT (rel_hdr->sh_entsize == sizeof (Elf_External_Rela));
1103
1104       erela = (Elf_External_Rela *) external_relocs;
1105       erelaend = erela + o->reloc_count;
1106       irela = internal_relocs;
1107       for (; erela < erelaend; erela++, irela++)
1108         elf_swap_reloca_in (abfd, erela, irela);
1109     }
1110
1111   /* Cache the results for next time, if we can.  */
1112   if (keep_memory)
1113     elf_section_data (o)->relocs = internal_relocs;
1114                  
1115   if (alloc1 != NULL)
1116     free (alloc1);
1117
1118   /* Don't free alloc2, since if it was allocated we are passing it
1119      back (under the name of internal_relocs).  */
1120
1121   return internal_relocs;
1122
1123  error_return:
1124   if (alloc1 != NULL)
1125     free (alloc1);
1126   if (alloc2 != NULL)
1127     free (alloc2);
1128   return NULL;
1129 }
1130
1131 /* Record an assignment to a symbol made by a linker script.  We need
1132    this in case some dynamic object refers to this symbol.  */
1133
1134 /*ARGSUSED*/
1135 boolean
1136 NAME(bfd_elf,record_link_assignment) (output_bfd, info, name, provide)
1137      bfd *output_bfd;
1138      struct bfd_link_info *info;
1139      const char *name;
1140      boolean provide;
1141 {
1142   struct elf_link_hash_entry *h;
1143
1144   if (info->hash->creator->flavour != bfd_target_elf_flavour)
1145     return true;
1146
1147   h = elf_link_hash_lookup (elf_hash_table (info), name, true, true, false);
1148   if (h == NULL)
1149     return false;
1150
1151   /* If this symbol is being provided by the linker script, and it is
1152      currently defined by a dynamic object, but not by a regular
1153      object, then mark it as undefined so that the generic linker will
1154      force the correct value.  */
1155   if (provide
1156       && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC) != 0
1157       && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) == 0)
1158     h->root.type = bfd_link_hash_undefined;
1159
1160   h->elf_link_hash_flags |= ELF_LINK_HASH_DEF_REGULAR;
1161   h->type = STT_OBJECT;
1162
1163   if (((h->elf_link_hash_flags & (ELF_LINK_HASH_DEF_DYNAMIC
1164                                   | ELF_LINK_HASH_REF_DYNAMIC)) != 0
1165        || info->shared)
1166       && h->dynindx == -1)
1167     {
1168       if (! _bfd_elf_link_record_dynamic_symbol (info, h))
1169         return false;
1170
1171       /* If this is a weak defined symbol, and we know a corresponding
1172          real symbol from the same dynamic object, make sure the real
1173          symbol is also made into a dynamic symbol.  */
1174       if (h->weakdef != NULL
1175           && h->weakdef->dynindx == -1)
1176         {
1177           if (! _bfd_elf_link_record_dynamic_symbol (info, h->weakdef))
1178             return false;
1179         }
1180     }
1181
1182   return true;
1183 }
1184
1185 /* Array used to determine the number of hash table buckets to use
1186    based on the number of symbols there are.  If there are fewer than
1187    3 symbols we use 1 bucket, fewer than 17 symbols we use 3 buckets,
1188    fewer than 37 we use 17 buckets, and so forth.  We never use more
1189    than 521 buckets.  */
1190
1191 static const size_t elf_buckets[] =
1192 {
1193   1, 3, 17, 37, 67, 97, 131, 197, 263, 521, 0
1194 };
1195
1196 /* Set up the sizes and contents of the ELF dynamic sections.  This is
1197    called by the ELF linker emulation before_allocation routine.  We
1198    must set the sizes of the sections before the linker sets the
1199    addresses of the various sections.  */
1200
1201 boolean
1202 NAME(bfd_elf,size_dynamic_sections) (output_bfd, soname, rpath,
1203                                      export_dynamic, info, sinterpptr)
1204      bfd *output_bfd;
1205      const char *soname;
1206      const char *rpath;
1207      boolean export_dynamic;
1208      struct bfd_link_info *info;
1209      asection **sinterpptr;
1210 {
1211   bfd *dynobj;
1212   struct elf_backend_data *bed;
1213
1214   *sinterpptr = NULL;
1215
1216   if (info->hash->creator->flavour != bfd_target_elf_flavour)
1217     return true;
1218
1219   dynobj = elf_hash_table (info)->dynobj;
1220
1221   /* If there were no dynamic objects in the link, there is nothing to
1222      do here.  */
1223   if (dynobj == NULL)
1224     return true;
1225
1226   /* If we are supposed to export all symbols into the dynamic symbol
1227      table (this is not the normal case), then do so.  */
1228   if (export_dynamic)
1229     {
1230       struct elf_info_failed eif;
1231
1232       eif.failed = false;
1233       eif.info = info;
1234       elf_link_hash_traverse (elf_hash_table (info), elf_export_symbol,
1235                               (PTR) &eif);
1236       if (eif.failed)
1237         return false;
1238     }
1239
1240   if (elf_hash_table (info)->dynamic_sections_created)
1241     {
1242       struct elf_info_failed eif;
1243       bfd_size_type strsize;
1244
1245       *sinterpptr = bfd_get_section_by_name (dynobj, ".interp");
1246       BFD_ASSERT (*sinterpptr != NULL || info->shared);
1247
1248       if (soname != NULL)
1249         {
1250           bfd_size_type indx;
1251
1252           indx = _bfd_stringtab_add (elf_hash_table (info)->dynstr, soname,
1253                                      true, true);
1254           if (indx == (bfd_size_type) -1
1255               || ! elf_add_dynamic_entry (info, DT_SONAME, indx))
1256             return false;
1257         }      
1258
1259       if (info->symbolic)
1260         {
1261           if (! elf_add_dynamic_entry (info, DT_SYMBOLIC, 0))
1262             return false;
1263         }
1264
1265       if (rpath != NULL)
1266         {
1267           bfd_size_type indx;
1268
1269           indx = _bfd_stringtab_add (elf_hash_table (info)->dynstr, rpath,
1270                                      true, true);
1271           if (indx == (bfd_size_type) -1
1272               || ! elf_add_dynamic_entry (info, DT_RPATH, indx))
1273             return false;
1274         }
1275
1276       /* Find all symbols which were defined in a dynamic object and make
1277          the backend pick a reasonable value for them.  */
1278       eif.failed = false;
1279       eif.info = info;
1280       elf_link_hash_traverse (elf_hash_table (info),
1281                               elf_adjust_dynamic_symbol,
1282                               (PTR) &eif);
1283       if (eif.failed)
1284         return false;
1285
1286       /* Add some entries to the .dynamic section.  We fill in some of the
1287          values later, in elf_bfd_final_link, but we must add the entries
1288          now so that we know the final size of the .dynamic section.  */
1289       if (elf_link_hash_lookup (elf_hash_table (info), "_init", false,
1290                                 false, false) != NULL)
1291         {
1292           if (! elf_add_dynamic_entry (info, DT_INIT, 0))
1293             return false;
1294         }
1295       if (elf_link_hash_lookup (elf_hash_table (info), "_fini", false,
1296                                 false, false) != NULL)
1297         {
1298           if (! elf_add_dynamic_entry (info, DT_FINI, 0))
1299             return false;
1300         }
1301       strsize = _bfd_stringtab_size (elf_hash_table (info)->dynstr);
1302       if (! elf_add_dynamic_entry (info, DT_HASH, 0)
1303           || ! elf_add_dynamic_entry (info, DT_STRTAB, 0)
1304           || ! elf_add_dynamic_entry (info, DT_SYMTAB, 0)
1305           || ! elf_add_dynamic_entry (info, DT_STRSZ, strsize)
1306           || ! elf_add_dynamic_entry (info, DT_SYMENT,
1307                                       sizeof (Elf_External_Sym)))
1308         return false;
1309     }
1310
1311   /* The backend must work out the sizes of all the other dynamic
1312      sections.  */
1313   bed = get_elf_backend_data (output_bfd);
1314   if (! (*bed->elf_backend_size_dynamic_sections) (output_bfd, info))
1315     return false;
1316
1317   if (elf_hash_table (info)->dynamic_sections_created)
1318     {
1319       size_t dynsymcount;
1320       asection *s;
1321       size_t i;
1322       size_t bucketcount = 0;
1323       Elf_Internal_Sym isym;
1324
1325       /* Set the size of the .dynsym and .hash sections.  We counted
1326          the number of dynamic symbols in elf_link_add_object_symbols.
1327          We will build the contents of .dynsym and .hash when we build
1328          the final symbol table, because until then we do not know the
1329          correct value to give the symbols.  We built the .dynstr
1330          section as we went along in elf_link_add_object_symbols.  */
1331       dynsymcount = elf_hash_table (info)->dynsymcount;
1332       s = bfd_get_section_by_name (dynobj, ".dynsym");
1333       BFD_ASSERT (s != NULL);
1334       s->_raw_size = dynsymcount * sizeof (Elf_External_Sym);
1335       s->contents = (bfd_byte *) bfd_alloc (output_bfd, s->_raw_size);
1336       if (s->contents == NULL && s->_raw_size != 0)
1337         {
1338           bfd_set_error (bfd_error_no_memory);
1339           return false;
1340         }
1341
1342       /* The first entry in .dynsym is a dummy symbol.  */
1343       isym.st_value = 0;
1344       isym.st_size = 0;
1345       isym.st_name = 0;
1346       isym.st_info = 0;
1347       isym.st_other = 0;
1348       isym.st_shndx = 0;
1349       elf_swap_symbol_out (output_bfd, &isym,
1350                            (PTR) (Elf_External_Sym *) s->contents);
1351
1352       for (i = 0; elf_buckets[i] != 0; i++)
1353         {
1354           bucketcount = elf_buckets[i];
1355           if (dynsymcount < elf_buckets[i + 1])
1356             break;
1357         }
1358
1359       s = bfd_get_section_by_name (dynobj, ".hash");
1360       BFD_ASSERT (s != NULL);
1361       s->_raw_size = (2 + bucketcount + dynsymcount) * (ARCH_SIZE / 8);
1362       s->contents = (bfd_byte *) bfd_alloc (output_bfd, s->_raw_size);
1363       if (s->contents == NULL)
1364         {
1365           bfd_set_error (bfd_error_no_memory);
1366           return false;
1367         }
1368       memset (s->contents, 0, (size_t) s->_raw_size);
1369
1370       put_word (output_bfd, bucketcount, s->contents);
1371       put_word (output_bfd, dynsymcount, s->contents + (ARCH_SIZE / 8));
1372
1373       elf_hash_table (info)->bucketcount = bucketcount;
1374
1375       s = bfd_get_section_by_name (dynobj, ".dynstr");
1376       BFD_ASSERT (s != NULL);
1377       s->_raw_size = _bfd_stringtab_size (elf_hash_table (info)->dynstr);
1378
1379       if (! elf_add_dynamic_entry (info, DT_NULL, 0))
1380         return false;
1381     }
1382
1383   return true;
1384 }
1385
1386 /* This routine is used to export all defined symbols into the dynamic
1387    symbol table.  It is called via elf_link_hash_traverse.  */
1388
1389 static boolean
1390 elf_export_symbol (h, data)
1391      struct elf_link_hash_entry *h;
1392      PTR data;
1393 {
1394   struct elf_info_failed *eif = (struct elf_info_failed *) data;
1395
1396   if (h->dynindx == -1
1397       && (h->elf_link_hash_flags
1398           & (ELF_LINK_HASH_DEF_REGULAR | ELF_LINK_HASH_REF_REGULAR)) != 0)
1399     {
1400       if (! _bfd_elf_link_record_dynamic_symbol (eif->info, h))
1401         {
1402           eif->failed = true;
1403           return false;
1404         }
1405     }
1406
1407   return true;
1408 }
1409
1410 /* Make the backend pick a good value for a dynamic symbol.  This is
1411    called via elf_link_hash_traverse, and also calls itself
1412    recursively.  */
1413
1414 static boolean
1415 elf_adjust_dynamic_symbol (h, data)
1416      struct elf_link_hash_entry *h;
1417      PTR data;
1418 {
1419   struct elf_info_failed *eif = (struct elf_info_failed *) data;
1420   bfd *dynobj;
1421   struct elf_backend_data *bed;
1422
1423   /* If -Bsymbolic was used (which means to bind references to global
1424      symbols to the definition within the shared object), and this
1425      symbol was defined in a regular object, then it actually doesn't
1426      need a PLT entry.  */
1427   if ((h->elf_link_hash_flags & ELF_LINK_HASH_NEEDS_PLT) != 0
1428       && eif->info->shared
1429       && eif->info->symbolic
1430       && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) != 0)
1431     h->elf_link_hash_flags &=~ ELF_LINK_HASH_NEEDS_PLT;
1432
1433   /* If this symbol does not require a PLT entry, and it is not
1434      defined by a dynamic object, or is not referenced by a regular
1435      object, ignore it.  FIXME: Do we need to worry about symbols
1436      which are defined by one dynamic object and referenced by another
1437      one?  */
1438   if ((h->elf_link_hash_flags & ELF_LINK_HASH_NEEDS_PLT) == 0
1439       && ((h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) != 0
1440           || (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC) == 0
1441           || (h->elf_link_hash_flags & ELF_LINK_HASH_REF_REGULAR) == 0))
1442     return true;
1443
1444   /* If we've already adjusted this symbol, don't do it again.  This
1445      can happen via a recursive call.  */
1446   if ((h->elf_link_hash_flags & ELF_LINK_HASH_DYNAMIC_ADJUSTED) != 0)
1447     return true;
1448
1449   /* Don't look at this symbol again.  Note that we must set this
1450      after checking the above conditions, because we may look at a
1451      symbol once, decide not to do anything, and then get called
1452      recursively later after REF_REGULAR is set below.  */
1453   h->elf_link_hash_flags |= ELF_LINK_HASH_DYNAMIC_ADJUSTED;
1454
1455   /* If this is a weak definition, and we know a real definition, and
1456      the real symbol is not itself defined by a regular object file,
1457      then get a good value for the real definition.  We handle the
1458      real symbol first, for the convenience of the backend routine.
1459
1460      Note that there is a confusing case here.  If the real definition
1461      is defined by a regular object file, we don't get the real symbol
1462      from the dynamic object, but we do get the weak symbol.  If the
1463      processor backend uses a COPY reloc, then if some routine in the
1464      dynamic object changes the real symbol, we will not see that
1465      change in the corresponding weak symbol.  This is the way other
1466      ELF linkers work as well, and seems to be a result of the shared
1467      library model.
1468
1469      I will clarify this issue.  Most SVR4 shared libraries define the
1470      variable _timezone and define timezone as a weak synonym.  The
1471      tzset call changes _timezone.  If you write
1472        extern int timezone;
1473        int _timezone = 5;
1474        int main () { tzset (); printf ("%d %d\n", timezone, _timezone); }
1475      you might expect that, since timezone is a synonym for _timezone,
1476      the same number will print both times.  However, if the processor
1477      backend uses a COPY reloc, then actually timezone will be copied
1478      into your process image, and, since you define _timezone
1479      yourself, _timezone will not.  Thus timezone and _timezone will
1480      wind up at different memory locations.  The tzset call will set
1481      _timezone, leaving timezone unchanged.  */
1482
1483   if (h->weakdef != NULL)
1484     {
1485       struct elf_link_hash_entry *weakdef;
1486
1487       BFD_ASSERT (h->root.type == bfd_link_hash_defined
1488                   || h->root.type == bfd_link_hash_defweak);
1489       weakdef = h->weakdef;
1490       BFD_ASSERT (weakdef->root.type == bfd_link_hash_defined
1491                   || weakdef->root.type == bfd_link_hash_defweak);
1492       BFD_ASSERT (weakdef->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC);
1493       if ((weakdef->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) != 0)
1494         {
1495           /* This symbol is defined by a regular object file, so we
1496              will not do anything special.  Clear weakdef for the
1497              convenience of the processor backend.  */
1498           h->weakdef = NULL;
1499         }
1500       else
1501         {
1502           /* There is an implicit reference by a regular object file
1503              via the weak symbol.  */
1504           weakdef->elf_link_hash_flags |= ELF_LINK_HASH_REF_REGULAR;
1505           if (! elf_adjust_dynamic_symbol (weakdef, (PTR) eif))
1506             return false;
1507         }
1508     }
1509
1510   dynobj = elf_hash_table (eif->info)->dynobj;
1511   bed = get_elf_backend_data (dynobj);
1512   if (! (*bed->elf_backend_adjust_dynamic_symbol) (eif->info, h))
1513     {
1514       eif->failed = true;
1515       return false;
1516     }
1517
1518   return true;
1519 }
1520 \f
1521 /* Final phase of ELF linker.  */
1522
1523 /* A structure we use to avoid passing large numbers of arguments.  */
1524
1525 struct elf_final_link_info
1526 {
1527   /* General link information.  */
1528   struct bfd_link_info *info;
1529   /* Output BFD.  */
1530   bfd *output_bfd;
1531   /* Symbol string table.  */
1532   struct bfd_strtab_hash *symstrtab;
1533   /* .dynsym section.  */
1534   asection *dynsym_sec;
1535   /* .hash section.  */
1536   asection *hash_sec;
1537   /* Buffer large enough to hold contents of any section.  */
1538   bfd_byte *contents;
1539   /* Buffer large enough to hold external relocs of any section.  */
1540   PTR external_relocs;
1541   /* Buffer large enough to hold internal relocs of any section.  */
1542   Elf_Internal_Rela *internal_relocs;
1543   /* Buffer large enough to hold external local symbols of any input
1544      BFD.  */
1545   Elf_External_Sym *external_syms;
1546   /* Buffer large enough to hold internal local symbols of any input
1547      BFD.  */
1548   Elf_Internal_Sym *internal_syms;
1549   /* Array large enough to hold a symbol index for each local symbol
1550      of any input BFD.  */
1551   long *indices;
1552   /* Array large enough to hold a section pointer for each local
1553      symbol of any input BFD.  */
1554   asection **sections;
1555   /* Buffer to hold swapped out symbols.  */
1556   Elf_External_Sym *symbuf;
1557   /* Number of swapped out symbols in buffer.  */
1558   size_t symbuf_count;
1559   /* Number of symbols which fit in symbuf.  */
1560   size_t symbuf_size;
1561 };
1562
1563 static boolean elf_link_output_sym
1564   PARAMS ((struct elf_final_link_info *, const char *,
1565            Elf_Internal_Sym *, asection *));
1566 static boolean elf_link_flush_output_syms
1567   PARAMS ((struct elf_final_link_info *));
1568 static boolean elf_link_output_extsym
1569   PARAMS ((struct elf_link_hash_entry *, PTR));
1570 static boolean elf_link_input_bfd
1571   PARAMS ((struct elf_final_link_info *, bfd *));
1572 static boolean elf_reloc_link_order
1573   PARAMS ((bfd *, struct bfd_link_info *, asection *,
1574            struct bfd_link_order *));
1575
1576 /* This struct is used to pass information to routines called via
1577    elf_link_hash_traverse which must return failure.  */
1578
1579 struct elf_finfo_failed
1580 {
1581   boolean failed;
1582   struct elf_final_link_info *finfo;
1583 };  
1584
1585 /* Do the final step of an ELF link.  */
1586
1587 boolean
1588 elf_bfd_final_link (abfd, info)
1589      bfd *abfd;
1590      struct bfd_link_info *info;
1591 {
1592   boolean dynamic;
1593   bfd *dynobj;
1594   struct elf_final_link_info finfo;
1595   register asection *o;
1596   register struct bfd_link_order *p;
1597   register bfd *sub;
1598   size_t max_contents_size;
1599   size_t max_external_reloc_size;
1600   size_t max_internal_reloc_count;
1601   size_t max_sym_count;
1602   file_ptr off;
1603   Elf_Internal_Sym elfsym;
1604   unsigned int i;
1605   Elf_Internal_Shdr *symtab_hdr;
1606   Elf_Internal_Shdr *symstrtab_hdr;
1607   struct elf_backend_data *bed = get_elf_backend_data (abfd);
1608   struct elf_finfo_failed eif;
1609
1610   if (info->shared)
1611     abfd->flags |= DYNAMIC;
1612
1613   dynamic = elf_hash_table (info)->dynamic_sections_created;
1614   dynobj = elf_hash_table (info)->dynobj;
1615
1616   finfo.info = info;
1617   finfo.output_bfd = abfd;
1618   finfo.symstrtab = elf_stringtab_init ();
1619   if (finfo.symstrtab == NULL)
1620     return false;
1621   if (! dynamic)
1622     {
1623       finfo.dynsym_sec = NULL;
1624       finfo.hash_sec = NULL;
1625     }
1626   else
1627     {
1628       finfo.dynsym_sec = bfd_get_section_by_name (dynobj, ".dynsym");
1629       finfo.hash_sec = bfd_get_section_by_name (dynobj, ".hash");
1630       BFD_ASSERT (finfo.dynsym_sec != NULL && finfo.hash_sec != NULL);
1631     }
1632   finfo.contents = NULL;
1633   finfo.external_relocs = NULL;
1634   finfo.internal_relocs = NULL;
1635   finfo.external_syms = NULL;
1636   finfo.internal_syms = NULL;
1637   finfo.indices = NULL;
1638   finfo.sections = NULL;
1639   finfo.symbuf = NULL;
1640   finfo.symbuf_count = 0;
1641
1642   /* Count up the number of relocations we will output for each output
1643      section, so that we know the sizes of the reloc sections.  We
1644      also figure out some maximum sizes.  */
1645   max_contents_size = 0;
1646   max_external_reloc_size = 0;
1647   max_internal_reloc_count = 0;
1648   max_sym_count = 0;
1649   for (o = abfd->sections; o != (asection *) NULL; o = o->next)
1650     {
1651       o->reloc_count = 0;
1652
1653       for (p = o->link_order_head; p != NULL; p = p->next)
1654         {
1655           if (p->type == bfd_section_reloc_link_order
1656               || p->type == bfd_symbol_reloc_link_order)
1657             ++o->reloc_count;
1658           else if (p->type == bfd_indirect_link_order)
1659             {
1660               asection *sec;
1661
1662               sec = p->u.indirect.section;
1663
1664               if (info->relocateable)
1665                 o->reloc_count += sec->reloc_count;
1666
1667               if (sec->_raw_size > max_contents_size)
1668                 max_contents_size = sec->_raw_size;
1669               if (sec->_cooked_size > max_contents_size)
1670                 max_contents_size = sec->_cooked_size;
1671
1672               /* We are interested in just local symbols, not all
1673                  symbols.  */
1674               if (bfd_get_flavour (sec->owner) == bfd_target_elf_flavour)
1675                 {
1676                   size_t sym_count;
1677
1678                   if (elf_bad_symtab (sec->owner))
1679                     sym_count = (elf_tdata (sec->owner)->symtab_hdr.sh_size
1680                                  / sizeof (Elf_External_Sym));
1681                   else
1682                     sym_count = elf_tdata (sec->owner)->symtab_hdr.sh_info;
1683
1684                   if (sym_count > max_sym_count)
1685                     max_sym_count = sym_count;
1686
1687                   if ((sec->flags & SEC_RELOC) != 0)
1688                     {
1689                       size_t ext_size;
1690
1691                       ext_size = elf_section_data (sec)->rel_hdr.sh_size;
1692                       if (ext_size > max_external_reloc_size)
1693                         max_external_reloc_size = ext_size;
1694                       if (sec->reloc_count > max_internal_reloc_count)
1695                         max_internal_reloc_count = sec->reloc_count;
1696                     }
1697                 }
1698             }
1699         }
1700
1701       if (o->reloc_count > 0)
1702         o->flags |= SEC_RELOC;
1703       else
1704         {
1705           /* Explicitly clear the SEC_RELOC flag.  The linker tends to
1706              set it (this is probably a bug) and if it is set
1707              assign_section_numbers will create a reloc section.  */
1708           o->flags &=~ SEC_RELOC;
1709         }
1710
1711       /* If the SEC_ALLOC flag is not set, force the section VMA to
1712          zero.  This is done in elf_fake_sections as well, but forcing
1713          the VMA to 0 here will ensure that relocs against these
1714          sections are handled correctly.  */
1715       if ((o->flags & SEC_ALLOC) == 0)
1716         o->vma = 0;
1717     }
1718
1719   /* Figure out the file positions for everything but the symbol table
1720      and the relocs.  We set symcount to force assign_section_numbers
1721      to create a symbol table.  */
1722   abfd->symcount = info->strip == strip_all ? 0 : 1;
1723   BFD_ASSERT (! abfd->output_has_begun);
1724   if (! _bfd_elf_compute_section_file_positions (abfd, info))
1725     goto error_return;
1726
1727   /* That created the reloc sections.  Set their sizes, and assign
1728      them file positions, and allocate some buffers.  */
1729   for (o = abfd->sections; o != NULL; o = o->next)
1730     {
1731       if ((o->flags & SEC_RELOC) != 0)
1732         {
1733           Elf_Internal_Shdr *rel_hdr;
1734           register struct elf_link_hash_entry **p, **pend;
1735
1736           rel_hdr = &elf_section_data (o)->rel_hdr;
1737
1738           rel_hdr->sh_size = rel_hdr->sh_entsize * o->reloc_count;
1739
1740           /* The contents field must last into write_object_contents,
1741              so we allocate it with bfd_alloc rather than malloc.  */
1742           rel_hdr->contents = (PTR) bfd_alloc (abfd, rel_hdr->sh_size);
1743           if (rel_hdr->contents == NULL && rel_hdr->sh_size != 0)
1744             {
1745               bfd_set_error (bfd_error_no_memory);
1746               goto error_return;
1747             }
1748
1749           p = ((struct elf_link_hash_entry **)
1750                malloc (o->reloc_count
1751                        * sizeof (struct elf_link_hash_entry *)));
1752           if (p == NULL && o->reloc_count != 0)
1753             {
1754               bfd_set_error (bfd_error_no_memory);
1755               goto error_return;
1756             }
1757           elf_section_data (o)->rel_hashes = p;
1758           pend = p + o->reloc_count;
1759           for (; p < pend; p++)
1760             *p = NULL;
1761
1762           /* Use the reloc_count field as an index when outputting the
1763              relocs.  */
1764           o->reloc_count = 0;
1765         }
1766     }
1767
1768   _bfd_elf_assign_file_positions_for_relocs (abfd);
1769
1770   /* We have now assigned file positions for all the sections except
1771      .symtab and .strtab.  We start the .symtab section at the current
1772      file position, and write directly to it.  We build the .strtab
1773      section in memory.  When we add .dynsym support, we will build
1774      that in memory as well (.dynsym is smaller than .symtab).  */
1775   abfd->symcount = 0;
1776   symtab_hdr = &elf_tdata (abfd)->symtab_hdr;
1777   /* sh_name is set in prep_headers.  */
1778   symtab_hdr->sh_type = SHT_SYMTAB;
1779   symtab_hdr->sh_flags = 0;
1780   symtab_hdr->sh_addr = 0;
1781   symtab_hdr->sh_size = 0;
1782   symtab_hdr->sh_entsize = sizeof (Elf_External_Sym);
1783   /* sh_link is set in assign_section_numbers.  */
1784   /* sh_info is set below.  */
1785   /* sh_offset is set just below.  */
1786   symtab_hdr->sh_addralign = 4;  /* FIXME: system dependent?  */
1787
1788   off = elf_tdata (abfd)->next_file_pos;
1789   off = _bfd_elf_assign_file_position_for_section (symtab_hdr, off, true);
1790
1791   /* Note that at this point elf_tdata (abfd)->next_file_pos is
1792      incorrect.  We do not yet know the size of the .symtab section.
1793      We correct next_file_pos below, after we do know the size.  */
1794
1795   /* Allocate a buffer to hold swapped out symbols.  This is to avoid
1796      continuously seeking to the right position in the file.  */
1797   if (! info->keep_memory || max_sym_count < 20)
1798     finfo.symbuf_size = 20;
1799   else
1800     finfo.symbuf_size = max_sym_count;
1801   finfo.symbuf = ((Elf_External_Sym *)
1802                   malloc (finfo.symbuf_size * sizeof (Elf_External_Sym)));
1803   if (finfo.symbuf == NULL)
1804     {
1805       bfd_set_error (bfd_error_no_memory);
1806       goto error_return;
1807     }
1808
1809   /* Start writing out the symbol table.  The first symbol is always a
1810      dummy symbol.  */
1811   elfsym.st_value = 0;
1812   elfsym.st_size = 0;
1813   elfsym.st_info = 0;
1814   elfsym.st_other = 0;
1815   elfsym.st_shndx = SHN_UNDEF;
1816   if (! elf_link_output_sym (&finfo, (const char *) NULL,
1817                              &elfsym, bfd_und_section_ptr))
1818     goto error_return;
1819
1820 #if 0
1821   /* Some standard ELF linkers do this, but we don't because it causes
1822      bootstrap comparison failures.  */
1823   /* Output a file symbol for the output file as the second symbol.
1824      We output this even if we are discarding local symbols, although
1825      I'm not sure if this is correct.  */
1826   elfsym.st_value = 0;
1827   elfsym.st_size = 0;
1828   elfsym.st_info = ELF_ST_INFO (STB_LOCAL, STT_FILE);
1829   elfsym.st_other = 0;
1830   elfsym.st_shndx = SHN_ABS;
1831   if (! elf_link_output_sym (&finfo, bfd_get_filename (abfd),
1832                              &elfsym, bfd_abs_section_ptr))
1833     goto error_return;
1834 #endif
1835
1836   /* Output a symbol for each section.  We output these even if we are
1837      discarding local symbols, since they are used for relocs.  These
1838      symbols have no names.  We store the index of each one in the
1839      index field of the section, so that we can find it again when
1840      outputting relocs.  */
1841   elfsym.st_value = 0;
1842   elfsym.st_size = 0;
1843   elfsym.st_info = ELF_ST_INFO (STB_LOCAL, STT_SECTION);
1844   elfsym.st_other = 0;
1845   for (i = 1; i < elf_elfheader (abfd)->e_shnum; i++)
1846     {
1847       o = section_from_elf_index (abfd, i);
1848       if (o != NULL)
1849         o->target_index = abfd->symcount;
1850       elfsym.st_shndx = i;
1851       if (! elf_link_output_sym (&finfo, (const char *) NULL,
1852                                  &elfsym, o))
1853         goto error_return;
1854     }
1855
1856   /* Allocate some memory to hold information read in from the input
1857      files.  */
1858   finfo.contents = (bfd_byte *) malloc (max_contents_size);
1859   finfo.external_relocs = (PTR) malloc (max_external_reloc_size);
1860   finfo.internal_relocs = ((Elf_Internal_Rela *)
1861                            malloc (max_internal_reloc_count
1862                                    * sizeof (Elf_Internal_Rela)));
1863   finfo.external_syms = ((Elf_External_Sym *)
1864                          malloc (max_sym_count * sizeof (Elf_External_Sym)));
1865   finfo.internal_syms = ((Elf_Internal_Sym *)
1866                          malloc (max_sym_count * sizeof (Elf_Internal_Sym)));
1867   finfo.indices = (long *) malloc (max_sym_count * sizeof (long));
1868   finfo.sections = (asection **) malloc (max_sym_count * sizeof (asection *));
1869   if ((finfo.contents == NULL && max_contents_size != 0)
1870       || (finfo.external_relocs == NULL && max_external_reloc_size != 0)
1871       || (finfo.internal_relocs == NULL && max_internal_reloc_count != 0)
1872       || (finfo.external_syms == NULL && max_sym_count != 0)
1873       || (finfo.internal_syms == NULL && max_sym_count != 0)
1874       || (finfo.indices == NULL && max_sym_count != 0)
1875       || (finfo.sections == NULL && max_sym_count != 0))
1876     {
1877       bfd_set_error (bfd_error_no_memory);
1878       goto error_return;
1879     }
1880
1881   /* Since ELF permits relocations to be against local symbols, we
1882      must have the local symbols available when we do the relocations.
1883      Since we would rather only read the local symbols once, and we
1884      would rather not keep them in memory, we handle all the
1885      relocations for a single input file at the same time.
1886
1887      Unfortunately, there is no way to know the total number of local
1888      symbols until we have seen all of them, and the local symbol
1889      indices precede the global symbol indices.  This means that when
1890      we are generating relocateable output, and we see a reloc against
1891      a global symbol, we can not know the symbol index until we have
1892      finished examining all the local symbols to see which ones we are
1893      going to output.  To deal with this, we keep the relocations in
1894      memory, and don't output them until the end of the link.  This is
1895      an unfortunate waste of memory, but I don't see a good way around
1896      it.  Fortunately, it only happens when performing a relocateable
1897      link, which is not the common case.  FIXME: If keep_memory is set
1898      we could write the relocs out and then read them again; I don't
1899      know how bad the memory loss will be.  */
1900
1901   for (sub = info->input_bfds; sub != NULL; sub = sub->next)
1902     sub->output_has_begun = false;
1903   for (o = abfd->sections; o != NULL; o = o->next)
1904     {
1905       for (p = o->link_order_head; p != NULL; p = p->next)
1906         {
1907           if (p->type == bfd_indirect_link_order
1908               && (bfd_get_flavour (p->u.indirect.section->owner)
1909                   == bfd_target_elf_flavour))
1910             {
1911               sub = p->u.indirect.section->owner;
1912               if (! sub->output_has_begun)
1913                 {
1914                   if (! elf_link_input_bfd (&finfo, sub))
1915                     goto error_return;
1916                   sub->output_has_begun = true;
1917                 }
1918             }
1919           else if (p->type == bfd_section_reloc_link_order
1920                    || p->type == bfd_symbol_reloc_link_order)
1921             {
1922               if (! elf_reloc_link_order (abfd, info, o, p))
1923                 goto error_return;
1924             }
1925           else
1926             {
1927               if (! _bfd_default_link_order (abfd, info, o, p))
1928                 goto error_return;
1929             }
1930         }
1931     }
1932
1933   /* That wrote out all the local symbols.  Finish up the symbol table
1934      with the global symbols.  */
1935
1936   /* The sh_info field records the index of the first non local
1937      symbol.  */
1938   symtab_hdr->sh_info = abfd->symcount;
1939   if (dynamic)
1940     elf_section_data (finfo.dynsym_sec->output_section)->this_hdr.sh_info = 1;
1941
1942   /* We get the global symbols from the hash table.  */
1943   eif.failed = false;
1944   eif.finfo = &finfo;
1945   elf_link_hash_traverse (elf_hash_table (info), elf_link_output_extsym,
1946                           (PTR) &eif);
1947   if (eif.failed)
1948     return false;
1949
1950   /* Flush all symbols to the file.  */
1951   if (! elf_link_flush_output_syms (&finfo))
1952     return false;
1953
1954   /* Now we know the size of the symtab section.  */
1955   off += symtab_hdr->sh_size;
1956
1957   /* Finish up and write out the symbol string table (.strtab)
1958      section.  */
1959   symstrtab_hdr = &elf_tdata (abfd)->strtab_hdr;
1960   /* sh_name was set in prep_headers.  */
1961   symstrtab_hdr->sh_type = SHT_STRTAB;
1962   symstrtab_hdr->sh_flags = 0;
1963   symstrtab_hdr->sh_addr = 0;
1964   symstrtab_hdr->sh_size = _bfd_stringtab_size (finfo.symstrtab);
1965   symstrtab_hdr->sh_entsize = 0;
1966   symstrtab_hdr->sh_link = 0;
1967   symstrtab_hdr->sh_info = 0;
1968   /* sh_offset is set just below.  */
1969   symstrtab_hdr->sh_addralign = 1;
1970
1971   off = _bfd_elf_assign_file_position_for_section (symstrtab_hdr, off, true);
1972   elf_tdata (abfd)->next_file_pos = off;
1973
1974   if (bfd_seek (abfd, symstrtab_hdr->sh_offset, SEEK_SET) != 0
1975       || ! _bfd_stringtab_emit (abfd, finfo.symstrtab))
1976     return false;
1977
1978   /* Adjust the relocs to have the correct symbol indices.  */
1979   for (o = abfd->sections; o != NULL; o = o->next)
1980     {
1981       struct elf_link_hash_entry **rel_hash;
1982       Elf_Internal_Shdr *rel_hdr;
1983
1984       if ((o->flags & SEC_RELOC) == 0)
1985         continue;
1986
1987       rel_hash = elf_section_data (o)->rel_hashes;
1988       rel_hdr = &elf_section_data (o)->rel_hdr;
1989       for (i = 0; i < o->reloc_count; i++, rel_hash++)
1990         {
1991           if (*rel_hash == NULL)
1992             continue;
1993               
1994           BFD_ASSERT ((*rel_hash)->indx >= 0);
1995
1996           if (rel_hdr->sh_entsize == sizeof (Elf_External_Rel))
1997             {
1998               Elf_External_Rel *erel;
1999               Elf_Internal_Rel irel;
2000
2001               erel = (Elf_External_Rel *) rel_hdr->contents + i;
2002               elf_swap_reloc_in (abfd, erel, &irel);
2003               irel.r_info = ELF_R_INFO ((*rel_hash)->indx,
2004                                         ELF_R_TYPE (irel.r_info));
2005               elf_swap_reloc_out (abfd, &irel, erel);
2006             }
2007           else
2008             {
2009               Elf_External_Rela *erela;
2010               Elf_Internal_Rela irela;
2011
2012               BFD_ASSERT (rel_hdr->sh_entsize
2013                           == sizeof (Elf_External_Rela));
2014
2015               erela = (Elf_External_Rela *) rel_hdr->contents + i;
2016               elf_swap_reloca_in (abfd, erela, &irela);
2017               irela.r_info = ELF_R_INFO ((*rel_hash)->indx,
2018                                          ELF_R_TYPE (irela.r_info));
2019               elf_swap_reloca_out (abfd, &irela, erela);
2020             }
2021         }
2022
2023       /* Set the reloc_count field to 0 to prevent write_relocs from
2024          trying to swap the relocs out itself.  */
2025       o->reloc_count = 0;
2026     }
2027
2028   /* If we are linking against a dynamic object, or generating a
2029      shared library, finish up the dynamic linking information.  */
2030   if (dynamic)
2031     {
2032       Elf_External_Dyn *dyncon, *dynconend;
2033
2034       /* Fix up .dynamic entries.  */
2035       o = bfd_get_section_by_name (dynobj, ".dynamic");
2036       BFD_ASSERT (o != NULL);
2037
2038       dyncon = (Elf_External_Dyn *) o->contents;
2039       dynconend = (Elf_External_Dyn *) (o->contents + o->_raw_size);
2040       for (; dyncon < dynconend; dyncon++)
2041         {
2042           Elf_Internal_Dyn dyn;
2043           const char *name;
2044           unsigned int type;
2045
2046           elf_swap_dyn_in (dynobj, dyncon, &dyn);
2047
2048           switch (dyn.d_tag)
2049             {
2050             default:
2051               break;
2052
2053               /* SVR4 linkers seem to set DT_INIT and DT_FINI based on
2054                  magic _init and _fini symbols.  This is pretty ugly,
2055                  but we are compatible.  */
2056             case DT_INIT:
2057               name = "_init";
2058               goto get_sym;
2059             case DT_FINI:
2060               name = "_fini";
2061             get_sym:
2062               {
2063                 struct elf_link_hash_entry *h;
2064
2065                 h = elf_link_hash_lookup (elf_hash_table (info), name,
2066                                           false, false, true);
2067                 BFD_ASSERT (h != NULL);
2068                 if (h->root.type == bfd_link_hash_defined
2069                     || h->root.type == bfd_link_hash_defweak)
2070                   {
2071                     dyn.d_un.d_val = h->root.u.def.value;
2072                     o = h->root.u.def.section;
2073                     if (o->output_section != NULL)
2074                       dyn.d_un.d_val += (o->output_section->vma
2075                                          + o->output_offset);
2076                     else
2077                       /* The symbol is imported from another shared
2078                          library and does not apply to this one.  */
2079                       dyn.d_un.d_val = 0;
2080                   }
2081                 elf_swap_dyn_out (dynobj, &dyn, dyncon);
2082               }
2083               break;
2084
2085             case DT_HASH:
2086               name = ".hash";
2087               goto get_vma;
2088             case DT_STRTAB:
2089               name = ".dynstr";
2090               goto get_vma;
2091             case DT_SYMTAB:
2092               name = ".dynsym";
2093             get_vma:
2094               o = bfd_get_section_by_name (abfd, name);
2095               BFD_ASSERT (o != NULL);
2096               dyn.d_un.d_ptr = o->vma;
2097               elf_swap_dyn_out (dynobj, &dyn, dyncon);
2098               break;
2099
2100             case DT_REL:
2101             case DT_RELA:
2102             case DT_RELSZ:
2103             case DT_RELASZ:
2104               if (dyn.d_tag == DT_REL || dyn.d_tag == DT_RELSZ)
2105                 type = SHT_REL;
2106               else
2107                 type = SHT_RELA;
2108               dyn.d_un.d_val = 0;
2109               for (i = 1; i < elf_elfheader (abfd)->e_shnum; i++)
2110                 {
2111                   Elf_Internal_Shdr *hdr;
2112
2113                   hdr = elf_elfsections (abfd)[i];
2114                   if (hdr->sh_type == type
2115                       && (hdr->sh_flags & SHF_ALLOC) != 0)
2116                     {
2117                       if (dyn.d_tag == DT_RELSZ || dyn.d_tag == DT_RELASZ)
2118                         dyn.d_un.d_val += hdr->sh_size;
2119                       else
2120                         {
2121                           if (dyn.d_un.d_val == 0
2122                               || hdr->sh_addr < dyn.d_un.d_val)
2123                             dyn.d_un.d_val = hdr->sh_addr;
2124                         }
2125                     }
2126                 }
2127               elf_swap_dyn_out (dynobj, &dyn, dyncon);
2128               break;
2129             }
2130         }
2131     }
2132
2133   /* If we have created any dynamic sections, then output them.  */
2134   if (dynobj != NULL)
2135     {
2136       if (! (*bed->elf_backend_finish_dynamic_sections) (abfd, info))
2137         goto error_return;
2138
2139       for (o = dynobj->sections; o != NULL; o = o->next)
2140         {
2141           if ((o->flags & SEC_HAS_CONTENTS) == 0
2142               || o->_raw_size == 0)
2143             continue;
2144           if ((o->flags & SEC_IN_MEMORY) == 0)
2145             {
2146               /* At this point, we are only interested in sections
2147                  created by elf_link_create_dynamic_sections.  FIXME:
2148                  This test is fragile.  */
2149               continue;
2150             }
2151           if ((elf_section_data (o->output_section)->this_hdr.sh_type
2152                != SHT_STRTAB)
2153               || strcmp (bfd_get_section_name (abfd, o), ".dynstr") != 0)
2154             {
2155               if (! bfd_set_section_contents (abfd, o->output_section,
2156                                               o->contents, o->output_offset,
2157                                               o->_raw_size))
2158                 goto error_return;
2159             }
2160           else
2161             {
2162               file_ptr off;
2163
2164               /* The contents of the .dynstr section are actually in a
2165                  stringtab.  */
2166               off = elf_section_data (o->output_section)->this_hdr.sh_offset;
2167               if (bfd_seek (abfd, off, SEEK_SET) != 0
2168                   || ! _bfd_stringtab_emit (abfd,
2169                                             elf_hash_table (info)->dynstr))
2170                 goto error_return;
2171             }
2172         }
2173     }
2174
2175   if (finfo.symstrtab != NULL)
2176     _bfd_stringtab_free (finfo.symstrtab);
2177   if (finfo.contents != NULL)
2178     free (finfo.contents);
2179   if (finfo.external_relocs != NULL)
2180     free (finfo.external_relocs);
2181   if (finfo.internal_relocs != NULL)
2182     free (finfo.internal_relocs);
2183   if (finfo.external_syms != NULL)
2184     free (finfo.external_syms);
2185   if (finfo.internal_syms != NULL)
2186     free (finfo.internal_syms);
2187   if (finfo.indices != NULL)
2188     free (finfo.indices);
2189   if (finfo.sections != NULL)
2190     free (finfo.sections);
2191   if (finfo.symbuf != NULL)
2192     free (finfo.symbuf);
2193   for (o = abfd->sections; o != NULL; o = o->next)
2194     {
2195       if ((o->flags & SEC_RELOC) != 0
2196           && elf_section_data (o)->rel_hashes != NULL)
2197         free (elf_section_data (o)->rel_hashes);
2198     }
2199
2200   elf_tdata (abfd)->linker = true;
2201
2202   return true;
2203
2204  error_return:
2205   if (finfo.symstrtab != NULL)
2206     _bfd_stringtab_free (finfo.symstrtab);
2207   if (finfo.contents != NULL)
2208     free (finfo.contents);
2209   if (finfo.external_relocs != NULL)
2210     free (finfo.external_relocs);
2211   if (finfo.internal_relocs != NULL)
2212     free (finfo.internal_relocs);
2213   if (finfo.external_syms != NULL)
2214     free (finfo.external_syms);
2215   if (finfo.internal_syms != NULL)
2216     free (finfo.internal_syms);
2217   if (finfo.indices != NULL)
2218     free (finfo.indices);
2219   if (finfo.sections != NULL)
2220     free (finfo.sections);
2221   if (finfo.symbuf != NULL)
2222     free (finfo.symbuf);
2223   for (o = abfd->sections; o != NULL; o = o->next)
2224     {
2225       if ((o->flags & SEC_RELOC) != 0
2226           && elf_section_data (o)->rel_hashes != NULL)
2227         free (elf_section_data (o)->rel_hashes);
2228     }
2229
2230   return false;
2231 }
2232
2233 /* Add a symbol to the output symbol table.  */
2234
2235 static boolean
2236 elf_link_output_sym (finfo, name, elfsym, input_sec)
2237      struct elf_final_link_info *finfo;
2238      const char *name;
2239      Elf_Internal_Sym *elfsym;
2240      asection *input_sec;
2241 {
2242   boolean (*output_symbol_hook) PARAMS ((bfd *,
2243                                          struct bfd_link_info *info,
2244                                          const char *,
2245                                          Elf_Internal_Sym *,
2246                                          asection *));
2247
2248   output_symbol_hook = get_elf_backend_data (finfo->output_bfd)->
2249     elf_backend_link_output_symbol_hook;
2250   if (output_symbol_hook != NULL)
2251     {
2252       if (! ((*output_symbol_hook)
2253              (finfo->output_bfd, finfo->info, name, elfsym, input_sec)))
2254         return false;
2255     }
2256
2257   if (name == (const char *) NULL || *name == '\0')
2258     elfsym->st_name = 0;
2259   else
2260     {
2261       elfsym->st_name = (unsigned long) _bfd_stringtab_add (finfo->symstrtab,
2262                                                             name, true,
2263                                                             false);
2264       if (elfsym->st_name == (unsigned long) -1)
2265         return false;
2266     }
2267
2268   if (finfo->symbuf_count >= finfo->symbuf_size)
2269     {
2270       if (! elf_link_flush_output_syms (finfo))
2271         return false;
2272     }
2273
2274   elf_swap_symbol_out (finfo->output_bfd, elfsym,
2275                        (PTR) (finfo->symbuf + finfo->symbuf_count));
2276   ++finfo->symbuf_count;
2277
2278   ++finfo->output_bfd->symcount;
2279
2280   return true;
2281 }
2282
2283 /* Flush the output symbols to the file.  */
2284
2285 static boolean
2286 elf_link_flush_output_syms (finfo)
2287      struct elf_final_link_info *finfo;
2288 {
2289   Elf_Internal_Shdr *symtab;
2290
2291   symtab = &elf_tdata (finfo->output_bfd)->symtab_hdr;
2292
2293   if (bfd_seek (finfo->output_bfd, symtab->sh_offset + symtab->sh_size,
2294                 SEEK_SET) != 0
2295       || (bfd_write ((PTR) finfo->symbuf, finfo->symbuf_count,
2296                      sizeof (Elf_External_Sym), finfo->output_bfd)
2297           != finfo->symbuf_count * sizeof (Elf_External_Sym)))
2298     return false;
2299
2300   symtab->sh_size += finfo->symbuf_count * sizeof (Elf_External_Sym);
2301
2302   finfo->symbuf_count = 0;
2303
2304   return true;
2305 }
2306
2307 /* Add an external symbol to the symbol table.  This is called from
2308    the hash table traversal routine.  */
2309
2310 static boolean
2311 elf_link_output_extsym (h, data)
2312      struct elf_link_hash_entry *h;
2313      PTR data;
2314 {
2315   struct elf_finfo_failed *eif = (struct elf_finfo_failed *) data;
2316   struct elf_final_link_info *finfo = eif->finfo;
2317   boolean strip;
2318   Elf_Internal_Sym sym;
2319   asection *input_sec;
2320
2321   /* If we are not creating a shared library, and this symbol is
2322      referenced by a shared library but is not defined anywhere, then
2323      warn that it is undefined.  If we do not do this, the runtime
2324      linker will complain that the symbol is undefined when the
2325      program is run.  We don't have to worry about symbols that are
2326      referenced by regular files, because we will already have issued
2327      warnings for them.  */
2328   if (! finfo->info->relocateable
2329       && ! finfo->info->shared
2330       && h->root.type == bfd_link_hash_undefined
2331       && (h->elf_link_hash_flags & ELF_LINK_HASH_REF_DYNAMIC) != 0
2332       && (h->elf_link_hash_flags & ELF_LINK_HASH_REF_REGULAR) == 0)
2333     {
2334       if (! ((*finfo->info->callbacks->undefined_symbol)
2335              (finfo->info, h->root.root.string, h->root.u.undef.abfd,
2336               (asection *) NULL, 0)))
2337         {
2338           eif->failed = true;
2339           return false;
2340         }
2341     }
2342
2343   /* We don't want to output symbols that have never been mentioned by
2344      a regular file, or that we have been told to strip.  However, if
2345      h->indx is set to -2, the symbol is used by a reloc and we must
2346      output it.  */
2347   if (h->indx == -2)
2348     strip = false;
2349   else if (((h->elf_link_hash_flags & ELF_LINK_HASH_DEF_DYNAMIC) != 0
2350             || (h->elf_link_hash_flags & ELF_LINK_HASH_REF_DYNAMIC) != 0)
2351            && (h->elf_link_hash_flags & ELF_LINK_HASH_DEF_REGULAR) == 0
2352            && (h->elf_link_hash_flags & ELF_LINK_HASH_REF_REGULAR) == 0)
2353     strip = true;
2354   else if (finfo->info->strip == strip_all
2355            || (finfo->info->strip == strip_some
2356                && bfd_hash_lookup (finfo->info->keep_hash,
2357                                    h->root.root.string,
2358                                    false, false) == NULL))
2359     strip = true;
2360   else
2361     strip = false;
2362
2363   /* If we're stripping it, and it's not a dynamic symbol, there's
2364      nothing else to do.  */
2365   if (strip && h->dynindx == -1)
2366     return true;
2367
2368   sym.st_value = 0;
2369   sym.st_size = h->size;
2370   sym.st_other = 0;
2371   if (h->root.type == bfd_link_hash_undefweak
2372       || h->root.type == bfd_link_hash_defweak)
2373     sym.st_info = ELF_ST_INFO (STB_WEAK, h->type);
2374   else
2375     sym.st_info = ELF_ST_INFO (STB_GLOBAL, h->type);
2376
2377   switch (h->root.type)
2378     {
2379     default:
2380     case bfd_link_hash_new:
2381       abort ();
2382       return false;
2383
2384     case bfd_link_hash_undefined:
2385       input_sec = bfd_und_section_ptr;
2386       sym.st_shndx = SHN_UNDEF;
2387       break;
2388
2389     case bfd_link_hash_undefweak:
2390       input_sec = bfd_und_section_ptr;
2391       sym.st_shndx = SHN_UNDEF;
2392       break;
2393
2394     case bfd_link_hash_defined:
2395     case bfd_link_hash_defweak:
2396       {
2397         input_sec = h->root.u.def.section;
2398         if (input_sec->output_section != NULL)
2399           {
2400             sym.st_shndx =
2401               _bfd_elf_section_from_bfd_section (finfo->output_bfd,
2402                                                  input_sec->output_section);
2403             if (sym.st_shndx == (unsigned short) -1)
2404               {
2405                 eif->failed = true;
2406                 return false;
2407               }
2408
2409             /* ELF symbols in relocateable files are section relative,
2410                but in nonrelocateable files they are virtual
2411                addresses.  */
2412             sym.st_value = h->root.u.def.value + input_sec->output_offset;
2413             if (! finfo->info->relocateable)
2414               sym.st_value += input_sec->output_section->vma;
2415           }
2416         else
2417           {
2418             BFD_ASSERT ((bfd_get_flavour (input_sec->owner)
2419                          == bfd_target_elf_flavour)
2420                         && elf_elfheader (input_sec->owner)->e_type == ET_DYN);
2421             sym.st_shndx = SHN_UNDEF;
2422             input_sec = bfd_und_section_ptr;
2423           }
2424       }
2425       break;
2426
2427     case bfd_link_hash_common:
2428       input_sec = bfd_com_section_ptr;
2429       sym.st_shndx = SHN_COMMON;
2430       sym.st_value = 1 << h->root.u.c.p->alignment_power;
2431       break;
2432
2433     case bfd_link_hash_indirect:
2434     case bfd_link_hash_warning:
2435       /* I have no idea how these should be handled.  */
2436       return true;
2437     }
2438
2439   /* If this symbol should be put in the .dynsym section, then put it
2440      there now.  We have already know the symbol index.  We also fill
2441      in the entry in the .hash section.  */
2442   if (h->dynindx != -1
2443       && elf_hash_table (finfo->info)->dynamic_sections_created)
2444     {
2445       struct elf_backend_data *bed;
2446       size_t bucketcount;
2447       size_t bucket;
2448       bfd_byte *bucketpos;
2449       bfd_vma chain;
2450
2451       sym.st_name = h->dynstr_index;
2452
2453       /* Give the processor backend a chance to tweak the symbol
2454          value, and also to finish up anything that needs to be done
2455          for this symbol.  */
2456       bed = get_elf_backend_data (finfo->output_bfd);
2457       if (! ((*bed->elf_backend_finish_dynamic_symbol)
2458              (finfo->output_bfd, finfo->info, h, &sym)))
2459         {
2460           eif->failed = true;
2461           return false;
2462         }
2463
2464       elf_swap_symbol_out (finfo->output_bfd, &sym,
2465                            (PTR) (((Elf_External_Sym *)
2466                                    finfo->dynsym_sec->contents)
2467                                   + h->dynindx));
2468
2469       bucketcount = elf_hash_table (finfo->info)->bucketcount;
2470       bucket = (bfd_elf_hash ((const unsigned char *) h->root.root.string)
2471                 % bucketcount);
2472       bucketpos = ((bfd_byte *) finfo->hash_sec->contents
2473                    + (bucket + 2) * (ARCH_SIZE / 8));
2474       chain = get_word (finfo->output_bfd, bucketpos);
2475       put_word (finfo->output_bfd, h->dynindx, bucketpos);
2476       put_word (finfo->output_bfd, chain,
2477                 ((bfd_byte *) finfo->hash_sec->contents
2478                  + (bucketcount + 2 + h->dynindx) * (ARCH_SIZE / 8)));
2479     }
2480
2481   /* If we're stripping it, then it was just a dynamic symbol, and
2482      there's nothing else to do.  */
2483   if (strip)
2484     return true;
2485
2486   h->indx = finfo->output_bfd->symcount;
2487
2488   if (! elf_link_output_sym (finfo, h->root.root.string, &sym, input_sec))
2489     {
2490       eif->failed = true;
2491       return false;
2492     }
2493
2494   return true;
2495 }
2496
2497 /* Link an input file into the linker output file.  This function
2498    handles all the sections and relocations of the input file at once.
2499    This is so that we only have to read the local symbols once, and
2500    don't have to keep them in memory.  */
2501
2502 static boolean
2503 elf_link_input_bfd (finfo, input_bfd)
2504      struct elf_final_link_info *finfo;
2505      bfd *input_bfd;
2506 {
2507   boolean (*relocate_section) PARAMS ((bfd *, struct bfd_link_info *,
2508                                        bfd *, asection *, bfd_byte *,
2509                                        Elf_Internal_Rela *,
2510                                        Elf_Internal_Sym *, asection **));
2511   bfd *output_bfd;
2512   Elf_Internal_Shdr *symtab_hdr;
2513   size_t locsymcount;
2514   size_t extsymoff;
2515   Elf_External_Sym *esym;
2516   Elf_External_Sym *esymend;
2517   Elf_Internal_Sym *isym;
2518   long *pindex;
2519   asection **ppsection;
2520   asection *o;
2521
2522   output_bfd = finfo->output_bfd;
2523   relocate_section =
2524     get_elf_backend_data (output_bfd)->elf_backend_relocate_section;
2525
2526   /* If this is a dynamic object, we don't want to do anything here:
2527      we don't want the local symbols, and we don't want the section
2528      contents.  */
2529   if (elf_elfheader (input_bfd)->e_type == ET_DYN)
2530     return true;
2531
2532   symtab_hdr = &elf_tdata (input_bfd)->symtab_hdr;
2533   if (elf_bad_symtab (input_bfd))
2534     {
2535       locsymcount = symtab_hdr->sh_size / sizeof (Elf_External_Sym);
2536       extsymoff = 0;
2537     }
2538   else
2539     {
2540       locsymcount = symtab_hdr->sh_info;
2541       extsymoff = symtab_hdr->sh_info;
2542     }
2543
2544   /* Read the local symbols.  */
2545   if (locsymcount > 0
2546       && (bfd_seek (input_bfd, symtab_hdr->sh_offset, SEEK_SET) != 0
2547           || (bfd_read (finfo->external_syms, sizeof (Elf_External_Sym),
2548                         locsymcount, input_bfd)
2549               != locsymcount * sizeof (Elf_External_Sym))))
2550     return false;
2551
2552   /* Swap in the local symbols and write out the ones which we know
2553      are going into the output file.  */
2554   esym = finfo->external_syms;
2555   esymend = esym + locsymcount;
2556   isym = finfo->internal_syms;
2557   pindex = finfo->indices;
2558   ppsection = finfo->sections;
2559   for (; esym < esymend; esym++, isym++, pindex++, ppsection++)
2560     {
2561       asection *isec;
2562       const char *name;
2563       Elf_Internal_Sym osym;
2564
2565       elf_swap_symbol_in (input_bfd, esym, isym);
2566       *pindex = -1;
2567
2568       if (elf_bad_symtab (input_bfd))
2569         {
2570           if (ELF_ST_BIND (isym->st_info) != STB_LOCAL)
2571             {
2572               *ppsection = NULL;
2573               continue;
2574             }
2575         }
2576
2577       if (isym->st_shndx == SHN_UNDEF)
2578         isec = bfd_und_section_ptr;
2579       else if (isym->st_shndx > 0 && isym->st_shndx < SHN_LORESERVE)
2580         isec = section_from_elf_index (input_bfd, isym->st_shndx);
2581       else if (isym->st_shndx == SHN_ABS)
2582         isec = bfd_abs_section_ptr;
2583       else if (isym->st_shndx == SHN_COMMON)
2584         isec = bfd_com_section_ptr;
2585       else
2586         {
2587           /* Who knows?  */
2588           isec = NULL;
2589         }
2590
2591       *ppsection = isec;
2592
2593       /* Don't output the first, undefined, symbol.  */
2594       if (esym == finfo->external_syms)
2595         continue;
2596
2597       /* If we are stripping all symbols, we don't want to output this
2598          one.  */
2599       if (finfo->info->strip == strip_all)
2600         continue;
2601
2602       /* We never output section symbols.  Instead, we use the section
2603          symbol of the corresponding section in the output file.  */
2604       if (ELF_ST_TYPE (isym->st_info) == STT_SECTION)
2605         continue;
2606
2607       /* If we are discarding all local symbols, we don't want to
2608          output this one.  If we are generating a relocateable output
2609          file, then some of the local symbols may be required by
2610          relocs; we output them below as we discover that they are
2611          needed.  */
2612       if (finfo->info->discard == discard_all)
2613         continue;
2614
2615       /* Get the name of the symbol.  */
2616       name = bfd_elf_string_from_elf_section (input_bfd, symtab_hdr->sh_link,
2617                                           isym->st_name);
2618       if (name == NULL)
2619         return false;
2620
2621       /* See if we are discarding symbols with this name.  */
2622       if ((finfo->info->strip == strip_some
2623            && (bfd_hash_lookup (finfo->info->keep_hash, name, false, false)
2624                == NULL))
2625           || (finfo->info->discard == discard_l
2626               && strncmp (name, finfo->info->lprefix,
2627                           finfo->info->lprefix_len) == 0))
2628         continue;
2629
2630       /* If we get here, we are going to output this symbol.  */
2631
2632       osym = *isym;
2633
2634       /* Adjust the section index for the output file.  */
2635       osym.st_shndx = _bfd_elf_section_from_bfd_section (output_bfd,
2636                                                          isec->output_section);
2637       if (osym.st_shndx == (unsigned short) -1)
2638         return false;
2639
2640       *pindex = output_bfd->symcount;
2641
2642       /* ELF symbols in relocateable files are section relative, but
2643          in executable files they are virtual addresses.  Note that
2644          this code assumes that all ELF sections have an associated
2645          BFD section with a reasonable value for output_offset; below
2646          we assume that they also have a reasonable value for
2647          output_section.  Any special sections must be set up to meet
2648          these requirements.  */
2649       osym.st_value += isec->output_offset;
2650       if (! finfo->info->relocateable)
2651         osym.st_value += isec->output_section->vma;
2652
2653       if (! elf_link_output_sym (finfo, name, &osym, isec))
2654         return false;
2655     }
2656
2657   /* Relocate the contents of each section.  */
2658   for (o = input_bfd->sections; o != NULL; o = o->next)
2659     {
2660       if ((o->flags & SEC_HAS_CONTENTS) == 0)
2661         continue;
2662
2663       if ((o->flags & SEC_IN_MEMORY) != 0
2664           && input_bfd == elf_hash_table (finfo->info)->dynobj)
2665         {
2666           /* Section was created by elf_link_create_dynamic_sections.
2667              FIXME: This test is fragile.  */
2668           continue;
2669         }
2670
2671       /* Read the contents of the section.  */
2672       if (! bfd_get_section_contents (input_bfd, o, finfo->contents,
2673                                       (file_ptr) 0, o->_raw_size))
2674         return false;
2675
2676       if ((o->flags & SEC_RELOC) != 0)
2677         {
2678           Elf_Internal_Rela *internal_relocs;
2679
2680           /* Get the swapped relocs.  */
2681           internal_relocs = elf_link_read_relocs (input_bfd, o,
2682                                                   finfo->external_relocs,
2683                                                   finfo->internal_relocs,
2684                                                   false);
2685           if (internal_relocs == NULL
2686               && o->reloc_count > 0)
2687             return false;
2688
2689           /* Relocate the section by invoking a back end routine.
2690
2691              The back end routine is responsible for adjusting the
2692              section contents as necessary, and (if using Rela relocs
2693              and generating a relocateable output file) adjusting the
2694              reloc addend as necessary.
2695
2696              The back end routine does not have to worry about setting
2697              the reloc address or the reloc symbol index.
2698
2699              The back end routine is given a pointer to the swapped in
2700              internal symbols, and can access the hash table entries
2701              for the external symbols via elf_sym_hashes (input_bfd).
2702
2703              When generating relocateable output, the back end routine
2704              must handle STB_LOCAL/STT_SECTION symbols specially.  The
2705              output symbol is going to be a section symbol
2706              corresponding to the output section, which will require
2707              the addend to be adjusted.  */
2708
2709           if (! (*relocate_section) (output_bfd, finfo->info,
2710                                      input_bfd, o,
2711                                      finfo->contents,
2712                                      internal_relocs,
2713                                      finfo->internal_syms,
2714                                      finfo->sections))
2715             return false;
2716
2717           if (finfo->info->relocateable)
2718             {
2719               Elf_Internal_Rela *irela;
2720               Elf_Internal_Rela *irelaend;
2721               struct elf_link_hash_entry **rel_hash;
2722               Elf_Internal_Shdr *input_rel_hdr;
2723               Elf_Internal_Shdr *output_rel_hdr;
2724
2725               /* Adjust the reloc addresses and symbol indices.  */
2726
2727               irela = internal_relocs;
2728               irelaend = irela + o->reloc_count;
2729               rel_hash = (elf_section_data (o->output_section)->rel_hashes
2730                           + o->output_section->reloc_count);
2731               for (; irela < irelaend; irela++, rel_hash++)
2732                 {
2733                   long r_symndx;
2734                   Elf_Internal_Sym *isym;
2735                   asection *sec;
2736
2737                   irela->r_offset += o->output_offset;
2738
2739                   r_symndx = ELF_R_SYM (irela->r_info);
2740
2741                   if (r_symndx == 0)
2742                     continue;
2743
2744                   if (r_symndx >= locsymcount
2745                       || (elf_bad_symtab (input_bfd)
2746                           && finfo->sections[r_symndx] == NULL))
2747                     {
2748                       long indx;
2749
2750                       /* This is a reloc against a global symbol.  We
2751                          have not yet output all the local symbols, so
2752                          we do not know the symbol index of any global
2753                          symbol.  We set the rel_hash entry for this
2754                          reloc to point to the global hash table entry
2755                          for this symbol.  The symbol index is then
2756                          set at the end of elf_bfd_final_link.  */
2757                       indx = r_symndx - extsymoff;
2758                       *rel_hash = elf_sym_hashes (input_bfd)[indx];
2759
2760                       /* Setting the index to -2 tells
2761                          elf_link_output_extsym that this symbol is
2762                          used by a reloc.  */
2763                       BFD_ASSERT ((*rel_hash)->indx < 0);
2764                       (*rel_hash)->indx = -2;
2765
2766                       continue;
2767                     }
2768
2769                   /* This is a reloc against a local symbol. */
2770
2771                   *rel_hash = NULL;
2772                   isym = finfo->internal_syms + r_symndx;
2773                   sec = finfo->sections[r_symndx];
2774                   if (ELF_ST_TYPE (isym->st_info) == STT_SECTION)
2775                     {
2776                       /* I suppose the backend ought to fill in the
2777                          section of any STT_SECTION symbol against a
2778                          processor specific section.  */
2779                       if (sec != NULL && bfd_is_abs_section (sec))
2780                         r_symndx = 0;
2781                       else if (sec == NULL || sec->owner == NULL)
2782                         {
2783                           bfd_set_error (bfd_error_bad_value);
2784                           return false;
2785                         }
2786                       else
2787                         {
2788                           r_symndx = sec->output_section->target_index;
2789                           BFD_ASSERT (r_symndx != 0);
2790                         }
2791                     }
2792                   else
2793                     {
2794                       if (finfo->indices[r_symndx] == -1)
2795                         {
2796                           unsigned long link;
2797                           const char *name;
2798                           asection *osec;
2799
2800                           if (finfo->info->strip == strip_all)
2801                             {
2802                               /* You can't do ld -r -s.  */
2803                               bfd_set_error (bfd_error_invalid_operation);
2804                               return false;
2805                             }
2806
2807                           /* This symbol was skipped earlier, but
2808                              since it is needed by a reloc, we
2809                              must output it now.  */
2810                           link = symtab_hdr->sh_link;
2811                           name = bfd_elf_string_from_elf_section (input_bfd,
2812                                                                   link,
2813                                                                   isym->st_name);
2814                           if (name == NULL)
2815                             return false;
2816
2817                           osec = sec->output_section;
2818                           isym->st_shndx =
2819                             _bfd_elf_section_from_bfd_section (output_bfd,
2820                                                                osec);
2821                           if (isym->st_shndx == (unsigned short) -1)
2822                             return false;
2823
2824                           isym->st_value += sec->output_offset;
2825                           if (! finfo->info->relocateable)
2826                             isym->st_value += osec->vma;
2827
2828                           finfo->indices[r_symndx] = output_bfd->symcount;
2829
2830                           if (! elf_link_output_sym (finfo, name, isym, sec))
2831                             return false;
2832                         }
2833
2834                       r_symndx = finfo->indices[r_symndx];
2835                     }
2836
2837                   irela->r_info = ELF_R_INFO (r_symndx,
2838                                               ELF_R_TYPE (irela->r_info));
2839                 }
2840
2841               /* Swap out the relocs.  */
2842               input_rel_hdr = &elf_section_data (o)->rel_hdr;
2843               output_rel_hdr = &elf_section_data (o->output_section)->rel_hdr;
2844               BFD_ASSERT (output_rel_hdr->sh_entsize
2845                           == input_rel_hdr->sh_entsize);
2846               irela = internal_relocs;
2847               irelaend = irela + o->reloc_count;
2848               if (input_rel_hdr->sh_entsize == sizeof (Elf_External_Rel))
2849                 {
2850                   Elf_External_Rel *erel;
2851
2852                   erel = ((Elf_External_Rel *) output_rel_hdr->contents
2853                           + o->output_section->reloc_count);
2854                   for (; irela < irelaend; irela++, erel++)
2855                     {
2856                       Elf_Internal_Rel irel;
2857
2858                       irel.r_offset = irela->r_offset;
2859                       irel.r_info = irela->r_info;
2860                       BFD_ASSERT (irela->r_addend == 0);
2861                       elf_swap_reloc_out (output_bfd, &irel, erel);
2862                     }
2863                 }
2864               else
2865                 {
2866                   Elf_External_Rela *erela;
2867
2868                   BFD_ASSERT (input_rel_hdr->sh_entsize
2869                               == sizeof (Elf_External_Rela));
2870                   erela = ((Elf_External_Rela *) output_rel_hdr->contents
2871                            + o->output_section->reloc_count);
2872                   for (; irela < irelaend; irela++, erela++)
2873                     elf_swap_reloca_out (output_bfd, irela, erela);
2874                 }
2875
2876               o->output_section->reloc_count += o->reloc_count;
2877             }
2878         }
2879
2880       /* Write out the modified section contents.  */
2881       if (! bfd_set_section_contents (output_bfd, o->output_section,
2882                                       finfo->contents, o->output_offset,
2883                                       (o->_cooked_size != 0
2884                                        ? o->_cooked_size
2885                                        : o->_raw_size)))
2886         return false;
2887     }
2888
2889   return true;
2890 }
2891
2892 /* Generate a reloc when linking an ELF file.  This is a reloc
2893    requested by the linker, and does come from any input file.  This
2894    is used to build constructor and destructor tables when linking
2895    with -Ur.  */
2896
2897 static boolean
2898 elf_reloc_link_order (output_bfd, info, output_section, link_order)
2899      bfd *output_bfd;
2900      struct bfd_link_info *info;
2901      asection *output_section;
2902      struct bfd_link_order *link_order;
2903 {
2904   reloc_howto_type *howto;
2905   long indx;
2906   bfd_vma offset;
2907   struct elf_link_hash_entry **rel_hash_ptr;
2908   Elf_Internal_Shdr *rel_hdr;
2909
2910   howto = bfd_reloc_type_lookup (output_bfd, link_order->u.reloc.p->reloc);
2911   if (howto == NULL)
2912     {
2913       bfd_set_error (bfd_error_bad_value);
2914       return false;
2915     }
2916
2917   /* If this is an inplace reloc, we must write the addend into the
2918      object file.  */
2919   if (howto->partial_inplace
2920       && link_order->u.reloc.p->addend != 0)
2921     {
2922       bfd_size_type size;
2923       bfd_reloc_status_type rstat;
2924       bfd_byte *buf;
2925       boolean ok;
2926
2927       size = bfd_get_reloc_size (howto);
2928       buf = (bfd_byte *) bfd_zmalloc (size);
2929       if (buf == (bfd_byte *) NULL)
2930         {
2931           bfd_set_error (bfd_error_no_memory);
2932           return false;
2933         }
2934       rstat = _bfd_relocate_contents (howto, output_bfd,
2935                                       link_order->u.reloc.p->addend, buf);
2936       switch (rstat)
2937         {
2938         case bfd_reloc_ok:
2939           break;
2940         default:
2941         case bfd_reloc_outofrange:
2942           abort ();
2943         case bfd_reloc_overflow:
2944           if (! ((*info->callbacks->reloc_overflow)
2945                  (info,
2946                   (link_order->type == bfd_section_reloc_link_order
2947                    ? bfd_section_name (output_bfd,
2948                                        link_order->u.reloc.p->u.section)
2949                    : link_order->u.reloc.p->u.name),
2950                   howto->name, link_order->u.reloc.p->addend,
2951                   (bfd *) NULL, (asection *) NULL, (bfd_vma) 0)))
2952             {
2953               free (buf);
2954               return false;
2955             }
2956           break;
2957         }
2958       ok = bfd_set_section_contents (output_bfd, output_section, (PTR) buf,
2959                                      (file_ptr) link_order->offset, size);
2960       free (buf);
2961       if (! ok)
2962         return false;
2963     }
2964
2965   /* Figure out the symbol index.  */
2966   rel_hash_ptr = (elf_section_data (output_section)->rel_hashes
2967                   + output_section->reloc_count);
2968   if (link_order->type == bfd_section_reloc_link_order)
2969     {
2970       indx = link_order->u.reloc.p->u.section->target_index;
2971       BFD_ASSERT (indx != 0);
2972       *rel_hash_ptr = NULL;
2973     }
2974   else
2975     {
2976       struct elf_link_hash_entry *h;
2977
2978       h = elf_link_hash_lookup (elf_hash_table (info),
2979                                 link_order->u.reloc.p->u.name,
2980                                 false, false, true);
2981       if (h != NULL)
2982         {
2983           /* Setting the index to -2 tells elf_link_output_extsym that
2984              this symbol is used by a reloc.  */
2985           h->indx = -2;
2986           *rel_hash_ptr = h;
2987           indx = 0;
2988         }
2989       else
2990         {
2991           if (! ((*info->callbacks->unattached_reloc)
2992                  (info, link_order->u.reloc.p->u.name, (bfd *) NULL,
2993                   (asection *) NULL, (bfd_vma) 0)))
2994             return false;
2995           indx = 0;
2996         }
2997     }
2998
2999   /* The address of a reloc is relative to the section in a
3000      relocateable file, and is a virtual address in an executable
3001      file.  */
3002   offset = link_order->offset;
3003   if (! info->relocateable)
3004     offset += output_section->vma;
3005
3006   rel_hdr = &elf_section_data (output_section)->rel_hdr;
3007
3008   if (rel_hdr->sh_type == SHT_REL)
3009     {
3010       Elf_Internal_Rel irel;
3011       Elf_External_Rel *erel;
3012
3013       irel.r_offset = offset;
3014       irel.r_info = ELF_R_INFO (indx, howto->type);
3015       erel = ((Elf_External_Rel *) rel_hdr->contents
3016               + output_section->reloc_count);
3017       elf_swap_reloc_out (output_bfd, &irel, erel);
3018     }
3019   else
3020     {
3021       Elf_Internal_Rela irela;
3022       Elf_External_Rela *erela;
3023
3024       irela.r_offset = offset;
3025       irela.r_info = ELF_R_INFO (indx, howto->type);
3026       irela.r_addend = link_order->u.reloc.p->addend;
3027       erela = ((Elf_External_Rela *) rel_hdr->contents
3028                + output_section->reloc_count);
3029       elf_swap_reloca_out (output_bfd, &irela, erela);
3030     }
3031
3032   ++output_section->reloc_count;
3033
3034   return true;
3035 }
3036