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