OSDN Git Service

Switch sources over to use the GPL version 3
[pf3gnuchains/pf3gnuchains3x.git] / bfd / stabs.c
1 /* Stabs in sections linking support.
2    Copyright 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2003, 2004, 2005,
3    2006, 2007 Free Software Foundation, Inc.
4    Written by Ian Lance Taylor, Cygnus Support.
5
6    This file is part of BFD, the Binary File Descriptor library.
7
8    This program is free software; you can redistribute it and/or modify
9    it under the terms of the GNU General Public License as published by
10    the Free Software Foundation; either version 3 of the License, or
11    (at your option) any later version.
12
13    This program is distributed in the hope that it will be useful,
14    but WITHOUT ANY WARRANTY; without even the implied warranty of
15    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
16    GNU General Public License for more details.
17
18    You should have received a copy of the GNU General Public License
19    along with this program; if not, write to the Free Software
20    Foundation, Inc., 51 Franklin Street - Fifth Floor, Boston,
21    MA 02110-1301, USA.  */
22
23
24 /* This file contains support for linking stabs in sections, as used
25    on COFF and ELF.  */
26
27 #include "sysdep.h"
28 #include "bfd.h"
29 #include "libbfd.h"
30 #include "aout/stab_gnu.h"
31 #include "safe-ctype.h"
32
33 /* Stabs entries use a 12 byte format:
34      4 byte string table index
35      1 byte stab type
36      1 byte stab other field
37      2 byte stab desc field
38      4 byte stab value
39    FIXME: This will have to change for a 64 bit object format.
40
41    The stabs symbols are divided into compilation units.  For the
42    first entry in each unit, the type of 0, the value is the length of
43    the string table for this unit, and the desc field is the number of
44    stabs symbols for this unit.  */
45
46 #define STRDXOFF  0
47 #define TYPEOFF   4
48 #define OTHEROFF  5
49 #define DESCOFF   6
50 #define VALOFF    8
51 #define STABSIZE  12
52
53 /* A linked list of totals that we have found for a particular header
54    file.  A total is a unique identifier for a particular BINCL...EINCL
55    sequence of STABs that can be used to identify duplicate sequences.
56    It consists of three fields, 'sum_chars' which is the sum of all the
57    STABS characters; 'num_chars' which is the number of these charactes
58    and 'symb' which is a buffer of all the symbols in the sequence.  This
59    buffer is only checked as a last resort.  */
60
61 struct stab_link_includes_totals
62 {
63   struct stab_link_includes_totals *next;
64   bfd_vma sum_chars;  /* Accumulated sum of STABS characters.  */
65   bfd_vma num_chars;  /* Number of STABS characters.  */
66   const char* symb;   /* The STABS characters themselves.  */
67 };
68
69 /* An entry in the header file hash table.  */
70
71 struct stab_link_includes_entry
72 {
73   struct bfd_hash_entry root;
74   /* List of totals we have found for this file.  */
75   struct stab_link_includes_totals *totals;
76 };
77
78 /* This structure is used to hold a list of N_BINCL symbols, some of
79    which might be converted into N_EXCL symbols.  */
80
81 struct stab_excl_list
82 {
83   /* The next symbol to convert.  */
84   struct stab_excl_list *next;
85   /* The offset to this symbol in the section contents.  */
86   bfd_size_type offset;
87   /* The value to use for the symbol.  */
88   bfd_vma val;
89   /* The type of this symbol (N_BINCL or N_EXCL).  */
90   int type;
91 };
92
93 /* This structure is stored with each .stab section.  */
94
95 struct stab_section_info
96 {
97   /* This is a linked list of N_BINCL symbols which should be
98      converted into N_EXCL symbols.  */
99   struct stab_excl_list *excls;
100
101   /* This is used to map input stab offsets within their sections
102      to output stab offsets, to take into account stabs that have
103      been deleted.  If it is NULL, the output offsets are the same
104      as the input offsets, because no stabs have been deleted from
105      this section.  Otherwise the i'th entry is the number of
106      bytes of stabs that have been deleted prior to the i'th
107      stab.  */
108   bfd_size_type *cumulative_skips;
109
110   /* This is an array of string indices.  For each stab symbol, we
111      store the string index here.  If a stab symbol should not be
112      included in the final output, the string index is -1.  */
113   bfd_size_type stridxs[1];
114 };
115
116 \f
117 /* The function to create a new entry in the header file hash table.  */
118
119 static struct bfd_hash_entry *
120 stab_link_includes_newfunc (struct bfd_hash_entry *entry,
121                             struct bfd_hash_table *table,
122                             const char *string)
123 {
124   struct stab_link_includes_entry *ret =
125     (struct stab_link_includes_entry *) entry;
126
127   /* Allocate the structure if it has not already been allocated by a
128      subclass.  */
129   if (ret == NULL)
130     ret = bfd_hash_allocate (table,
131                              sizeof (struct stab_link_includes_entry));
132   if (ret == NULL)
133     return NULL;
134
135   /* Call the allocation method of the superclass.  */
136   ret = ((struct stab_link_includes_entry *)
137          bfd_hash_newfunc ((struct bfd_hash_entry *) ret, table, string));
138   if (ret)
139     /* Set local fields.  */
140     ret->totals = NULL;
141
142   return (struct bfd_hash_entry *) ret;
143 }
144 \f
145 /* This function is called for each input file from the add_symbols
146    pass of the linker.  */
147
148 bfd_boolean
149 _bfd_link_section_stabs (bfd *abfd,
150                          struct stab_info *sinfo,
151                          asection *stabsec,
152                          asection *stabstrsec,
153                          void * *psecinfo,
154                          bfd_size_type *pstring_offset)
155 {
156   bfd_boolean first;
157   bfd_size_type count, amt;
158   struct stab_section_info *secinfo;
159   bfd_byte *stabbuf = NULL;
160   bfd_byte *stabstrbuf = NULL;
161   bfd_byte *sym, *symend;
162   bfd_size_type stroff, next_stroff, skip;
163   bfd_size_type *pstridx;
164
165   if (stabsec->size == 0
166       || stabstrsec->size == 0)
167     /* This file does not contain stabs debugging information.  */
168     return TRUE;
169
170   if (stabsec->size % STABSIZE != 0)
171     /* Something is wrong with the format of these stab symbols.
172        Don't try to optimize them.  */
173     return TRUE;
174
175   if ((stabstrsec->flags & SEC_RELOC) != 0)
176     /* We shouldn't see relocations in the strings, and we aren't
177        prepared to handle them.  */
178     return TRUE;
179
180   if (bfd_is_abs_section (stabsec->output_section)
181       || bfd_is_abs_section (stabstrsec->output_section))
182     /* At least one of the sections is being discarded from the
183        link, so we should just ignore them.  */
184     return TRUE;
185
186   first = FALSE;
187
188   if (sinfo->stabstr == NULL)
189     {
190       flagword flags;
191
192       /* Initialize the stabs information we need to keep track of.  */
193       first = TRUE;
194       sinfo->strings = _bfd_stringtab_init ();
195       if (sinfo->strings == NULL)
196         goto error_return;
197       /* Make sure the first byte is zero.  */
198       (void) _bfd_stringtab_add (sinfo->strings, "", TRUE, TRUE);
199       if (! bfd_hash_table_init (&sinfo->includes,
200                                  stab_link_includes_newfunc,
201                                  sizeof (struct stab_link_includes_entry)))
202         goto error_return;
203       flags = (SEC_HAS_CONTENTS | SEC_READONLY | SEC_DEBUGGING
204                | SEC_LINKER_CREATED);
205       sinfo->stabstr = bfd_make_section_anyway_with_flags (abfd, ".stabstr",
206                                                            flags);
207       if (sinfo->stabstr == NULL)
208         goto error_return;
209     }
210
211   /* Initialize the information we are going to store for this .stab
212      section.  */
213   count = stabsec->size / STABSIZE;
214
215   amt = sizeof (struct stab_section_info);
216   amt += (count - 1) * sizeof (bfd_size_type);
217   *psecinfo = bfd_alloc (abfd, amt);
218   if (*psecinfo == NULL)
219     goto error_return;
220
221   secinfo = (struct stab_section_info *) *psecinfo;
222   secinfo->excls = NULL;
223   stabsec->rawsize = stabsec->size;
224   secinfo->cumulative_skips = NULL;
225   memset (secinfo->stridxs, 0, (size_t) count * sizeof (bfd_size_type));
226
227   /* Read the stabs information from abfd.  */
228   if (!bfd_malloc_and_get_section (abfd, stabsec, &stabbuf)
229       || !bfd_malloc_and_get_section (abfd, stabstrsec, &stabstrbuf))
230     goto error_return;
231
232   /* Look through the stabs symbols, work out the new string indices,
233      and identify N_BINCL symbols which can be eliminated.  */
234   stroff = 0;
235   /* The stabs sections can be split when
236      -split-by-reloc/-split-by-file is used.  We must keep track of
237      each stab section's place in the single concatenated string
238      table.  */
239   next_stroff = pstring_offset ? *pstring_offset : 0;
240   skip = 0;
241
242   symend = stabbuf + stabsec->size;
243   for (sym = stabbuf, pstridx = secinfo->stridxs;
244        sym < symend;
245        sym += STABSIZE, ++pstridx)
246     {
247       bfd_size_type symstroff;
248       int type;
249       const char *string;
250
251       if (*pstridx != 0)
252         /* This symbol has already been handled by an N_BINCL pass.  */
253         continue;
254
255       type = sym[TYPEOFF];
256
257       if (type == 0)
258         {
259           /* Special type 0 stabs indicate the offset to the next
260              string table.  We only copy the very first one.  */
261           stroff = next_stroff;
262           next_stroff += bfd_get_32 (abfd, sym + 8);
263           if (pstring_offset)
264             *pstring_offset = next_stroff;
265           if (! first)
266             {
267               *pstridx = (bfd_size_type) -1;
268               ++skip;
269               continue;
270             }
271           first = FALSE;
272         }
273
274       /* Store the string in the hash table, and record the index.  */
275       symstroff = stroff + bfd_get_32 (abfd, sym + STRDXOFF);
276       if (symstroff >= stabstrsec->size)
277         {
278           (*_bfd_error_handler)
279             (_("%B(%A+0x%lx): Stabs entry has invalid string index."),
280              abfd, stabsec, (long) (sym - stabbuf));
281           bfd_set_error (bfd_error_bad_value);
282           goto error_return;
283         }
284       string = (char *) stabstrbuf + symstroff;
285       *pstridx = _bfd_stringtab_add (sinfo->strings, string, TRUE, TRUE);
286
287       /* An N_BINCL symbol indicates the start of the stabs entries
288          for a header file.  We need to scan ahead to the next N_EINCL
289          symbol, ignoring nesting, adding up all the characters in the
290          symbol names, not including the file numbers in types (the
291          first number after an open parenthesis).  */
292       if (type == (int) N_BINCL)
293         {
294           bfd_vma sum_chars;
295           bfd_vma num_chars;
296           bfd_vma buf_len = 0;
297           char * symb;
298           char * symb_rover;
299           int nest;
300           bfd_byte * incl_sym;
301           struct stab_link_includes_entry * incl_entry;
302           struct stab_link_includes_totals * t;
303           struct stab_excl_list * ne;
304
305           symb = symb_rover = NULL;
306           sum_chars = num_chars = 0;
307           nest = 0;
308
309           for (incl_sym = sym + STABSIZE;
310                incl_sym < symend;
311                incl_sym += STABSIZE)
312             {
313               int incl_type;
314
315               incl_type = incl_sym[TYPEOFF];
316               if (incl_type == 0)
317                 break;
318               else if (incl_type == (int) N_EXCL)
319                 continue;
320               else if (incl_type == (int) N_EINCL)
321                 {
322                   if (nest == 0)
323                     break;
324                   --nest;
325                 }
326               else if (incl_type == (int) N_BINCL)
327                 ++nest;
328               else if (nest == 0)
329                 {
330                   const char *str;
331
332                   str = ((char *) stabstrbuf
333                          + stroff
334                          + bfd_get_32 (abfd, incl_sym + STRDXOFF));
335                   for (; *str != '\0'; str++)
336                     {
337                       if (num_chars >= buf_len)
338                         {
339                           buf_len += 32 * 1024;
340                           symb = bfd_realloc (symb, buf_len);
341                           if (symb == NULL)
342                             goto error_return;
343                           symb_rover = symb + num_chars;
344                         }
345                       * symb_rover ++ = * str;
346                       sum_chars += *str;
347                       num_chars ++;
348                       if (*str == '(')
349                         {
350                           /* Skip the file number.  */
351                           ++str;
352                           while (ISDIGIT (*str))
353                             ++str;
354                           --str;
355                         }
356                     }
357                 }
358             }
359
360           BFD_ASSERT (num_chars == (bfd_vma) (symb_rover - symb));
361
362           /* If we have already included a header file with the same
363              value, then replaced this one with an N_EXCL symbol.  */
364           incl_entry = (struct stab_link_includes_entry * )
365             bfd_hash_lookup (&sinfo->includes, string, TRUE, TRUE);
366           if (incl_entry == NULL)
367             goto error_return;
368
369           for (t = incl_entry->totals; t != NULL; t = t->next)
370             if (t->sum_chars == sum_chars
371                 && t->num_chars == num_chars
372                 && memcmp (t->symb, symb, num_chars) == 0)
373               break;
374
375           /* Record this symbol, so that we can set the value
376              correctly.  */
377           amt = sizeof *ne;
378           ne = bfd_alloc (abfd, amt);
379           if (ne == NULL)
380             goto error_return;
381           ne->offset = sym - stabbuf;
382           ne->val = sum_chars;
383           ne->type = (int) N_BINCL;
384           ne->next = secinfo->excls;
385           secinfo->excls = ne;
386
387           if (t == NULL)
388             {
389               /* This is the first time we have seen this header file
390                  with this set of stabs strings.  */
391               t = bfd_hash_allocate (&sinfo->includes, sizeof *t);
392               if (t == NULL)
393                 goto error_return;
394               t->sum_chars = sum_chars;
395               t->num_chars = num_chars;
396               t->symb = bfd_realloc (symb, num_chars); /* Trim data down.  */
397               t->next = incl_entry->totals;
398               incl_entry->totals = t;
399             }
400           else
401             {
402               bfd_size_type *incl_pstridx;
403
404               /* We have seen this header file before.  Tell the final
405                  pass to change the type to N_EXCL.  */
406               ne->type = (int) N_EXCL;
407
408               /* Free off superfluous symbols.  */
409               free (symb);
410
411               /* Mark the skipped symbols.  */
412
413               nest = 0;
414               for (incl_sym = sym + STABSIZE, incl_pstridx = pstridx + 1;
415                    incl_sym < symend;
416                    incl_sym += STABSIZE, ++incl_pstridx)
417                 {
418                   int incl_type;
419
420                   incl_type = incl_sym[TYPEOFF];
421
422                   if (incl_type == (int) N_EINCL)
423                     {
424                       if (nest == 0)
425                         {
426                           *incl_pstridx = (bfd_size_type) -1;
427                           ++skip;
428                           break;
429                         }
430                       --nest;
431                     }
432                   else if (incl_type == (int) N_BINCL)
433                     ++nest;
434                   else if (incl_type == (int) N_EXCL)
435                     /* Keep existing exclusion marks.  */
436                     continue;
437                   else if (nest == 0)
438                     {
439                       *incl_pstridx = (bfd_size_type) -1;
440                       ++skip;
441                     }
442                 }
443             }
444         }
445     }
446
447   free (stabbuf);
448   stabbuf = NULL;
449   free (stabstrbuf);
450   stabstrbuf = NULL;
451
452   /* We need to set the section sizes such that the linker will
453      compute the output section sizes correctly.  We set the .stab
454      size to not include the entries we don't want.  We set
455      SEC_EXCLUDE for the .stabstr section, so that it will be dropped
456      from the link.  We record the size of the strtab in the first
457      .stabstr section we saw, and make sure we don't set SEC_EXCLUDE
458      for that section.  */
459   stabsec->size = (count - skip) * STABSIZE;
460   if (stabsec->size == 0)
461     stabsec->flags |= SEC_EXCLUDE | SEC_KEEP;
462   stabstrsec->flags |= SEC_EXCLUDE | SEC_KEEP;
463   sinfo->stabstr->size = _bfd_stringtab_size (sinfo->strings);
464
465   /* Calculate the `cumulative_skips' array now that stabs have been
466      deleted for this section.  */
467
468   if (skip != 0)
469     {
470       bfd_size_type i, offset;
471       bfd_size_type *pskips;
472
473       amt = count * sizeof (bfd_size_type);
474       secinfo->cumulative_skips = bfd_alloc (abfd, amt);
475       if (secinfo->cumulative_skips == NULL)
476         goto error_return;
477
478       pskips = secinfo->cumulative_skips;
479       pstridx = secinfo->stridxs;
480       offset = 0;
481
482       for (i = 0; i < count; i++, pskips++, pstridx++)
483         {
484           *pskips = offset;
485           if (*pstridx == (bfd_size_type) -1)
486             offset += STABSIZE;
487         }
488
489       BFD_ASSERT (offset != 0);
490     }
491
492   return TRUE;
493
494  error_return:
495   if (stabbuf != NULL)
496     free (stabbuf);
497   if (stabstrbuf != NULL)
498     free (stabstrbuf);
499   return FALSE;
500 }
501 \f
502 /* This function is called for each input file before the stab
503    section is relocated.  It discards stab entries for discarded
504    functions and variables.  The function returns TRUE iff
505    any entries have been deleted.
506 */
507
508 bfd_boolean
509 _bfd_discard_section_stabs (bfd *abfd,
510                             asection *stabsec,
511                             void * psecinfo,
512                             bfd_boolean (*reloc_symbol_deleted_p) (bfd_vma, void *),
513                             void * cookie)
514 {
515   bfd_size_type count, amt;
516   struct stab_section_info *secinfo;
517   bfd_byte *stabbuf = NULL;
518   bfd_byte *sym, *symend;
519   bfd_size_type skip;
520   bfd_size_type *pstridx;
521   int deleting;
522
523   if (stabsec->size == 0)
524     /* This file does not contain stabs debugging information.  */
525     return FALSE;
526
527   if (stabsec->size % STABSIZE != 0)
528     /* Something is wrong with the format of these stab symbols.
529        Don't try to optimize them.  */
530     return FALSE;
531
532   if ((stabsec->output_section != NULL
533        && bfd_is_abs_section (stabsec->output_section)))
534     /* At least one of the sections is being discarded from the
535        link, so we should just ignore them.  */
536     return FALSE;
537
538   /* We should have initialized our data in _bfd_link_stab_sections.
539      If there was some bizarre error reading the string sections, though,
540      we might not have.  Bail rather than asserting.  */
541   if (psecinfo == NULL)
542     return FALSE;
543
544   count = stabsec->rawsize / STABSIZE;
545   secinfo = (struct stab_section_info *) psecinfo;
546
547   /* Read the stabs information from abfd.  */
548   if (!bfd_malloc_and_get_section (abfd, stabsec, &stabbuf))
549     goto error_return;
550
551   /* Look through the stabs symbols and discard any information for
552      discarded functions.  */
553   skip = 0;
554   deleting = -1;
555
556   symend = stabbuf + stabsec->rawsize;
557   for (sym = stabbuf, pstridx = secinfo->stridxs;
558        sym < symend;
559        sym += STABSIZE, ++pstridx)
560     {
561       int type;
562
563       if (*pstridx == (bfd_size_type) -1)
564         /* This stab was deleted in a previous pass.  */
565         continue;
566
567       type = sym[TYPEOFF];
568
569       if (type == (int) N_FUN)
570         {
571           int strx = bfd_get_32 (abfd, sym + STRDXOFF);
572
573           if (strx == 0)
574             {
575               if (deleting)
576                 {
577                   skip++;
578                   *pstridx = -1;
579                 }
580               deleting = -1;
581               continue;
582             }
583           deleting = 0;
584           if ((*reloc_symbol_deleted_p) (sym + VALOFF - stabbuf, cookie))
585             deleting = 1;
586         }
587
588       if (deleting == 1)
589         {
590           *pstridx = -1;
591           skip++;
592         }
593       else if (deleting == -1)
594         {
595           /* Outside of a function.  Check for deleted variables.  */
596           if (type == (int) N_STSYM || type == (int) N_LCSYM)
597             if ((*reloc_symbol_deleted_p) (sym + VALOFF - stabbuf, cookie))
598               {
599                 *pstridx = -1;
600                 skip ++;
601               }
602           /* We should also check for N_GSYM entries which reference a
603              deleted global, but those are less harmful to debuggers
604              and would require parsing the stab strings.  */
605         }
606     }
607
608   free (stabbuf);
609   stabbuf = NULL;
610
611   /* Shrink the stabsec as needed.  */
612   stabsec->size -= skip * STABSIZE;
613   if (stabsec->size == 0)
614     stabsec->flags |= SEC_EXCLUDE | SEC_KEEP;
615
616   /* Recalculate the `cumulative_skips' array now that stabs have been
617      deleted for this section.  */
618
619   if (skip != 0)
620     {
621       bfd_size_type i, offset;
622       bfd_size_type *pskips;
623
624       if (secinfo->cumulative_skips == NULL)
625         {
626           amt = count * sizeof (bfd_size_type);
627           secinfo->cumulative_skips = bfd_alloc (abfd, amt);
628           if (secinfo->cumulative_skips == NULL)
629             goto error_return;
630         }
631
632       pskips = secinfo->cumulative_skips;
633       pstridx = secinfo->stridxs;
634       offset = 0;
635
636       for (i = 0; i < count; i++, pskips++, pstridx++)
637         {
638           *pskips = offset;
639           if (*pstridx == (bfd_size_type) -1)
640             offset += STABSIZE;
641         }
642
643       BFD_ASSERT (offset != 0);
644     }
645
646   return skip > 0;
647
648  error_return:
649   if (stabbuf != NULL)
650     free (stabbuf);
651   return FALSE;
652 }
653
654 /* Write out the stab section.  This is called with the relocated
655    contents.  */
656
657 bfd_boolean
658 _bfd_write_section_stabs (bfd *output_bfd,
659                           struct stab_info *sinfo,
660                           asection *stabsec,
661                           void * *psecinfo,
662                           bfd_byte *contents)
663 {
664   struct stab_section_info *secinfo;
665   struct stab_excl_list *e;
666   bfd_byte *sym, *tosym, *symend;
667   bfd_size_type *pstridx;
668
669   secinfo = (struct stab_section_info *) *psecinfo;
670
671   if (secinfo == NULL)
672     return bfd_set_section_contents (output_bfd, stabsec->output_section,
673                                      contents, stabsec->output_offset,
674                                      stabsec->size);
675
676   /* Handle each N_BINCL entry.  */
677   for (e = secinfo->excls; e != NULL; e = e->next)
678     {
679       bfd_byte *excl_sym;
680
681       BFD_ASSERT (e->offset < stabsec->rawsize);
682       excl_sym = contents + e->offset;
683       bfd_put_32 (output_bfd, e->val, excl_sym + VALOFF);
684       excl_sym[TYPEOFF] = e->type;
685     }
686
687   /* Copy over all the stabs symbols, omitting the ones we don't want,
688      and correcting the string indices for those we do want.  */
689   tosym = contents;
690   symend = contents + stabsec->rawsize;
691   for (sym = contents, pstridx = secinfo->stridxs;
692        sym < symend;
693        sym += STABSIZE, ++pstridx)
694     {
695       if (*pstridx != (bfd_size_type) -1)
696         {
697           if (tosym != sym)
698             memcpy (tosym, sym, STABSIZE);
699           bfd_put_32 (output_bfd, *pstridx, tosym + STRDXOFF);
700
701           if (sym[TYPEOFF] == 0)
702             {
703               /* This is the header symbol for the stabs section.  We
704                  don't really need one, since we have merged all the
705                  input stabs sections into one, but we generate one
706                  for the benefit of readers which expect to see one.  */
707               BFD_ASSERT (sym == contents);
708               bfd_put_32 (output_bfd, _bfd_stringtab_size (sinfo->strings),
709                           tosym + VALOFF);
710               bfd_put_16 (output_bfd,
711                           stabsec->output_section->size / STABSIZE - 1,
712                           tosym + DESCOFF);
713             }
714
715           tosym += STABSIZE;
716         }
717     }
718
719   BFD_ASSERT ((bfd_size_type) (tosym - contents) == stabsec->size);
720
721   return bfd_set_section_contents (output_bfd, stabsec->output_section,
722                                    contents, (file_ptr) stabsec->output_offset,
723                                    stabsec->size);
724 }
725
726 /* Write out the .stabstr section.  */
727
728 bfd_boolean
729 _bfd_write_stab_strings (bfd *output_bfd, struct stab_info *sinfo)
730 {
731   if (bfd_is_abs_section (sinfo->stabstr->output_section))
732     /* The section was discarded from the link.  */
733     return TRUE;
734
735   BFD_ASSERT ((sinfo->stabstr->output_offset
736                + _bfd_stringtab_size (sinfo->strings))
737               <= sinfo->stabstr->output_section->size);
738
739   if (bfd_seek (output_bfd,
740                 (file_ptr) (sinfo->stabstr->output_section->filepos
741                             + sinfo->stabstr->output_offset),
742                 SEEK_SET) != 0)
743     return FALSE;
744
745   if (! _bfd_stringtab_emit (output_bfd, sinfo->strings))
746     return FALSE;
747
748   /* We no longer need the stabs information.  */
749   _bfd_stringtab_free (sinfo->strings);
750   bfd_hash_table_free (&sinfo->includes);
751
752   return TRUE;
753 }
754
755 /* Adjust an address in the .stab section.  Given OFFSET within
756    STABSEC, this returns the new offset in the adjusted stab section,
757    or -1 if the address refers to a stab which has been removed.  */
758
759 bfd_vma
760 _bfd_stab_section_offset (asection *stabsec,
761                           void * psecinfo,
762                           bfd_vma offset)
763 {
764   struct stab_section_info *secinfo;
765
766   secinfo = (struct stab_section_info *) psecinfo;
767
768   if (secinfo == NULL)
769     return offset;
770
771   if (offset >= stabsec->rawsize)
772     return offset - stabsec->rawsize + stabsec->size;
773
774   if (secinfo->cumulative_skips)
775     {
776       bfd_vma i;
777
778       i = offset / STABSIZE;
779
780       if (secinfo->stridxs [i] == (bfd_size_type) -1)
781         return (bfd_vma) -1;
782
783       return offset - secinfo->cumulative_skips [i];
784     }
785
786   return offset;
787 }