1*fae548d3Szrj /* frags.c - manage frags -
2*fae548d3Szrj Copyright (C) 1987-2020 Free Software Foundation, Inc.
3*fae548d3Szrj
4*fae548d3Szrj This file is part of GAS, the GNU Assembler.
5*fae548d3Szrj
6*fae548d3Szrj GAS is free software; you can redistribute it and/or modify
7*fae548d3Szrj it under the terms of the GNU General Public License as published by
8*fae548d3Szrj the Free Software Foundation; either version 3, or (at your option)
9*fae548d3Szrj any later version.
10*fae548d3Szrj
11*fae548d3Szrj GAS is distributed in the hope that it will be useful,
12*fae548d3Szrj but WITHOUT ANY WARRANTY; without even the implied warranty of
13*fae548d3Szrj MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
14*fae548d3Szrj GNU General Public License for more details.
15*fae548d3Szrj
16*fae548d3Szrj You should have received a copy of the GNU General Public License
17*fae548d3Szrj along with GAS; see the file COPYING. If not, write to the Free
18*fae548d3Szrj Software Foundation, 51 Franklin Street - Fifth Floor, Boston, MA
19*fae548d3Szrj 02110-1301, USA. */
20*fae548d3Szrj
21*fae548d3Szrj #include "as.h"
22*fae548d3Szrj #include "subsegs.h"
23*fae548d3Szrj #include "obstack.h"
24*fae548d3Szrj
25*fae548d3Szrj extern fragS zero_address_frag;
26*fae548d3Szrj extern fragS predefined_address_frag;
27*fae548d3Szrj
28*fae548d3Szrj static int totalfrags;
29*fae548d3Szrj
30*fae548d3Szrj int
get_frag_count(void)31*fae548d3Szrj get_frag_count (void)
32*fae548d3Szrj {
33*fae548d3Szrj return totalfrags;
34*fae548d3Szrj }
35*fae548d3Szrj
36*fae548d3Szrj void
clear_frag_count(void)37*fae548d3Szrj clear_frag_count (void)
38*fae548d3Szrj {
39*fae548d3Szrj totalfrags = 0;
40*fae548d3Szrj }
41*fae548d3Szrj
42*fae548d3Szrj /* Initialization for frag routines. */
43*fae548d3Szrj
44*fae548d3Szrj void
frag_init(void)45*fae548d3Szrj frag_init (void)
46*fae548d3Szrj {
47*fae548d3Szrj zero_address_frag.fr_type = rs_fill;
48*fae548d3Szrj predefined_address_frag.fr_type = rs_fill;
49*fae548d3Szrj }
50*fae548d3Szrj
51*fae548d3Szrj /* Check that we're not trying to assemble into a section that can't
52*fae548d3Szrj allocate frags (currently, this is only possible in the absolute
53*fae548d3Szrj section), or into an mri common. */
54*fae548d3Szrj
55*fae548d3Szrj static void
frag_alloc_check(const struct obstack * ob)56*fae548d3Szrj frag_alloc_check (const struct obstack *ob)
57*fae548d3Szrj {
58*fae548d3Szrj if (ob->chunk_size == 0)
59*fae548d3Szrj {
60*fae548d3Szrj as_bad (_("attempt to allocate data in absolute section"));
61*fae548d3Szrj subseg_set (text_section, 0);
62*fae548d3Szrj }
63*fae548d3Szrj
64*fae548d3Szrj if (mri_common_symbol != NULL)
65*fae548d3Szrj {
66*fae548d3Szrj as_bad (_("attempt to allocate data in common section"));
67*fae548d3Szrj mri_common_symbol = NULL;
68*fae548d3Szrj }
69*fae548d3Szrj }
70*fae548d3Szrj
71*fae548d3Szrj /* Allocate a frag on the specified obstack.
72*fae548d3Szrj Call this routine from everywhere else, so that all the weird alignment
73*fae548d3Szrj hackery can be done in just one place. */
74*fae548d3Szrj
75*fae548d3Szrj fragS *
frag_alloc(struct obstack * ob)76*fae548d3Szrj frag_alloc (struct obstack *ob)
77*fae548d3Szrj {
78*fae548d3Szrj fragS *ptr;
79*fae548d3Szrj int oalign;
80*fae548d3Szrj
81*fae548d3Szrj (void) obstack_alloc (ob, 0);
82*fae548d3Szrj oalign = obstack_alignment_mask (ob);
83*fae548d3Szrj obstack_alignment_mask (ob) = 0;
84*fae548d3Szrj ptr = (fragS *) obstack_alloc (ob, SIZEOF_STRUCT_FRAG);
85*fae548d3Szrj obstack_alignment_mask (ob) = oalign;
86*fae548d3Szrj memset (ptr, 0, SIZEOF_STRUCT_FRAG);
87*fae548d3Szrj totalfrags++;
88*fae548d3Szrj return ptr;
89*fae548d3Szrj }
90*fae548d3Szrj
91*fae548d3Szrj /* Try to augment current frag by nchars chars.
92*fae548d3Szrj If there is no room, close of the current frag with a ".fill 0"
93*fae548d3Szrj and begin a new frag. Unless the new frag has nchars chars available
94*fae548d3Szrj do not return. Do not set up any fields of *now_frag. */
95*fae548d3Szrj
96*fae548d3Szrj void
frag_grow(size_t nchars)97*fae548d3Szrj frag_grow (size_t nchars)
98*fae548d3Szrj {
99*fae548d3Szrj if (obstack_room (&frchain_now->frch_obstack) < nchars)
100*fae548d3Szrj {
101*fae548d3Szrj size_t oldc;
102*fae548d3Szrj size_t newc;
103*fae548d3Szrj
104*fae548d3Szrj /* Try to allocate a bit more than needed right now. But don't do
105*fae548d3Szrj this if we would waste too much memory. Especially necessary
106*fae548d3Szrj for extremely big (like 2GB initialized) frags. */
107*fae548d3Szrj if (nchars < 0x10000)
108*fae548d3Szrj newc = 2 * nchars;
109*fae548d3Szrj else
110*fae548d3Szrj newc = nchars + 0x10000;
111*fae548d3Szrj newc += SIZEOF_STRUCT_FRAG;
112*fae548d3Szrj
113*fae548d3Szrj /* Check for possible overflow. */
114*fae548d3Szrj if (newc < nchars)
115*fae548d3Szrj as_fatal (ngettext ("can't extend frag %lu char",
116*fae548d3Szrj "can't extend frag %lu chars",
117*fae548d3Szrj (unsigned long) nchars),
118*fae548d3Szrj (unsigned long) nchars);
119*fae548d3Szrj
120*fae548d3Szrj /* Force to allocate at least NEWC bytes, but not less than the
121*fae548d3Szrj default. */
122*fae548d3Szrj oldc = obstack_chunk_size (&frchain_now->frch_obstack);
123*fae548d3Szrj if (newc > oldc)
124*fae548d3Szrj obstack_chunk_size (&frchain_now->frch_obstack) = newc;
125*fae548d3Szrj
126*fae548d3Szrj while (obstack_room (&frchain_now->frch_obstack) < nchars)
127*fae548d3Szrj {
128*fae548d3Szrj /* Not enough room in this frag. Close it and start a new one.
129*fae548d3Szrj This must be done in a loop because the created frag may not
130*fae548d3Szrj be big enough if the current obstack chunk is used. */
131*fae548d3Szrj frag_wane (frag_now);
132*fae548d3Szrj frag_new (0);
133*fae548d3Szrj }
134*fae548d3Szrj
135*fae548d3Szrj /* Restore the old chunk size. */
136*fae548d3Szrj obstack_chunk_size (&frchain_now->frch_obstack) = oldc;
137*fae548d3Szrj }
138*fae548d3Szrj }
139*fae548d3Szrj
140*fae548d3Szrj /* Call this to close off a completed frag, and start up a new (empty)
141*fae548d3Szrj frag, in the same subsegment as the old frag.
142*fae548d3Szrj [frchain_now remains the same but frag_now is updated.]
143*fae548d3Szrj Because this calculates the correct value of fr_fix by
144*fae548d3Szrj looking at the obstack 'frags', it needs to know how many
145*fae548d3Szrj characters at the end of the old frag belong to the maximal
146*fae548d3Szrj variable part; The rest must belong to fr_fix.
147*fae548d3Szrj It doesn't actually set up the old frag's fr_var. You may have
148*fae548d3Szrj set fr_var == 1, but allocated 10 chars to the end of the frag;
149*fae548d3Szrj In this case you pass old_frags_var_max_size == 10.
150*fae548d3Szrj In fact, you may use fr_var for something totally unrelated to the
151*fae548d3Szrj size of the variable part of the frag; None of the generic frag
152*fae548d3Szrj handling code makes use of fr_var.
153*fae548d3Szrj
154*fae548d3Szrj Make a new frag, initialising some components. Link new frag at end
155*fae548d3Szrj of frchain_now. */
156*fae548d3Szrj
157*fae548d3Szrj void
frag_new(size_t old_frags_var_max_size)158*fae548d3Szrj frag_new (size_t old_frags_var_max_size
159*fae548d3Szrj /* Number of chars (already allocated on obstack frags) in
160*fae548d3Szrj variable_length part of frag. */)
161*fae548d3Szrj {
162*fae548d3Szrj fragS *former_last_fragP;
163*fae548d3Szrj frchainS *frchP;
164*fae548d3Szrj
165*fae548d3Szrj gas_assert (frchain_now->frch_last == frag_now);
166*fae548d3Szrj
167*fae548d3Szrj /* Fix up old frag's fr_fix. */
168*fae548d3Szrj frag_now->fr_fix = frag_now_fix_octets ();
169*fae548d3Szrj gas_assert (frag_now->fr_fix >= old_frags_var_max_size);
170*fae548d3Szrj frag_now->fr_fix -= old_frags_var_max_size;
171*fae548d3Szrj /* Make sure its type is valid. */
172*fae548d3Szrj gas_assert (frag_now->fr_type != 0);
173*fae548d3Szrj
174*fae548d3Szrj /* This will align the obstack so the next struct we allocate on it
175*fae548d3Szrj will begin at a correct boundary. */
176*fae548d3Szrj obstack_finish (&frchain_now->frch_obstack);
177*fae548d3Szrj frchP = frchain_now;
178*fae548d3Szrj know (frchP);
179*fae548d3Szrj former_last_fragP = frchP->frch_last;
180*fae548d3Szrj gas_assert (former_last_fragP != 0);
181*fae548d3Szrj gas_assert (former_last_fragP == frag_now);
182*fae548d3Szrj frag_now = frag_alloc (&frchP->frch_obstack);
183*fae548d3Szrj
184*fae548d3Szrj frag_now->fr_file = as_where (&frag_now->fr_line);
185*fae548d3Szrj
186*fae548d3Szrj /* Generally, frag_now->points to an address rounded up to next
187*fae548d3Szrj alignment. However, characters will add to obstack frags
188*fae548d3Szrj IMMEDIATELY after the struct frag, even if they are not starting
189*fae548d3Szrj at an alignment address. */
190*fae548d3Szrj former_last_fragP->fr_next = frag_now;
191*fae548d3Szrj frchP->frch_last = frag_now;
192*fae548d3Szrj
193*fae548d3Szrj #ifndef NO_LISTING
194*fae548d3Szrj {
195*fae548d3Szrj extern struct list_info_struct *listing_tail;
196*fae548d3Szrj frag_now->line = listing_tail;
197*fae548d3Szrj }
198*fae548d3Szrj #endif
199*fae548d3Szrj
200*fae548d3Szrj gas_assert (frchain_now->frch_last == frag_now);
201*fae548d3Szrj
202*fae548d3Szrj frag_now->fr_next = NULL;
203*fae548d3Szrj }
204*fae548d3Szrj
205*fae548d3Szrj /* Start a new frag unless we have n more chars of room in the current frag.
206*fae548d3Szrj Close off the old frag with a .fill 0.
207*fae548d3Szrj
208*fae548d3Szrj Return the address of the 1st char to write into. Advance
209*fae548d3Szrj frag_now_growth past the new chars. */
210*fae548d3Szrj
211*fae548d3Szrj char *
frag_more(size_t nchars)212*fae548d3Szrj frag_more (size_t nchars)
213*fae548d3Szrj {
214*fae548d3Szrj char *retval;
215*fae548d3Szrj
216*fae548d3Szrj frag_alloc_check (&frchain_now->frch_obstack);
217*fae548d3Szrj frag_grow (nchars);
218*fae548d3Szrj retval = obstack_next_free (&frchain_now->frch_obstack);
219*fae548d3Szrj obstack_blank_fast (&frchain_now->frch_obstack, nchars);
220*fae548d3Szrj return retval;
221*fae548d3Szrj }
222*fae548d3Szrj
223*fae548d3Szrj /* Close the current frag, setting its fields for a relaxable frag. Start a
224*fae548d3Szrj new frag. */
225*fae548d3Szrj
226*fae548d3Szrj static void
frag_var_init(relax_stateT type,size_t max_chars,size_t var,relax_substateT subtype,symbolS * symbol,offsetT offset,char * opcode)227*fae548d3Szrj frag_var_init (relax_stateT type, size_t max_chars, size_t var,
228*fae548d3Szrj relax_substateT subtype, symbolS *symbol, offsetT offset,
229*fae548d3Szrj char *opcode)
230*fae548d3Szrj {
231*fae548d3Szrj frag_now->fr_var = var;
232*fae548d3Szrj frag_now->fr_type = type;
233*fae548d3Szrj frag_now->fr_subtype = subtype;
234*fae548d3Szrj frag_now->fr_symbol = symbol;
235*fae548d3Szrj frag_now->fr_offset = offset;
236*fae548d3Szrj frag_now->fr_opcode = opcode;
237*fae548d3Szrj #ifdef USING_CGEN
238*fae548d3Szrj frag_now->fr_cgen.insn = 0;
239*fae548d3Szrj frag_now->fr_cgen.opindex = 0;
240*fae548d3Szrj frag_now->fr_cgen.opinfo = 0;
241*fae548d3Szrj #endif
242*fae548d3Szrj #ifdef TC_FRAG_INIT
243*fae548d3Szrj TC_FRAG_INIT (frag_now, max_chars);
244*fae548d3Szrj #endif
245*fae548d3Szrj frag_now->fr_file = as_where (&frag_now->fr_line);
246*fae548d3Szrj
247*fae548d3Szrj frag_new (max_chars);
248*fae548d3Szrj }
249*fae548d3Szrj
250*fae548d3Szrj /* Start a new frag unless we have max_chars more chars of room in the
251*fae548d3Szrj current frag. Close off the old frag with a .fill 0.
252*fae548d3Szrj
253*fae548d3Szrj Set up a machine_dependent relaxable frag, then start a new frag.
254*fae548d3Szrj Return the address of the 1st char of the var part of the old frag
255*fae548d3Szrj to write into. */
256*fae548d3Szrj
257*fae548d3Szrj char *
frag_var(relax_stateT type,size_t max_chars,size_t var,relax_substateT subtype,symbolS * symbol,offsetT offset,char * opcode)258*fae548d3Szrj frag_var (relax_stateT type, size_t max_chars, size_t var,
259*fae548d3Szrj relax_substateT subtype, symbolS *symbol, offsetT offset,
260*fae548d3Szrj char *opcode)
261*fae548d3Szrj {
262*fae548d3Szrj char *retval;
263*fae548d3Szrj
264*fae548d3Szrj frag_grow (max_chars);
265*fae548d3Szrj retval = obstack_next_free (&frchain_now->frch_obstack);
266*fae548d3Szrj obstack_blank_fast (&frchain_now->frch_obstack, max_chars);
267*fae548d3Szrj frag_var_init (type, max_chars, var, subtype, symbol, offset, opcode);
268*fae548d3Szrj return retval;
269*fae548d3Szrj }
270*fae548d3Szrj
271*fae548d3Szrj /* OVE: This variant of frag_var assumes that space for the tail has been
272*fae548d3Szrj allocated by caller.
273*fae548d3Szrj No call to frag_grow is done. */
274*fae548d3Szrj
275*fae548d3Szrj char *
frag_variant(relax_stateT type,size_t max_chars,size_t var,relax_substateT subtype,symbolS * symbol,offsetT offset,char * opcode)276*fae548d3Szrj frag_variant (relax_stateT type, size_t max_chars, size_t var,
277*fae548d3Szrj relax_substateT subtype, symbolS *symbol, offsetT offset,
278*fae548d3Szrj char *opcode)
279*fae548d3Szrj {
280*fae548d3Szrj char *retval;
281*fae548d3Szrj
282*fae548d3Szrj retval = obstack_next_free (&frchain_now->frch_obstack);
283*fae548d3Szrj frag_var_init (type, max_chars, var, subtype, symbol, offset, opcode);
284*fae548d3Szrj
285*fae548d3Szrj return retval;
286*fae548d3Szrj }
287*fae548d3Szrj
288*fae548d3Szrj /* Reduce the variable end of a frag to a harmless state. */
289*fae548d3Szrj
290*fae548d3Szrj void
frag_wane(fragS * fragP)291*fae548d3Szrj frag_wane (fragS *fragP)
292*fae548d3Szrj {
293*fae548d3Szrj fragP->fr_type = rs_fill;
294*fae548d3Szrj fragP->fr_offset = 0;
295*fae548d3Szrj fragP->fr_var = 0;
296*fae548d3Szrj }
297*fae548d3Szrj
298*fae548d3Szrj /* Return the number of bytes by which the current frag can be grown. */
299*fae548d3Szrj
300*fae548d3Szrj size_t
frag_room(void)301*fae548d3Szrj frag_room (void)
302*fae548d3Szrj {
303*fae548d3Szrj return obstack_room (&frchain_now->frch_obstack);
304*fae548d3Szrj }
305*fae548d3Szrj
306*fae548d3Szrj /* Make an alignment frag. The size of this frag will be adjusted to
307*fae548d3Szrj force the next frag to have the appropriate alignment. ALIGNMENT
308*fae548d3Szrj is the power of two to which to align. FILL_CHARACTER is the
309*fae548d3Szrj character to use to fill in any bytes which are skipped. MAX is
310*fae548d3Szrj the maximum number of characters to skip when doing the alignment,
311*fae548d3Szrj or 0 if there is no maximum. */
312*fae548d3Szrj
313*fae548d3Szrj void
frag_align(int alignment,int fill_character,int max)314*fae548d3Szrj frag_align (int alignment, int fill_character, int max)
315*fae548d3Szrj {
316*fae548d3Szrj if (now_seg == absolute_section)
317*fae548d3Szrj {
318*fae548d3Szrj addressT new_off;
319*fae548d3Szrj addressT mask;
320*fae548d3Szrj
321*fae548d3Szrj mask = (~(addressT) 0) << alignment;
322*fae548d3Szrj new_off = (abs_section_offset + ~mask) & mask;
323*fae548d3Szrj if (max == 0 || new_off - abs_section_offset <= (addressT) max)
324*fae548d3Szrj abs_section_offset = new_off;
325*fae548d3Szrj }
326*fae548d3Szrj else
327*fae548d3Szrj {
328*fae548d3Szrj char *p;
329*fae548d3Szrj
330*fae548d3Szrj p = frag_var (rs_align, 1, 1, (relax_substateT) max,
331*fae548d3Szrj (symbolS *) 0, (offsetT) alignment, (char *) 0);
332*fae548d3Szrj *p = fill_character;
333*fae548d3Szrj }
334*fae548d3Szrj }
335*fae548d3Szrj
336*fae548d3Szrj /* Make an alignment frag like frag_align, but fill with a repeating
337*fae548d3Szrj pattern rather than a single byte. ALIGNMENT is the power of two
338*fae548d3Szrj to which to align. FILL_PATTERN is the fill pattern to repeat in
339*fae548d3Szrj the bytes which are skipped. N_FILL is the number of bytes in
340*fae548d3Szrj FILL_PATTERN. MAX is the maximum number of characters to skip when
341*fae548d3Szrj doing the alignment, or 0 if there is no maximum. */
342*fae548d3Szrj
343*fae548d3Szrj void
frag_align_pattern(int alignment,const char * fill_pattern,size_t n_fill,int max)344*fae548d3Szrj frag_align_pattern (int alignment, const char *fill_pattern,
345*fae548d3Szrj size_t n_fill, int max)
346*fae548d3Szrj {
347*fae548d3Szrj char *p;
348*fae548d3Szrj
349*fae548d3Szrj p = frag_var (rs_align, n_fill, n_fill, (relax_substateT) max,
350*fae548d3Szrj (symbolS *) 0, (offsetT) alignment, (char *) 0);
351*fae548d3Szrj memcpy (p, fill_pattern, n_fill);
352*fae548d3Szrj }
353*fae548d3Szrj
354*fae548d3Szrj /* The NOP_OPCODE is for the alignment fill value. Fill it with a nop
355*fae548d3Szrj instruction so that the disassembler does not choke on it. */
356*fae548d3Szrj #ifndef NOP_OPCODE
357*fae548d3Szrj #define NOP_OPCODE 0x00
358*fae548d3Szrj #endif
359*fae548d3Szrj
360*fae548d3Szrj /* Use this to restrict the amount of memory allocated for representing
361*fae548d3Szrj the alignment code. Needs to be large enough to hold any fixed sized
362*fae548d3Szrj prologue plus the replicating portion. */
363*fae548d3Szrj #ifndef MAX_MEM_FOR_RS_ALIGN_CODE
364*fae548d3Szrj /* Assume that if HANDLE_ALIGN is not defined then no special action
365*fae548d3Szrj is required to code fill, which means that we get just repeat the
366*fae548d3Szrj one NOP_OPCODE byte. */
367*fae548d3Szrj # ifndef HANDLE_ALIGN
368*fae548d3Szrj # define MAX_MEM_FOR_RS_ALIGN_CODE 1
369*fae548d3Szrj # else
370*fae548d3Szrj # define MAX_MEM_FOR_RS_ALIGN_CODE ((1 << alignment) - 1)
371*fae548d3Szrj # endif
372*fae548d3Szrj #endif
373*fae548d3Szrj
374*fae548d3Szrj void
frag_align_code(int alignment,int max)375*fae548d3Szrj frag_align_code (int alignment, int max)
376*fae548d3Szrj {
377*fae548d3Szrj char *p;
378*fae548d3Szrj
379*fae548d3Szrj p = frag_var (rs_align_code, MAX_MEM_FOR_RS_ALIGN_CODE, 1,
380*fae548d3Szrj (relax_substateT) max, (symbolS *) 0,
381*fae548d3Szrj (offsetT) alignment, (char *) 0);
382*fae548d3Szrj *p = NOP_OPCODE;
383*fae548d3Szrj }
384*fae548d3Szrj
385*fae548d3Szrj addressT
frag_now_fix_octets(void)386*fae548d3Szrj frag_now_fix_octets (void)
387*fae548d3Szrj {
388*fae548d3Szrj if (now_seg == absolute_section)
389*fae548d3Szrj return abs_section_offset;
390*fae548d3Szrj
391*fae548d3Szrj return ((char *) obstack_next_free (&frchain_now->frch_obstack)
392*fae548d3Szrj - frag_now->fr_literal);
393*fae548d3Szrj }
394*fae548d3Szrj
395*fae548d3Szrj addressT
frag_now_fix(void)396*fae548d3Szrj frag_now_fix (void)
397*fae548d3Szrj {
398*fae548d3Szrj /* Symbols whose section has SEC_ELF_OCTETS set,
399*fae548d3Szrj resolve to octets instead of target bytes. */
400*fae548d3Szrj if (now_seg->flags & SEC_OCTETS)
401*fae548d3Szrj return frag_now_fix_octets ();
402*fae548d3Szrj else
403*fae548d3Szrj return frag_now_fix_octets () / OCTETS_PER_BYTE;
404*fae548d3Szrj }
405*fae548d3Szrj
406*fae548d3Szrj void
frag_append_1_char(int datum)407*fae548d3Szrj frag_append_1_char (int datum)
408*fae548d3Szrj {
409*fae548d3Szrj frag_alloc_check (&frchain_now->frch_obstack);
410*fae548d3Szrj if (obstack_room (&frchain_now->frch_obstack) <= 1)
411*fae548d3Szrj {
412*fae548d3Szrj frag_wane (frag_now);
413*fae548d3Szrj frag_new (0);
414*fae548d3Szrj }
415*fae548d3Szrj obstack_1grow (&frchain_now->frch_obstack, datum);
416*fae548d3Szrj }
417*fae548d3Szrj
418*fae548d3Szrj /* Return TRUE if FRAG1 and FRAG2 have a fixed relationship between
419*fae548d3Szrj their start addresses. Set OFFSET to the difference in address
420*fae548d3Szrj not already accounted for in the frag FR_ADDRESS. */
421*fae548d3Szrj
422*fae548d3Szrj bfd_boolean
frag_offset_fixed_p(const fragS * frag1,const fragS * frag2,offsetT * offset)423*fae548d3Szrj frag_offset_fixed_p (const fragS *frag1, const fragS *frag2, offsetT *offset)
424*fae548d3Szrj {
425*fae548d3Szrj const fragS *frag;
426*fae548d3Szrj offsetT off;
427*fae548d3Szrj
428*fae548d3Szrj /* Start with offset initialised to difference between the two frags.
429*fae548d3Szrj Prior to assigning frag addresses this will be zero. */
430*fae548d3Szrj off = frag1->fr_address - frag2->fr_address;
431*fae548d3Szrj if (frag1 == frag2)
432*fae548d3Szrj {
433*fae548d3Szrj *offset = off;
434*fae548d3Szrj return TRUE;
435*fae548d3Szrj }
436*fae548d3Szrj
437*fae548d3Szrj /* Maybe frag2 is after frag1. */
438*fae548d3Szrj frag = frag1;
439*fae548d3Szrj while (frag->fr_type == rs_fill)
440*fae548d3Szrj {
441*fae548d3Szrj off += frag->fr_fix + frag->fr_offset * frag->fr_var;
442*fae548d3Szrj frag = frag->fr_next;
443*fae548d3Szrj if (frag == NULL)
444*fae548d3Szrj break;
445*fae548d3Szrj if (frag == frag2)
446*fae548d3Szrj {
447*fae548d3Szrj *offset = off;
448*fae548d3Szrj return TRUE;
449*fae548d3Szrj }
450*fae548d3Szrj }
451*fae548d3Szrj
452*fae548d3Szrj /* Maybe frag1 is after frag2. */
453*fae548d3Szrj off = frag1->fr_address - frag2->fr_address;
454*fae548d3Szrj frag = frag2;
455*fae548d3Szrj while (frag->fr_type == rs_fill)
456*fae548d3Szrj {
457*fae548d3Szrj off -= frag->fr_fix + frag->fr_offset * frag->fr_var;
458*fae548d3Szrj frag = frag->fr_next;
459*fae548d3Szrj if (frag == NULL)
460*fae548d3Szrj break;
461*fae548d3Szrj if (frag == frag1)
462*fae548d3Szrj {
463*fae548d3Szrj *offset = off;
464*fae548d3Szrj return TRUE;
465*fae548d3Szrj }
466*fae548d3Szrj }
467*fae548d3Szrj
468*fae548d3Szrj return FALSE;
469*fae548d3Szrj }
470*fae548d3Szrj
471*fae548d3Szrj /* Return TRUE if we can determine whether FRAG2 OFF2 appears after
472*fae548d3Szrj (strict >, not >=) FRAG1 OFF1, assuming it is not before. Set
473*fae548d3Szrj *OFFSET so that resolve_expression will resolve an O_gt operation
474*fae548d3Szrj between them to false (0) if they are guaranteed to be at the same
475*fae548d3Szrj location, or to true (-1) if they are guaranteed to be at different
476*fae548d3Szrj locations. Return FALSE conservatively, e.g. if neither result can
477*fae548d3Szrj be guaranteed (yet).
478*fae548d3Szrj
479*fae548d3Szrj They are known to be in the same segment, and not the same frag
480*fae548d3Szrj (this is a fallback for frag_offset_fixed_p, that always takes care
481*fae548d3Szrj of this case), and it is expected (from the uses this is designed
482*fae548d3Szrj to simplify, namely location view increments) that frag2 is
483*fae548d3Szrj reachable from frag1 following the fr_next links, rather than the
484*fae548d3Szrj other way round. */
485*fae548d3Szrj
486*fae548d3Szrj bfd_boolean
frag_gtoffset_p(valueT off2,const fragS * frag2,valueT off1,const fragS * frag1,offsetT * offset)487*fae548d3Szrj frag_gtoffset_p (valueT off2, const fragS *frag2,
488*fae548d3Szrj valueT off1, const fragS *frag1, offsetT *offset)
489*fae548d3Szrj {
490*fae548d3Szrj /* Insanity check. */
491*fae548d3Szrj if (frag2 == frag1 || off1 > frag1->fr_fix)
492*fae548d3Szrj return FALSE;
493*fae548d3Szrj
494*fae548d3Szrj /* If the first symbol offset is at the end of the first frag and
495*fae548d3Szrj the second symbol offset at the beginning of the second frag then
496*fae548d3Szrj it is possible they are at the same address. Go looking for a
497*fae548d3Szrj non-zero fr_fix in any frag between these frags. If found then
498*fae548d3Szrj we can say the O_gt result will be true. If no such frag is
499*fae548d3Szrj found we assume that frag1 or any of the following frags might
500*fae548d3Szrj have a variable tail and thus the answer is unknown. This isn't
501*fae548d3Szrj strictly true; some frags don't have a variable tail, but it
502*fae548d3Szrj doesn't seem worth optimizing for those cases. */
503*fae548d3Szrj const fragS *frag = frag1;
504*fae548d3Szrj offsetT delta = off2 - off1;
505*fae548d3Szrj for (;;)
506*fae548d3Szrj {
507*fae548d3Szrj delta += frag->fr_fix;
508*fae548d3Szrj frag = frag->fr_next;
509*fae548d3Szrj if (frag == frag2)
510*fae548d3Szrj {
511*fae548d3Szrj if (delta == 0)
512*fae548d3Szrj return FALSE;
513*fae548d3Szrj break;
514*fae548d3Szrj }
515*fae548d3Szrj /* If we run off the end of the frag chain then we have a case
516*fae548d3Szrj where frag2 is not after frag1, ie. an O_gt expression not
517*fae548d3Szrj created for .loc view. */
518*fae548d3Szrj if (frag == NULL)
519*fae548d3Szrj return FALSE;
520*fae548d3Szrj }
521*fae548d3Szrj
522*fae548d3Szrj *offset = (off2 - off1 - delta) * OCTETS_PER_BYTE;
523*fae548d3Szrj return TRUE;
524*fae548d3Szrj }
525