1*56bb7041Schristos /* dwarf2dbg.c - DWARF2 debug support
2*56bb7041Schristos    Copyright (C) 1999-2020 Free Software Foundation, Inc.
3*56bb7041Schristos    Contributed by David Mosberger-Tang <davidm@hpl.hp.com>
4*56bb7041Schristos 
5*56bb7041Schristos    This file is part of GAS, the GNU Assembler.
6*56bb7041Schristos 
7*56bb7041Schristos    GAS is free software; you can redistribute it and/or modify
8*56bb7041Schristos    it under the terms of the GNU General Public License as published by
9*56bb7041Schristos    the Free Software Foundation; either version 3, or (at your option)
10*56bb7041Schristos    any later version.
11*56bb7041Schristos 
12*56bb7041Schristos    GAS is distributed in the hope that it will be useful,
13*56bb7041Schristos    but WITHOUT ANY WARRANTY; without even the implied warranty of
14*56bb7041Schristos    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15*56bb7041Schristos    GNU General Public License for more details.
16*56bb7041Schristos 
17*56bb7041Schristos    You should have received a copy of the GNU General Public License
18*56bb7041Schristos    along with GAS; see the file COPYING.  If not, write to the Free
19*56bb7041Schristos    Software Foundation, 51 Franklin Street - Fifth Floor, Boston, MA
20*56bb7041Schristos    02110-1301, USA.  */
21*56bb7041Schristos 
22*56bb7041Schristos /* Logical line numbers can be controlled by the compiler via the
23*56bb7041Schristos    following directives:
24*56bb7041Schristos 
25*56bb7041Schristos 	.file FILENO "file.c"
26*56bb7041Schristos 	.loc  FILENO LINENO [COLUMN] [basic_block] [prologue_end] \
27*56bb7041Schristos 	      [epilogue_begin] [is_stmt VALUE] [isa VALUE] \
28*56bb7041Schristos 	      [discriminator VALUE]
29*56bb7041Schristos */
30*56bb7041Schristos 
31*56bb7041Schristos #include "as.h"
32*56bb7041Schristos #include "safe-ctype.h"
33*56bb7041Schristos 
34*56bb7041Schristos #ifdef HAVE_LIMITS_H
35*56bb7041Schristos #include <limits.h>
36*56bb7041Schristos #else
37*56bb7041Schristos #ifdef HAVE_SYS_PARAM_H
38*56bb7041Schristos #include <sys/param.h>
39*56bb7041Schristos #endif
40*56bb7041Schristos #ifndef INT_MAX
41*56bb7041Schristos #define INT_MAX (int) (((unsigned) (-1)) >> 1)
42*56bb7041Schristos #endif
43*56bb7041Schristos #endif
44*56bb7041Schristos 
45*56bb7041Schristos #include "dwarf2dbg.h"
46*56bb7041Schristos #include <filenames.h>
47*56bb7041Schristos 
48*56bb7041Schristos #ifdef HAVE_DOS_BASED_FILE_SYSTEM
49*56bb7041Schristos /* We need to decide which character to use as a directory separator.
50*56bb7041Schristos    Just because HAVE_DOS_BASED_FILE_SYSTEM is defined, it does not
51*56bb7041Schristos    necessarily mean that the backslash character is the one to use.
52*56bb7041Schristos    Some environments, eg Cygwin, can support both naming conventions.
53*56bb7041Schristos    So we use the heuristic that we only need to use the backslash if
54*56bb7041Schristos    the path is an absolute path starting with a DOS style drive
55*56bb7041Schristos    selector.  eg C: or D:  */
56*56bb7041Schristos # define INSERT_DIR_SEPARATOR(string, offset) \
57*56bb7041Schristos   do \
58*56bb7041Schristos     { \
59*56bb7041Schristos       if (offset > 1 \
60*56bb7041Schristos 	  && string[0] != 0 \
61*56bb7041Schristos 	  && string[1] == ':') \
62*56bb7041Schristos        string [offset] = '\\'; \
63*56bb7041Schristos       else \
64*56bb7041Schristos        string [offset] = '/'; \
65*56bb7041Schristos     } \
66*56bb7041Schristos   while (0)
67*56bb7041Schristos #else
68*56bb7041Schristos # define INSERT_DIR_SEPARATOR(string, offset) string[offset] = '/'
69*56bb7041Schristos #endif
70*56bb7041Schristos 
71*56bb7041Schristos #ifndef DWARF2_FORMAT
72*56bb7041Schristos # define DWARF2_FORMAT(SEC) dwarf2_format_32bit
73*56bb7041Schristos #endif
74*56bb7041Schristos 
75*56bb7041Schristos #ifndef DWARF2_ADDR_SIZE
76*56bb7041Schristos # define DWARF2_ADDR_SIZE(bfd) (bfd_arch_bits_per_address (bfd) / 8)
77*56bb7041Schristos #endif
78*56bb7041Schristos 
79*56bb7041Schristos #ifndef DWARF2_FILE_NAME
80*56bb7041Schristos #define DWARF2_FILE_NAME(FILENAME, DIRNAME) FILENAME
81*56bb7041Schristos #endif
82*56bb7041Schristos 
83*56bb7041Schristos #ifndef DWARF2_FILE_TIME_NAME
84*56bb7041Schristos #define DWARF2_FILE_TIME_NAME(FILENAME,DIRNAME) -1
85*56bb7041Schristos #endif
86*56bb7041Schristos 
87*56bb7041Schristos #ifndef DWARF2_FILE_SIZE_NAME
88*56bb7041Schristos #define DWARF2_FILE_SIZE_NAME(FILENAME,DIRNAME) -1
89*56bb7041Schristos #endif
90*56bb7041Schristos 
91*56bb7041Schristos #ifndef DWARF2_VERSION
92*56bb7041Schristos #define DWARF2_VERSION dwarf_level
93*56bb7041Schristos #endif
94*56bb7041Schristos 
95*56bb7041Schristos /* The .debug_aranges version has been 2 in DWARF version 2, 3 and 4. */
96*56bb7041Schristos #ifndef DWARF2_ARANGES_VERSION
97*56bb7041Schristos #define DWARF2_ARANGES_VERSION 2
98*56bb7041Schristos #endif
99*56bb7041Schristos 
100*56bb7041Schristos /* This implementation outputs version 3 .debug_line information.  */
101*56bb7041Schristos #ifndef DWARF2_LINE_VERSION
102*56bb7041Schristos #define DWARF2_LINE_VERSION (dwarf_level > 3 ? dwarf_level : 3)
103*56bb7041Schristos #endif
104*56bb7041Schristos 
105*56bb7041Schristos /* The .debug_rnglists has only been in DWARF version 5. */
106*56bb7041Schristos #ifndef DWARF2_RNGLISTS_VERSION
107*56bb7041Schristos #define DWARF2_RNGLISTS_VERSION 5
108*56bb7041Schristos #endif
109*56bb7041Schristos 
110*56bb7041Schristos #include "subsegs.h"
111*56bb7041Schristos 
112*56bb7041Schristos #include "dwarf2.h"
113*56bb7041Schristos 
114*56bb7041Schristos /* Since we can't generate the prolog until the body is complete, we
115*56bb7041Schristos    use three different subsegments for .debug_line: one holding the
116*56bb7041Schristos    prolog, one for the directory and filename info, and one for the
117*56bb7041Schristos    body ("statement program").  */
118*56bb7041Schristos #define DL_PROLOG	0
119*56bb7041Schristos #define DL_FILES	1
120*56bb7041Schristos #define DL_BODY		2
121*56bb7041Schristos 
122*56bb7041Schristos /* If linker relaxation might change offsets in the code, the DWARF special
123*56bb7041Schristos    opcodes and variable-length operands cannot be used.  If this macro is
124*56bb7041Schristos    nonzero, use the DW_LNS_fixed_advance_pc opcode instead.  */
125*56bb7041Schristos #ifndef DWARF2_USE_FIXED_ADVANCE_PC
126*56bb7041Schristos # define DWARF2_USE_FIXED_ADVANCE_PC	linkrelax
127*56bb7041Schristos #endif
128*56bb7041Schristos 
129*56bb7041Schristos /* First special line opcode - leave room for the standard opcodes.
130*56bb7041Schristos    Note: If you want to change this, you'll have to update the
131*56bb7041Schristos    "standard_opcode_lengths" table that is emitted below in
132*56bb7041Schristos    out_debug_line().  */
133*56bb7041Schristos #define DWARF2_LINE_OPCODE_BASE		13
134*56bb7041Schristos 
135*56bb7041Schristos #ifndef DWARF2_LINE_BASE
136*56bb7041Schristos   /* Minimum line offset in a special line info. opcode.  This value
137*56bb7041Schristos      was chosen to give a reasonable range of values.  */
138*56bb7041Schristos # define DWARF2_LINE_BASE		-5
139*56bb7041Schristos #endif
140*56bb7041Schristos 
141*56bb7041Schristos /* Range of line offsets in a special line info. opcode.  */
142*56bb7041Schristos #ifndef DWARF2_LINE_RANGE
143*56bb7041Schristos # define DWARF2_LINE_RANGE		14
144*56bb7041Schristos #endif
145*56bb7041Schristos 
146*56bb7041Schristos #ifndef DWARF2_LINE_MIN_INSN_LENGTH
147*56bb7041Schristos   /* Define the architecture-dependent minimum instruction length (in
148*56bb7041Schristos      bytes).  This value should be rather too small than too big.  */
149*56bb7041Schristos # define DWARF2_LINE_MIN_INSN_LENGTH	1
150*56bb7041Schristos #endif
151*56bb7041Schristos 
152*56bb7041Schristos /* Flag that indicates the initial value of the is_stmt_start flag.  */
153*56bb7041Schristos #define	DWARF2_LINE_DEFAULT_IS_STMT	1
154*56bb7041Schristos 
155*56bb7041Schristos #ifndef DWARF2_LINE_MAX_OPS_PER_INSN
156*56bb7041Schristos #define DWARF2_LINE_MAX_OPS_PER_INSN	1
157*56bb7041Schristos #endif
158*56bb7041Schristos 
159*56bb7041Schristos /* Given a special op, return the line skip amount.  */
160*56bb7041Schristos #define SPECIAL_LINE(op) \
161*56bb7041Schristos 	(((op) - DWARF2_LINE_OPCODE_BASE)%DWARF2_LINE_RANGE + DWARF2_LINE_BASE)
162*56bb7041Schristos 
163*56bb7041Schristos /* Given a special op, return the address skip amount (in units of
164*56bb7041Schristos    DWARF2_LINE_MIN_INSN_LENGTH.  */
165*56bb7041Schristos #define SPECIAL_ADDR(op) (((op) - DWARF2_LINE_OPCODE_BASE)/DWARF2_LINE_RANGE)
166*56bb7041Schristos 
167*56bb7041Schristos /* The maximum address skip amount that can be encoded with a special op.  */
168*56bb7041Schristos #define MAX_SPECIAL_ADDR_DELTA		SPECIAL_ADDR(255)
169*56bb7041Schristos 
170*56bb7041Schristos #ifndef TC_PARSE_CONS_RETURN_NONE
171*56bb7041Schristos #define TC_PARSE_CONS_RETURN_NONE BFD_RELOC_NONE
172*56bb7041Schristos #endif
173*56bb7041Schristos 
174*56bb7041Schristos struct line_entry
175*56bb7041Schristos {
176*56bb7041Schristos   struct line_entry *next;
177*56bb7041Schristos   symbolS *label;
178*56bb7041Schristos   struct dwarf2_line_info loc;
179*56bb7041Schristos };
180*56bb7041Schristos 
181*56bb7041Schristos /* Don't change the offset of next in line_entry.  set_or_check_view
182*56bb7041Schristos    calls in dwarf2_gen_line_info_1 depend on it.  */
183*56bb7041Schristos static char unused[offsetof(struct line_entry, next) ? -1 : 1]
184*56bb7041Schristos ATTRIBUTE_UNUSED;
185*56bb7041Schristos 
186*56bb7041Schristos struct line_subseg
187*56bb7041Schristos {
188*56bb7041Schristos   struct line_subseg *next;
189*56bb7041Schristos   subsegT subseg;
190*56bb7041Schristos   struct line_entry *head;
191*56bb7041Schristos   struct line_entry **ptail;
192*56bb7041Schristos   struct line_entry **pmove_tail;
193*56bb7041Schristos };
194*56bb7041Schristos 
195*56bb7041Schristos struct line_seg
196*56bb7041Schristos {
197*56bb7041Schristos   struct line_seg *next;
198*56bb7041Schristos   segT seg;
199*56bb7041Schristos   struct line_subseg *head;
200*56bb7041Schristos   symbolS *text_start;
201*56bb7041Schristos   symbolS *text_end;
202*56bb7041Schristos };
203*56bb7041Schristos 
204*56bb7041Schristos /* Collects data for all line table entries during assembly.  */
205*56bb7041Schristos static struct line_seg *all_segs;
206*56bb7041Schristos static struct line_seg **last_seg_ptr;
207*56bb7041Schristos 
208*56bb7041Schristos #define NUM_MD5_BYTES       16
209*56bb7041Schristos 
210*56bb7041Schristos struct file_entry
211*56bb7041Schristos {
212*56bb7041Schristos   const char *   filename;
213*56bb7041Schristos   unsigned int   dir;
214*56bb7041Schristos   bfd_boolean    auto_assigned;
215*56bb7041Schristos   unsigned char  md5[NUM_MD5_BYTES];
216*56bb7041Schristos };
217*56bb7041Schristos 
218*56bb7041Schristos /* Table of files used by .debug_line.  */
219*56bb7041Schristos static struct file_entry *files;
220*56bb7041Schristos static unsigned int files_in_use;
221*56bb7041Schristos static unsigned int files_allocated;
222*56bb7041Schristos 
223*56bb7041Schristos /* Table of directories used by .debug_line.  */
224*56bb7041Schristos static char **       dirs = NULL;
225*56bb7041Schristos static unsigned int  dirs_in_use = 0;
226*56bb7041Schristos static unsigned int  dirs_allocated = 0;
227*56bb7041Schristos 
228*56bb7041Schristos /* TRUE when we've seen a .loc directive recently.  Used to avoid
229*56bb7041Schristos    doing work when there's nothing to do.  Will be reset by
230*56bb7041Schristos    dwarf2_consume_line_info.  */
231*56bb7041Schristos bfd_boolean dwarf2_loc_directive_seen;
232*56bb7041Schristos 
233*56bb7041Schristos /* TRUE when we've seen any .loc directive at any time during parsing.
234*56bb7041Schristos    Indicates the user wants us to generate a .debug_line section.
235*56bb7041Schristos    Used in dwarf2_finish as sanity check.  */
236*56bb7041Schristos static bfd_boolean dwarf2_any_loc_directive_seen;
237*56bb7041Schristos 
238*56bb7041Schristos /* TRUE when we're supposed to set the basic block mark whenever a
239*56bb7041Schristos    label is seen.  */
240*56bb7041Schristos bfd_boolean dwarf2_loc_mark_labels;
241*56bb7041Schristos 
242*56bb7041Schristos /* Current location as indicated by the most recent .loc directive.  */
243*56bb7041Schristos static struct dwarf2_line_info current =
244*56bb7041Schristos {
245*56bb7041Schristos   1, 1, 0, 0,
246*56bb7041Schristos   DWARF2_LINE_DEFAULT_IS_STMT ? DWARF2_FLAG_IS_STMT : 0,
247*56bb7041Schristos   0, NULL
248*56bb7041Schristos };
249*56bb7041Schristos 
250*56bb7041Schristos /* This symbol is used to recognize view number forced resets in loc
251*56bb7041Schristos    lists.  */
252*56bb7041Schristos static symbolS *force_reset_view;
253*56bb7041Schristos 
254*56bb7041Schristos /* This symbol evaluates to an expression that, if nonzero, indicates
255*56bb7041Schristos    some view assert check failed.  */
256*56bb7041Schristos static symbolS *view_assert_failed;
257*56bb7041Schristos 
258*56bb7041Schristos /* The size of an address on the target.  */
259*56bb7041Schristos static unsigned int sizeof_address;
260*56bb7041Schristos 
261*56bb7041Schristos #ifndef TC_DWARF2_EMIT_OFFSET
262*56bb7041Schristos #define TC_DWARF2_EMIT_OFFSET  generic_dwarf2_emit_offset
263*56bb7041Schristos 
264*56bb7041Schristos /* Create an offset to .dwarf2_*.  */
265*56bb7041Schristos 
266*56bb7041Schristos static void
generic_dwarf2_emit_offset(symbolS * symbol,unsigned int size)267*56bb7041Schristos generic_dwarf2_emit_offset (symbolS *symbol, unsigned int size)
268*56bb7041Schristos {
269*56bb7041Schristos   expressionS exp;
270*56bb7041Schristos 
271*56bb7041Schristos   memset (&exp, 0, sizeof exp);
272*56bb7041Schristos   exp.X_op = O_symbol;
273*56bb7041Schristos   exp.X_add_symbol = symbol;
274*56bb7041Schristos   exp.X_add_number = 0;
275*56bb7041Schristos   emit_expr (&exp, size);
276*56bb7041Schristos }
277*56bb7041Schristos #endif
278*56bb7041Schristos 
279*56bb7041Schristos /* Find or create (if CREATE_P) an entry for SEG+SUBSEG in ALL_SEGS.  */
280*56bb7041Schristos 
281*56bb7041Schristos static struct line_subseg *
get_line_subseg(segT seg,subsegT subseg,bfd_boolean create_p)282*56bb7041Schristos get_line_subseg (segT seg, subsegT subseg, bfd_boolean create_p)
283*56bb7041Schristos {
284*56bb7041Schristos   struct line_seg *s = seg_info (seg)->dwarf2_line_seg;
285*56bb7041Schristos   struct line_subseg **pss, *lss;
286*56bb7041Schristos 
287*56bb7041Schristos   if (s == NULL)
288*56bb7041Schristos     {
289*56bb7041Schristos       if (!create_p)
290*56bb7041Schristos 	return NULL;
291*56bb7041Schristos 
292*56bb7041Schristos       s = XNEW (struct line_seg);
293*56bb7041Schristos       s->next = NULL;
294*56bb7041Schristos       s->seg = seg;
295*56bb7041Schristos       s->head = NULL;
296*56bb7041Schristos       *last_seg_ptr = s;
297*56bb7041Schristos       last_seg_ptr = &s->next;
298*56bb7041Schristos       seg_info (seg)->dwarf2_line_seg = s;
299*56bb7041Schristos     }
300*56bb7041Schristos 
301*56bb7041Schristos   gas_assert (seg == s->seg);
302*56bb7041Schristos 
303*56bb7041Schristos   for (pss = &s->head; (lss = *pss) != NULL ; pss = &lss->next)
304*56bb7041Schristos     {
305*56bb7041Schristos       if (lss->subseg == subseg)
306*56bb7041Schristos 	goto found_subseg;
307*56bb7041Schristos       if (lss->subseg > subseg)
308*56bb7041Schristos 	break;
309*56bb7041Schristos     }
310*56bb7041Schristos 
311*56bb7041Schristos   lss = XNEW (struct line_subseg);
312*56bb7041Schristos   lss->next = *pss;
313*56bb7041Schristos   lss->subseg = subseg;
314*56bb7041Schristos   lss->head = NULL;
315*56bb7041Schristos   lss->ptail = &lss->head;
316*56bb7041Schristos   lss->pmove_tail = &lss->head;
317*56bb7041Schristos   *pss = lss;
318*56bb7041Schristos 
319*56bb7041Schristos  found_subseg:
320*56bb7041Schristos   return lss;
321*56bb7041Schristos }
322*56bb7041Schristos 
323*56bb7041Schristos /* (Un)reverse the line_entry list starting from H.  */
324*56bb7041Schristos 
325*56bb7041Schristos static struct line_entry *
reverse_line_entry_list(struct line_entry * h)326*56bb7041Schristos reverse_line_entry_list (struct line_entry *h)
327*56bb7041Schristos {
328*56bb7041Schristos   struct line_entry *p = NULL, *e, *n;
329*56bb7041Schristos 
330*56bb7041Schristos   for (e = h; e; e = n)
331*56bb7041Schristos     {
332*56bb7041Schristos       n = e->next;
333*56bb7041Schristos       e->next = p;
334*56bb7041Schristos       p = e;
335*56bb7041Schristos     }
336*56bb7041Schristos   return p;
337*56bb7041Schristos }
338*56bb7041Schristos 
339*56bb7041Schristos /* Compute the view for E based on the previous entry P.  If we
340*56bb7041Schristos    introduce an (undefined) view symbol for P, and H is given (P must
341*56bb7041Schristos    be the tail in this case), introduce view symbols for earlier list
342*56bb7041Schristos    entries as well, until one of them is constant.  */
343*56bb7041Schristos 
344*56bb7041Schristos static void
set_or_check_view(struct line_entry * e,struct line_entry * p,struct line_entry * h)345*56bb7041Schristos set_or_check_view (struct line_entry *e, struct line_entry *p,
346*56bb7041Schristos 		   struct line_entry *h)
347*56bb7041Schristos {
348*56bb7041Schristos   expressionS viewx;
349*56bb7041Schristos 
350*56bb7041Schristos   memset (&viewx, 0, sizeof (viewx));
351*56bb7041Schristos   viewx.X_unsigned = 1;
352*56bb7041Schristos 
353*56bb7041Schristos   /* First, compute !(E->label > P->label), to tell whether or not
354*56bb7041Schristos      we're to reset the view number.  If we can't resolve it to a
355*56bb7041Schristos      constant, keep it symbolic.  */
356*56bb7041Schristos   if (!p || (e->loc.view == force_reset_view && force_reset_view))
357*56bb7041Schristos     {
358*56bb7041Schristos       viewx.X_op = O_constant;
359*56bb7041Schristos       viewx.X_add_number = 0;
360*56bb7041Schristos       viewx.X_add_symbol = NULL;
361*56bb7041Schristos       viewx.X_op_symbol = NULL;
362*56bb7041Schristos     }
363*56bb7041Schristos   else
364*56bb7041Schristos     {
365*56bb7041Schristos       viewx.X_op = O_gt;
366*56bb7041Schristos       viewx.X_add_number = 0;
367*56bb7041Schristos       viewx.X_add_symbol = e->label;
368*56bb7041Schristos       viewx.X_op_symbol = p->label;
369*56bb7041Schristos       resolve_expression (&viewx);
370*56bb7041Schristos       if (viewx.X_op == O_constant)
371*56bb7041Schristos 	viewx.X_add_number = !viewx.X_add_number;
372*56bb7041Schristos       else
373*56bb7041Schristos 	{
374*56bb7041Schristos 	  viewx.X_add_symbol = make_expr_symbol (&viewx);
375*56bb7041Schristos 	  viewx.X_add_number = 0;
376*56bb7041Schristos 	  viewx.X_op_symbol = NULL;
377*56bb7041Schristos 	  viewx.X_op = O_logical_not;
378*56bb7041Schristos 	}
379*56bb7041Schristos     }
380*56bb7041Schristos 
381*56bb7041Schristos   if (S_IS_DEFINED (e->loc.view) && symbol_constant_p (e->loc.view))
382*56bb7041Schristos     {
383*56bb7041Schristos       expressionS *value = symbol_get_value_expression (e->loc.view);
384*56bb7041Schristos       /* We can't compare the view numbers at this point, because in
385*56bb7041Schristos 	 VIEWX we've only determined whether we're to reset it so
386*56bb7041Schristos 	 far.  */
387*56bb7041Schristos       if (viewx.X_op == O_constant)
388*56bb7041Schristos 	{
389*56bb7041Schristos 	  if (!value->X_add_number != !viewx.X_add_number)
390*56bb7041Schristos 	    as_bad (_("view number mismatch"));
391*56bb7041Schristos 	}
392*56bb7041Schristos       /* Record the expression to check it later.  It is the result of
393*56bb7041Schristos 	 a logical not, thus 0 or 1.  We just add up all such deferred
394*56bb7041Schristos 	 expressions, and resolve it at the end.  */
395*56bb7041Schristos       else if (!value->X_add_number)
396*56bb7041Schristos 	{
397*56bb7041Schristos 	  symbolS *deferred = make_expr_symbol (&viewx);
398*56bb7041Schristos 	  if (view_assert_failed)
399*56bb7041Schristos 	    {
400*56bb7041Schristos 	      expressionS chk;
401*56bb7041Schristos 
402*56bb7041Schristos 	      memset (&chk, 0, sizeof (chk));
403*56bb7041Schristos 	      chk.X_unsigned = 1;
404*56bb7041Schristos 	      chk.X_op = O_add;
405*56bb7041Schristos 	      chk.X_add_number = 0;
406*56bb7041Schristos 	      chk.X_add_symbol = view_assert_failed;
407*56bb7041Schristos 	      chk.X_op_symbol = deferred;
408*56bb7041Schristos 	      deferred = make_expr_symbol (&chk);
409*56bb7041Schristos 	    }
410*56bb7041Schristos 	  view_assert_failed = deferred;
411*56bb7041Schristos 	}
412*56bb7041Schristos     }
413*56bb7041Schristos 
414*56bb7041Schristos   if (viewx.X_op != O_constant || viewx.X_add_number)
415*56bb7041Schristos     {
416*56bb7041Schristos       expressionS incv;
417*56bb7041Schristos 
418*56bb7041Schristos       if (!p->loc.view)
419*56bb7041Schristos 	{
420*56bb7041Schristos 	  p->loc.view = symbol_temp_make ();
421*56bb7041Schristos 	  gas_assert (!S_IS_DEFINED (p->loc.view));
422*56bb7041Schristos 	}
423*56bb7041Schristos 
424*56bb7041Schristos       memset (&incv, 0, sizeof (incv));
425*56bb7041Schristos       incv.X_unsigned = 1;
426*56bb7041Schristos       incv.X_op = O_symbol;
427*56bb7041Schristos       incv.X_add_symbol = p->loc.view;
428*56bb7041Schristos       incv.X_add_number = 1;
429*56bb7041Schristos 
430*56bb7041Schristos       if (viewx.X_op == O_constant)
431*56bb7041Schristos 	{
432*56bb7041Schristos 	  gas_assert (viewx.X_add_number == 1);
433*56bb7041Schristos 	  viewx = incv;
434*56bb7041Schristos 	}
435*56bb7041Schristos       else
436*56bb7041Schristos 	{
437*56bb7041Schristos 	  viewx.X_add_symbol = make_expr_symbol (&viewx);
438*56bb7041Schristos 	  viewx.X_add_number = 0;
439*56bb7041Schristos 	  viewx.X_op_symbol = make_expr_symbol (&incv);
440*56bb7041Schristos 	  viewx.X_op = O_multiply;
441*56bb7041Schristos 	}
442*56bb7041Schristos     }
443*56bb7041Schristos 
444*56bb7041Schristos   if (!S_IS_DEFINED (e->loc.view))
445*56bb7041Schristos     {
446*56bb7041Schristos       symbol_set_value_expression (e->loc.view, &viewx);
447*56bb7041Schristos       S_SET_SEGMENT (e->loc.view, expr_section);
448*56bb7041Schristos       symbol_set_frag (e->loc.view, &zero_address_frag);
449*56bb7041Schristos     }
450*56bb7041Schristos 
451*56bb7041Schristos   /* Define and attempt to simplify any earlier views needed to
452*56bb7041Schristos      compute E's.  */
453*56bb7041Schristos   if (h && p && p->loc.view && !S_IS_DEFINED (p->loc.view))
454*56bb7041Schristos     {
455*56bb7041Schristos       struct line_entry *h2;
456*56bb7041Schristos       /* Reverse the list to avoid quadratic behavior going backwards
457*56bb7041Schristos 	 in a single-linked list.  */
458*56bb7041Schristos       struct line_entry *r = reverse_line_entry_list (h);
459*56bb7041Schristos 
460*56bb7041Schristos       gas_assert (r == p);
461*56bb7041Schristos       /* Set or check views until we find a defined or absent view.  */
462*56bb7041Schristos       do
463*56bb7041Schristos 	{
464*56bb7041Schristos 	  /* Do not define the head of a (sub?)segment view while
465*56bb7041Schristos 	     handling others.  It would be defined too early, without
466*56bb7041Schristos 	     regard to the last view of other subsegments.
467*56bb7041Schristos 	     set_or_check_view will be called for every head segment
468*56bb7041Schristos 	     that needs it.  */
469*56bb7041Schristos 	  if (r == h)
470*56bb7041Schristos 	    break;
471*56bb7041Schristos 	  set_or_check_view (r, r->next, NULL);
472*56bb7041Schristos 	}
473*56bb7041Schristos       while (r->next && r->next->loc.view && !S_IS_DEFINED (r->next->loc.view)
474*56bb7041Schristos 	     && (r = r->next));
475*56bb7041Schristos 
476*56bb7041Schristos       /* Unreverse the list, so that we can go forward again.  */
477*56bb7041Schristos       h2 = reverse_line_entry_list (p);
478*56bb7041Schristos       gas_assert (h2 == h);
479*56bb7041Schristos 
480*56bb7041Schristos       /* Starting from the last view we just defined, attempt to
481*56bb7041Schristos 	 simplify the view expressions, until we do so to P.  */
482*56bb7041Schristos       do
483*56bb7041Schristos 	{
484*56bb7041Schristos 	  /* The head view of a subsegment may remain undefined while
485*56bb7041Schristos 	     handling other elements, before it is linked to the last
486*56bb7041Schristos 	     view of the previous subsegment.  */
487*56bb7041Schristos 	  if (r == h)
488*56bb7041Schristos 	    continue;
489*56bb7041Schristos 	  gas_assert (S_IS_DEFINED (r->loc.view));
490*56bb7041Schristos 	  resolve_expression (symbol_get_value_expression (r->loc.view));
491*56bb7041Schristos 	}
492*56bb7041Schristos       while (r != p && (r = r->next));
493*56bb7041Schristos 
494*56bb7041Schristos       /* Now that we've defined and computed all earlier views that might
495*56bb7041Schristos 	 be needed to compute E's, attempt to simplify it.  */
496*56bb7041Schristos       resolve_expression (symbol_get_value_expression (e->loc.view));
497*56bb7041Schristos     }
498*56bb7041Schristos }
499*56bb7041Schristos 
500*56bb7041Schristos /* Record an entry for LOC occurring at LABEL.  */
501*56bb7041Schristos 
502*56bb7041Schristos static void
dwarf2_gen_line_info_1(symbolS * label,struct dwarf2_line_info * loc)503*56bb7041Schristos dwarf2_gen_line_info_1 (symbolS *label, struct dwarf2_line_info *loc)
504*56bb7041Schristos {
505*56bb7041Schristos   struct line_subseg *lss;
506*56bb7041Schristos   struct line_entry *e;
507*56bb7041Schristos 
508*56bb7041Schristos   e = XNEW (struct line_entry);
509*56bb7041Schristos   e->next = NULL;
510*56bb7041Schristos   e->label = label;
511*56bb7041Schristos   e->loc = *loc;
512*56bb7041Schristos 
513*56bb7041Schristos   lss = get_line_subseg (now_seg, now_subseg, TRUE);
514*56bb7041Schristos 
515*56bb7041Schristos   /* Subseg heads are chained to previous subsegs in
516*56bb7041Schristos      dwarf2_finish.  */
517*56bb7041Schristos   if (loc->view && lss->head)
518*56bb7041Schristos     set_or_check_view (e,
519*56bb7041Schristos 		       (struct line_entry *)lss->ptail,
520*56bb7041Schristos 		       lss->head);
521*56bb7041Schristos 
522*56bb7041Schristos   *lss->ptail = e;
523*56bb7041Schristos   lss->ptail = &e->next;
524*56bb7041Schristos }
525*56bb7041Schristos 
526*56bb7041Schristos /* Record an entry for LOC occurring at OFS within the current fragment.  */
527*56bb7041Schristos 
528*56bb7041Schristos void
dwarf2_gen_line_info(addressT ofs,struct dwarf2_line_info * loc)529*56bb7041Schristos dwarf2_gen_line_info (addressT ofs, struct dwarf2_line_info *loc)
530*56bb7041Schristos {
531*56bb7041Schristos   static unsigned int line = -1;
532*56bb7041Schristos   static unsigned int filenum = -1;
533*56bb7041Schristos 
534*56bb7041Schristos   symbolS *sym;
535*56bb7041Schristos 
536*56bb7041Schristos   /* Early out for as-yet incomplete location information.  */
537*56bb7041Schristos   if (loc->line == 0)
538*56bb7041Schristos     return;
539*56bb7041Schristos   if (loc->filenum == 0 && DWARF2_LINE_VERSION < 5)
540*56bb7041Schristos     return;
541*56bb7041Schristos 
542*56bb7041Schristos   /* Don't emit sequences of line symbols for the same line when the
543*56bb7041Schristos      symbols apply to assembler code.  It is necessary to emit
544*56bb7041Schristos      duplicate line symbols when a compiler asks for them, because GDB
545*56bb7041Schristos      uses them to determine the end of the prologue.  */
546*56bb7041Schristos   if (debug_type == DEBUG_DWARF2
547*56bb7041Schristos       && line == loc->line && filenum == loc->filenum)
548*56bb7041Schristos     return;
549*56bb7041Schristos 
550*56bb7041Schristos   line = loc->line;
551*56bb7041Schristos   filenum = loc->filenum;
552*56bb7041Schristos 
553*56bb7041Schristos   if (linkrelax)
554*56bb7041Schristos     {
555*56bb7041Schristos       char name[120];
556*56bb7041Schristos 
557*56bb7041Schristos       /* Use a non-fake name for the line number location,
558*56bb7041Schristos 	 so that it can be referred to by relocations.  */
559*56bb7041Schristos       sprintf (name, ".Loc.%u.%u", line, filenum);
560*56bb7041Schristos       sym = symbol_new (name, now_seg, frag_now, ofs);
561*56bb7041Schristos     }
562*56bb7041Schristos   else
563*56bb7041Schristos     sym = symbol_temp_new (now_seg, frag_now, ofs);
564*56bb7041Schristos   dwarf2_gen_line_info_1 (sym, loc);
565*56bb7041Schristos }
566*56bb7041Schristos 
567*56bb7041Schristos static const char *
get_basename(const char * pathname)568*56bb7041Schristos get_basename (const char * pathname)
569*56bb7041Schristos {
570*56bb7041Schristos   const char * file;
571*56bb7041Schristos 
572*56bb7041Schristos   file = lbasename (pathname);
573*56bb7041Schristos   /* Don't make empty string from / or A: from A:/ .  */
574*56bb7041Schristos #ifdef HAVE_DOS_BASED_FILE_SYSTEM
575*56bb7041Schristos   if (file <= pathname + 3)
576*56bb7041Schristos     file = pathname;
577*56bb7041Schristos #else
578*56bb7041Schristos   if (file == pathname + 1)
579*56bb7041Schristos     file = pathname;
580*56bb7041Schristos #endif
581*56bb7041Schristos   return file;
582*56bb7041Schristos }
583*56bb7041Schristos 
584*56bb7041Schristos static unsigned int
get_directory_table_entry(const char * dirname,size_t dirlen,bfd_boolean can_use_zero)585*56bb7041Schristos get_directory_table_entry (const char *  dirname,
586*56bb7041Schristos 			   size_t        dirlen,
587*56bb7041Schristos 			   bfd_boolean   can_use_zero)
588*56bb7041Schristos {
589*56bb7041Schristos   unsigned int d;
590*56bb7041Schristos 
591*56bb7041Schristos   if (dirlen == 0)
592*56bb7041Schristos     return 0;
593*56bb7041Schristos 
594*56bb7041Schristos #ifndef DWARF2_DIR_SHOULD_END_WITH_SEPARATOR
595*56bb7041Schristos   if (IS_DIR_SEPARATOR (dirname[dirlen - 1]))
596*56bb7041Schristos     {
597*56bb7041Schristos       -- dirlen;
598*56bb7041Schristos       if (dirlen == 0)
599*56bb7041Schristos 	return 0;
600*56bb7041Schristos     }
601*56bb7041Schristos #endif
602*56bb7041Schristos 
603*56bb7041Schristos   for (d = 0; d < dirs_in_use; ++d)
604*56bb7041Schristos     {
605*56bb7041Schristos       if (dirs[d] != NULL
606*56bb7041Schristos 	  && filename_ncmp (dirname, dirs[d], dirlen) == 0
607*56bb7041Schristos 	  && dirs[d][dirlen] == '\0')
608*56bb7041Schristos 	return d;
609*56bb7041Schristos     }
610*56bb7041Schristos 
611*56bb7041Schristos   if (can_use_zero)
612*56bb7041Schristos     {
613*56bb7041Schristos       if (dirs == NULL || dirs[0] == NULL)
614*56bb7041Schristos 	d = 0;
615*56bb7041Schristos     }
616*56bb7041Schristos   else if (d == 0)
617*56bb7041Schristos     d = 1;
618*56bb7041Schristos 
619*56bb7041Schristos   if (d >= dirs_allocated)
620*56bb7041Schristos     {
621*56bb7041Schristos       unsigned int old = dirs_allocated;
622*56bb7041Schristos 
623*56bb7041Schristos       dirs_allocated = d + 32;
624*56bb7041Schristos       dirs = XRESIZEVEC (char *, dirs, dirs_allocated);
625*56bb7041Schristos       memset (dirs + old, 0, (dirs_allocated - old) * sizeof (char *));
626*56bb7041Schristos     }
627*56bb7041Schristos 
628*56bb7041Schristos   dirs[d] = xmemdup0 (dirname, dirlen);
629*56bb7041Schristos   if (dirs_in_use <= d)
630*56bb7041Schristos     dirs_in_use = d + 1;
631*56bb7041Schristos 
632*56bb7041Schristos   return d;
633*56bb7041Schristos }
634*56bb7041Schristos 
635*56bb7041Schristos static bfd_boolean
assign_file_to_slot(unsigned long i,const char * file,unsigned int dir,bfd_boolean auto_assign)636*56bb7041Schristos assign_file_to_slot (unsigned long i, const char *file, unsigned int dir, bfd_boolean auto_assign)
637*56bb7041Schristos {
638*56bb7041Schristos   if (i >= files_allocated)
639*56bb7041Schristos     {
640*56bb7041Schristos       unsigned int old = files_allocated;
641*56bb7041Schristos 
642*56bb7041Schristos       files_allocated = i + 32;
643*56bb7041Schristos       /* Catch wraparound.  */
644*56bb7041Schristos       if (files_allocated <= old)
645*56bb7041Schristos 	{
646*56bb7041Schristos 	  as_bad (_("file number %lu is too big"), (unsigned long) i);
647*56bb7041Schristos 	  return FALSE;
648*56bb7041Schristos 	}
649*56bb7041Schristos 
650*56bb7041Schristos       files = XRESIZEVEC (struct file_entry, files, files_allocated);
651*56bb7041Schristos       memset (files + old, 0, (i + 32 - old) * sizeof (struct file_entry));
652*56bb7041Schristos     }
653*56bb7041Schristos 
654*56bb7041Schristos   files[i].filename = file;
655*56bb7041Schristos   files[i].dir = dir;
656*56bb7041Schristos   files[i].auto_assigned = auto_assign;
657*56bb7041Schristos   memset (files[i].md5, 0, NUM_MD5_BYTES);
658*56bb7041Schristos 
659*56bb7041Schristos   if (files_in_use < i + 1)
660*56bb7041Schristos     files_in_use = i + 1;
661*56bb7041Schristos 
662*56bb7041Schristos   return TRUE;
663*56bb7041Schristos }
664*56bb7041Schristos 
665*56bb7041Schristos /* Get a .debug_line file number for PATHNAME.  If there is a
666*56bb7041Schristos    directory component to PATHNAME, then this will be stored
667*56bb7041Schristos    in the directory table, if it is not already present.
668*56bb7041Schristos    Returns the slot number allocated to that filename or -1
669*56bb7041Schristos    if there was a problem.  */
670*56bb7041Schristos 
671*56bb7041Schristos static signed int
allocate_filenum(const char * pathname)672*56bb7041Schristos allocate_filenum (const char * pathname)
673*56bb7041Schristos {
674*56bb7041Schristos   static signed int last_used = -1, last_used_dir_len = 0;
675*56bb7041Schristos   const char *file;
676*56bb7041Schristos   size_t dir_len;
677*56bb7041Schristos   unsigned int i, dir;
678*56bb7041Schristos 
679*56bb7041Schristos   /* Short circuit the common case of adding the same pathname
680*56bb7041Schristos      as last time.  */
681*56bb7041Schristos   if (last_used != -1)
682*56bb7041Schristos     {
683*56bb7041Schristos       const char * dirname = NULL;
684*56bb7041Schristos 
685*56bb7041Schristos       if (dirs != NULL)
686*56bb7041Schristos 	dirname = dirs[files[last_used].dir];
687*56bb7041Schristos 
688*56bb7041Schristos       if (dirname == NULL)
689*56bb7041Schristos 	{
690*56bb7041Schristos 	  if (filename_cmp (pathname, files[last_used].filename) == 0)
691*56bb7041Schristos 	    return last_used;
692*56bb7041Schristos 	}
693*56bb7041Schristos       else
694*56bb7041Schristos 	{
695*56bb7041Schristos 	  if (filename_ncmp (pathname, dirname, last_used_dir_len) == 0
696*56bb7041Schristos 	      && IS_DIR_SEPARATOR (pathname [last_used_dir_len])
697*56bb7041Schristos 	      && filename_cmp (pathname + last_used_dir_len + 1,
698*56bb7041Schristos 			       files[last_used].filename) == 0)
699*56bb7041Schristos 	    return last_used;
700*56bb7041Schristos 	}
701*56bb7041Schristos     }
702*56bb7041Schristos 
703*56bb7041Schristos   file = get_basename (pathname);
704*56bb7041Schristos   dir_len = file - pathname;
705*56bb7041Schristos 
706*56bb7041Schristos   dir = get_directory_table_entry (pathname, dir_len, FALSE);
707*56bb7041Schristos 
708*56bb7041Schristos   /* Do not use slot-0.  That is specifically reserved for use by
709*56bb7041Schristos      the '.file 0 "name"' directive.  */
710*56bb7041Schristos   for (i = 1; i < files_in_use; ++i)
711*56bb7041Schristos     if (files[i].dir == dir
712*56bb7041Schristos 	&& files[i].filename
713*56bb7041Schristos 	&& filename_cmp (file, files[i].filename) == 0)
714*56bb7041Schristos       {
715*56bb7041Schristos 	last_used = i;
716*56bb7041Schristos 	last_used_dir_len = dir_len;
717*56bb7041Schristos 	return i;
718*56bb7041Schristos       }
719*56bb7041Schristos 
720*56bb7041Schristos   if (!assign_file_to_slot (i, file, dir, TRUE))
721*56bb7041Schristos     return -1;
722*56bb7041Schristos 
723*56bb7041Schristos   last_used = i;
724*56bb7041Schristos   last_used_dir_len = dir_len;
725*56bb7041Schristos 
726*56bb7041Schristos   return i;
727*56bb7041Schristos }
728*56bb7041Schristos 
729*56bb7041Schristos /* Allocate slot NUM in the .debug_line file table to FILENAME.
730*56bb7041Schristos    If DIRNAME is not NULL or there is a directory component to FILENAME
731*56bb7041Schristos    then this will be stored in the directory table, if not already present.
732*56bb7041Schristos    if WITH_MD5 is TRUE then there is a md5 value in generic_bignum.
733*56bb7041Schristos    Returns TRUE if allocation succeeded, FALSE otherwise.  */
734*56bb7041Schristos 
735*56bb7041Schristos static bfd_boolean
allocate_filename_to_slot(const char * dirname,const char * filename,unsigned int num,bfd_boolean with_md5)736*56bb7041Schristos allocate_filename_to_slot (const char *  dirname,
737*56bb7041Schristos 			   const char *  filename,
738*56bb7041Schristos 			   unsigned int  num,
739*56bb7041Schristos 			   bfd_boolean   with_md5)
740*56bb7041Schristos {
741*56bb7041Schristos   const char *file;
742*56bb7041Schristos   size_t dirlen;
743*56bb7041Schristos   unsigned int i, d;
744*56bb7041Schristos 
745*56bb7041Schristos   /* Short circuit the common case of adding the same pathname
746*56bb7041Schristos      as last time.  */
747*56bb7041Schristos   if (num < files_allocated && files[num].filename != NULL)
748*56bb7041Schristos     {
749*56bb7041Schristos       const char * dir = NULL;
750*56bb7041Schristos 
751*56bb7041Schristos       if (dirs)
752*56bb7041Schristos 	dir = dirs[files[num].dir];
753*56bb7041Schristos 
754*56bb7041Schristos       if (with_md5
755*56bb7041Schristos 	  && memcmp (generic_bignum, files[num].md5, NUM_MD5_BYTES) != 0)
756*56bb7041Schristos 	goto fail;
757*56bb7041Schristos 
758*56bb7041Schristos       if (dirname != NULL)
759*56bb7041Schristos 	{
760*56bb7041Schristos 	  if (dir != NULL && filename_cmp (dir, dirname) != 0)
761*56bb7041Schristos 	    goto fail;
762*56bb7041Schristos 
763*56bb7041Schristos 	  if (filename_cmp (filename, files[num].filename) != 0)
764*56bb7041Schristos 	    goto fail;
765*56bb7041Schristos 
766*56bb7041Schristos 	  /* If the filenames match, but the directory table entry was
767*56bb7041Schristos 	     empty, then fill it with the provided directory name.  */
768*56bb7041Schristos 	  if (dir == NULL)
769*56bb7041Schristos 	    dirs[files[num].dir] = xmemdup0 (dirname, strlen (dirname));
770*56bb7041Schristos 
771*56bb7041Schristos 	  return TRUE;
772*56bb7041Schristos 	}
773*56bb7041Schristos       else if (dir != NULL)
774*56bb7041Schristos 	{
775*56bb7041Schristos 	  dirlen = strlen (dir);
776*56bb7041Schristos 	  if (filename_ncmp (filename, dir, dirlen) == 0
777*56bb7041Schristos 	      && IS_DIR_SEPARATOR (filename [dirlen])
778*56bb7041Schristos 	      && filename_cmp (filename + dirlen + 1, files[num].filename) == 0)
779*56bb7041Schristos 	    return TRUE;
780*56bb7041Schristos 	}
781*56bb7041Schristos       else /* dir == NULL  */
782*56bb7041Schristos 	{
783*56bb7041Schristos 	  file = get_basename (filename);
784*56bb7041Schristos 	  if (filename_cmp (file, files[num].filename) == 0)
785*56bb7041Schristos 	    {
786*56bb7041Schristos 	      if (file > filename)
787*56bb7041Schristos 		/* The filenames match, but the directory table entry is empty.
788*56bb7041Schristos 		   Fill it with the provided directory name.  */
789*56bb7041Schristos 		dirs[files[num].dir] = xmemdup0 (filename, file - filename);
790*56bb7041Schristos 	      return TRUE;
791*56bb7041Schristos 	    }
792*56bb7041Schristos 	}
793*56bb7041Schristos 
794*56bb7041Schristos     fail:
795*56bb7041Schristos       /* If NUM was previously allocated automatically then
796*56bb7041Schristos 	 choose another slot for it, so that we can reuse NUM.  */
797*56bb7041Schristos       if (files[num].auto_assigned)
798*56bb7041Schristos 	{
799*56bb7041Schristos 	  /* Find an unused slot.  */
800*56bb7041Schristos 	  for (i = 1; i < files_in_use; ++i)
801*56bb7041Schristos 	    if (files[i].filename == NULL)
802*56bb7041Schristos 	      break;
803*56bb7041Schristos 	  if (! assign_file_to_slot (i, files[num].filename, files[num].dir, TRUE))
804*56bb7041Schristos 	    return FALSE;
805*56bb7041Schristos 	  files[num].filename = NULL;
806*56bb7041Schristos 	}
807*56bb7041Schristos       else
808*56bb7041Schristos 	{
809*56bb7041Schristos 	  as_bad (_("file table slot %u is already occupied by a different file (%s%s%s vs %s%s%s)"),
810*56bb7041Schristos 		  num,
811*56bb7041Schristos 		  dir == NULL ? "" : dir,
812*56bb7041Schristos 		  dir == NULL ? "" : "/",
813*56bb7041Schristos 		  files[num].filename,
814*56bb7041Schristos 		  dirname == NULL ? "" : dirname,
815*56bb7041Schristos 		  dirname == NULL ? "" : "/",
816*56bb7041Schristos 		  filename);
817*56bb7041Schristos 	  return FALSE;
818*56bb7041Schristos 	}
819*56bb7041Schristos     }
820*56bb7041Schristos 
821*56bb7041Schristos   if (dirname == NULL)
822*56bb7041Schristos     {
823*56bb7041Schristos       dirname = filename;
824*56bb7041Schristos       file = get_basename (filename);
825*56bb7041Schristos       dirlen = file - filename;
826*56bb7041Schristos     }
827*56bb7041Schristos   else
828*56bb7041Schristos     {
829*56bb7041Schristos       dirlen = strlen (dirname);
830*56bb7041Schristos       file = filename;
831*56bb7041Schristos     }
832*56bb7041Schristos 
833*56bb7041Schristos   d = get_directory_table_entry (dirname, dirlen, num == 0);
834*56bb7041Schristos   i = num;
835*56bb7041Schristos 
836*56bb7041Schristos   if (! assign_file_to_slot (i, file, d, FALSE))
837*56bb7041Schristos     return FALSE;
838*56bb7041Schristos 
839*56bb7041Schristos   if (with_md5)
840*56bb7041Schristos     {
841*56bb7041Schristos       if (target_big_endian)
842*56bb7041Schristos 	{
843*56bb7041Schristos 	  /* md5's are stored in litte endian format.  */
844*56bb7041Schristos 	  unsigned int     bits_remaining = NUM_MD5_BYTES * BITS_PER_CHAR;
845*56bb7041Schristos 	  unsigned int     byte = NUM_MD5_BYTES;
846*56bb7041Schristos 	  unsigned int     bignum_index = 0;
847*56bb7041Schristos 
848*56bb7041Schristos 	  while (bits_remaining)
849*56bb7041Schristos 	    {
850*56bb7041Schristos 	      unsigned int bignum_bits_remaining = LITTLENUM_NUMBER_OF_BITS;
851*56bb7041Schristos 	      valueT       bignum_value = generic_bignum [bignum_index];
852*56bb7041Schristos 	      bignum_index ++;
853*56bb7041Schristos 
854*56bb7041Schristos 	      while (bignum_bits_remaining)
855*56bb7041Schristos 		{
856*56bb7041Schristos 		  files[i].md5[--byte] = bignum_value & 0xff;
857*56bb7041Schristos 		  bignum_value >>= 8;
858*56bb7041Schristos 		  bignum_bits_remaining -= 8;
859*56bb7041Schristos 		  bits_remaining -= 8;
860*56bb7041Schristos 		}
861*56bb7041Schristos 	    }
862*56bb7041Schristos 	}
863*56bb7041Schristos       else
864*56bb7041Schristos 	{
865*56bb7041Schristos 	  unsigned int     bits_remaining = NUM_MD5_BYTES * BITS_PER_CHAR;
866*56bb7041Schristos 	  unsigned int     byte = 0;
867*56bb7041Schristos 	  unsigned int     bignum_index = 0;
868*56bb7041Schristos 
869*56bb7041Schristos 	  while (bits_remaining)
870*56bb7041Schristos 	    {
871*56bb7041Schristos 	      unsigned int bignum_bits_remaining = LITTLENUM_NUMBER_OF_BITS;
872*56bb7041Schristos 	      valueT       bignum_value = generic_bignum [bignum_index];
873*56bb7041Schristos 
874*56bb7041Schristos 	      bignum_index ++;
875*56bb7041Schristos 
876*56bb7041Schristos 	      while (bignum_bits_remaining)
877*56bb7041Schristos 		{
878*56bb7041Schristos 		  files[i].md5[byte++] = bignum_value & 0xff;
879*56bb7041Schristos 		  bignum_value >>= 8;
880*56bb7041Schristos 		  bignum_bits_remaining -= 8;
881*56bb7041Schristos 		  bits_remaining -= 8;
882*56bb7041Schristos 		}
883*56bb7041Schristos 	    }
884*56bb7041Schristos 	}
885*56bb7041Schristos     }
886*56bb7041Schristos   else
887*56bb7041Schristos     memset (files[i].md5, 0, NUM_MD5_BYTES);
888*56bb7041Schristos 
889*56bb7041Schristos   return TRUE;
890*56bb7041Schristos }
891*56bb7041Schristos 
892*56bb7041Schristos /* Returns the current source information.  If .file directives have
893*56bb7041Schristos    been encountered, the info for the corresponding source file is
894*56bb7041Schristos    returned.  Otherwise, the info for the assembly source file is
895*56bb7041Schristos    returned.  */
896*56bb7041Schristos 
897*56bb7041Schristos void
dwarf2_where(struct dwarf2_line_info * line)898*56bb7041Schristos dwarf2_where (struct dwarf2_line_info *line)
899*56bb7041Schristos {
900*56bb7041Schristos   if (debug_type == DEBUG_DWARF2)
901*56bb7041Schristos     {
902*56bb7041Schristos       const char *filename;
903*56bb7041Schristos 
904*56bb7041Schristos       memset (line, 0, sizeof (*line));
905*56bb7041Schristos       filename = as_where (&line->line);
906*56bb7041Schristos       line->filenum = allocate_filenum (filename);
907*56bb7041Schristos       /* FIXME: We should check the return value from allocate_filenum.  */
908*56bb7041Schristos       line->column = 0;
909*56bb7041Schristos       line->flags = DWARF2_FLAG_IS_STMT;
910*56bb7041Schristos       line->isa = current.isa;
911*56bb7041Schristos       line->discriminator = current.discriminator;
912*56bb7041Schristos       line->view = NULL;
913*56bb7041Schristos     }
914*56bb7041Schristos   else
915*56bb7041Schristos     *line = current;
916*56bb7041Schristos }
917*56bb7041Schristos 
918*56bb7041Schristos /* A hook to allow the target backend to inform the line number state
919*56bb7041Schristos    machine of isa changes when assembler debug info is enabled.  */
920*56bb7041Schristos 
921*56bb7041Schristos void
dwarf2_set_isa(unsigned int isa)922*56bb7041Schristos dwarf2_set_isa (unsigned int isa)
923*56bb7041Schristos {
924*56bb7041Schristos   current.isa = isa;
925*56bb7041Schristos }
926*56bb7041Schristos 
927*56bb7041Schristos /* Called for each machine instruction, or relatively atomic group of
928*56bb7041Schristos    machine instructions (ie built-in macro).  The instruction or group
929*56bb7041Schristos    is SIZE bytes in length.  If dwarf2 line number generation is called
930*56bb7041Schristos    for, emit a line statement appropriately.  */
931*56bb7041Schristos 
932*56bb7041Schristos void
dwarf2_emit_insn(int size)933*56bb7041Schristos dwarf2_emit_insn (int size)
934*56bb7041Schristos {
935*56bb7041Schristos   struct dwarf2_line_info loc;
936*56bb7041Schristos 
937*56bb7041Schristos   if (debug_type != DEBUG_DWARF2
938*56bb7041Schristos       ? !dwarf2_loc_directive_seen
939*56bb7041Schristos       : !seen_at_least_1_file ())
940*56bb7041Schristos     return;
941*56bb7041Schristos 
942*56bb7041Schristos   dwarf2_where (&loc);
943*56bb7041Schristos 
944*56bb7041Schristos   dwarf2_gen_line_info ((frag_now_fix_octets () - size) / OCTETS_PER_BYTE, &loc);
945*56bb7041Schristos   dwarf2_consume_line_info ();
946*56bb7041Schristos }
947*56bb7041Schristos 
948*56bb7041Schristos /* Move all previously-emitted line entries for the current position by
949*56bb7041Schristos    DELTA bytes.  This function cannot be used to move the same entries
950*56bb7041Schristos    twice.  */
951*56bb7041Schristos 
952*56bb7041Schristos void
dwarf2_move_insn(int delta)953*56bb7041Schristos dwarf2_move_insn (int delta)
954*56bb7041Schristos {
955*56bb7041Schristos   struct line_subseg *lss;
956*56bb7041Schristos   struct line_entry *e;
957*56bb7041Schristos   valueT now;
958*56bb7041Schristos 
959*56bb7041Schristos   if (delta == 0)
960*56bb7041Schristos     return;
961*56bb7041Schristos 
962*56bb7041Schristos   lss = get_line_subseg (now_seg, now_subseg, FALSE);
963*56bb7041Schristos   if (!lss)
964*56bb7041Schristos     return;
965*56bb7041Schristos 
966*56bb7041Schristos   now = frag_now_fix ();
967*56bb7041Schristos   while ((e = *lss->pmove_tail))
968*56bb7041Schristos     {
969*56bb7041Schristos       if (S_GET_VALUE (e->label) == now)
970*56bb7041Schristos 	S_SET_VALUE (e->label, now + delta);
971*56bb7041Schristos       lss->pmove_tail = &e->next;
972*56bb7041Schristos     }
973*56bb7041Schristos }
974*56bb7041Schristos 
975*56bb7041Schristos /* Called after the current line information has been either used with
976*56bb7041Schristos    dwarf2_gen_line_info or saved with a machine instruction for later use.
977*56bb7041Schristos    This resets the state of the line number information to reflect that
978*56bb7041Schristos    it has been used.  */
979*56bb7041Schristos 
980*56bb7041Schristos void
dwarf2_consume_line_info(void)981*56bb7041Schristos dwarf2_consume_line_info (void)
982*56bb7041Schristos {
983*56bb7041Schristos   /* Unless we generate DWARF2 debugging information for each
984*56bb7041Schristos      assembler line, we only emit one line symbol for one LOC.  */
985*56bb7041Schristos   dwarf2_loc_directive_seen = FALSE;
986*56bb7041Schristos 
987*56bb7041Schristos   current.flags &= ~(DWARF2_FLAG_BASIC_BLOCK
988*56bb7041Schristos 		     | DWARF2_FLAG_PROLOGUE_END
989*56bb7041Schristos 		     | DWARF2_FLAG_EPILOGUE_BEGIN);
990*56bb7041Schristos   current.discriminator = 0;
991*56bb7041Schristos   current.view = NULL;
992*56bb7041Schristos }
993*56bb7041Schristos 
994*56bb7041Schristos /* Called for each (preferably code) label.  If dwarf2_loc_mark_labels
995*56bb7041Schristos    is enabled, emit a basic block marker.  */
996*56bb7041Schristos 
997*56bb7041Schristos void
dwarf2_emit_label(symbolS * label)998*56bb7041Schristos dwarf2_emit_label (symbolS *label)
999*56bb7041Schristos {
1000*56bb7041Schristos   struct dwarf2_line_info loc;
1001*56bb7041Schristos 
1002*56bb7041Schristos   if (!dwarf2_loc_mark_labels)
1003*56bb7041Schristos     return;
1004*56bb7041Schristos   if (S_GET_SEGMENT (label) != now_seg)
1005*56bb7041Schristos     return;
1006*56bb7041Schristos   if (!(bfd_section_flags (now_seg) & SEC_CODE))
1007*56bb7041Schristos     return;
1008*56bb7041Schristos   if (files_in_use == 0 && debug_type != DEBUG_DWARF2)
1009*56bb7041Schristos     return;
1010*56bb7041Schristos 
1011*56bb7041Schristos   dwarf2_where (&loc);
1012*56bb7041Schristos 
1013*56bb7041Schristos   loc.flags |= DWARF2_FLAG_BASIC_BLOCK;
1014*56bb7041Schristos 
1015*56bb7041Schristos   dwarf2_gen_line_info_1 (label, &loc);
1016*56bb7041Schristos   dwarf2_consume_line_info ();
1017*56bb7041Schristos }
1018*56bb7041Schristos 
1019*56bb7041Schristos /* Handle two forms of .file directive:
1020*56bb7041Schristos    - Pass .file "source.c" to s_app_file
1021*56bb7041Schristos    - Handle .file 1 "source.c" by adding an entry to the DWARF-2 file table
1022*56bb7041Schristos 
1023*56bb7041Schristos    If an entry is added to the file table, return a pointer to the filename.  */
1024*56bb7041Schristos 
1025*56bb7041Schristos char *
dwarf2_directive_filename(void)1026*56bb7041Schristos dwarf2_directive_filename (void)
1027*56bb7041Schristos {
1028*56bb7041Schristos   bfd_boolean with_md5 = FALSE;
1029*56bb7041Schristos   valueT num;
1030*56bb7041Schristos   char *filename;
1031*56bb7041Schristos   const char * dirname = NULL;
1032*56bb7041Schristos   int filename_len;
1033*56bb7041Schristos 
1034*56bb7041Schristos   /* Continue to accept a bare string and pass it off.  */
1035*56bb7041Schristos   SKIP_WHITESPACE ();
1036*56bb7041Schristos   if (*input_line_pointer == '"')
1037*56bb7041Schristos     {
1038*56bb7041Schristos       s_app_file (0);
1039*56bb7041Schristos       return NULL;
1040*56bb7041Schristos     }
1041*56bb7041Schristos 
1042*56bb7041Schristos   num = get_absolute_expression ();
1043*56bb7041Schristos 
1044*56bb7041Schristos   if ((offsetT) num < 1 && DWARF2_LINE_VERSION < 5)
1045*56bb7041Schristos     {
1046*56bb7041Schristos       as_bad (_("file number less than one"));
1047*56bb7041Schristos       ignore_rest_of_line ();
1048*56bb7041Schristos       return NULL;
1049*56bb7041Schristos     }
1050*56bb7041Schristos 
1051*56bb7041Schristos   /* FIXME: Should we allow ".file <N>\n" as an expression meaning
1052*56bb7041Schristos      "switch back to the already allocated file <N> as the current
1053*56bb7041Schristos      file" ?  */
1054*56bb7041Schristos 
1055*56bb7041Schristos   filename = demand_copy_C_string (&filename_len);
1056*56bb7041Schristos   if (filename == NULL)
1057*56bb7041Schristos     /* demand_copy_C_string will have already generated an error message.  */
1058*56bb7041Schristos     return NULL;
1059*56bb7041Schristos 
1060*56bb7041Schristos   /* For DWARF-5 support we also accept:
1061*56bb7041Schristos      .file <NUM> ["<dir>"] "<file>" [md5 <NUM>]  */
1062*56bb7041Schristos   if (DWARF2_LINE_VERSION > 4)
1063*56bb7041Schristos     {
1064*56bb7041Schristos       SKIP_WHITESPACE ();
1065*56bb7041Schristos       if (*input_line_pointer == '"')
1066*56bb7041Schristos 	{
1067*56bb7041Schristos 	  dirname = filename;
1068*56bb7041Schristos 	  filename = demand_copy_C_string (&filename_len);
1069*56bb7041Schristos 	  SKIP_WHITESPACE ();
1070*56bb7041Schristos 	}
1071*56bb7041Schristos 
1072*56bb7041Schristos       if (strncmp (input_line_pointer, "md5", 3) == 0)
1073*56bb7041Schristos 	{
1074*56bb7041Schristos 	  input_line_pointer += 3;
1075*56bb7041Schristos 	  SKIP_WHITESPACE ();
1076*56bb7041Schristos 
1077*56bb7041Schristos 	  expressionS exp;
1078*56bb7041Schristos 	  expression_and_evaluate (& exp);
1079*56bb7041Schristos 	  if (exp.X_op != O_big)
1080*56bb7041Schristos 	    as_bad (_("md5 value too small or not a constant"));
1081*56bb7041Schristos 	  else
1082*56bb7041Schristos 	    with_md5 = TRUE;
1083*56bb7041Schristos 	}
1084*56bb7041Schristos     }
1085*56bb7041Schristos 
1086*56bb7041Schristos   demand_empty_rest_of_line ();
1087*56bb7041Schristos 
1088*56bb7041Schristos   /* A .file directive implies compiler generated debug information is
1089*56bb7041Schristos      being supplied.  Turn off gas generated debug info.  */
1090*56bb7041Schristos   debug_type = DEBUG_NONE;
1091*56bb7041Schristos 
1092*56bb7041Schristos   if (num != (unsigned int) num
1093*56bb7041Schristos       || num >= (size_t) -1 / sizeof (struct file_entry) - 32)
1094*56bb7041Schristos     {
1095*56bb7041Schristos       as_bad (_("file number %lu is too big"), (unsigned long) num);
1096*56bb7041Schristos       return NULL;
1097*56bb7041Schristos     }
1098*56bb7041Schristos 
1099*56bb7041Schristos   if (! allocate_filename_to_slot (dirname, filename, (unsigned int) num,
1100*56bb7041Schristos 				   with_md5))
1101*56bb7041Schristos     return NULL;
1102*56bb7041Schristos 
1103*56bb7041Schristos   return filename;
1104*56bb7041Schristos }
1105*56bb7041Schristos 
1106*56bb7041Schristos /* Calls dwarf2_directive_filename, but discards its result.
1107*56bb7041Schristos    Used in pseudo-op tables where the function result is ignored.  */
1108*56bb7041Schristos 
1109*56bb7041Schristos void
dwarf2_directive_file(int dummy ATTRIBUTE_UNUSED)1110*56bb7041Schristos dwarf2_directive_file (int dummy ATTRIBUTE_UNUSED)
1111*56bb7041Schristos {
1112*56bb7041Schristos   (void) dwarf2_directive_filename ();
1113*56bb7041Schristos }
1114*56bb7041Schristos 
1115*56bb7041Schristos void
dwarf2_directive_loc(int dummy ATTRIBUTE_UNUSED)1116*56bb7041Schristos dwarf2_directive_loc (int dummy ATTRIBUTE_UNUSED)
1117*56bb7041Schristos {
1118*56bb7041Schristos   offsetT filenum, line;
1119*56bb7041Schristos 
1120*56bb7041Schristos   /* If we see two .loc directives in a row, force the first one to be
1121*56bb7041Schristos      output now.  */
1122*56bb7041Schristos   if (dwarf2_loc_directive_seen)
1123*56bb7041Schristos     dwarf2_emit_insn (0);
1124*56bb7041Schristos 
1125*56bb7041Schristos   filenum = get_absolute_expression ();
1126*56bb7041Schristos   SKIP_WHITESPACE ();
1127*56bb7041Schristos   line = get_absolute_expression ();
1128*56bb7041Schristos 
1129*56bb7041Schristos   if (filenum < 1)
1130*56bb7041Schristos     {
1131*56bb7041Schristos       if (filenum != 0 || DWARF2_LINE_VERSION < 5)
1132*56bb7041Schristos 	{
1133*56bb7041Schristos 	  as_bad (_("file number less than one"));
1134*56bb7041Schristos 	  return;
1135*56bb7041Schristos 	}
1136*56bb7041Schristos     }
1137*56bb7041Schristos 
1138*56bb7041Schristos   if (filenum >= (int) files_in_use || files[filenum].filename == NULL)
1139*56bb7041Schristos     {
1140*56bb7041Schristos       as_bad (_("unassigned file number %ld"), (long) filenum);
1141*56bb7041Schristos       return;
1142*56bb7041Schristos     }
1143*56bb7041Schristos 
1144*56bb7041Schristos   current.filenum = filenum;
1145*56bb7041Schristos   current.line = line;
1146*56bb7041Schristos   current.discriminator = 0;
1147*56bb7041Schristos 
1148*56bb7041Schristos #ifndef NO_LISTING
1149*56bb7041Schristos   if (listing)
1150*56bb7041Schristos     {
1151*56bb7041Schristos       if (files[filenum].dir)
1152*56bb7041Schristos 	{
1153*56bb7041Schristos 	  size_t dir_len = strlen (dirs[files[filenum].dir]);
1154*56bb7041Schristos 	  size_t file_len = strlen (files[filenum].filename);
1155*56bb7041Schristos 	  char *cp = XNEWVEC (char, dir_len + 1 + file_len + 1);
1156*56bb7041Schristos 
1157*56bb7041Schristos 	  memcpy (cp, dirs[files[filenum].dir], dir_len);
1158*56bb7041Schristos 	  INSERT_DIR_SEPARATOR (cp, dir_len);
1159*56bb7041Schristos 	  memcpy (cp + dir_len + 1, files[filenum].filename, file_len);
1160*56bb7041Schristos 	  cp[dir_len + file_len + 1] = '\0';
1161*56bb7041Schristos 	  listing_source_file (cp);
1162*56bb7041Schristos 	  free (cp);
1163*56bb7041Schristos 	}
1164*56bb7041Schristos       else
1165*56bb7041Schristos 	listing_source_file (files[filenum].filename);
1166*56bb7041Schristos       listing_source_line (line);
1167*56bb7041Schristos     }
1168*56bb7041Schristos #endif
1169*56bb7041Schristos 
1170*56bb7041Schristos   SKIP_WHITESPACE ();
1171*56bb7041Schristos   if (ISDIGIT (*input_line_pointer))
1172*56bb7041Schristos     {
1173*56bb7041Schristos       current.column = get_absolute_expression ();
1174*56bb7041Schristos       SKIP_WHITESPACE ();
1175*56bb7041Schristos     }
1176*56bb7041Schristos 
1177*56bb7041Schristos   while (ISALPHA (*input_line_pointer))
1178*56bb7041Schristos     {
1179*56bb7041Schristos       char *p, c;
1180*56bb7041Schristos       offsetT value;
1181*56bb7041Schristos 
1182*56bb7041Schristos       c = get_symbol_name (& p);
1183*56bb7041Schristos 
1184*56bb7041Schristos       if (strcmp (p, "basic_block") == 0)
1185*56bb7041Schristos 	{
1186*56bb7041Schristos 	  current.flags |= DWARF2_FLAG_BASIC_BLOCK;
1187*56bb7041Schristos 	  *input_line_pointer = c;
1188*56bb7041Schristos 	}
1189*56bb7041Schristos       else if (strcmp (p, "prologue_end") == 0)
1190*56bb7041Schristos 	{
1191*56bb7041Schristos 	  current.flags |= DWARF2_FLAG_PROLOGUE_END;
1192*56bb7041Schristos 	  *input_line_pointer = c;
1193*56bb7041Schristos 	}
1194*56bb7041Schristos       else if (strcmp (p, "epilogue_begin") == 0)
1195*56bb7041Schristos 	{
1196*56bb7041Schristos 	  current.flags |= DWARF2_FLAG_EPILOGUE_BEGIN;
1197*56bb7041Schristos 	  *input_line_pointer = c;
1198*56bb7041Schristos 	}
1199*56bb7041Schristos       else if (strcmp (p, "is_stmt") == 0)
1200*56bb7041Schristos 	{
1201*56bb7041Schristos 	  (void) restore_line_pointer (c);
1202*56bb7041Schristos 	  value = get_absolute_expression ();
1203*56bb7041Schristos 	  if (value == 0)
1204*56bb7041Schristos 	    current.flags &= ~DWARF2_FLAG_IS_STMT;
1205*56bb7041Schristos 	  else if (value == 1)
1206*56bb7041Schristos 	    current.flags |= DWARF2_FLAG_IS_STMT;
1207*56bb7041Schristos 	  else
1208*56bb7041Schristos 	    {
1209*56bb7041Schristos 	      as_bad (_("is_stmt value not 0 or 1"));
1210*56bb7041Schristos 	      return;
1211*56bb7041Schristos 	    }
1212*56bb7041Schristos 	}
1213*56bb7041Schristos       else if (strcmp (p, "isa") == 0)
1214*56bb7041Schristos 	{
1215*56bb7041Schristos 	  (void) restore_line_pointer (c);
1216*56bb7041Schristos 	  value = get_absolute_expression ();
1217*56bb7041Schristos 	  if (value >= 0)
1218*56bb7041Schristos 	    current.isa = value;
1219*56bb7041Schristos 	  else
1220*56bb7041Schristos 	    {
1221*56bb7041Schristos 	      as_bad (_("isa number less than zero"));
1222*56bb7041Schristos 	      return;
1223*56bb7041Schristos 	    }
1224*56bb7041Schristos 	}
1225*56bb7041Schristos       else if (strcmp (p, "discriminator") == 0)
1226*56bb7041Schristos 	{
1227*56bb7041Schristos 	  (void) restore_line_pointer (c);
1228*56bb7041Schristos 	  value = get_absolute_expression ();
1229*56bb7041Schristos 	  if (value >= 0)
1230*56bb7041Schristos 	    current.discriminator = value;
1231*56bb7041Schristos 	  else
1232*56bb7041Schristos 	    {
1233*56bb7041Schristos 	      as_bad (_("discriminator less than zero"));
1234*56bb7041Schristos 	      return;
1235*56bb7041Schristos 	    }
1236*56bb7041Schristos 	}
1237*56bb7041Schristos       else if (strcmp (p, "view") == 0)
1238*56bb7041Schristos 	{
1239*56bb7041Schristos 	  symbolS *sym;
1240*56bb7041Schristos 
1241*56bb7041Schristos 	  (void) restore_line_pointer (c);
1242*56bb7041Schristos 	  SKIP_WHITESPACE ();
1243*56bb7041Schristos 
1244*56bb7041Schristos 	  if (ISDIGIT (*input_line_pointer)
1245*56bb7041Schristos 	      || *input_line_pointer == '-')
1246*56bb7041Schristos 	    {
1247*56bb7041Schristos 	      bfd_boolean force_reset = *input_line_pointer == '-';
1248*56bb7041Schristos 
1249*56bb7041Schristos 	      value = get_absolute_expression ();
1250*56bb7041Schristos 	      if (value != 0)
1251*56bb7041Schristos 		{
1252*56bb7041Schristos 		  as_bad (_("numeric view can only be asserted to zero"));
1253*56bb7041Schristos 		  return;
1254*56bb7041Schristos 		}
1255*56bb7041Schristos 	      if (force_reset && force_reset_view)
1256*56bb7041Schristos 		sym = force_reset_view;
1257*56bb7041Schristos 	      else
1258*56bb7041Schristos 		{
1259*56bb7041Schristos 		  sym = symbol_temp_new (absolute_section, &zero_address_frag,
1260*56bb7041Schristos 					 value);
1261*56bb7041Schristos 		  if (force_reset)
1262*56bb7041Schristos 		    force_reset_view = sym;
1263*56bb7041Schristos 		}
1264*56bb7041Schristos 	    }
1265*56bb7041Schristos 	  else
1266*56bb7041Schristos 	    {
1267*56bb7041Schristos 	      char *name = read_symbol_name ();
1268*56bb7041Schristos 
1269*56bb7041Schristos 	      if (!name)
1270*56bb7041Schristos 		return;
1271*56bb7041Schristos 	      sym = symbol_find_or_make (name);
1272*56bb7041Schristos 	      if (S_IS_DEFINED (sym) || symbol_equated_p (sym))
1273*56bb7041Schristos 		{
1274*56bb7041Schristos 		  if (S_IS_VOLATILE (sym))
1275*56bb7041Schristos 		    sym = symbol_clone (sym, 1);
1276*56bb7041Schristos 		  else if (!S_CAN_BE_REDEFINED (sym))
1277*56bb7041Schristos 		    {
1278*56bb7041Schristos 		      as_bad (_("symbol `%s' is already defined"), name);
1279*56bb7041Schristos 		      return;
1280*56bb7041Schristos 		    }
1281*56bb7041Schristos 		}
1282*56bb7041Schristos 	      S_SET_SEGMENT (sym, undefined_section);
1283*56bb7041Schristos 	      S_SET_VALUE (sym, 0);
1284*56bb7041Schristos 	      symbol_set_frag (sym, &zero_address_frag);
1285*56bb7041Schristos 	    }
1286*56bb7041Schristos 	  current.view = sym;
1287*56bb7041Schristos 	}
1288*56bb7041Schristos       else
1289*56bb7041Schristos 	{
1290*56bb7041Schristos 	  as_bad (_("unknown .loc sub-directive `%s'"), p);
1291*56bb7041Schristos 	  (void) restore_line_pointer (c);
1292*56bb7041Schristos 	  return;
1293*56bb7041Schristos 	}
1294*56bb7041Schristos 
1295*56bb7041Schristos       SKIP_WHITESPACE_AFTER_NAME ();
1296*56bb7041Schristos     }
1297*56bb7041Schristos 
1298*56bb7041Schristos   demand_empty_rest_of_line ();
1299*56bb7041Schristos   dwarf2_any_loc_directive_seen = dwarf2_loc_directive_seen = TRUE;
1300*56bb7041Schristos   debug_type = DEBUG_NONE;
1301*56bb7041Schristos 
1302*56bb7041Schristos   /* If we were given a view id, emit the row right away.  */
1303*56bb7041Schristos   if (current.view)
1304*56bb7041Schristos     dwarf2_emit_insn (0);
1305*56bb7041Schristos }
1306*56bb7041Schristos 
1307*56bb7041Schristos void
dwarf2_directive_loc_mark_labels(int dummy ATTRIBUTE_UNUSED)1308*56bb7041Schristos dwarf2_directive_loc_mark_labels (int dummy ATTRIBUTE_UNUSED)
1309*56bb7041Schristos {
1310*56bb7041Schristos   offsetT value = get_absolute_expression ();
1311*56bb7041Schristos 
1312*56bb7041Schristos   if (value != 0 && value != 1)
1313*56bb7041Schristos     {
1314*56bb7041Schristos       as_bad (_("expected 0 or 1"));
1315*56bb7041Schristos       ignore_rest_of_line ();
1316*56bb7041Schristos     }
1317*56bb7041Schristos   else
1318*56bb7041Schristos     {
1319*56bb7041Schristos       dwarf2_loc_mark_labels = value != 0;
1320*56bb7041Schristos       demand_empty_rest_of_line ();
1321*56bb7041Schristos     }
1322*56bb7041Schristos }
1323*56bb7041Schristos 
1324*56bb7041Schristos static struct frag *
first_frag_for_seg(segT seg)1325*56bb7041Schristos first_frag_for_seg (segT seg)
1326*56bb7041Schristos {
1327*56bb7041Schristos   return seg_info (seg)->frchainP->frch_root;
1328*56bb7041Schristos }
1329*56bb7041Schristos 
1330*56bb7041Schristos static struct frag *
last_frag_for_seg(segT seg)1331*56bb7041Schristos last_frag_for_seg (segT seg)
1332*56bb7041Schristos {
1333*56bb7041Schristos   frchainS *f = seg_info (seg)->frchainP;
1334*56bb7041Schristos 
1335*56bb7041Schristos   while (f->frch_next != NULL)
1336*56bb7041Schristos     f = f->frch_next;
1337*56bb7041Schristos 
1338*56bb7041Schristos   return f->frch_last;
1339*56bb7041Schristos }
1340*56bb7041Schristos 
1341*56bb7041Schristos /* Emit a single byte into the current segment.  */
1342*56bb7041Schristos 
1343*56bb7041Schristos static inline void
out_byte(int byte)1344*56bb7041Schristos out_byte (int byte)
1345*56bb7041Schristos {
1346*56bb7041Schristos   FRAG_APPEND_1_CHAR (byte);
1347*56bb7041Schristos }
1348*56bb7041Schristos 
1349*56bb7041Schristos /* Emit a statement program opcode into the current segment.  */
1350*56bb7041Schristos 
1351*56bb7041Schristos static inline void
out_opcode(int opc)1352*56bb7041Schristos out_opcode (int opc)
1353*56bb7041Schristos {
1354*56bb7041Schristos   out_byte (opc);
1355*56bb7041Schristos }
1356*56bb7041Schristos 
1357*56bb7041Schristos /* Emit a two-byte word into the current segment.  */
1358*56bb7041Schristos 
1359*56bb7041Schristos static inline void
out_two(int data)1360*56bb7041Schristos out_two (int data)
1361*56bb7041Schristos {
1362*56bb7041Schristos   md_number_to_chars (frag_more (2), data, 2);
1363*56bb7041Schristos }
1364*56bb7041Schristos 
1365*56bb7041Schristos /* Emit a four byte word into the current segment.  */
1366*56bb7041Schristos 
1367*56bb7041Schristos static inline void
out_four(int data)1368*56bb7041Schristos out_four (int data)
1369*56bb7041Schristos {
1370*56bb7041Schristos   md_number_to_chars (frag_more (4), data, 4);
1371*56bb7041Schristos }
1372*56bb7041Schristos 
1373*56bb7041Schristos /* Emit an unsigned "little-endian base 128" number.  */
1374*56bb7041Schristos 
1375*56bb7041Schristos static void
out_uleb128(addressT value)1376*56bb7041Schristos out_uleb128 (addressT value)
1377*56bb7041Schristos {
1378*56bb7041Schristos   output_leb128 (frag_more (sizeof_leb128 (value, 0)), value, 0);
1379*56bb7041Schristos }
1380*56bb7041Schristos 
1381*56bb7041Schristos /* Emit a signed "little-endian base 128" number.  */
1382*56bb7041Schristos 
1383*56bb7041Schristos static void
out_leb128(addressT value)1384*56bb7041Schristos out_leb128 (addressT value)
1385*56bb7041Schristos {
1386*56bb7041Schristos   output_leb128 (frag_more (sizeof_leb128 (value, 1)), value, 1);
1387*56bb7041Schristos }
1388*56bb7041Schristos 
1389*56bb7041Schristos /* Emit a tuple for .debug_abbrev.  */
1390*56bb7041Schristos 
1391*56bb7041Schristos static inline void
out_abbrev(int name,int form)1392*56bb7041Schristos out_abbrev (int name, int form)
1393*56bb7041Schristos {
1394*56bb7041Schristos   out_uleb128 (name);
1395*56bb7041Schristos   out_uleb128 (form);
1396*56bb7041Schristos }
1397*56bb7041Schristos 
1398*56bb7041Schristos /* Get the size of a fragment.  */
1399*56bb7041Schristos 
1400*56bb7041Schristos static offsetT
get_frag_fix(fragS * frag,segT seg)1401*56bb7041Schristos get_frag_fix (fragS *frag, segT seg)
1402*56bb7041Schristos {
1403*56bb7041Schristos   frchainS *fr;
1404*56bb7041Schristos 
1405*56bb7041Schristos   if (frag->fr_next)
1406*56bb7041Schristos     return frag->fr_fix;
1407*56bb7041Schristos 
1408*56bb7041Schristos   /* If a fragment is the last in the chain, special measures must be
1409*56bb7041Schristos      taken to find its size before relaxation, since it may be pending
1410*56bb7041Schristos      on some subsegment chain.  */
1411*56bb7041Schristos   for (fr = seg_info (seg)->frchainP; fr; fr = fr->frch_next)
1412*56bb7041Schristos     if (fr->frch_last == frag)
1413*56bb7041Schristos       return (char *) obstack_next_free (&fr->frch_obstack) - frag->fr_literal;
1414*56bb7041Schristos 
1415*56bb7041Schristos   abort ();
1416*56bb7041Schristos }
1417*56bb7041Schristos 
1418*56bb7041Schristos /* Set an absolute address (may result in a relocation entry).  */
1419*56bb7041Schristos 
1420*56bb7041Schristos static void
out_set_addr(symbolS * sym)1421*56bb7041Schristos out_set_addr (symbolS *sym)
1422*56bb7041Schristos {
1423*56bb7041Schristos   expressionS exp;
1424*56bb7041Schristos 
1425*56bb7041Schristos   memset (&exp, 0, sizeof exp);
1426*56bb7041Schristos   out_opcode (DW_LNS_extended_op);
1427*56bb7041Schristos   out_uleb128 (sizeof_address + 1);
1428*56bb7041Schristos 
1429*56bb7041Schristos   out_opcode (DW_LNE_set_address);
1430*56bb7041Schristos   exp.X_op = O_symbol;
1431*56bb7041Schristos   exp.X_add_symbol = sym;
1432*56bb7041Schristos   exp.X_add_number = 0;
1433*56bb7041Schristos   emit_expr (&exp, sizeof_address);
1434*56bb7041Schristos }
1435*56bb7041Schristos 
1436*56bb7041Schristos static void scale_addr_delta (addressT *);
1437*56bb7041Schristos 
1438*56bb7041Schristos static void
scale_addr_delta(addressT * addr_delta)1439*56bb7041Schristos scale_addr_delta (addressT *addr_delta)
1440*56bb7041Schristos {
1441*56bb7041Schristos   static int printed_this = 0;
1442*56bb7041Schristos   if (DWARF2_LINE_MIN_INSN_LENGTH > 1)
1443*56bb7041Schristos     {
1444*56bb7041Schristos       if (*addr_delta % DWARF2_LINE_MIN_INSN_LENGTH != 0  && !printed_this)
1445*56bb7041Schristos 	{
1446*56bb7041Schristos 	  as_bad("unaligned opcodes detected in executable segment");
1447*56bb7041Schristos 	  printed_this = 1;
1448*56bb7041Schristos 	}
1449*56bb7041Schristos       *addr_delta /= DWARF2_LINE_MIN_INSN_LENGTH;
1450*56bb7041Schristos     }
1451*56bb7041Schristos }
1452*56bb7041Schristos 
1453*56bb7041Schristos /* Encode a pair of line and address skips as efficiently as possible.
1454*56bb7041Schristos    Note that the line skip is signed, whereas the address skip is unsigned.
1455*56bb7041Schristos 
1456*56bb7041Schristos    The following two routines *must* be kept in sync.  This is
1457*56bb7041Schristos    enforced by making emit_inc_line_addr abort if we do not emit
1458*56bb7041Schristos    exactly the expected number of bytes.  */
1459*56bb7041Schristos 
1460*56bb7041Schristos static int
size_inc_line_addr(int line_delta,addressT addr_delta)1461*56bb7041Schristos size_inc_line_addr (int line_delta, addressT addr_delta)
1462*56bb7041Schristos {
1463*56bb7041Schristos   unsigned int tmp, opcode;
1464*56bb7041Schristos   int len = 0;
1465*56bb7041Schristos 
1466*56bb7041Schristos   /* Scale the address delta by the minimum instruction length.  */
1467*56bb7041Schristos   scale_addr_delta (&addr_delta);
1468*56bb7041Schristos 
1469*56bb7041Schristos   /* INT_MAX is a signal that this is actually a DW_LNE_end_sequence.
1470*56bb7041Schristos      We cannot use special opcodes here, since we want the end_sequence
1471*56bb7041Schristos      to emit the matrix entry.  */
1472*56bb7041Schristos   if (line_delta == INT_MAX)
1473*56bb7041Schristos     {
1474*56bb7041Schristos       if (addr_delta == MAX_SPECIAL_ADDR_DELTA)
1475*56bb7041Schristos 	len = 1;
1476*56bb7041Schristos       else if (addr_delta)
1477*56bb7041Schristos 	len = 1 + sizeof_leb128 (addr_delta, 0);
1478*56bb7041Schristos       return len + 3;
1479*56bb7041Schristos     }
1480*56bb7041Schristos 
1481*56bb7041Schristos   /* Bias the line delta by the base.  */
1482*56bb7041Schristos   tmp = line_delta - DWARF2_LINE_BASE;
1483*56bb7041Schristos 
1484*56bb7041Schristos   /* If the line increment is out of range of a special opcode, we
1485*56bb7041Schristos      must encode it with DW_LNS_advance_line.  */
1486*56bb7041Schristos   if (tmp >= DWARF2_LINE_RANGE)
1487*56bb7041Schristos     {
1488*56bb7041Schristos       len = 1 + sizeof_leb128 (line_delta, 1);
1489*56bb7041Schristos       line_delta = 0;
1490*56bb7041Schristos       tmp = 0 - DWARF2_LINE_BASE;
1491*56bb7041Schristos     }
1492*56bb7041Schristos 
1493*56bb7041Schristos   /* Bias the opcode by the special opcode base.  */
1494*56bb7041Schristos   tmp += DWARF2_LINE_OPCODE_BASE;
1495*56bb7041Schristos 
1496*56bb7041Schristos   /* Avoid overflow when addr_delta is large.  */
1497*56bb7041Schristos   if (addr_delta < 256 + MAX_SPECIAL_ADDR_DELTA)
1498*56bb7041Schristos     {
1499*56bb7041Schristos       /* Try using a special opcode.  */
1500*56bb7041Schristos       opcode = tmp + addr_delta * DWARF2_LINE_RANGE;
1501*56bb7041Schristos       if (opcode <= 255)
1502*56bb7041Schristos 	return len + 1;
1503*56bb7041Schristos 
1504*56bb7041Schristos       /* Try using DW_LNS_const_add_pc followed by special op.  */
1505*56bb7041Schristos       opcode = tmp + (addr_delta - MAX_SPECIAL_ADDR_DELTA) * DWARF2_LINE_RANGE;
1506*56bb7041Schristos       if (opcode <= 255)
1507*56bb7041Schristos 	return len + 2;
1508*56bb7041Schristos     }
1509*56bb7041Schristos 
1510*56bb7041Schristos   /* Otherwise use DW_LNS_advance_pc.  */
1511*56bb7041Schristos   len += 1 + sizeof_leb128 (addr_delta, 0);
1512*56bb7041Schristos 
1513*56bb7041Schristos   /* DW_LNS_copy or special opcode.  */
1514*56bb7041Schristos   len += 1;
1515*56bb7041Schristos 
1516*56bb7041Schristos   return len;
1517*56bb7041Schristos }
1518*56bb7041Schristos 
1519*56bb7041Schristos static void
emit_inc_line_addr(int line_delta,addressT addr_delta,char * p,int len)1520*56bb7041Schristos emit_inc_line_addr (int line_delta, addressT addr_delta, char *p, int len)
1521*56bb7041Schristos {
1522*56bb7041Schristos   unsigned int tmp, opcode;
1523*56bb7041Schristos   int need_copy = 0;
1524*56bb7041Schristos   char *end = p + len;
1525*56bb7041Schristos 
1526*56bb7041Schristos   /* Line number sequences cannot go backward in addresses.  This means
1527*56bb7041Schristos      we've incorrectly ordered the statements in the sequence.  */
1528*56bb7041Schristos   gas_assert ((offsetT) addr_delta >= 0);
1529*56bb7041Schristos 
1530*56bb7041Schristos   /* Scale the address delta by the minimum instruction length.  */
1531*56bb7041Schristos   scale_addr_delta (&addr_delta);
1532*56bb7041Schristos 
1533*56bb7041Schristos   /* INT_MAX is a signal that this is actually a DW_LNE_end_sequence.
1534*56bb7041Schristos      We cannot use special opcodes here, since we want the end_sequence
1535*56bb7041Schristos      to emit the matrix entry.  */
1536*56bb7041Schristos   if (line_delta == INT_MAX)
1537*56bb7041Schristos     {
1538*56bb7041Schristos       if (addr_delta == MAX_SPECIAL_ADDR_DELTA)
1539*56bb7041Schristos 	*p++ = DW_LNS_const_add_pc;
1540*56bb7041Schristos       else if (addr_delta)
1541*56bb7041Schristos 	{
1542*56bb7041Schristos 	  *p++ = DW_LNS_advance_pc;
1543*56bb7041Schristos 	  p += output_leb128 (p, addr_delta, 0);
1544*56bb7041Schristos 	}
1545*56bb7041Schristos 
1546*56bb7041Schristos       *p++ = DW_LNS_extended_op;
1547*56bb7041Schristos       *p++ = 1;
1548*56bb7041Schristos       *p++ = DW_LNE_end_sequence;
1549*56bb7041Schristos       goto done;
1550*56bb7041Schristos     }
1551*56bb7041Schristos 
1552*56bb7041Schristos   /* Bias the line delta by the base.  */
1553*56bb7041Schristos   tmp = line_delta - DWARF2_LINE_BASE;
1554*56bb7041Schristos 
1555*56bb7041Schristos   /* If the line increment is out of range of a special opcode, we
1556*56bb7041Schristos      must encode it with DW_LNS_advance_line.  */
1557*56bb7041Schristos   if (tmp >= DWARF2_LINE_RANGE)
1558*56bb7041Schristos     {
1559*56bb7041Schristos       *p++ = DW_LNS_advance_line;
1560*56bb7041Schristos       p += output_leb128 (p, line_delta, 1);
1561*56bb7041Schristos 
1562*56bb7041Schristos       line_delta = 0;
1563*56bb7041Schristos       tmp = 0 - DWARF2_LINE_BASE;
1564*56bb7041Schristos       need_copy = 1;
1565*56bb7041Schristos     }
1566*56bb7041Schristos 
1567*56bb7041Schristos   /* Prettier, I think, to use DW_LNS_copy instead of a "line +0, addr +0"
1568*56bb7041Schristos      special opcode.  */
1569*56bb7041Schristos   if (line_delta == 0 && addr_delta == 0)
1570*56bb7041Schristos     {
1571*56bb7041Schristos       *p++ = DW_LNS_copy;
1572*56bb7041Schristos       goto done;
1573*56bb7041Schristos     }
1574*56bb7041Schristos 
1575*56bb7041Schristos   /* Bias the opcode by the special opcode base.  */
1576*56bb7041Schristos   tmp += DWARF2_LINE_OPCODE_BASE;
1577*56bb7041Schristos 
1578*56bb7041Schristos   /* Avoid overflow when addr_delta is large.  */
1579*56bb7041Schristos   if (addr_delta < 256 + MAX_SPECIAL_ADDR_DELTA)
1580*56bb7041Schristos     {
1581*56bb7041Schristos       /* Try using a special opcode.  */
1582*56bb7041Schristos       opcode = tmp + addr_delta * DWARF2_LINE_RANGE;
1583*56bb7041Schristos       if (opcode <= 255)
1584*56bb7041Schristos 	{
1585*56bb7041Schristos 	  *p++ = opcode;
1586*56bb7041Schristos 	  goto done;
1587*56bb7041Schristos 	}
1588*56bb7041Schristos 
1589*56bb7041Schristos       /* Try using DW_LNS_const_add_pc followed by special op.  */
1590*56bb7041Schristos       opcode = tmp + (addr_delta - MAX_SPECIAL_ADDR_DELTA) * DWARF2_LINE_RANGE;
1591*56bb7041Schristos       if (opcode <= 255)
1592*56bb7041Schristos 	{
1593*56bb7041Schristos 	  *p++ = DW_LNS_const_add_pc;
1594*56bb7041Schristos 	  *p++ = opcode;
1595*56bb7041Schristos 	  goto done;
1596*56bb7041Schristos 	}
1597*56bb7041Schristos     }
1598*56bb7041Schristos 
1599*56bb7041Schristos   /* Otherwise use DW_LNS_advance_pc.  */
1600*56bb7041Schristos   *p++ = DW_LNS_advance_pc;
1601*56bb7041Schristos   p += output_leb128 (p, addr_delta, 0);
1602*56bb7041Schristos 
1603*56bb7041Schristos   if (need_copy)
1604*56bb7041Schristos     *p++ = DW_LNS_copy;
1605*56bb7041Schristos   else
1606*56bb7041Schristos     *p++ = tmp;
1607*56bb7041Schristos 
1608*56bb7041Schristos  done:
1609*56bb7041Schristos   gas_assert (p == end);
1610*56bb7041Schristos }
1611*56bb7041Schristos 
1612*56bb7041Schristos /* Handy routine to combine calls to the above two routines.  */
1613*56bb7041Schristos 
1614*56bb7041Schristos static void
out_inc_line_addr(int line_delta,addressT addr_delta)1615*56bb7041Schristos out_inc_line_addr (int line_delta, addressT addr_delta)
1616*56bb7041Schristos {
1617*56bb7041Schristos   int len = size_inc_line_addr (line_delta, addr_delta);
1618*56bb7041Schristos   emit_inc_line_addr (line_delta, addr_delta, frag_more (len), len);
1619*56bb7041Schristos }
1620*56bb7041Schristos 
1621*56bb7041Schristos /* Write out an alternative form of line and address skips using
1622*56bb7041Schristos    DW_LNS_fixed_advance_pc opcodes.  This uses more space than the default
1623*56bb7041Schristos    line and address information, but it is required if linker relaxation
1624*56bb7041Schristos    could change the code offsets.  The following two routines *must* be
1625*56bb7041Schristos    kept in sync.  */
1626*56bb7041Schristos #define ADDR_DELTA_LIMIT 50000
1627*56bb7041Schristos 
1628*56bb7041Schristos static int
size_fixed_inc_line_addr(int line_delta,addressT addr_delta)1629*56bb7041Schristos size_fixed_inc_line_addr (int line_delta, addressT addr_delta)
1630*56bb7041Schristos {
1631*56bb7041Schristos   int len = 0;
1632*56bb7041Schristos 
1633*56bb7041Schristos   /* INT_MAX is a signal that this is actually a DW_LNE_end_sequence.  */
1634*56bb7041Schristos   if (line_delta != INT_MAX)
1635*56bb7041Schristos     len = 1 + sizeof_leb128 (line_delta, 1);
1636*56bb7041Schristos 
1637*56bb7041Schristos   if (addr_delta > ADDR_DELTA_LIMIT)
1638*56bb7041Schristos     {
1639*56bb7041Schristos       /* DW_LNS_extended_op */
1640*56bb7041Schristos       len += 1 + sizeof_leb128 (sizeof_address + 1, 0);
1641*56bb7041Schristos       /* DW_LNE_set_address */
1642*56bb7041Schristos       len += 1 + sizeof_address;
1643*56bb7041Schristos     }
1644*56bb7041Schristos   else
1645*56bb7041Schristos     /* DW_LNS_fixed_advance_pc */
1646*56bb7041Schristos     len += 3;
1647*56bb7041Schristos 
1648*56bb7041Schristos   if (line_delta == INT_MAX)
1649*56bb7041Schristos     /* DW_LNS_extended_op + DW_LNE_end_sequence */
1650*56bb7041Schristos     len += 3;
1651*56bb7041Schristos   else
1652*56bb7041Schristos     /* DW_LNS_copy */
1653*56bb7041Schristos     len += 1;
1654*56bb7041Schristos 
1655*56bb7041Schristos   return len;
1656*56bb7041Schristos }
1657*56bb7041Schristos 
1658*56bb7041Schristos static void
emit_fixed_inc_line_addr(int line_delta,addressT addr_delta,fragS * frag,char * p,int len)1659*56bb7041Schristos emit_fixed_inc_line_addr (int line_delta, addressT addr_delta, fragS *frag,
1660*56bb7041Schristos 			  char *p, int len)
1661*56bb7041Schristos {
1662*56bb7041Schristos   expressionS *pexp;
1663*56bb7041Schristos   char *end = p + len;
1664*56bb7041Schristos 
1665*56bb7041Schristos   /* Line number sequences cannot go backward in addresses.  This means
1666*56bb7041Schristos      we've incorrectly ordered the statements in the sequence.  */
1667*56bb7041Schristos   gas_assert ((offsetT) addr_delta >= 0);
1668*56bb7041Schristos 
1669*56bb7041Schristos   /* Verify that we have kept in sync with size_fixed_inc_line_addr.  */
1670*56bb7041Schristos   gas_assert (len == size_fixed_inc_line_addr (line_delta, addr_delta));
1671*56bb7041Schristos 
1672*56bb7041Schristos   /* INT_MAX is a signal that this is actually a DW_LNE_end_sequence.  */
1673*56bb7041Schristos   if (line_delta != INT_MAX)
1674*56bb7041Schristos     {
1675*56bb7041Schristos       *p++ = DW_LNS_advance_line;
1676*56bb7041Schristos       p += output_leb128 (p, line_delta, 1);
1677*56bb7041Schristos     }
1678*56bb7041Schristos 
1679*56bb7041Schristos   pexp = symbol_get_value_expression (frag->fr_symbol);
1680*56bb7041Schristos 
1681*56bb7041Schristos   /* The DW_LNS_fixed_advance_pc opcode has a 2-byte operand so it can
1682*56bb7041Schristos      advance the address by at most 64K.  Linker relaxation (without
1683*56bb7041Schristos      which this function would not be used) could change the operand by
1684*56bb7041Schristos      an unknown amount.  If the address increment is getting close to
1685*56bb7041Schristos      the limit, just reset the address.  */
1686*56bb7041Schristos   if (addr_delta > ADDR_DELTA_LIMIT)
1687*56bb7041Schristos     {
1688*56bb7041Schristos       symbolS *to_sym;
1689*56bb7041Schristos       expressionS exp;
1690*56bb7041Schristos 
1691*56bb7041Schristos       memset (&exp, 0, sizeof exp);
1692*56bb7041Schristos       gas_assert (pexp->X_op == O_subtract);
1693*56bb7041Schristos       to_sym = pexp->X_add_symbol;
1694*56bb7041Schristos 
1695*56bb7041Schristos       *p++ = DW_LNS_extended_op;
1696*56bb7041Schristos       p += output_leb128 (p, sizeof_address + 1, 0);
1697*56bb7041Schristos       *p++ = DW_LNE_set_address;
1698*56bb7041Schristos       exp.X_op = O_symbol;
1699*56bb7041Schristos       exp.X_add_symbol = to_sym;
1700*56bb7041Schristos       exp.X_add_number = 0;
1701*56bb7041Schristos       emit_expr_fix (&exp, sizeof_address, frag, p, TC_PARSE_CONS_RETURN_NONE);
1702*56bb7041Schristos       p += sizeof_address;
1703*56bb7041Schristos     }
1704*56bb7041Schristos   else
1705*56bb7041Schristos     {
1706*56bb7041Schristos       *p++ = DW_LNS_fixed_advance_pc;
1707*56bb7041Schristos       emit_expr_fix (pexp, 2, frag, p, TC_PARSE_CONS_RETURN_NONE);
1708*56bb7041Schristos       p += 2;
1709*56bb7041Schristos     }
1710*56bb7041Schristos 
1711*56bb7041Schristos   if (line_delta == INT_MAX)
1712*56bb7041Schristos     {
1713*56bb7041Schristos       *p++ = DW_LNS_extended_op;
1714*56bb7041Schristos       *p++ = 1;
1715*56bb7041Schristos       *p++ = DW_LNE_end_sequence;
1716*56bb7041Schristos     }
1717*56bb7041Schristos   else
1718*56bb7041Schristos     *p++ = DW_LNS_copy;
1719*56bb7041Schristos 
1720*56bb7041Schristos   gas_assert (p == end);
1721*56bb7041Schristos }
1722*56bb7041Schristos 
1723*56bb7041Schristos /* Generate a variant frag that we can use to relax address/line
1724*56bb7041Schristos    increments between fragments of the target segment.  */
1725*56bb7041Schristos 
1726*56bb7041Schristos static void
relax_inc_line_addr(int line_delta,symbolS * to_sym,symbolS * from_sym)1727*56bb7041Schristos relax_inc_line_addr (int line_delta, symbolS *to_sym, symbolS *from_sym)
1728*56bb7041Schristos {
1729*56bb7041Schristos   expressionS exp;
1730*56bb7041Schristos   int max_chars;
1731*56bb7041Schristos 
1732*56bb7041Schristos   memset (&exp, 0, sizeof exp);
1733*56bb7041Schristos   exp.X_op = O_subtract;
1734*56bb7041Schristos   exp.X_add_symbol = to_sym;
1735*56bb7041Schristos   exp.X_op_symbol = from_sym;
1736*56bb7041Schristos   exp.X_add_number = 0;
1737*56bb7041Schristos 
1738*56bb7041Schristos   /* The maximum size of the frag is the line delta with a maximum
1739*56bb7041Schristos      sized address delta.  */
1740*56bb7041Schristos   if (DWARF2_USE_FIXED_ADVANCE_PC)
1741*56bb7041Schristos     max_chars = size_fixed_inc_line_addr (line_delta,
1742*56bb7041Schristos 					  -DWARF2_LINE_MIN_INSN_LENGTH);
1743*56bb7041Schristos   else
1744*56bb7041Schristos     max_chars = size_inc_line_addr (line_delta, -DWARF2_LINE_MIN_INSN_LENGTH);
1745*56bb7041Schristos 
1746*56bb7041Schristos   frag_var (rs_dwarf2dbg, max_chars, max_chars, 1,
1747*56bb7041Schristos 	    make_expr_symbol (&exp), line_delta, NULL);
1748*56bb7041Schristos }
1749*56bb7041Schristos 
1750*56bb7041Schristos /* The function estimates the size of a rs_dwarf2dbg variant frag
1751*56bb7041Schristos    based on the current values of the symbols.  It is called before
1752*56bb7041Schristos    the relaxation loop.  We set fr_subtype to the expected length.  */
1753*56bb7041Schristos 
1754*56bb7041Schristos int
dwarf2dbg_estimate_size_before_relax(fragS * frag)1755*56bb7041Schristos dwarf2dbg_estimate_size_before_relax (fragS *frag)
1756*56bb7041Schristos {
1757*56bb7041Schristos   offsetT addr_delta;
1758*56bb7041Schristos   int size;
1759*56bb7041Schristos 
1760*56bb7041Schristos   addr_delta = resolve_symbol_value (frag->fr_symbol);
1761*56bb7041Schristos   if (DWARF2_USE_FIXED_ADVANCE_PC)
1762*56bb7041Schristos     size = size_fixed_inc_line_addr (frag->fr_offset, addr_delta);
1763*56bb7041Schristos   else
1764*56bb7041Schristos     size = size_inc_line_addr (frag->fr_offset, addr_delta);
1765*56bb7041Schristos 
1766*56bb7041Schristos   frag->fr_subtype = size;
1767*56bb7041Schristos 
1768*56bb7041Schristos   return size;
1769*56bb7041Schristos }
1770*56bb7041Schristos 
1771*56bb7041Schristos /* This function relaxes a rs_dwarf2dbg variant frag based on the
1772*56bb7041Schristos    current values of the symbols.  fr_subtype is the current length
1773*56bb7041Schristos    of the frag.  This returns the change in frag length.  */
1774*56bb7041Schristos 
1775*56bb7041Schristos int
dwarf2dbg_relax_frag(fragS * frag)1776*56bb7041Schristos dwarf2dbg_relax_frag (fragS *frag)
1777*56bb7041Schristos {
1778*56bb7041Schristos   int old_size, new_size;
1779*56bb7041Schristos 
1780*56bb7041Schristos   old_size = frag->fr_subtype;
1781*56bb7041Schristos   new_size = dwarf2dbg_estimate_size_before_relax (frag);
1782*56bb7041Schristos 
1783*56bb7041Schristos   return new_size - old_size;
1784*56bb7041Schristos }
1785*56bb7041Schristos 
1786*56bb7041Schristos /* This function converts a rs_dwarf2dbg variant frag into a normal
1787*56bb7041Schristos    fill frag.  This is called after all relaxation has been done.
1788*56bb7041Schristos    fr_subtype will be the desired length of the frag.  */
1789*56bb7041Schristos 
1790*56bb7041Schristos void
dwarf2dbg_convert_frag(fragS * frag)1791*56bb7041Schristos dwarf2dbg_convert_frag (fragS *frag)
1792*56bb7041Schristos {
1793*56bb7041Schristos   offsetT addr_diff;
1794*56bb7041Schristos 
1795*56bb7041Schristos   if (DWARF2_USE_FIXED_ADVANCE_PC)
1796*56bb7041Schristos     {
1797*56bb7041Schristos       /* If linker relaxation is enabled then the distance between the two
1798*56bb7041Schristos 	 symbols in the frag->fr_symbol expression might change.  Hence we
1799*56bb7041Schristos 	 cannot rely upon the value computed by resolve_symbol_value.
1800*56bb7041Schristos 	 Instead we leave the expression unfinalized and allow
1801*56bb7041Schristos 	 emit_fixed_inc_line_addr to create a fixup (which later becomes a
1802*56bb7041Schristos 	 relocation) that will allow the linker to correctly compute the
1803*56bb7041Schristos 	 actual address difference.  We have to use a fixed line advance for
1804*56bb7041Schristos 	 this as we cannot (easily) relocate leb128 encoded values.  */
1805*56bb7041Schristos       int saved_finalize_syms = finalize_syms;
1806*56bb7041Schristos 
1807*56bb7041Schristos       finalize_syms = 0;
1808*56bb7041Schristos       addr_diff = resolve_symbol_value (frag->fr_symbol);
1809*56bb7041Schristos       finalize_syms = saved_finalize_syms;
1810*56bb7041Schristos     }
1811*56bb7041Schristos   else
1812*56bb7041Schristos     addr_diff = resolve_symbol_value (frag->fr_symbol);
1813*56bb7041Schristos 
1814*56bb7041Schristos   /* fr_var carries the max_chars that we created the fragment with.
1815*56bb7041Schristos      fr_subtype carries the current expected length.  We must, of
1816*56bb7041Schristos      course, have allocated enough memory earlier.  */
1817*56bb7041Schristos   gas_assert (frag->fr_var >= (int) frag->fr_subtype);
1818*56bb7041Schristos 
1819*56bb7041Schristos   if (DWARF2_USE_FIXED_ADVANCE_PC)
1820*56bb7041Schristos     emit_fixed_inc_line_addr (frag->fr_offset, addr_diff, frag,
1821*56bb7041Schristos 			      frag->fr_literal + frag->fr_fix,
1822*56bb7041Schristos 			      frag->fr_subtype);
1823*56bb7041Schristos   else
1824*56bb7041Schristos     emit_inc_line_addr (frag->fr_offset, addr_diff,
1825*56bb7041Schristos 			frag->fr_literal + frag->fr_fix, frag->fr_subtype);
1826*56bb7041Schristos 
1827*56bb7041Schristos   frag->fr_fix += frag->fr_subtype;
1828*56bb7041Schristos   frag->fr_type = rs_fill;
1829*56bb7041Schristos   frag->fr_var = 0;
1830*56bb7041Schristos   frag->fr_offset = 0;
1831*56bb7041Schristos }
1832*56bb7041Schristos 
1833*56bb7041Schristos /* Generate .debug_line content for the chain of line number entries
1834*56bb7041Schristos    beginning at E, for segment SEG.  */
1835*56bb7041Schristos 
1836*56bb7041Schristos static void
process_entries(segT seg,struct line_entry * e)1837*56bb7041Schristos process_entries (segT seg, struct line_entry *e)
1838*56bb7041Schristos {
1839*56bb7041Schristos   unsigned filenum = 1;
1840*56bb7041Schristos   unsigned line = 1;
1841*56bb7041Schristos   unsigned column = 0;
1842*56bb7041Schristos   unsigned isa = 0;
1843*56bb7041Schristos   unsigned flags = DWARF2_LINE_DEFAULT_IS_STMT ? DWARF2_FLAG_IS_STMT : 0;
1844*56bb7041Schristos   fragS *last_frag = NULL, *frag;
1845*56bb7041Schristos   addressT last_frag_ofs = 0, frag_ofs;
1846*56bb7041Schristos   symbolS *last_lab = NULL, *lab;
1847*56bb7041Schristos   struct line_entry *next;
1848*56bb7041Schristos 
1849*56bb7041Schristos   if (flag_dwarf_sections)
1850*56bb7041Schristos     {
1851*56bb7041Schristos       char * name;
1852*56bb7041Schristos       const char * sec_name;
1853*56bb7041Schristos 
1854*56bb7041Schristos       /* Switch to the relevant sub-section before we start to emit
1855*56bb7041Schristos 	 the line number table.
1856*56bb7041Schristos 
1857*56bb7041Schristos 	 FIXME: These sub-sections do not have a normal Line Number
1858*56bb7041Schristos 	 Program Header, thus strictly speaking they are not valid
1859*56bb7041Schristos 	 DWARF sections.  Unfortunately the DWARF standard assumes
1860*56bb7041Schristos 	 a one-to-one relationship between compilation units and
1861*56bb7041Schristos 	 line number tables.  Thus we have to have a .debug_line
1862*56bb7041Schristos 	 section, as well as our sub-sections, and we have to ensure
1863*56bb7041Schristos 	 that all of the sub-sections are merged into a proper
1864*56bb7041Schristos 	 .debug_line section before a debugger sees them.  */
1865*56bb7041Schristos 
1866*56bb7041Schristos       sec_name = bfd_section_name (seg);
1867*56bb7041Schristos       if (strcmp (sec_name, ".text") != 0)
1868*56bb7041Schristos 	{
1869*56bb7041Schristos 	  name = concat (".debug_line", sec_name, (char *) NULL);
1870*56bb7041Schristos 	  subseg_set (subseg_get (name, FALSE), 0);
1871*56bb7041Schristos 	}
1872*56bb7041Schristos       else
1873*56bb7041Schristos 	/* Don't create a .debug_line.text section -
1874*56bb7041Schristos 	   that is redundant.  Instead just switch back to the
1875*56bb7041Schristos 	   normal .debug_line section.  */
1876*56bb7041Schristos 	subseg_set (subseg_get (".debug_line", FALSE), 0);
1877*56bb7041Schristos     }
1878*56bb7041Schristos 
1879*56bb7041Schristos   do
1880*56bb7041Schristos     {
1881*56bb7041Schristos       int line_delta;
1882*56bb7041Schristos 
1883*56bb7041Schristos       if (filenum != e->loc.filenum)
1884*56bb7041Schristos 	{
1885*56bb7041Schristos 	  filenum = e->loc.filenum;
1886*56bb7041Schristos 	  out_opcode (DW_LNS_set_file);
1887*56bb7041Schristos 	  out_uleb128 (filenum);
1888*56bb7041Schristos 	}
1889*56bb7041Schristos 
1890*56bb7041Schristos       if (column != e->loc.column)
1891*56bb7041Schristos 	{
1892*56bb7041Schristos 	  column = e->loc.column;
1893*56bb7041Schristos 	  out_opcode (DW_LNS_set_column);
1894*56bb7041Schristos 	  out_uleb128 (column);
1895*56bb7041Schristos 	}
1896*56bb7041Schristos 
1897*56bb7041Schristos       if (e->loc.discriminator != 0)
1898*56bb7041Schristos 	{
1899*56bb7041Schristos 	  out_opcode (DW_LNS_extended_op);
1900*56bb7041Schristos 	  out_leb128 (1 + sizeof_leb128 (e->loc.discriminator, 0));
1901*56bb7041Schristos 	  out_opcode (DW_LNE_set_discriminator);
1902*56bb7041Schristos 	  out_uleb128 (e->loc.discriminator);
1903*56bb7041Schristos 	}
1904*56bb7041Schristos 
1905*56bb7041Schristos       if (isa != e->loc.isa)
1906*56bb7041Schristos 	{
1907*56bb7041Schristos 	  isa = e->loc.isa;
1908*56bb7041Schristos 	  out_opcode (DW_LNS_set_isa);
1909*56bb7041Schristos 	  out_uleb128 (isa);
1910*56bb7041Schristos 	}
1911*56bb7041Schristos 
1912*56bb7041Schristos       if ((e->loc.flags ^ flags) & DWARF2_FLAG_IS_STMT)
1913*56bb7041Schristos 	{
1914*56bb7041Schristos 	  flags = e->loc.flags;
1915*56bb7041Schristos 	  out_opcode (DW_LNS_negate_stmt);
1916*56bb7041Schristos 	}
1917*56bb7041Schristos 
1918*56bb7041Schristos       if (e->loc.flags & DWARF2_FLAG_BASIC_BLOCK)
1919*56bb7041Schristos 	out_opcode (DW_LNS_set_basic_block);
1920*56bb7041Schristos 
1921*56bb7041Schristos       if (e->loc.flags & DWARF2_FLAG_PROLOGUE_END)
1922*56bb7041Schristos 	out_opcode (DW_LNS_set_prologue_end);
1923*56bb7041Schristos 
1924*56bb7041Schristos       if (e->loc.flags & DWARF2_FLAG_EPILOGUE_BEGIN)
1925*56bb7041Schristos 	out_opcode (DW_LNS_set_epilogue_begin);
1926*56bb7041Schristos 
1927*56bb7041Schristos       /* Don't try to optimize away redundant entries; gdb wants two
1928*56bb7041Schristos 	 entries for a function where the code starts on the same line as
1929*56bb7041Schristos 	 the {, and there's no way to identify that case here.  Trust gcc
1930*56bb7041Schristos 	 to optimize appropriately.  */
1931*56bb7041Schristos       line_delta = e->loc.line - line;
1932*56bb7041Schristos       lab = e->label;
1933*56bb7041Schristos       frag = symbol_get_frag (lab);
1934*56bb7041Schristos       frag_ofs = S_GET_VALUE (lab);
1935*56bb7041Schristos 
1936*56bb7041Schristos       if (last_frag == NULL
1937*56bb7041Schristos 	  || (e->loc.view == force_reset_view && force_reset_view
1938*56bb7041Schristos 	      /* If we're going to reset the view, but we know we're
1939*56bb7041Schristos 		 advancing the PC, we don't have to force with
1940*56bb7041Schristos 		 set_address.  We know we do when we're at the same
1941*56bb7041Schristos 		 address of the same frag, and we know we might when
1942*56bb7041Schristos 		 we're in the beginning of a frag, and we were at the
1943*56bb7041Schristos 		 end of the previous frag.  */
1944*56bb7041Schristos 	      && (frag == last_frag
1945*56bb7041Schristos 		  ? (last_frag_ofs == frag_ofs)
1946*56bb7041Schristos 		  : (frag_ofs == 0
1947*56bb7041Schristos 		     && ((offsetT)last_frag_ofs
1948*56bb7041Schristos 			 >= get_frag_fix (last_frag, seg))))))
1949*56bb7041Schristos 	{
1950*56bb7041Schristos 	  out_set_addr (lab);
1951*56bb7041Schristos 	  out_inc_line_addr (line_delta, 0);
1952*56bb7041Schristos 	}
1953*56bb7041Schristos       else if (frag == last_frag && ! DWARF2_USE_FIXED_ADVANCE_PC)
1954*56bb7041Schristos 	out_inc_line_addr (line_delta, frag_ofs - last_frag_ofs);
1955*56bb7041Schristos       else
1956*56bb7041Schristos 	relax_inc_line_addr (line_delta, lab, last_lab);
1957*56bb7041Schristos 
1958*56bb7041Schristos       line = e->loc.line;
1959*56bb7041Schristos       last_lab = lab;
1960*56bb7041Schristos       last_frag = frag;
1961*56bb7041Schristos       last_frag_ofs = frag_ofs;
1962*56bb7041Schristos 
1963*56bb7041Schristos       next = e->next;
1964*56bb7041Schristos       free (e);
1965*56bb7041Schristos       e = next;
1966*56bb7041Schristos     }
1967*56bb7041Schristos   while (e);
1968*56bb7041Schristos 
1969*56bb7041Schristos   /* Emit a DW_LNE_end_sequence for the end of the section.  */
1970*56bb7041Schristos   frag = last_frag_for_seg (seg);
1971*56bb7041Schristos   frag_ofs = get_frag_fix (frag, seg);
1972*56bb7041Schristos   if (frag == last_frag && ! DWARF2_USE_FIXED_ADVANCE_PC)
1973*56bb7041Schristos     out_inc_line_addr (INT_MAX, frag_ofs - last_frag_ofs);
1974*56bb7041Schristos   else
1975*56bb7041Schristos     {
1976*56bb7041Schristos       lab = symbol_temp_new (seg, frag, frag_ofs);
1977*56bb7041Schristos       relax_inc_line_addr (INT_MAX, lab, last_lab);
1978*56bb7041Schristos     }
1979*56bb7041Schristos }
1980*56bb7041Schristos 
1981*56bb7041Schristos /* Switch to LINE_STR_SEG and output the given STR.  Return the
1982*56bb7041Schristos    symbol pointing to the new string in the section.  */
1983*56bb7041Schristos 
1984*56bb7041Schristos static symbolS *
add_line_strp(segT line_str_seg,const char * str)1985*56bb7041Schristos add_line_strp (segT line_str_seg, const char *str)
1986*56bb7041Schristos {
1987*56bb7041Schristos   char *cp;
1988*56bb7041Schristos   size_t size;
1989*56bb7041Schristos   symbolS *sym;
1990*56bb7041Schristos 
1991*56bb7041Schristos   subseg_set (line_str_seg, 0);
1992*56bb7041Schristos 
1993*56bb7041Schristos   sym = symbol_temp_new_now_octets ();
1994*56bb7041Schristos 
1995*56bb7041Schristos   size = strlen (str) + 1;
1996*56bb7041Schristos   cp = frag_more (size);
1997*56bb7041Schristos   memcpy (cp, str, size);
1998*56bb7041Schristos 
1999*56bb7041Schristos   return sym;
2000*56bb7041Schristos }
2001*56bb7041Schristos 
2002*56bb7041Schristos 
2003*56bb7041Schristos /* Emit the directory and file tables for .debug_line.  */
2004*56bb7041Schristos 
2005*56bb7041Schristos static void
out_dir_and_file_list(segT line_seg,int sizeof_offset)2006*56bb7041Schristos out_dir_and_file_list (segT line_seg, int sizeof_offset)
2007*56bb7041Schristos {
2008*56bb7041Schristos   size_t size;
2009*56bb7041Schristos   const char *dir;
2010*56bb7041Schristos   char *cp;
2011*56bb7041Schristos   unsigned int i;
2012*56bb7041Schristos   bfd_boolean emit_md5 = FALSE;
2013*56bb7041Schristos   bfd_boolean emit_timestamps = TRUE;
2014*56bb7041Schristos   bfd_boolean emit_filesize = TRUE;
2015*56bb7041Schristos   segT line_str_seg = NULL;
2016*56bb7041Schristos   symbolS *line_strp;
2017*56bb7041Schristos 
2018*56bb7041Schristos   /* Output the Directory Table.  */
2019*56bb7041Schristos   if (DWARF2_LINE_VERSION >= 5)
2020*56bb7041Schristos     {
2021*56bb7041Schristos       /* We only have one column in the directory table.  */
2022*56bb7041Schristos       out_byte (1);
2023*56bb7041Schristos 
2024*56bb7041Schristos       /* Describe the purpose and format of the column.  */
2025*56bb7041Schristos       out_uleb128 (DW_LNCT_path);
2026*56bb7041Schristos       /* Store these strings in the .debug_line_str section so they
2027*56bb7041Schristos 	 can be shared.  */
2028*56bb7041Schristos       out_uleb128 (DW_FORM_line_strp);
2029*56bb7041Schristos 
2030*56bb7041Schristos       /* Now state how many rows there are in the table.  We need at
2031*56bb7041Schristos 	 least 1 if there is one or more file names to store the
2032*56bb7041Schristos 	 "working directory".  */
2033*56bb7041Schristos       if (dirs_in_use == 0 && files_in_use > 0)
2034*56bb7041Schristos 	out_uleb128 (1);
2035*56bb7041Schristos       else
2036*56bb7041Schristos 	out_uleb128 (dirs_in_use);
2037*56bb7041Schristos     }
2038*56bb7041Schristos 
2039*56bb7041Schristos   /* Emit directory list.  */
2040*56bb7041Schristos   if (DWARF2_LINE_VERSION >= 5 && (dirs_in_use > 0 || files_in_use > 0))
2041*56bb7041Schristos     {
2042*56bb7041Schristos       line_str_seg = subseg_new (".debug_line_str", 0);
2043*56bb7041Schristos       bfd_set_section_flags (line_str_seg,
2044*56bb7041Schristos 			     SEC_READONLY | SEC_DEBUGGING | SEC_OCTETS
2045*56bb7041Schristos 			     | SEC_MERGE | SEC_STRINGS);
2046*56bb7041Schristos       line_str_seg->entsize = 1;
2047*56bb7041Schristos 
2048*56bb7041Schristos       /* DWARF5 uses slot zero, but that is only set explicitly
2049*56bb7041Schristos 	 using a .file 0 directive.  If that isn't used, but dir
2050*56bb7041Schristos 	 one is used, then use that as main file directory.
2051*56bb7041Schristos 	 Otherwise use pwd as main file directory.  */
2052*56bb7041Schristos       if (dirs_in_use > 0 && dirs != NULL && dirs[0] != NULL)
2053*56bb7041Schristos 	dir = remap_debug_filename (dirs[0]);
2054*56bb7041Schristos       else if (dirs_in_use > 1 && dirs != NULL && dirs[1] != NULL)
2055*56bb7041Schristos 	dir = remap_debug_filename (dirs[1]);
2056*56bb7041Schristos       else
2057*56bb7041Schristos 	dir = remap_debug_filename (getpwd ());
2058*56bb7041Schristos 
2059*56bb7041Schristos       line_strp = add_line_strp (line_str_seg, dir);
2060*56bb7041Schristos       subseg_set (line_seg, 0);
2061*56bb7041Schristos       TC_DWARF2_EMIT_OFFSET (line_strp, sizeof_offset);
2062*56bb7041Schristos     }
2063*56bb7041Schristos   for (i = 1; i < dirs_in_use; ++i)
2064*56bb7041Schristos     {
2065*56bb7041Schristos       dir = remap_debug_filename (dirs[i]);
2066*56bb7041Schristos       if (DWARF2_LINE_VERSION < 5)
2067*56bb7041Schristos 	{
2068*56bb7041Schristos 	  size = strlen (dir) + 1;
2069*56bb7041Schristos 	  cp = frag_more (size);
2070*56bb7041Schristos 	  memcpy (cp, dir, size);
2071*56bb7041Schristos 	}
2072*56bb7041Schristos       else
2073*56bb7041Schristos 	{
2074*56bb7041Schristos 	  line_strp = add_line_strp (line_str_seg, dir);
2075*56bb7041Schristos 	  subseg_set (line_seg, 0);
2076*56bb7041Schristos 	  TC_DWARF2_EMIT_OFFSET (line_strp, sizeof_offset);
2077*56bb7041Schristos 	}
2078*56bb7041Schristos     }
2079*56bb7041Schristos 
2080*56bb7041Schristos   if (DWARF2_LINE_VERSION < 5)
2081*56bb7041Schristos     /* Terminate it.  */
2082*56bb7041Schristos     out_byte ('\0');
2083*56bb7041Schristos 
2084*56bb7041Schristos   /* Output the File Name Table.  */
2085*56bb7041Schristos   if (DWARF2_LINE_VERSION >= 5)
2086*56bb7041Schristos     {
2087*56bb7041Schristos       unsigned int columns = 4;
2088*56bb7041Schristos 
2089*56bb7041Schristos       if (((unsigned long) DWARF2_FILE_TIME_NAME ("", "")) == -1UL)
2090*56bb7041Schristos 	{
2091*56bb7041Schristos 	  emit_timestamps = FALSE;
2092*56bb7041Schristos 	  -- columns;
2093*56bb7041Schristos 	}
2094*56bb7041Schristos 
2095*56bb7041Schristos       if (DWARF2_FILE_SIZE_NAME ("", "") == -1)
2096*56bb7041Schristos 	{
2097*56bb7041Schristos 	  emit_filesize = FALSE;
2098*56bb7041Schristos 	  -- columns;
2099*56bb7041Schristos 	}
2100*56bb7041Schristos 
2101*56bb7041Schristos       for (i = 0; i < files_in_use; ++i)
2102*56bb7041Schristos 	if (files[i].md5[0] != 0)
2103*56bb7041Schristos 	  break;
2104*56bb7041Schristos       if (i < files_in_use)
2105*56bb7041Schristos 	{
2106*56bb7041Schristos 	  emit_md5 = TRUE;
2107*56bb7041Schristos 	  ++ columns;
2108*56bb7041Schristos 	}
2109*56bb7041Schristos 
2110*56bb7041Schristos       /* The number of format entries to follow.  */
2111*56bb7041Schristos       out_byte (columns);
2112*56bb7041Schristos       /* The format of the file name.  */
2113*56bb7041Schristos       out_uleb128 (DW_LNCT_path);
2114*56bb7041Schristos       /* Store these strings in the .debug_line_str section so they
2115*56bb7041Schristos 	 can be shared.  */
2116*56bb7041Schristos       out_uleb128 (DW_FORM_line_strp);
2117*56bb7041Schristos 
2118*56bb7041Schristos       /* The format of the directory index.  */
2119*56bb7041Schristos       out_uleb128 (DW_LNCT_directory_index);
2120*56bb7041Schristos       out_uleb128 (DW_FORM_udata);
2121*56bb7041Schristos 
2122*56bb7041Schristos       if (emit_timestamps)
2123*56bb7041Schristos 	{
2124*56bb7041Schristos 	  /* The format of the timestamp.  */
2125*56bb7041Schristos 	  out_uleb128 (DW_LNCT_timestamp);
2126*56bb7041Schristos 	  out_uleb128 (DW_FORM_udata);
2127*56bb7041Schristos 	}
2128*56bb7041Schristos 
2129*56bb7041Schristos       if (emit_filesize)
2130*56bb7041Schristos 	{
2131*56bb7041Schristos 	  /* The format of the file size.  */
2132*56bb7041Schristos 	  out_uleb128 (DW_LNCT_size);
2133*56bb7041Schristos 	  out_uleb128 (DW_FORM_udata);
2134*56bb7041Schristos 	}
2135*56bb7041Schristos 
2136*56bb7041Schristos       if (emit_md5)
2137*56bb7041Schristos 	{
2138*56bb7041Schristos 	  /* The format of the MD5 sum.  */
2139*56bb7041Schristos 	  out_uleb128 (DW_LNCT_MD5);
2140*56bb7041Schristos 	  out_uleb128 (DW_FORM_data16);
2141*56bb7041Schristos 	}
2142*56bb7041Schristos 
2143*56bb7041Schristos       /* The number of entries in the table.  */
2144*56bb7041Schristos       out_uleb128 (files_in_use);
2145*56bb7041Schristos    }
2146*56bb7041Schristos 
2147*56bb7041Schristos   for (i = DWARF2_LINE_VERSION > 4 ? 0 : 1; i < files_in_use; ++i)
2148*56bb7041Schristos     {
2149*56bb7041Schristos       const char *fullfilename;
2150*56bb7041Schristos 
2151*56bb7041Schristos       if (files[i].filename == NULL)
2152*56bb7041Schristos 	{
2153*56bb7041Schristos 	  /* Prevent a crash later, particularly for file 1.  DWARF5
2154*56bb7041Schristos 	     uses slot zero, but that is only set explicitly using a
2155*56bb7041Schristos 	     .file 0 directive.  If that isn't used, but file 1 is,
2156*56bb7041Schristos 	     then use that as main file name.  */
2157*56bb7041Schristos 	  if (DWARF2_LINE_VERSION >= 5 && i == 0 && files_in_use >= 1)
2158*56bb7041Schristos 	      files[0].filename = files[1].filename;
2159*56bb7041Schristos 	  else
2160*56bb7041Schristos 	    files[i].filename = "";
2161*56bb7041Schristos 	  if (DWARF2_LINE_VERSION < 5 || i != 0)
2162*56bb7041Schristos 	    {
2163*56bb7041Schristos 	      as_bad (_("unassigned file number %ld"), (long) i);
2164*56bb7041Schristos 	      continue;
2165*56bb7041Schristos 	    }
2166*56bb7041Schristos 	}
2167*56bb7041Schristos 
2168*56bb7041Schristos       fullfilename = DWARF2_FILE_NAME (files[i].filename,
2169*56bb7041Schristos 				       files[i].dir ? dirs [files [i].dir] : "");
2170*56bb7041Schristos       if (DWARF2_LINE_VERSION < 5)
2171*56bb7041Schristos 	{
2172*56bb7041Schristos 	  size = strlen (fullfilename) + 1;
2173*56bb7041Schristos 	  cp = frag_more (size);
2174*56bb7041Schristos 	  memcpy (cp, fullfilename, size);
2175*56bb7041Schristos 	}
2176*56bb7041Schristos       else
2177*56bb7041Schristos 	{
2178*56bb7041Schristos 	  line_strp = add_line_strp (line_str_seg, fullfilename);
2179*56bb7041Schristos 	  subseg_set (line_seg, 0);
2180*56bb7041Schristos 	  TC_DWARF2_EMIT_OFFSET (line_strp, sizeof_offset);
2181*56bb7041Schristos 	}
2182*56bb7041Schristos 
2183*56bb7041Schristos       /* Directory number.  */
2184*56bb7041Schristos       out_uleb128 (files[i].dir);
2185*56bb7041Schristos 
2186*56bb7041Schristos       /* Output the last modification timestamp.  */
2187*56bb7041Schristos       if (emit_timestamps)
2188*56bb7041Schristos 	{
2189*56bb7041Schristos 	  offsetT timestamp;
2190*56bb7041Schristos 
2191*56bb7041Schristos 	  timestamp = DWARF2_FILE_TIME_NAME (files[i].filename,
2192*56bb7041Schristos 					     files[i].dir ? dirs [files [i].dir] : "");
2193*56bb7041Schristos 	  if (timestamp == -1)
2194*56bb7041Schristos 	    timestamp = 0;
2195*56bb7041Schristos 	  out_uleb128 (timestamp);
2196*56bb7041Schristos 	}
2197*56bb7041Schristos 
2198*56bb7041Schristos       /* Output the filesize.  */
2199*56bb7041Schristos       if (emit_filesize)
2200*56bb7041Schristos 	{
2201*56bb7041Schristos 	  offsetT filesize;
2202*56bb7041Schristos 	  filesize = DWARF2_FILE_SIZE_NAME (files[i].filename,
2203*56bb7041Schristos 					    files[i].dir ? dirs [files [i].dir] : "");
2204*56bb7041Schristos 	  if (filesize == -1)
2205*56bb7041Schristos 	    filesize = 0;
2206*56bb7041Schristos 	  out_uleb128 (filesize);
2207*56bb7041Schristos 	}
2208*56bb7041Schristos 
2209*56bb7041Schristos       /* Output the md5 sum.  */
2210*56bb7041Schristos       if (emit_md5)
2211*56bb7041Schristos 	{
2212*56bb7041Schristos 	  int b;
2213*56bb7041Schristos 
2214*56bb7041Schristos 	  for (b = 0; b < NUM_MD5_BYTES; b++)
2215*56bb7041Schristos 	    out_byte (files[i].md5[b]);
2216*56bb7041Schristos 	}
2217*56bb7041Schristos     }
2218*56bb7041Schristos 
2219*56bb7041Schristos   if (DWARF2_LINE_VERSION < 5)
2220*56bb7041Schristos     /* Terminate filename list.  */
2221*56bb7041Schristos     out_byte (0);
2222*56bb7041Schristos }
2223*56bb7041Schristos 
2224*56bb7041Schristos /* Switch to SEC and output a header length field.  Return the size of
2225*56bb7041Schristos    offsets used in SEC.  The caller must set EXPR->X_add_symbol value
2226*56bb7041Schristos    to the end of the section.  EXPR->X_add_number will be set to the
2227*56bb7041Schristos    negative size of the header.  */
2228*56bb7041Schristos 
2229*56bb7041Schristos static int
out_header(asection * sec,expressionS * exp)2230*56bb7041Schristos out_header (asection *sec, expressionS *exp)
2231*56bb7041Schristos {
2232*56bb7041Schristos   symbolS *start_sym;
2233*56bb7041Schristos   symbolS *end_sym;
2234*56bb7041Schristos 
2235*56bb7041Schristos   subseg_set (sec, 0);
2236*56bb7041Schristos 
2237*56bb7041Schristos   if (flag_dwarf_sections)
2238*56bb7041Schristos     {
2239*56bb7041Schristos       /* If we are going to put the start and end symbols in different
2240*56bb7041Schristos 	 sections, then we need real symbols, not just fake, local ones.  */
2241*56bb7041Schristos       frag_now_fix ();
2242*56bb7041Schristos       start_sym = symbol_make (".Ldebug_line_start");
2243*56bb7041Schristos       end_sym = symbol_make (".Ldebug_line_end");
2244*56bb7041Schristos       symbol_set_value_now (start_sym);
2245*56bb7041Schristos     }
2246*56bb7041Schristos   else
2247*56bb7041Schristos     {
2248*56bb7041Schristos       start_sym = symbol_temp_new_now_octets ();
2249*56bb7041Schristos       end_sym = symbol_temp_make ();
2250*56bb7041Schristos     }
2251*56bb7041Schristos 
2252*56bb7041Schristos   /* Total length of the information.  */
2253*56bb7041Schristos   exp->X_op = O_subtract;
2254*56bb7041Schristos   exp->X_add_symbol = end_sym;
2255*56bb7041Schristos   exp->X_op_symbol = start_sym;
2256*56bb7041Schristos 
2257*56bb7041Schristos   switch (DWARF2_FORMAT (sec))
2258*56bb7041Schristos     {
2259*56bb7041Schristos     case dwarf2_format_32bit:
2260*56bb7041Schristos       exp->X_add_number = -4;
2261*56bb7041Schristos       emit_expr (exp, 4);
2262*56bb7041Schristos       return 4;
2263*56bb7041Schristos 
2264*56bb7041Schristos     case dwarf2_format_64bit:
2265*56bb7041Schristos       exp->X_add_number = -12;
2266*56bb7041Schristos       out_four (-1);
2267*56bb7041Schristos       emit_expr (exp, 8);
2268*56bb7041Schristos       return 8;
2269*56bb7041Schristos 
2270*56bb7041Schristos     case dwarf2_format_64bit_irix:
2271*56bb7041Schristos       exp->X_add_number = -8;
2272*56bb7041Schristos       emit_expr (exp, 8);
2273*56bb7041Schristos       return 8;
2274*56bb7041Schristos     }
2275*56bb7041Schristos 
2276*56bb7041Schristos   as_fatal (_("internal error: unknown dwarf2 format"));
2277*56bb7041Schristos   return 0;
2278*56bb7041Schristos }
2279*56bb7041Schristos 
2280*56bb7041Schristos /* Emit the collected .debug_line data.  */
2281*56bb7041Schristos 
2282*56bb7041Schristos static void
out_debug_line(segT line_seg)2283*56bb7041Schristos out_debug_line (segT line_seg)
2284*56bb7041Schristos {
2285*56bb7041Schristos   expressionS exp;
2286*56bb7041Schristos   symbolS *prologue_start, *prologue_end;
2287*56bb7041Schristos   symbolS *line_end;
2288*56bb7041Schristos   struct line_seg *s;
2289*56bb7041Schristos   int sizeof_offset;
2290*56bb7041Schristos 
2291*56bb7041Schristos   memset (&exp, 0, sizeof exp);
2292*56bb7041Schristos   sizeof_offset = out_header (line_seg, &exp);
2293*56bb7041Schristos   line_end = exp.X_add_symbol;
2294*56bb7041Schristos 
2295*56bb7041Schristos   /* Version.  */
2296*56bb7041Schristos   out_two (DWARF2_LINE_VERSION);
2297*56bb7041Schristos 
2298*56bb7041Schristos   if (DWARF2_LINE_VERSION >= 5)
2299*56bb7041Schristos     {
2300*56bb7041Schristos       out_byte (sizeof_address);
2301*56bb7041Schristos       out_byte (0); /* Segment Selector size.  */
2302*56bb7041Schristos     }
2303*56bb7041Schristos   /* Length of the prologue following this length.  */
2304*56bb7041Schristos   prologue_start = symbol_temp_make ();
2305*56bb7041Schristos   prologue_end = symbol_temp_make ();
2306*56bb7041Schristos   exp.X_op = O_subtract;
2307*56bb7041Schristos   exp.X_add_symbol = prologue_end;
2308*56bb7041Schristos   exp.X_op_symbol = prologue_start;
2309*56bb7041Schristos   exp.X_add_number = 0;
2310*56bb7041Schristos   emit_expr (&exp, sizeof_offset);
2311*56bb7041Schristos   symbol_set_value_now (prologue_start);
2312*56bb7041Schristos 
2313*56bb7041Schristos   /* Parameters of the state machine.  */
2314*56bb7041Schristos   out_byte (DWARF2_LINE_MIN_INSN_LENGTH);
2315*56bb7041Schristos   if (DWARF2_LINE_VERSION >= 4)
2316*56bb7041Schristos     out_byte (DWARF2_LINE_MAX_OPS_PER_INSN);
2317*56bb7041Schristos   out_byte (DWARF2_LINE_DEFAULT_IS_STMT);
2318*56bb7041Schristos   out_byte (DWARF2_LINE_BASE);
2319*56bb7041Schristos   out_byte (DWARF2_LINE_RANGE);
2320*56bb7041Schristos   out_byte (DWARF2_LINE_OPCODE_BASE);
2321*56bb7041Schristos 
2322*56bb7041Schristos   /* Standard opcode lengths.  */
2323*56bb7041Schristos   out_byte (0);			/* DW_LNS_copy */
2324*56bb7041Schristos   out_byte (1);			/* DW_LNS_advance_pc */
2325*56bb7041Schristos   out_byte (1);			/* DW_LNS_advance_line */
2326*56bb7041Schristos   out_byte (1);			/* DW_LNS_set_file */
2327*56bb7041Schristos   out_byte (1);			/* DW_LNS_set_column */
2328*56bb7041Schristos   out_byte (0);			/* DW_LNS_negate_stmt */
2329*56bb7041Schristos   out_byte (0);			/* DW_LNS_set_basic_block */
2330*56bb7041Schristos   out_byte (0);			/* DW_LNS_const_add_pc */
2331*56bb7041Schristos   out_byte (1);			/* DW_LNS_fixed_advance_pc */
2332*56bb7041Schristos   out_byte (0);			/* DW_LNS_set_prologue_end */
2333*56bb7041Schristos   out_byte (0);			/* DW_LNS_set_epilogue_begin */
2334*56bb7041Schristos   out_byte (1);			/* DW_LNS_set_isa */
2335*56bb7041Schristos   /* We have emitted 12 opcode lengths, so make that this
2336*56bb7041Schristos      matches up to the opcode base value we have been using.  */
2337*56bb7041Schristos   gas_assert (DWARF2_LINE_OPCODE_BASE == 13);
2338*56bb7041Schristos 
2339*56bb7041Schristos   out_dir_and_file_list (line_seg, sizeof_offset);
2340*56bb7041Schristos 
2341*56bb7041Schristos   symbol_set_value_now (prologue_end);
2342*56bb7041Schristos 
2343*56bb7041Schristos   /* For each section, emit a statement program.  */
2344*56bb7041Schristos   for (s = all_segs; s; s = s->next)
2345*56bb7041Schristos     if (SEG_NORMAL (s->seg))
2346*56bb7041Schristos       process_entries (s->seg, s->head->head);
2347*56bb7041Schristos     else
2348*56bb7041Schristos       as_warn ("dwarf line number information for %s ignored",
2349*56bb7041Schristos 	       segment_name (s->seg));
2350*56bb7041Schristos 
2351*56bb7041Schristos   if (flag_dwarf_sections)
2352*56bb7041Schristos     /* We have to switch to the special .debug_line_end section
2353*56bb7041Schristos        before emitting the end-of-debug_line symbol.  The linker
2354*56bb7041Schristos        script arranges for this section to be placed after all the
2355*56bb7041Schristos        (potentially garbage collected) .debug_line.<foo> sections.
2356*56bb7041Schristos        This section contains the line_end symbol which is used to
2357*56bb7041Schristos        compute the size of the linked .debug_line section, as seen
2358*56bb7041Schristos        in the DWARF Line Number header.  */
2359*56bb7041Schristos     subseg_set (subseg_get (".debug_line_end", FALSE), 0);
2360*56bb7041Schristos 
2361*56bb7041Schristos   symbol_set_value_now (line_end);
2362*56bb7041Schristos }
2363*56bb7041Schristos 
2364*56bb7041Schristos static void
out_debug_ranges(segT ranges_seg,symbolS ** ranges_sym)2365*56bb7041Schristos out_debug_ranges (segT ranges_seg, symbolS **ranges_sym)
2366*56bb7041Schristos {
2367*56bb7041Schristos   unsigned int addr_size = sizeof_address;
2368*56bb7041Schristos   struct line_seg *s;
2369*56bb7041Schristos   expressionS exp;
2370*56bb7041Schristos   unsigned int i;
2371*56bb7041Schristos 
2372*56bb7041Schristos   memset (&exp, 0, sizeof exp);
2373*56bb7041Schristos   subseg_set (ranges_seg, 0);
2374*56bb7041Schristos 
2375*56bb7041Schristos   /* For DW_AT_ranges to point at (there is no header, so really start
2376*56bb7041Schristos      of section, but see out_debug_rnglists).  */
2377*56bb7041Schristos   *ranges_sym = symbol_temp_new_now_octets ();
2378*56bb7041Schristos 
2379*56bb7041Schristos   /* Base Address Entry.  */
2380*56bb7041Schristos   for (i = 0; i < addr_size; i++)
2381*56bb7041Schristos     out_byte (0xff);
2382*56bb7041Schristos   for (i = 0; i < addr_size; i++)
2383*56bb7041Schristos     out_byte (0);
2384*56bb7041Schristos 
2385*56bb7041Schristos   /* Range List Entry.  */
2386*56bb7041Schristos   for (s = all_segs; s; s = s->next)
2387*56bb7041Schristos     {
2388*56bb7041Schristos       fragS *frag;
2389*56bb7041Schristos       symbolS *beg, *end;
2390*56bb7041Schristos 
2391*56bb7041Schristos       frag = first_frag_for_seg (s->seg);
2392*56bb7041Schristos       beg = symbol_temp_new (s->seg, frag, 0);
2393*56bb7041Schristos       s->text_start = beg;
2394*56bb7041Schristos 
2395*56bb7041Schristos       frag = last_frag_for_seg (s->seg);
2396*56bb7041Schristos       end = symbol_temp_new (s->seg, frag, get_frag_fix (frag, s->seg));
2397*56bb7041Schristos       s->text_end = end;
2398*56bb7041Schristos 
2399*56bb7041Schristos       exp.X_op = O_symbol;
2400*56bb7041Schristos       exp.X_add_symbol = beg;
2401*56bb7041Schristos       exp.X_add_number = 0;
2402*56bb7041Schristos       emit_expr (&exp, addr_size);
2403*56bb7041Schristos 
2404*56bb7041Schristos       exp.X_op = O_symbol;
2405*56bb7041Schristos       exp.X_add_symbol = end;
2406*56bb7041Schristos       exp.X_add_number = 0;
2407*56bb7041Schristos       emit_expr (&exp, addr_size);
2408*56bb7041Schristos     }
2409*56bb7041Schristos 
2410*56bb7041Schristos   /* End of Range Entry.   */
2411*56bb7041Schristos   for (i = 0; i < addr_size; i++)
2412*56bb7041Schristos     out_byte (0);
2413*56bb7041Schristos   for (i = 0; i < addr_size; i++)
2414*56bb7041Schristos     out_byte (0);
2415*56bb7041Schristos }
2416*56bb7041Schristos 
2417*56bb7041Schristos static void
out_debug_rnglists(segT ranges_seg,symbolS ** ranges_sym)2418*56bb7041Schristos out_debug_rnglists (segT ranges_seg, symbolS **ranges_sym)
2419*56bb7041Schristos {
2420*56bb7041Schristos   expressionS exp;
2421*56bb7041Schristos   symbolS *ranges_end;
2422*56bb7041Schristos   struct line_seg *s;
2423*56bb7041Schristos 
2424*56bb7041Schristos   /* Unit length.  */
2425*56bb7041Schristos   memset (&exp, 0, sizeof exp);
2426*56bb7041Schristos   out_header (ranges_seg, &exp);
2427*56bb7041Schristos   ranges_end = exp.X_add_symbol;
2428*56bb7041Schristos 
2429*56bb7041Schristos   out_two (DWARF2_RNGLISTS_VERSION);
2430*56bb7041Schristos   out_byte (sizeof_address);
2431*56bb7041Schristos   out_byte (0); /* Segment Selector size.  */
2432*56bb7041Schristos   out_four (0); /* Offset entry count.  */
2433*56bb7041Schristos 
2434*56bb7041Schristos   /* For DW_AT_ranges to point at (must be after the header).   */
2435*56bb7041Schristos   *ranges_sym = symbol_temp_new_now_octets ();
2436*56bb7041Schristos 
2437*56bb7041Schristos   for (s = all_segs; s; s = s->next)
2438*56bb7041Schristos     {
2439*56bb7041Schristos       fragS *frag;
2440*56bb7041Schristos       symbolS *beg, *end;
2441*56bb7041Schristos 
2442*56bb7041Schristos       out_byte (DW_RLE_start_length);
2443*56bb7041Schristos 
2444*56bb7041Schristos       frag = first_frag_for_seg (s->seg);
2445*56bb7041Schristos       beg = symbol_temp_new (s->seg, frag, 0);
2446*56bb7041Schristos       s->text_start = beg;
2447*56bb7041Schristos 
2448*56bb7041Schristos       frag = last_frag_for_seg (s->seg);
2449*56bb7041Schristos       end = symbol_temp_new (s->seg, frag, get_frag_fix (frag, s->seg));
2450*56bb7041Schristos       s->text_end = end;
2451*56bb7041Schristos 
2452*56bb7041Schristos       exp.X_op = O_symbol;
2453*56bb7041Schristos       exp.X_add_symbol = beg;
2454*56bb7041Schristos       exp.X_add_number = 0;
2455*56bb7041Schristos       emit_expr (&exp, sizeof_address);
2456*56bb7041Schristos 
2457*56bb7041Schristos       exp.X_op = O_symbol;
2458*56bb7041Schristos       exp.X_add_symbol = end;
2459*56bb7041Schristos       exp.X_add_number = 0;
2460*56bb7041Schristos       emit_leb128_expr (&exp, 0);
2461*56bb7041Schristos     }
2462*56bb7041Schristos 
2463*56bb7041Schristos   out_byte (DW_RLE_end_of_list);
2464*56bb7041Schristos 
2465*56bb7041Schristos   symbol_set_value_now (ranges_end);
2466*56bb7041Schristos }
2467*56bb7041Schristos 
2468*56bb7041Schristos /* Emit data for .debug_aranges.  */
2469*56bb7041Schristos 
2470*56bb7041Schristos static void
out_debug_aranges(segT aranges_seg,segT info_seg)2471*56bb7041Schristos out_debug_aranges (segT aranges_seg, segT info_seg)
2472*56bb7041Schristos {
2473*56bb7041Schristos   unsigned int addr_size = sizeof_address;
2474*56bb7041Schristos   offsetT size;
2475*56bb7041Schristos   struct line_seg *s;
2476*56bb7041Schristos   expressionS exp;
2477*56bb7041Schristos   symbolS *aranges_end;
2478*56bb7041Schristos   char *p;
2479*56bb7041Schristos   int sizeof_offset;
2480*56bb7041Schristos 
2481*56bb7041Schristos   memset (&exp, 0, sizeof exp);
2482*56bb7041Schristos   sizeof_offset = out_header (aranges_seg, &exp);
2483*56bb7041Schristos   aranges_end = exp.X_add_symbol;
2484*56bb7041Schristos   size = -exp.X_add_number;
2485*56bb7041Schristos 
2486*56bb7041Schristos   /* Version.  */
2487*56bb7041Schristos   out_two (DWARF2_ARANGES_VERSION);
2488*56bb7041Schristos   size += 2;
2489*56bb7041Schristos 
2490*56bb7041Schristos   /* Offset to .debug_info.  */
2491*56bb7041Schristos   TC_DWARF2_EMIT_OFFSET (section_symbol (info_seg), sizeof_offset);
2492*56bb7041Schristos   size += sizeof_offset;
2493*56bb7041Schristos 
2494*56bb7041Schristos   /* Size of an address (offset portion).  */
2495*56bb7041Schristos   out_byte (addr_size);
2496*56bb7041Schristos   size++;
2497*56bb7041Schristos 
2498*56bb7041Schristos   /* Size of a segment descriptor.  */
2499*56bb7041Schristos   out_byte (0);
2500*56bb7041Schristos   size++;
2501*56bb7041Schristos 
2502*56bb7041Schristos   /* Align the header.  */
2503*56bb7041Schristos   while ((size++ % (2 * addr_size)) > 0)
2504*56bb7041Schristos     out_byte (0);
2505*56bb7041Schristos 
2506*56bb7041Schristos   for (s = all_segs; s; s = s->next)
2507*56bb7041Schristos     {
2508*56bb7041Schristos       fragS *frag;
2509*56bb7041Schristos       symbolS *beg, *end;
2510*56bb7041Schristos 
2511*56bb7041Schristos       frag = first_frag_for_seg (s->seg);
2512*56bb7041Schristos       beg = symbol_temp_new (s->seg, frag, 0);
2513*56bb7041Schristos       s->text_start = beg;
2514*56bb7041Schristos 
2515*56bb7041Schristos       frag = last_frag_for_seg (s->seg);
2516*56bb7041Schristos       end = symbol_temp_new (s->seg, frag, get_frag_fix (frag, s->seg));
2517*56bb7041Schristos       s->text_end = end;
2518*56bb7041Schristos 
2519*56bb7041Schristos       exp.X_op = O_symbol;
2520*56bb7041Schristos       exp.X_add_symbol = beg;
2521*56bb7041Schristos       exp.X_add_number = 0;
2522*56bb7041Schristos       emit_expr (&exp, addr_size);
2523*56bb7041Schristos 
2524*56bb7041Schristos       exp.X_op = O_subtract;
2525*56bb7041Schristos       exp.X_add_symbol = end;
2526*56bb7041Schristos       exp.X_op_symbol = beg;
2527*56bb7041Schristos       exp.X_add_number = 0;
2528*56bb7041Schristos       emit_expr (&exp, addr_size);
2529*56bb7041Schristos     }
2530*56bb7041Schristos 
2531*56bb7041Schristos   p = frag_more (2 * addr_size);
2532*56bb7041Schristos   md_number_to_chars (p, 0, addr_size);
2533*56bb7041Schristos   md_number_to_chars (p + addr_size, 0, addr_size);
2534*56bb7041Schristos 
2535*56bb7041Schristos   symbol_set_value_now (aranges_end);
2536*56bb7041Schristos }
2537*56bb7041Schristos 
2538*56bb7041Schristos /* Emit data for .debug_abbrev.  Note that this must be kept in
2539*56bb7041Schristos    sync with out_debug_info below.  */
2540*56bb7041Schristos 
2541*56bb7041Schristos static void
out_debug_abbrev(segT abbrev_seg,segT info_seg ATTRIBUTE_UNUSED,segT line_seg ATTRIBUTE_UNUSED)2542*56bb7041Schristos out_debug_abbrev (segT abbrev_seg,
2543*56bb7041Schristos 		  segT info_seg ATTRIBUTE_UNUSED,
2544*56bb7041Schristos 		  segT line_seg ATTRIBUTE_UNUSED)
2545*56bb7041Schristos {
2546*56bb7041Schristos   int secoff_form;
2547*56bb7041Schristos   subseg_set (abbrev_seg, 0);
2548*56bb7041Schristos 
2549*56bb7041Schristos   out_uleb128 (1);
2550*56bb7041Schristos   out_uleb128 (DW_TAG_compile_unit);
2551*56bb7041Schristos   out_byte (DW_CHILDREN_no);
2552*56bb7041Schristos   if (DWARF2_VERSION < 4)
2553*56bb7041Schristos     {
2554*56bb7041Schristos       if (DWARF2_FORMAT (line_seg) == dwarf2_format_32bit)
2555*56bb7041Schristos 	secoff_form = DW_FORM_data4;
2556*56bb7041Schristos       else
2557*56bb7041Schristos 	secoff_form = DW_FORM_data8;
2558*56bb7041Schristos     }
2559*56bb7041Schristos   else
2560*56bb7041Schristos     secoff_form = DW_FORM_sec_offset;
2561*56bb7041Schristos   out_abbrev (DW_AT_stmt_list, secoff_form);
2562*56bb7041Schristos   if (all_segs->next == NULL)
2563*56bb7041Schristos     {
2564*56bb7041Schristos       out_abbrev (DW_AT_low_pc, DW_FORM_addr);
2565*56bb7041Schristos       if (DWARF2_VERSION < 4)
2566*56bb7041Schristos 	out_abbrev (DW_AT_high_pc, DW_FORM_addr);
2567*56bb7041Schristos       else
2568*56bb7041Schristos 	out_abbrev (DW_AT_high_pc, DW_FORM_udata);
2569*56bb7041Schristos     }
2570*56bb7041Schristos   else
2571*56bb7041Schristos     out_abbrev (DW_AT_ranges, secoff_form);
2572*56bb7041Schristos   out_abbrev (DW_AT_name, DW_FORM_strp);
2573*56bb7041Schristos   out_abbrev (DW_AT_comp_dir, DW_FORM_strp);
2574*56bb7041Schristos   out_abbrev (DW_AT_producer, DW_FORM_strp);
2575*56bb7041Schristos   out_abbrev (DW_AT_language, DW_FORM_data2);
2576*56bb7041Schristos   out_abbrev (0, 0);
2577*56bb7041Schristos 
2578*56bb7041Schristos   /* Terminate the abbreviations for this compilation unit.  */
2579*56bb7041Schristos   out_byte (0);
2580*56bb7041Schristos }
2581*56bb7041Schristos 
2582*56bb7041Schristos /* Emit a description of this compilation unit for .debug_info.  */
2583*56bb7041Schristos 
2584*56bb7041Schristos static void
out_debug_info(segT info_seg,segT abbrev_seg,segT line_seg,symbolS * ranges_sym,symbolS * name_sym,symbolS * comp_dir_sym,symbolS * producer_sym)2585*56bb7041Schristos out_debug_info (segT info_seg, segT abbrev_seg, segT line_seg,
2586*56bb7041Schristos 		symbolS *ranges_sym, symbolS *name_sym,
2587*56bb7041Schristos 		symbolS *comp_dir_sym, symbolS *producer_sym)
2588*56bb7041Schristos {
2589*56bb7041Schristos   expressionS exp;
2590*56bb7041Schristos   symbolS *info_end;
2591*56bb7041Schristos   int sizeof_offset;
2592*56bb7041Schristos 
2593*56bb7041Schristos   memset (&exp, 0, sizeof exp);
2594*56bb7041Schristos   sizeof_offset = out_header (info_seg, &exp);
2595*56bb7041Schristos   info_end = exp.X_add_symbol;
2596*56bb7041Schristos 
2597*56bb7041Schristos   /* DWARF version.  */
2598*56bb7041Schristos   out_two (DWARF2_VERSION);
2599*56bb7041Schristos 
2600*56bb7041Schristos   if (DWARF2_VERSION < 5)
2601*56bb7041Schristos     {
2602*56bb7041Schristos       /* .debug_abbrev offset */
2603*56bb7041Schristos       TC_DWARF2_EMIT_OFFSET (section_symbol (abbrev_seg), sizeof_offset);
2604*56bb7041Schristos     }
2605*56bb7041Schristos   else
2606*56bb7041Schristos     {
2607*56bb7041Schristos       /* unit (header) type */
2608*56bb7041Schristos       out_byte (DW_UT_compile);
2609*56bb7041Schristos     }
2610*56bb7041Schristos 
2611*56bb7041Schristos   /* Target address size.  */
2612*56bb7041Schristos   out_byte (sizeof_address);
2613*56bb7041Schristos 
2614*56bb7041Schristos   if (DWARF2_VERSION >= 5)
2615*56bb7041Schristos     {
2616*56bb7041Schristos       /* .debug_abbrev offset */
2617*56bb7041Schristos       TC_DWARF2_EMIT_OFFSET (section_symbol (abbrev_seg), sizeof_offset);
2618*56bb7041Schristos     }
2619*56bb7041Schristos 
2620*56bb7041Schristos   /* DW_TAG_compile_unit DIE abbrev */
2621*56bb7041Schristos   out_uleb128 (1);
2622*56bb7041Schristos 
2623*56bb7041Schristos   /* DW_AT_stmt_list */
2624*56bb7041Schristos   TC_DWARF2_EMIT_OFFSET (section_symbol (line_seg),
2625*56bb7041Schristos 			 (DWARF2_FORMAT (line_seg) == dwarf2_format_32bit
2626*56bb7041Schristos 			  ? 4 : 8));
2627*56bb7041Schristos 
2628*56bb7041Schristos   /* These two attributes are emitted if all of the code is contiguous.  */
2629*56bb7041Schristos   if (all_segs->next == NULL)
2630*56bb7041Schristos     {
2631*56bb7041Schristos       /* DW_AT_low_pc */
2632*56bb7041Schristos       exp.X_op = O_symbol;
2633*56bb7041Schristos       exp.X_add_symbol = all_segs->text_start;
2634*56bb7041Schristos       exp.X_add_number = 0;
2635*56bb7041Schristos       emit_expr (&exp, sizeof_address);
2636*56bb7041Schristos 
2637*56bb7041Schristos       /* DW_AT_high_pc */
2638*56bb7041Schristos       if (DWARF2_VERSION < 4)
2639*56bb7041Schristos 	exp.X_op = O_symbol;
2640*56bb7041Schristos       else
2641*56bb7041Schristos 	{
2642*56bb7041Schristos 	  exp.X_op = O_subtract;
2643*56bb7041Schristos 	  exp.X_op_symbol = all_segs->text_start;
2644*56bb7041Schristos 	}
2645*56bb7041Schristos       exp.X_add_symbol = all_segs->text_end;
2646*56bb7041Schristos       exp.X_add_number = 0;
2647*56bb7041Schristos       if (DWARF2_VERSION < 4)
2648*56bb7041Schristos 	emit_expr (&exp, sizeof_address);
2649*56bb7041Schristos       else
2650*56bb7041Schristos 	emit_leb128_expr (&exp, 0);
2651*56bb7041Schristos     }
2652*56bb7041Schristos   else
2653*56bb7041Schristos     {
2654*56bb7041Schristos       /* This attribute is emitted if the code is disjoint.  */
2655*56bb7041Schristos       /* DW_AT_ranges.  */
2656*56bb7041Schristos       TC_DWARF2_EMIT_OFFSET (ranges_sym, sizeof_offset);
2657*56bb7041Schristos     }
2658*56bb7041Schristos 
2659*56bb7041Schristos   /* DW_AT_name, DW_AT_comp_dir and DW_AT_producer.  Symbols in .debug_str
2660*56bb7041Schristos      setup in out_debug_str below.  */
2661*56bb7041Schristos   TC_DWARF2_EMIT_OFFSET (name_sym, sizeof_offset);
2662*56bb7041Schristos   TC_DWARF2_EMIT_OFFSET (comp_dir_sym, sizeof_offset);
2663*56bb7041Schristos   TC_DWARF2_EMIT_OFFSET (producer_sym, sizeof_offset);
2664*56bb7041Schristos 
2665*56bb7041Schristos   /* DW_AT_language.  Yes, this is probably not really MIPS, but the
2666*56bb7041Schristos      dwarf2 draft has no standard code for assembler.  */
2667*56bb7041Schristos   out_two (DW_LANG_Mips_Assembler);
2668*56bb7041Schristos 
2669*56bb7041Schristos   symbol_set_value_now (info_end);
2670*56bb7041Schristos }
2671*56bb7041Schristos 
2672*56bb7041Schristos /* Emit the three debug strings needed in .debug_str and setup symbols
2673*56bb7041Schristos    to them for use in out_debug_info.  */
2674*56bb7041Schristos static void
out_debug_str(segT str_seg,symbolS ** name_sym,symbolS ** comp_dir_sym,symbolS ** producer_sym)2675*56bb7041Schristos out_debug_str (segT str_seg, symbolS **name_sym, symbolS **comp_dir_sym,
2676*56bb7041Schristos 	       symbolS **producer_sym)
2677*56bb7041Schristos {
2678*56bb7041Schristos   char producer[128];
2679*56bb7041Schristos   const char *comp_dir;
2680*56bb7041Schristos   const char *dirname;
2681*56bb7041Schristos   char *p;
2682*56bb7041Schristos   int len;
2683*56bb7041Schristos   int first_file = DWARF2_LINE_VERSION > 4 ? 0 : 1;
2684*56bb7041Schristos 
2685*56bb7041Schristos   subseg_set (str_seg, 0);
2686*56bb7041Schristos 
2687*56bb7041Schristos   /* DW_AT_name.  We don't have the actual file name that was present
2688*56bb7041Schristos      on the command line, so assume files[first_file] is the main input file.
2689*56bb7041Schristos      We're not supposed to get called unless at least one line number
2690*56bb7041Schristos      entry was emitted, so this should always be defined.  */
2691*56bb7041Schristos   *name_sym = symbol_temp_new_now_octets ();
2692*56bb7041Schristos   if (files_in_use == 0)
2693*56bb7041Schristos     abort ();
2694*56bb7041Schristos   if (files[first_file].dir)
2695*56bb7041Schristos     {
2696*56bb7041Schristos       dirname = remap_debug_filename (dirs[files[first_file].dir]);
2697*56bb7041Schristos       len = strlen (dirname);
2698*56bb7041Schristos #ifdef TE_VMS
2699*56bb7041Schristos       /* Already has trailing slash.  */
2700*56bb7041Schristos       p = frag_more (len);
2701*56bb7041Schristos       memcpy (p, dirname, len);
2702*56bb7041Schristos #else
2703*56bb7041Schristos       p = frag_more (len + 1);
2704*56bb7041Schristos       memcpy (p, dirname, len);
2705*56bb7041Schristos       INSERT_DIR_SEPARATOR (p, len);
2706*56bb7041Schristos #endif
2707*56bb7041Schristos     }
2708*56bb7041Schristos   len = strlen (files[first_file].filename) + 1;
2709*56bb7041Schristos   p = frag_more (len);
2710*56bb7041Schristos   memcpy (p, files[first_file].filename, len);
2711*56bb7041Schristos 
2712*56bb7041Schristos   /* DW_AT_comp_dir */
2713*56bb7041Schristos   *comp_dir_sym = symbol_temp_new_now_octets ();
2714*56bb7041Schristos   comp_dir = remap_debug_filename (getpwd ());
2715*56bb7041Schristos   len = strlen (comp_dir) + 1;
2716*56bb7041Schristos   p = frag_more (len);
2717*56bb7041Schristos   memcpy (p, comp_dir, len);
2718*56bb7041Schristos 
2719*56bb7041Schristos   /* DW_AT_producer */
2720*56bb7041Schristos   *producer_sym = symbol_temp_new_now_octets ();
2721*56bb7041Schristos   sprintf (producer, "GNU AS %s", VERSION);
2722*56bb7041Schristos   len = strlen (producer) + 1;
2723*56bb7041Schristos   p = frag_more (len);
2724*56bb7041Schristos   memcpy (p, producer, len);
2725*56bb7041Schristos }
2726*56bb7041Schristos 
2727*56bb7041Schristos void
dwarf2_init(void)2728*56bb7041Schristos dwarf2_init (void)
2729*56bb7041Schristos {
2730*56bb7041Schristos   last_seg_ptr = &all_segs;
2731*56bb7041Schristos 
2732*56bb7041Schristos   /* Select the default CIE version to produce here.  The global
2733*56bb7041Schristos      starts with a value of -1 and will be modified to a valid value
2734*56bb7041Schristos      either by the user providing a command line option, or some
2735*56bb7041Schristos      targets will select their own default in md_after_parse_args.  If
2736*56bb7041Schristos      we get here and the global still contains -1 then it is up to us
2737*56bb7041Schristos      to pick a sane default.  The default we choose is 1, this is the
2738*56bb7041Schristos      CIE version gas has produced for a long time, and there seems no
2739*56bb7041Schristos      reason to change it yet.  */
2740*56bb7041Schristos   if (flag_dwarf_cie_version == -1)
2741*56bb7041Schristos     flag_dwarf_cie_version = 1;
2742*56bb7041Schristos }
2743*56bb7041Schristos 
2744*56bb7041Schristos 
2745*56bb7041Schristos /* Finish the dwarf2 debug sections.  We emit .debug.line if there
2746*56bb7041Schristos    were any .file/.loc directives, or --gdwarf2 was given, and if the
2747*56bb7041Schristos    file has a non-empty .debug_info section and an empty .debug_line
2748*56bb7041Schristos    section.  If we emit .debug_line, and the .debug_info section is
2749*56bb7041Schristos    empty, we also emit .debug_info, .debug_aranges and .debug_abbrev.
2750*56bb7041Schristos    ALL_SEGS will be non-null if there were any .file/.loc directives,
2751*56bb7041Schristos    or --gdwarf2 was given and there were any located instructions
2752*56bb7041Schristos    emitted.  */
2753*56bb7041Schristos 
2754*56bb7041Schristos void
dwarf2_finish(void)2755*56bb7041Schristos dwarf2_finish (void)
2756*56bb7041Schristos {
2757*56bb7041Schristos   segT line_seg;
2758*56bb7041Schristos   struct line_seg *s;
2759*56bb7041Schristos   segT info_seg;
2760*56bb7041Schristos   int emit_other_sections = 0;
2761*56bb7041Schristos   int empty_debug_line = 0;
2762*56bb7041Schristos 
2763*56bb7041Schristos   info_seg = bfd_get_section_by_name (stdoutput, ".debug_info");
2764*56bb7041Schristos   emit_other_sections = info_seg == NULL || !seg_not_empty_p (info_seg);
2765*56bb7041Schristos 
2766*56bb7041Schristos   line_seg = bfd_get_section_by_name (stdoutput, ".debug_line");
2767*56bb7041Schristos   empty_debug_line = line_seg == NULL || !seg_not_empty_p (line_seg);
2768*56bb7041Schristos 
2769*56bb7041Schristos   /* We can't construct a new debug_line section if we already have one.
2770*56bb7041Schristos      Give an error if we have seen any .loc, otherwise trust the user
2771*56bb7041Schristos      knows what they are doing and want to generate the .debug_line
2772*56bb7041Schristos      (and all other debug sections) themselves.  */
2773*56bb7041Schristos   if (all_segs && !empty_debug_line && dwarf2_any_loc_directive_seen)
2774*56bb7041Schristos     as_fatal ("duplicate .debug_line sections");
2775*56bb7041Schristos 
2776*56bb7041Schristos   if ((!all_segs && emit_other_sections)
2777*56bb7041Schristos       || (!emit_other_sections && !empty_debug_line))
2778*56bb7041Schristos     /* If there is no line information and no non-empty .debug_info
2779*56bb7041Schristos        section, or if there is both a non-empty .debug_info and a non-empty
2780*56bb7041Schristos        .debug_line, then we do nothing.  */
2781*56bb7041Schristos     return;
2782*56bb7041Schristos 
2783*56bb7041Schristos   /* Calculate the size of an address for the target machine.  */
2784*56bb7041Schristos   sizeof_address = DWARF2_ADDR_SIZE (stdoutput);
2785*56bb7041Schristos 
2786*56bb7041Schristos   /* Create and switch to the line number section.  */
2787*56bb7041Schristos   if (empty_debug_line)
2788*56bb7041Schristos     {
2789*56bb7041Schristos       line_seg = subseg_new (".debug_line", 0);
2790*56bb7041Schristos       bfd_set_section_flags (line_seg,
2791*56bb7041Schristos 			     SEC_READONLY | SEC_DEBUGGING | SEC_OCTETS);
2792*56bb7041Schristos     }
2793*56bb7041Schristos 
2794*56bb7041Schristos   /* For each subsection, chain the debug entries together.  */
2795*56bb7041Schristos   for (s = all_segs; s; s = s->next)
2796*56bb7041Schristos     {
2797*56bb7041Schristos       struct line_subseg *lss = s->head;
2798*56bb7041Schristos       struct line_entry **ptail = lss->ptail;
2799*56bb7041Schristos 
2800*56bb7041Schristos       /* Reset the initial view of the first subsection of the
2801*56bb7041Schristos 	 section.  */
2802*56bb7041Schristos       if (lss->head && lss->head->loc.view)
2803*56bb7041Schristos 	set_or_check_view (lss->head, NULL, NULL);
2804*56bb7041Schristos 
2805*56bb7041Schristos       while ((lss = lss->next) != NULL)
2806*56bb7041Schristos 	{
2807*56bb7041Schristos 	  /* Link the first view of subsequent subsections to the
2808*56bb7041Schristos 	     previous view.  */
2809*56bb7041Schristos 	  if (lss->head && lss->head->loc.view)
2810*56bb7041Schristos 	    set_or_check_view (lss->head,
2811*56bb7041Schristos 			       !s->head ? NULL : (struct line_entry *)ptail,
2812*56bb7041Schristos 			       s->head ? s->head->head : NULL);
2813*56bb7041Schristos 	  *ptail = lss->head;
2814*56bb7041Schristos 	  ptail = lss->ptail;
2815*56bb7041Schristos 	}
2816*56bb7041Schristos     }
2817*56bb7041Schristos 
2818*56bb7041Schristos   if (empty_debug_line)
2819*56bb7041Schristos     out_debug_line (line_seg);
2820*56bb7041Schristos 
2821*56bb7041Schristos   /* If this is assembler generated line info, and there is no
2822*56bb7041Schristos      debug_info already, we need .debug_info, .debug_abbrev and
2823*56bb7041Schristos      .debug_str sections as well.  */
2824*56bb7041Schristos   if (emit_other_sections)
2825*56bb7041Schristos     {
2826*56bb7041Schristos       segT abbrev_seg;
2827*56bb7041Schristos       segT aranges_seg;
2828*56bb7041Schristos       segT str_seg;
2829*56bb7041Schristos       symbolS *name_sym, *comp_dir_sym, *producer_sym, *ranges_sym;
2830*56bb7041Schristos 
2831*56bb7041Schristos       gas_assert (all_segs);
2832*56bb7041Schristos 
2833*56bb7041Schristos       info_seg = subseg_new (".debug_info", 0);
2834*56bb7041Schristos       abbrev_seg = subseg_new (".debug_abbrev", 0);
2835*56bb7041Schristos       aranges_seg = subseg_new (".debug_aranges", 0);
2836*56bb7041Schristos       str_seg = subseg_new (".debug_str", 0);
2837*56bb7041Schristos 
2838*56bb7041Schristos       bfd_set_section_flags (info_seg,
2839*56bb7041Schristos 			      SEC_READONLY | SEC_DEBUGGING | SEC_OCTETS);
2840*56bb7041Schristos       bfd_set_section_flags (abbrev_seg,
2841*56bb7041Schristos 			      SEC_READONLY | SEC_DEBUGGING | SEC_OCTETS);
2842*56bb7041Schristos       bfd_set_section_flags (aranges_seg,
2843*56bb7041Schristos 			      SEC_READONLY | SEC_DEBUGGING | SEC_OCTETS);
2844*56bb7041Schristos       bfd_set_section_flags (str_seg,
2845*56bb7041Schristos 			      SEC_READONLY | SEC_DEBUGGING | SEC_OCTETS
2846*56bb7041Schristos 				       | SEC_MERGE | SEC_STRINGS);
2847*56bb7041Schristos       str_seg->entsize = 1;
2848*56bb7041Schristos 
2849*56bb7041Schristos       record_alignment (aranges_seg, ffs (2 * sizeof_address) - 1);
2850*56bb7041Schristos 
2851*56bb7041Schristos       if (all_segs->next == NULL)
2852*56bb7041Schristos 	ranges_sym = NULL;
2853*56bb7041Schristos       else
2854*56bb7041Schristos 	{
2855*56bb7041Schristos 	  if (DWARF2_VERSION < 5)
2856*56bb7041Schristos 	    {
2857*56bb7041Schristos 	      segT ranges_seg = subseg_new (".debug_ranges", 0);
2858*56bb7041Schristos 	      bfd_set_section_flags (ranges_seg, (SEC_READONLY
2859*56bb7041Schristos 						  | SEC_DEBUGGING
2860*56bb7041Schristos 						  | SEC_OCTETS));
2861*56bb7041Schristos 	      record_alignment (ranges_seg, ffs (2 * sizeof_address) - 1);
2862*56bb7041Schristos 	      out_debug_ranges (ranges_seg, &ranges_sym);
2863*56bb7041Schristos 	    }
2864*56bb7041Schristos 	  else
2865*56bb7041Schristos 	    {
2866*56bb7041Schristos 	      segT rnglists_seg = subseg_new (".debug_rnglists", 0);
2867*56bb7041Schristos 	      bfd_set_section_flags (rnglists_seg, (SEC_READONLY
2868*56bb7041Schristos 						    | SEC_DEBUGGING
2869*56bb7041Schristos 						    | SEC_OCTETS));
2870*56bb7041Schristos 	      out_debug_rnglists (rnglists_seg, &ranges_sym);
2871*56bb7041Schristos 	    }
2872*56bb7041Schristos 	}
2873*56bb7041Schristos 
2874*56bb7041Schristos       out_debug_aranges (aranges_seg, info_seg);
2875*56bb7041Schristos       out_debug_abbrev (abbrev_seg, info_seg, line_seg);
2876*56bb7041Schristos       out_debug_str (str_seg, &name_sym, &comp_dir_sym, &producer_sym);
2877*56bb7041Schristos       out_debug_info (info_seg, abbrev_seg, line_seg, ranges_sym,
2878*56bb7041Schristos 		      name_sym, comp_dir_sym, producer_sym);
2879*56bb7041Schristos     }
2880*56bb7041Schristos }
2881*56bb7041Schristos 
2882*56bb7041Schristos /* Perform any deferred checks pertaining to debug information.  */
2883*56bb7041Schristos 
2884*56bb7041Schristos void
dwarf2dbg_final_check(void)2885*56bb7041Schristos dwarf2dbg_final_check (void)
2886*56bb7041Schristos {
2887*56bb7041Schristos   /* Perform reset-view checks.  Don't evaluate view_assert_failed
2888*56bb7041Schristos      recursively: it could be very deep.  It's a chain of adds, with
2889*56bb7041Schristos      each chain element pointing to the next in X_add_symbol, and
2890*56bb7041Schristos      holding the check value in X_op_symbol.  */
2891*56bb7041Schristos   while (view_assert_failed)
2892*56bb7041Schristos     {
2893*56bb7041Schristos       expressionS *exp;
2894*56bb7041Schristos       symbolS *sym;
2895*56bb7041Schristos       offsetT failed;
2896*56bb7041Schristos 
2897*56bb7041Schristos       gas_assert (!symbol_resolved_p (view_assert_failed));
2898*56bb7041Schristos 
2899*56bb7041Schristos       exp = symbol_get_value_expression (view_assert_failed);
2900*56bb7041Schristos       sym = view_assert_failed;
2901*56bb7041Schristos 
2902*56bb7041Schristos       /* If view_assert_failed looks like a compound check in the
2903*56bb7041Schristos 	 chain, break it up.  */
2904*56bb7041Schristos       if (exp->X_op == O_add && exp->X_add_number == 0 && exp->X_unsigned)
2905*56bb7041Schristos 	{
2906*56bb7041Schristos 	  view_assert_failed = exp->X_add_symbol;
2907*56bb7041Schristos 	  sym = exp->X_op_symbol;
2908*56bb7041Schristos 	}
2909*56bb7041Schristos       else
2910*56bb7041Schristos 	view_assert_failed = NULL;
2911*56bb7041Schristos 
2912*56bb7041Schristos       failed = resolve_symbol_value (sym);
2913*56bb7041Schristos       if (!symbol_resolved_p (sym) || failed)
2914*56bb7041Schristos 	{
2915*56bb7041Schristos 	  as_bad (_("view number mismatch"));
2916*56bb7041Schristos 	  break;
2917*56bb7041Schristos 	}
2918*56bb7041Schristos     }
2919*56bb7041Schristos }
2920