xref: /openbsd-src/gnu/usr.bin/binutils-2.17/gas/ecoff.c (revision 3d8817e467ea46cf4772788d6804dd293abfb01a)
1*3d8817e4Smiod /* ECOFF debugging support.
2*3d8817e4Smiod    Copyright 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002,
3*3d8817e4Smiod    2003, 2004, 2005
4*3d8817e4Smiod    Free Software Foundation, Inc.
5*3d8817e4Smiod    Contributed by Cygnus Support.
6*3d8817e4Smiod    This file was put together by Ian Lance Taylor <ian@cygnus.com>.  A
7*3d8817e4Smiod    good deal of it comes directly from mips-tfile.c, by Michael
8*3d8817e4Smiod    Meissner <meissner@osf.org>.
9*3d8817e4Smiod 
10*3d8817e4Smiod    This file is part of GAS.
11*3d8817e4Smiod 
12*3d8817e4Smiod    GAS is free software; you can redistribute it and/or modify
13*3d8817e4Smiod    it under the terms of the GNU General Public License as published by
14*3d8817e4Smiod    the Free Software Foundation; either version 2, or (at your option)
15*3d8817e4Smiod    any later version.
16*3d8817e4Smiod 
17*3d8817e4Smiod    GAS is distributed in the hope that it will be useful,
18*3d8817e4Smiod    but WITHOUT ANY WARRANTY; without even the implied warranty of
19*3d8817e4Smiod    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
20*3d8817e4Smiod    GNU General Public License for more details.
21*3d8817e4Smiod 
22*3d8817e4Smiod    You should have received a copy of the GNU General Public License
23*3d8817e4Smiod    along with GAS; see the file COPYING.  If not, write to the Free
24*3d8817e4Smiod    Software Foundation, 51 Franklin Street - Fifth Floor, Boston, MA
25*3d8817e4Smiod    02110-1301, USA.  */
26*3d8817e4Smiod 
27*3d8817e4Smiod #include "as.h"
28*3d8817e4Smiod 
29*3d8817e4Smiod /* This file is compiled conditionally for those targets which use
30*3d8817e4Smiod    ECOFF debugging information (e.g., MIPS ECOFF, MIPS ELF, Alpha
31*3d8817e4Smiod    ECOFF).  */
32*3d8817e4Smiod 
33*3d8817e4Smiod #include "ecoff.h"
34*3d8817e4Smiod 
35*3d8817e4Smiod #ifdef ECOFF_DEBUGGING
36*3d8817e4Smiod 
37*3d8817e4Smiod #include "coff/internal.h"
38*3d8817e4Smiod #include "coff/symconst.h"
39*3d8817e4Smiod #include "aout/stab_gnu.h"
40*3d8817e4Smiod 
41*3d8817e4Smiod #include "safe-ctype.h"
42*3d8817e4Smiod 
43*3d8817e4Smiod /* Why isn't this in coff/sym.h?  */
44*3d8817e4Smiod #define ST_RFDESCAPE 0xfff
45*3d8817e4Smiod 
46*3d8817e4Smiod /* This file constructs the information used by the ECOFF debugging
47*3d8817e4Smiod    format.  It just builds a large block of data.
48*3d8817e4Smiod 
49*3d8817e4Smiod    We support both ECOFF style debugging and stabs debugging (the
50*3d8817e4Smiod    stabs symbols are encapsulated in ECOFF symbols).  This should let
51*3d8817e4Smiod    us handle anything the compiler might throw at us.  */
52*3d8817e4Smiod 
53*3d8817e4Smiod /* Here is a brief description of the MIPS ECOFF symbol table, by
54*3d8817e4Smiod    Michael Meissner.  The MIPS symbol table has the following pieces:
55*3d8817e4Smiod 
56*3d8817e4Smiod 	Symbolic Header
57*3d8817e4Smiod 	    |
58*3d8817e4Smiod 	    +--	Auxiliary Symbols
59*3d8817e4Smiod 	    |
60*3d8817e4Smiod 	    +--	Dense number table
61*3d8817e4Smiod 	    |
62*3d8817e4Smiod 	    +--	Optimizer Symbols
63*3d8817e4Smiod 	    |
64*3d8817e4Smiod 	    +--	External Strings
65*3d8817e4Smiod 	    |
66*3d8817e4Smiod 	    +--	External Symbols
67*3d8817e4Smiod 	    |
68*3d8817e4Smiod 	    +--	Relative file descriptors
69*3d8817e4Smiod 	    |
70*3d8817e4Smiod 	    +--	File table
71*3d8817e4Smiod 		    |
72*3d8817e4Smiod 		    +--	Procedure table
73*3d8817e4Smiod 		    |
74*3d8817e4Smiod 		    +--	Line number table
75*3d8817e4Smiod 		    |
76*3d8817e4Smiod 		    +--	Local Strings
77*3d8817e4Smiod 		    |
78*3d8817e4Smiod 		    +--	Local Symbols
79*3d8817e4Smiod 
80*3d8817e4Smiod    The symbolic header points to each of the other tables, and also
81*3d8817e4Smiod    contains the number of entries.  It also contains a magic number
82*3d8817e4Smiod    and MIPS compiler version number, such as 2.0.
83*3d8817e4Smiod 
84*3d8817e4Smiod    The auxiliary table is a series of 32 bit integers, that are
85*3d8817e4Smiod    referenced as needed from the local symbol table.  Unlike standard
86*3d8817e4Smiod    COFF, the aux.  information does not follow the symbol that uses
87*3d8817e4Smiod    it, but rather is a separate table.  In theory, this would allow
88*3d8817e4Smiod    the MIPS compilers to collapse duplicate aux. entries, but I've not
89*3d8817e4Smiod    noticed this happening with the 1.31 compiler suite.  The different
90*3d8817e4Smiod    types of aux. entries are:
91*3d8817e4Smiod 
92*3d8817e4Smiod     1)	dnLow: Low bound on array dimension.
93*3d8817e4Smiod 
94*3d8817e4Smiod     2)	dnHigh: High bound on array dimension.
95*3d8817e4Smiod 
96*3d8817e4Smiod     3)	isym: Index to the local symbol which is the start of the
97*3d8817e4Smiod 	function for the end of function first aux. entry.
98*3d8817e4Smiod 
99*3d8817e4Smiod     4)	width: Width of structures and bitfields.
100*3d8817e4Smiod 
101*3d8817e4Smiod     5)	count: Count of ranges for variant part.
102*3d8817e4Smiod 
103*3d8817e4Smiod     6)	rndx: A relative index into the symbol table.  The relative
104*3d8817e4Smiod 	index field has two parts: rfd which is a pointer into the
105*3d8817e4Smiod 	relative file index table or ST_RFDESCAPE which says the next
106*3d8817e4Smiod 	aux. entry is the file number, and index: which is the pointer
107*3d8817e4Smiod 	into the local symbol within a given file table.  This is for
108*3d8817e4Smiod 	things like references to types defined in another file.
109*3d8817e4Smiod 
110*3d8817e4Smiod     7)	Type information: This is like the COFF type bits, except it
111*3d8817e4Smiod 	is 32 bits instead of 16; they still have room to add new
112*3d8817e4Smiod 	basic types; and they can handle more than 6 levels of array,
113*3d8817e4Smiod 	pointer, function, etc.  Each type information field contains
114*3d8817e4Smiod 	the following structure members:
115*3d8817e4Smiod 
116*3d8817e4Smiod 	    a)	fBitfield: a bit that says this is a bitfield, and the
117*3d8817e4Smiod 		size in bits follows as the next aux. entry.
118*3d8817e4Smiod 
119*3d8817e4Smiod 	    b)	continued: a bit that says the next aux. entry is a
120*3d8817e4Smiod 		continuation of the current type information (in case
121*3d8817e4Smiod 		there are more than 6 levels of array/ptr/function).
122*3d8817e4Smiod 
123*3d8817e4Smiod 	    c)	bt: an integer containing the base type before adding
124*3d8817e4Smiod 		array, pointer, function, etc. qualifiers.  The
125*3d8817e4Smiod 		current base types that I have documentation for are:
126*3d8817e4Smiod 
127*3d8817e4Smiod 			btNil		-- undefined
128*3d8817e4Smiod 			btAdr		-- address - integer same size as ptr
129*3d8817e4Smiod 			btChar		-- character
130*3d8817e4Smiod 			btUChar		-- unsigned character
131*3d8817e4Smiod 			btShort		-- short
132*3d8817e4Smiod 			btUShort	-- unsigned short
133*3d8817e4Smiod 			btInt		-- int
134*3d8817e4Smiod 			btUInt		-- unsigned int
135*3d8817e4Smiod 			btLong		-- long
136*3d8817e4Smiod 			btULong		-- unsigned long
137*3d8817e4Smiod 			btFloat		-- float (real)
138*3d8817e4Smiod 			btDouble	-- Double (real)
139*3d8817e4Smiod 			btStruct	-- Structure (Record)
140*3d8817e4Smiod 			btUnion		-- Union (variant)
141*3d8817e4Smiod 			btEnum		-- Enumerated
142*3d8817e4Smiod 			btTypedef	-- defined via a typedef isymRef
143*3d8817e4Smiod 			btRange		-- subrange of int
144*3d8817e4Smiod 			btSet		-- pascal sets
145*3d8817e4Smiod 			btComplex	-- fortran complex
146*3d8817e4Smiod 			btDComplex	-- fortran double complex
147*3d8817e4Smiod 			btIndirect	-- forward or unnamed typedef
148*3d8817e4Smiod 			btFixedDec	-- Fixed Decimal
149*3d8817e4Smiod 			btFloatDec	-- Float Decimal
150*3d8817e4Smiod 			btString	-- Varying Length Character String
151*3d8817e4Smiod 			btBit		-- Aligned Bit String
152*3d8817e4Smiod 			btPicture	-- Picture
153*3d8817e4Smiod 			btVoid		-- Void (MIPS cc revision >= 2.00)
154*3d8817e4Smiod 
155*3d8817e4Smiod 	    d)	tq0 - tq5: type qualifier fields as needed.  The
156*3d8817e4Smiod 		current type qualifier fields I have documentation for
157*3d8817e4Smiod 		are:
158*3d8817e4Smiod 
159*3d8817e4Smiod 			tqNil		-- no more qualifiers
160*3d8817e4Smiod 			tqPtr		-- pointer
161*3d8817e4Smiod 			tqProc		-- procedure
162*3d8817e4Smiod 			tqArray		-- array
163*3d8817e4Smiod 			tqFar		-- 8086 far pointers
164*3d8817e4Smiod 			tqVol		-- volatile
165*3d8817e4Smiod 
166*3d8817e4Smiod    The dense number table is used in the front ends, and disappears by
167*3d8817e4Smiod    the time the .o is created.
168*3d8817e4Smiod 
169*3d8817e4Smiod    With the 1.31 compiler suite, the optimization symbols don't seem
170*3d8817e4Smiod    to be used as far as I can tell.
171*3d8817e4Smiod 
172*3d8817e4Smiod    The linker is the first entity that creates the relative file
173*3d8817e4Smiod    descriptor table, and I believe it is used so that the individual
174*3d8817e4Smiod    file table pointers don't have to be rewritten when the objects are
175*3d8817e4Smiod    merged together into the program file.
176*3d8817e4Smiod 
177*3d8817e4Smiod    Unlike COFF, the basic symbol & string tables are split into
178*3d8817e4Smiod    external and local symbols/strings.  The relocation information
179*3d8817e4Smiod    only goes off of the external symbol table, and the debug
180*3d8817e4Smiod    information only goes off of the internal symbol table.  The
181*3d8817e4Smiod    external symbols can have links to an appropriate file index and
182*3d8817e4Smiod    symbol within the file to give it the appropriate type information.
183*3d8817e4Smiod    Because of this, the external symbols are actually larger than the
184*3d8817e4Smiod    internal symbols (to contain the link information), and contain the
185*3d8817e4Smiod    local symbol structure as a member, though this member is not the
186*3d8817e4Smiod    first member of the external symbol structure (!).  I suspect this
187*3d8817e4Smiod    split is to make strip easier to deal with.
188*3d8817e4Smiod 
189*3d8817e4Smiod    Each file table has offsets for where the line numbers, local
190*3d8817e4Smiod    strings, local symbols, and procedure table starts from within the
191*3d8817e4Smiod    global tables, and the indexs are reset to 0 for each of those
192*3d8817e4Smiod    tables for the file.
193*3d8817e4Smiod 
194*3d8817e4Smiod    The procedure table contains the binary equivalents of the .ent
195*3d8817e4Smiod    (start of the function address), .frame (what register is the
196*3d8817e4Smiod    virtual frame pointer, constant offset from the register to obtain
197*3d8817e4Smiod    the VFP, and what register holds the return address), .mask/.fmask
198*3d8817e4Smiod    (bitmask of saved registers, and where the first register is stored
199*3d8817e4Smiod    relative to the VFP) assembler directives.  It also contains the
200*3d8817e4Smiod    low and high bounds of the line numbers if debugging is turned on.
201*3d8817e4Smiod 
202*3d8817e4Smiod    The line number table is a compressed form of the normal COFF line
203*3d8817e4Smiod    table.  Each line number entry is either 1 or 3 bytes long, and
204*3d8817e4Smiod    contains a signed delta from the previous line, and an unsigned
205*3d8817e4Smiod    count of the number of instructions this statement takes.
206*3d8817e4Smiod 
207*3d8817e4Smiod    The local symbol table contains the following fields:
208*3d8817e4Smiod 
209*3d8817e4Smiod     1)	iss: index to the local string table giving the name of the
210*3d8817e4Smiod 	symbol.
211*3d8817e4Smiod 
212*3d8817e4Smiod     2)	value: value of the symbol (address, register number, etc.).
213*3d8817e4Smiod 
214*3d8817e4Smiod     3)	st: symbol type.  The current symbol types are:
215*3d8817e4Smiod 
216*3d8817e4Smiod 	    stNil	  -- Nuthin' special
217*3d8817e4Smiod 	    stGlobal	  -- external symbol
218*3d8817e4Smiod 	    stStatic	  -- static
219*3d8817e4Smiod 	    stParam	  -- procedure argument
220*3d8817e4Smiod 	    stLocal	  -- local variable
221*3d8817e4Smiod 	    stLabel	  -- label
222*3d8817e4Smiod 	    stProc	  -- External Procedure
223*3d8817e4Smiod 	    stBlock	  -- beginning of block
224*3d8817e4Smiod 	    stEnd	  -- end (of anything)
225*3d8817e4Smiod 	    stMember	  -- member (of anything)
226*3d8817e4Smiod 	    stTypedef	  -- type definition
227*3d8817e4Smiod 	    stFile	  -- file name
228*3d8817e4Smiod 	    stRegReloc	  -- register relocation
229*3d8817e4Smiod 	    stForward	  -- forwarding address
230*3d8817e4Smiod 	    stStaticProc  -- Static procedure
231*3d8817e4Smiod 	    stConstant	  -- const
232*3d8817e4Smiod 
233*3d8817e4Smiod     4)	sc: storage class.  The current storage classes are:
234*3d8817e4Smiod 
235*3d8817e4Smiod 	    scText	  -- text symbol
236*3d8817e4Smiod 	    scData	  -- initialized data symbol
237*3d8817e4Smiod 	    scBss	  -- un-initialized data symbol
238*3d8817e4Smiod 	    scRegister	  -- value of symbol is register number
239*3d8817e4Smiod 	    scAbs	  -- value of symbol is absolute
240*3d8817e4Smiod 	    scUndefined   -- who knows?
241*3d8817e4Smiod 	    scCdbLocal	  -- variable's value is IN se->va.??
242*3d8817e4Smiod 	    scBits	  -- this is a bit field
243*3d8817e4Smiod 	    scCdbSystem	  -- value is IN debugger's address space
244*3d8817e4Smiod 	    scRegImage	  -- register value saved on stack
245*3d8817e4Smiod 	    scInfo	  -- symbol contains debugger information
246*3d8817e4Smiod 	    scUserStruct  -- addr in struct user for current process
247*3d8817e4Smiod 	    scSData	  -- load time only small data
248*3d8817e4Smiod 	    scSBss	  -- load time only small common
249*3d8817e4Smiod 	    scRData	  -- load time only read only data
250*3d8817e4Smiod 	    scVar	  -- Var parameter (fortranpascal)
251*3d8817e4Smiod 	    scCommon	  -- common variable
252*3d8817e4Smiod 	    scSCommon	  -- small common
253*3d8817e4Smiod 	    scVarRegister -- Var parameter in a register
254*3d8817e4Smiod 	    scVariant	  -- Variant record
255*3d8817e4Smiod 	    scSUndefined  -- small undefined(external) data
256*3d8817e4Smiod 	    scInit	  -- .init section symbol
257*3d8817e4Smiod 
258*3d8817e4Smiod     5)	index: pointer to a local symbol or aux. entry.
259*3d8817e4Smiod 
260*3d8817e4Smiod    For the following program:
261*3d8817e4Smiod 
262*3d8817e4Smiod 	#include <stdio.h>
263*3d8817e4Smiod 
264*3d8817e4Smiod 	main(){
265*3d8817e4Smiod 		printf("Hello World!\n");
266*3d8817e4Smiod 		return 0;
267*3d8817e4Smiod 	}
268*3d8817e4Smiod 
269*3d8817e4Smiod    Mips-tdump produces the following information:
270*3d8817e4Smiod 
271*3d8817e4Smiod    Global file header:
272*3d8817e4Smiod        magic number             0x162
273*3d8817e4Smiod        # sections               2
274*3d8817e4Smiod        timestamp                645311799, Wed Jun 13 17:16:39 1990
275*3d8817e4Smiod        symbolic header offset   284
276*3d8817e4Smiod        symbolic header size     96
277*3d8817e4Smiod        optional header          56
278*3d8817e4Smiod        flags                    0x0
279*3d8817e4Smiod 
280*3d8817e4Smiod    Symbolic header, magic number = 0x7009, vstamp = 1.31:
281*3d8817e4Smiod 
282*3d8817e4Smiod        Info                      Offset      Number       Bytes
283*3d8817e4Smiod        ====                      ======      ======      =====
284*3d8817e4Smiod 
285*3d8817e4Smiod        Line numbers                 380           4           4 [13]
286*3d8817e4Smiod        Dense numbers                  0           0           0
287*3d8817e4Smiod        Procedures Tables            384           1          52
288*3d8817e4Smiod        Local Symbols                436          16         192
289*3d8817e4Smiod        Optimization Symbols           0           0           0
290*3d8817e4Smiod        Auxiliary Symbols            628          39         156
291*3d8817e4Smiod        Local Strings                784          80          80
292*3d8817e4Smiod        External Strings             864         144         144
293*3d8817e4Smiod        File Tables                 1008           2         144
294*3d8817e4Smiod        Relative Files                 0           0           0
295*3d8817e4Smiod        External Symbols            1152          20         320
296*3d8817e4Smiod 
297*3d8817e4Smiod    File #0, "hello2.c"
298*3d8817e4Smiod 
299*3d8817e4Smiod        Name index  = 1          Readin      = No
300*3d8817e4Smiod        Merge       = No         Endian      = LITTLE
301*3d8817e4Smiod        Debug level = G2         Language    = C
302*3d8817e4Smiod        Adr         = 0x00000000
303*3d8817e4Smiod 
304*3d8817e4Smiod        Info                       Start      Number        Size      Offset
305*3d8817e4Smiod        ====                       =====      ======        ====      ======
306*3d8817e4Smiod        Local strings                  0          15          15         784
307*3d8817e4Smiod        Local symbols                  0           6          72         436
308*3d8817e4Smiod        Line numbers                   0          13          13         380
309*3d8817e4Smiod        Optimization symbols           0           0           0           0
310*3d8817e4Smiod        Procedures                     0           1          52         384
311*3d8817e4Smiod        Auxiliary symbols              0          14          56         628
312*3d8817e4Smiod        Relative Files                 0           0           0           0
313*3d8817e4Smiod 
314*3d8817e4Smiod     There are 6 local symbols, starting at 436
315*3d8817e4Smiod 
316*3d8817e4Smiod 	Symbol# 0: "hello2.c"
317*3d8817e4Smiod 	    End+1 symbol  = 6
318*3d8817e4Smiod 	    String index  = 1
319*3d8817e4Smiod 	    Storage class = Text        Index  = 6
320*3d8817e4Smiod 	    Symbol type   = File        Value  = 0
321*3d8817e4Smiod 
322*3d8817e4Smiod 	Symbol# 1: "main"
323*3d8817e4Smiod 	    End+1 symbol  = 5
324*3d8817e4Smiod 	    Type          = int
325*3d8817e4Smiod 	    String index  = 10
326*3d8817e4Smiod 	    Storage class = Text        Index  = 12
327*3d8817e4Smiod 	    Symbol type   = Proc        Value  = 0
328*3d8817e4Smiod 
329*3d8817e4Smiod 	Symbol# 2: ""
330*3d8817e4Smiod 	    End+1 symbol  = 4
331*3d8817e4Smiod 	    String index  = 0
332*3d8817e4Smiod 	    Storage class = Text        Index  = 4
333*3d8817e4Smiod 	    Symbol type   = Block       Value  = 8
334*3d8817e4Smiod 
335*3d8817e4Smiod 	Symbol# 3: ""
336*3d8817e4Smiod 	    First symbol  = 2
337*3d8817e4Smiod 	    String index  = 0
338*3d8817e4Smiod 	    Storage class = Text        Index  = 2
339*3d8817e4Smiod 	    Symbol type   = End         Value  = 28
340*3d8817e4Smiod 
341*3d8817e4Smiod 	Symbol# 4: "main"
342*3d8817e4Smiod 	    First symbol  = 1
343*3d8817e4Smiod 	    String index  = 10
344*3d8817e4Smiod 	    Storage class = Text        Index  = 1
345*3d8817e4Smiod 	    Symbol type   = End         Value  = 52
346*3d8817e4Smiod 
347*3d8817e4Smiod 	Symbol# 5: "hello2.c"
348*3d8817e4Smiod 	    First symbol  = 0
349*3d8817e4Smiod 	    String index  = 1
350*3d8817e4Smiod 	    Storage class = Text        Index  = 0
351*3d8817e4Smiod 	    Symbol type   = End         Value  = 0
352*3d8817e4Smiod 
353*3d8817e4Smiod     There are 14 auxiliary table entries, starting at 628.
354*3d8817e4Smiod 
355*3d8817e4Smiod 	* #0               0, [   0/      0], [ 0 0:0 0:0:0:0:0:0]
356*3d8817e4Smiod 	* #1              24, [  24/      0], [ 6 0:0 0:0:0:0:0:0]
357*3d8817e4Smiod 	* #2               8, [   8/      0], [ 2 0:0 0:0:0:0:0:0]
358*3d8817e4Smiod 	* #3              16, [  16/      0], [ 4 0:0 0:0:0:0:0:0]
359*3d8817e4Smiod 	* #4              24, [  24/      0], [ 6 0:0 0:0:0:0:0:0]
360*3d8817e4Smiod 	* #5              32, [  32/      0], [ 8 0:0 0:0:0:0:0:0]
361*3d8817e4Smiod 	* #6              40, [  40/      0], [10 0:0 0:0:0:0:0:0]
362*3d8817e4Smiod 	* #7              44, [  44/      0], [11 0:0 0:0:0:0:0:0]
363*3d8817e4Smiod 	* #8              12, [  12/      0], [ 3 0:0 0:0:0:0:0:0]
364*3d8817e4Smiod 	* #9              20, [  20/      0], [ 5 0:0 0:0:0:0:0:0]
365*3d8817e4Smiod 	* #10             28, [  28/      0], [ 7 0:0 0:0:0:0:0:0]
366*3d8817e4Smiod 	* #11             36, [  36/      0], [ 9 0:0 0:0:0:0:0:0]
367*3d8817e4Smiod 	  #12              5, [   5/      0], [ 1 1:0 0:0:0:0:0:0]
368*3d8817e4Smiod 	  #13             24, [  24/      0], [ 6 0:0 0:0:0:0:0:0]
369*3d8817e4Smiod 
370*3d8817e4Smiod     There are 1 procedure descriptor entries, starting at 0.
371*3d8817e4Smiod 
372*3d8817e4Smiod 	Procedure descriptor 0:
373*3d8817e4Smiod 	    Name index   = 10          Name          = "main"
374*3d8817e4Smiod 	    .mask 0x80000000,-4        .fmask 0x00000000,0
375*3d8817e4Smiod 	    .frame $29,24,$31
376*3d8817e4Smiod 	    Opt. start   = -1          Symbols start = 1
377*3d8817e4Smiod 	    First line # = 3           Last line #   = 6
378*3d8817e4Smiod 	    Line Offset  = 0           Address       = 0x00000000
379*3d8817e4Smiod 
380*3d8817e4Smiod 	There are 4 bytes holding line numbers, starting at 380.
381*3d8817e4Smiod 	    Line           3,   delta     0,   count  2
382*3d8817e4Smiod 	    Line           4,   delta     1,   count  3
383*3d8817e4Smiod 	    Line           5,   delta     1,   count  2
384*3d8817e4Smiod 	    Line           6,   delta     1,   count  6
385*3d8817e4Smiod 
386*3d8817e4Smiod    File #1, "/usr/include/stdio.h"
387*3d8817e4Smiod 
388*3d8817e4Smiod     Name index  = 1          Readin      = No
389*3d8817e4Smiod     Merge       = Yes        Endian      = LITTLE
390*3d8817e4Smiod     Debug level = G2         Language    = C
391*3d8817e4Smiod     Adr         = 0x00000000
392*3d8817e4Smiod 
393*3d8817e4Smiod     Info                       Start      Number        Size      Offset
394*3d8817e4Smiod     ====                       =====      ======        ====      ======
395*3d8817e4Smiod     Local strings                 15          65          65         799
396*3d8817e4Smiod     Local symbols                  6          10         120         508
397*3d8817e4Smiod     Line numbers                   0           0           0         380
398*3d8817e4Smiod     Optimization symbols           0           0           0           0
399*3d8817e4Smiod     Procedures                     1           0           0         436
400*3d8817e4Smiod     Auxiliary symbols             14          25         100         684
401*3d8817e4Smiod     Relative Files                 0           0           0           0
402*3d8817e4Smiod 
403*3d8817e4Smiod     There are 10 local symbols, starting at 442
404*3d8817e4Smiod 
405*3d8817e4Smiod 	Symbol# 0: "/usr/include/stdio.h"
406*3d8817e4Smiod 	    End+1 symbol  = 10
407*3d8817e4Smiod 	    String index  = 1
408*3d8817e4Smiod 	    Storage class = Text        Index  = 10
409*3d8817e4Smiod 	    Symbol type   = File        Value  = 0
410*3d8817e4Smiod 
411*3d8817e4Smiod 	Symbol# 1: "_iobuf"
412*3d8817e4Smiod 	    End+1 symbol  = 9
413*3d8817e4Smiod 	    String index  = 22
414*3d8817e4Smiod 	    Storage class = Info        Index  = 9
415*3d8817e4Smiod 	    Symbol type   = Block       Value  = 20
416*3d8817e4Smiod 
417*3d8817e4Smiod 	Symbol# 2: "_cnt"
418*3d8817e4Smiod 	    Type          = int
419*3d8817e4Smiod 	    String index  = 29
420*3d8817e4Smiod 	    Storage class = Info        Index  = 4
421*3d8817e4Smiod 	    Symbol type   = Member      Value  = 0
422*3d8817e4Smiod 
423*3d8817e4Smiod 	Symbol# 3: "_ptr"
424*3d8817e4Smiod 	    Type          = ptr to char
425*3d8817e4Smiod 	    String index  = 34
426*3d8817e4Smiod 	    Storage class = Info        Index  = 15
427*3d8817e4Smiod 	    Symbol type   = Member      Value  = 32
428*3d8817e4Smiod 
429*3d8817e4Smiod 	Symbol# 4: "_base"
430*3d8817e4Smiod 	    Type          = ptr to char
431*3d8817e4Smiod 	    String index  = 39
432*3d8817e4Smiod 	    Storage class = Info        Index  = 16
433*3d8817e4Smiod 	    Symbol type   = Member      Value  = 64
434*3d8817e4Smiod 
435*3d8817e4Smiod 	Symbol# 5: "_bufsiz"
436*3d8817e4Smiod 	    Type          = int
437*3d8817e4Smiod 	    String index  = 45
438*3d8817e4Smiod 	    Storage class = Info        Index  = 4
439*3d8817e4Smiod 	    Symbol type   = Member      Value  = 96
440*3d8817e4Smiod 
441*3d8817e4Smiod 	Symbol# 6: "_flag"
442*3d8817e4Smiod 	    Type          = short
443*3d8817e4Smiod 	    String index  = 53
444*3d8817e4Smiod 	    Storage class = Info        Index  = 3
445*3d8817e4Smiod 	    Symbol type   = Member      Value  = 128
446*3d8817e4Smiod 
447*3d8817e4Smiod 	Symbol# 7: "_file"
448*3d8817e4Smiod 	    Type          = char
449*3d8817e4Smiod 	    String index  = 59
450*3d8817e4Smiod 	    Storage class = Info        Index  = 2
451*3d8817e4Smiod 	    Symbol type   = Member      Value  = 144
452*3d8817e4Smiod 
453*3d8817e4Smiod 	Symbol# 8: ""
454*3d8817e4Smiod 	    First symbol  = 1
455*3d8817e4Smiod 	    String index  = 0
456*3d8817e4Smiod 	    Storage class = Info        Index  = 1
457*3d8817e4Smiod 	    Symbol type   = End         Value  = 0
458*3d8817e4Smiod 
459*3d8817e4Smiod 	Symbol# 9: "/usr/include/stdio.h"
460*3d8817e4Smiod 	    First symbol  = 0
461*3d8817e4Smiod 	    String index  = 1
462*3d8817e4Smiod 	    Storage class = Text        Index  = 0
463*3d8817e4Smiod 	    Symbol type   = End         Value  = 0
464*3d8817e4Smiod 
465*3d8817e4Smiod     There are 25 auxiliary table entries, starting at 642.
466*3d8817e4Smiod 
467*3d8817e4Smiod 	* #14             -1, [4095/1048575], [63 1:1 f:f:f:f:f:f]
468*3d8817e4Smiod 	  #15          65544, [   8/     16], [ 2 0:0 1:0:0:0:0:0]
469*3d8817e4Smiod 	  #16          65544, [   8/     16], [ 2 0:0 1:0:0:0:0:0]
470*3d8817e4Smiod 	* #17         196656, [  48/     48], [12 0:0 3:0:0:0:0:0]
471*3d8817e4Smiod 	* #18           8191, [4095/      1], [63 1:1 0:0:0:0:f:1]
472*3d8817e4Smiod 	* #19              1, [   1/      0], [ 0 1:0 0:0:0:0:0:0]
473*3d8817e4Smiod 	* #20          20479, [4095/      4], [63 1:1 0:0:0:0:f:4]
474*3d8817e4Smiod 	* #21              1, [   1/      0], [ 0 1:0 0:0:0:0:0:0]
475*3d8817e4Smiod 	* #22              0, [   0/      0], [ 0 0:0 0:0:0:0:0:0]
476*3d8817e4Smiod 	* #23              2, [   2/      0], [ 0 0:1 0:0:0:0:0:0]
477*3d8817e4Smiod 	* #24            160, [ 160/      0], [40 0:0 0:0:0:0:0:0]
478*3d8817e4Smiod 	* #25              0, [   0/      0], [ 0 0:0 0:0:0:0:0:0]
479*3d8817e4Smiod 	* #26              0, [   0/      0], [ 0 0:0 0:0:0:0:0:0]
480*3d8817e4Smiod 	* #27              0, [   0/      0], [ 0 0:0 0:0:0:0:0:0]
481*3d8817e4Smiod 	* #28              0, [   0/      0], [ 0 0:0 0:0:0:0:0:0]
482*3d8817e4Smiod 	* #29              0, [   0/      0], [ 0 0:0 0:0:0:0:0:0]
483*3d8817e4Smiod 	* #30              0, [   0/      0], [ 0 0:0 0:0:0:0:0:0]
484*3d8817e4Smiod 	* #31              0, [   0/      0], [ 0 0:0 0:0:0:0:0:0]
485*3d8817e4Smiod 	* #32              0, [   0/      0], [ 0 0:0 0:0:0:0:0:0]
486*3d8817e4Smiod 	* #33              0, [   0/      0], [ 0 0:0 0:0:0:0:0:0]
487*3d8817e4Smiod 	* #34              0, [   0/      0], [ 0 0:0 0:0:0:0:0:0]
488*3d8817e4Smiod 	* #35              0, [   0/      0], [ 0 0:0 0:0:0:0:0:0]
489*3d8817e4Smiod 	* #36              0, [   0/      0], [ 0 0:0 0:0:0:0:0:0]
490*3d8817e4Smiod 	* #37              0, [   0/      0], [ 0 0:0 0:0:0:0:0:0]
491*3d8817e4Smiod 	* #38              0, [   0/      0], [ 0 0:0 0:0:0:0:0:0]
492*3d8817e4Smiod 
493*3d8817e4Smiod     There are 0 procedure descriptor entries, starting at 1.
494*3d8817e4Smiod 
495*3d8817e4Smiod    There are 20 external symbols, starting at 1152
496*3d8817e4Smiod 
497*3d8817e4Smiod 	Symbol# 0: "_iob"
498*3d8817e4Smiod 	    Type          = array [3 {160}] of struct _iobuf { ifd = 1, index = 1 }
499*3d8817e4Smiod 	    String index  = 0           Ifd    = 1
500*3d8817e4Smiod 	    Storage class = Nil         Index  = 17
501*3d8817e4Smiod 	    Symbol type   = Global      Value  = 60
502*3d8817e4Smiod 
503*3d8817e4Smiod 	Symbol# 1: "fopen"
504*3d8817e4Smiod 	    String index  = 5           Ifd    = 1
505*3d8817e4Smiod 	    Storage class = Nil         Index  = 1048575
506*3d8817e4Smiod 	    Symbol type   = Proc        Value  = 0
507*3d8817e4Smiod 
508*3d8817e4Smiod 	Symbol# 2: "fdopen"
509*3d8817e4Smiod 	    String index  = 11          Ifd    = 1
510*3d8817e4Smiod 	    Storage class = Nil         Index  = 1048575
511*3d8817e4Smiod 	    Symbol type   = Proc        Value  = 0
512*3d8817e4Smiod 
513*3d8817e4Smiod 	Symbol# 3: "freopen"
514*3d8817e4Smiod 	    String index  = 18          Ifd    = 1
515*3d8817e4Smiod 	    Storage class = Nil         Index  = 1048575
516*3d8817e4Smiod 	    Symbol type   = Proc        Value  = 0
517*3d8817e4Smiod 
518*3d8817e4Smiod 	Symbol# 4: "popen"
519*3d8817e4Smiod 	    String index  = 26          Ifd    = 1
520*3d8817e4Smiod 	    Storage class = Nil         Index  = 1048575
521*3d8817e4Smiod 	    Symbol type   = Proc        Value  = 0
522*3d8817e4Smiod 
523*3d8817e4Smiod 	Symbol# 5: "tmpfile"
524*3d8817e4Smiod 	    String index  = 32          Ifd    = 1
525*3d8817e4Smiod 	    Storage class = Nil         Index  = 1048575
526*3d8817e4Smiod 	    Symbol type   = Proc        Value  = 0
527*3d8817e4Smiod 
528*3d8817e4Smiod 	Symbol# 6: "ftell"
529*3d8817e4Smiod 	    String index  = 40          Ifd    = 1
530*3d8817e4Smiod 	    Storage class = Nil         Index  = 1048575
531*3d8817e4Smiod 	    Symbol type   = Proc        Value  = 0
532*3d8817e4Smiod 
533*3d8817e4Smiod 	Symbol# 7: "rewind"
534*3d8817e4Smiod 	    String index  = 46          Ifd    = 1
535*3d8817e4Smiod 	    Storage class = Nil         Index  = 1048575
536*3d8817e4Smiod 	    Symbol type   = Proc        Value  = 0
537*3d8817e4Smiod 
538*3d8817e4Smiod 	Symbol# 8: "setbuf"
539*3d8817e4Smiod 	    String index  = 53          Ifd    = 1
540*3d8817e4Smiod 	    Storage class = Nil         Index  = 1048575
541*3d8817e4Smiod 	    Symbol type   = Proc        Value  = 0
542*3d8817e4Smiod 
543*3d8817e4Smiod 	Symbol# 9: "setbuffer"
544*3d8817e4Smiod 	    String index  = 60          Ifd    = 1
545*3d8817e4Smiod 	    Storage class = Nil         Index  = 1048575
546*3d8817e4Smiod 	    Symbol type   = Proc        Value  = 0
547*3d8817e4Smiod 
548*3d8817e4Smiod 	Symbol# 10: "setlinebuf"
549*3d8817e4Smiod 	    String index  = 70          Ifd    = 1
550*3d8817e4Smiod 	    Storage class = Nil         Index  = 1048575
551*3d8817e4Smiod 	    Symbol type   = Proc        Value  = 0
552*3d8817e4Smiod 
553*3d8817e4Smiod 	Symbol# 11: "fgets"
554*3d8817e4Smiod 	    String index  = 81          Ifd    = 1
555*3d8817e4Smiod 	    Storage class = Nil         Index  = 1048575
556*3d8817e4Smiod 	    Symbol type   = Proc        Value  = 0
557*3d8817e4Smiod 
558*3d8817e4Smiod 	Symbol# 12: "gets"
559*3d8817e4Smiod 	    String index  = 87          Ifd    = 1
560*3d8817e4Smiod 	    Storage class = Nil         Index  = 1048575
561*3d8817e4Smiod 	    Symbol type   = Proc        Value  = 0
562*3d8817e4Smiod 
563*3d8817e4Smiod 	Symbol# 13: "ctermid"
564*3d8817e4Smiod 	    String index  = 92          Ifd    = 1
565*3d8817e4Smiod 	    Storage class = Nil         Index  = 1048575
566*3d8817e4Smiod 	    Symbol type   = Proc        Value  = 0
567*3d8817e4Smiod 
568*3d8817e4Smiod 	Symbol# 14: "cuserid"
569*3d8817e4Smiod 	    String index  = 100         Ifd    = 1
570*3d8817e4Smiod 	    Storage class = Nil         Index  = 1048575
571*3d8817e4Smiod 	    Symbol type   = Proc        Value  = 0
572*3d8817e4Smiod 
573*3d8817e4Smiod 	Symbol# 15: "tempnam"
574*3d8817e4Smiod 	    String index  = 108         Ifd    = 1
575*3d8817e4Smiod 	    Storage class = Nil         Index  = 1048575
576*3d8817e4Smiod 	    Symbol type   = Proc        Value  = 0
577*3d8817e4Smiod 
578*3d8817e4Smiod 	Symbol# 16: "tmpnam"
579*3d8817e4Smiod 	    String index  = 116         Ifd    = 1
580*3d8817e4Smiod 	    Storage class = Nil         Index  = 1048575
581*3d8817e4Smiod 	    Symbol type   = Proc        Value  = 0
582*3d8817e4Smiod 
583*3d8817e4Smiod 	Symbol# 17: "sprintf"
584*3d8817e4Smiod 	    String index  = 123         Ifd    = 1
585*3d8817e4Smiod 	    Storage class = Nil         Index  = 1048575
586*3d8817e4Smiod 	    Symbol type   = Proc        Value  = 0
587*3d8817e4Smiod 
588*3d8817e4Smiod 	Symbol# 18: "main"
589*3d8817e4Smiod 	    Type          = int
590*3d8817e4Smiod 	    String index  = 131         Ifd    = 0
591*3d8817e4Smiod 	    Storage class = Text        Index  = 1
592*3d8817e4Smiod 	    Symbol type   = Proc        Value  = 0
593*3d8817e4Smiod 
594*3d8817e4Smiod 	Symbol# 19: "printf"
595*3d8817e4Smiod 	    String index  = 136         Ifd    = 0
596*3d8817e4Smiod 	    Storage class = Undefined   Index  = 1048575
597*3d8817e4Smiod 	    Symbol type   = Proc        Value  = 0
598*3d8817e4Smiod 
599*3d8817e4Smiod    The following auxiliary table entries were unused:
600*3d8817e4Smiod 
601*3d8817e4Smiod     #0               0  0x00000000  void
602*3d8817e4Smiod     #2               8  0x00000008  char
603*3d8817e4Smiod     #3              16  0x00000010  short
604*3d8817e4Smiod     #4              24  0x00000018  int
605*3d8817e4Smiod     #5              32  0x00000020  long
606*3d8817e4Smiod     #6              40  0x00000028  float
607*3d8817e4Smiod     #7              44  0x0000002c  double
608*3d8817e4Smiod     #8              12  0x0000000c  unsigned char
609*3d8817e4Smiod     #9              20  0x00000014  unsigned short
610*3d8817e4Smiod     #10             28  0x0000001c  unsigned int
611*3d8817e4Smiod     #11             36  0x00000024  unsigned long
612*3d8817e4Smiod     #14              0  0x00000000  void
613*3d8817e4Smiod     #15             24  0x00000018  int
614*3d8817e4Smiod     #19             32  0x00000020  long
615*3d8817e4Smiod     #20             40  0x00000028  float
616*3d8817e4Smiod     #21             44  0x0000002c  double
617*3d8817e4Smiod     #22             12  0x0000000c  unsigned char
618*3d8817e4Smiod     #23             20  0x00000014  unsigned short
619*3d8817e4Smiod     #24             28  0x0000001c  unsigned int
620*3d8817e4Smiod     #25             36  0x00000024  unsigned long
621*3d8817e4Smiod     #26             48  0x00000030  struct no name { ifd = -1, index = 1048575 }
622*3d8817e4Smiod */
623*3d8817e4Smiod 
624*3d8817e4Smiod /* Redefinition of of storage classes as an enumeration for better
625*3d8817e4Smiod    debugging.  */
626*3d8817e4Smiod 
627*3d8817e4Smiod typedef enum sc {
628*3d8817e4Smiod   sc_Nil	 = scNil,	  /* no storage class */
629*3d8817e4Smiod   sc_Text	 = scText,	  /* text symbol */
630*3d8817e4Smiod   sc_Data	 = scData,	  /* initialized data symbol */
631*3d8817e4Smiod   sc_Bss	 = scBss,	  /* un-initialized data symbol */
632*3d8817e4Smiod   sc_Register	 = scRegister,	  /* value of symbol is register number */
633*3d8817e4Smiod   sc_Abs	 = scAbs,	  /* value of symbol is absolute */
634*3d8817e4Smiod   sc_Undefined	 = scUndefined,	  /* who knows? */
635*3d8817e4Smiod   sc_CdbLocal	 = scCdbLocal,	  /* variable's value is IN se->va.?? */
636*3d8817e4Smiod   sc_Bits	 = scBits,	  /* this is a bit field */
637*3d8817e4Smiod   sc_CdbSystem	 = scCdbSystem,	  /* value is IN CDB's address space */
638*3d8817e4Smiod   sc_RegImage	 = scRegImage,	  /* register value saved on stack */
639*3d8817e4Smiod   sc_Info	 = scInfo,	  /* symbol contains debugger information */
640*3d8817e4Smiod   sc_UserStruct	 = scUserStruct,  /* addr in struct user for current process */
641*3d8817e4Smiod   sc_SData	 = scSData,	  /* load time only small data */
642*3d8817e4Smiod   sc_SBss	 = scSBss,	  /* load time only small common */
643*3d8817e4Smiod   sc_RData	 = scRData,	  /* load time only read only data */
644*3d8817e4Smiod   sc_Var	 = scVar,	  /* Var parameter (fortran,pascal) */
645*3d8817e4Smiod   sc_Common	 = scCommon,	  /* common variable */
646*3d8817e4Smiod   sc_SCommon	 = scSCommon,	  /* small common */
647*3d8817e4Smiod   sc_VarRegister = scVarRegister, /* Var parameter in a register */
648*3d8817e4Smiod   sc_Variant	 = scVariant,	  /* Variant record */
649*3d8817e4Smiod   sc_SUndefined	 = scSUndefined,  /* small undefined(external) data */
650*3d8817e4Smiod   sc_Init	 = scInit,	  /* .init section symbol */
651*3d8817e4Smiod   sc_Max	 = scMax	  /* Max storage class+1 */
652*3d8817e4Smiod } sc_t;
653*3d8817e4Smiod 
654*3d8817e4Smiod /* Redefinition of symbol type.  */
655*3d8817e4Smiod 
656*3d8817e4Smiod typedef enum st {
657*3d8817e4Smiod   st_Nil	= stNil,	/* Nuthin' special */
658*3d8817e4Smiod   st_Global	= stGlobal,	/* external symbol */
659*3d8817e4Smiod   st_Static	= stStatic,	/* static */
660*3d8817e4Smiod   st_Param	= stParam,	/* procedure argument */
661*3d8817e4Smiod   st_Local	= stLocal,	/* local variable */
662*3d8817e4Smiod   st_Label	= stLabel,	/* label */
663*3d8817e4Smiod   st_Proc	= stProc,	/*     "      "	 Procedure */
664*3d8817e4Smiod   st_Block	= stBlock,	/* beginning of block */
665*3d8817e4Smiod   st_End	= stEnd,	/* end (of anything) */
666*3d8817e4Smiod   st_Member	= stMember,	/* member (of anything	- struct/union/enum */
667*3d8817e4Smiod   st_Typedef	= stTypedef,	/* type definition */
668*3d8817e4Smiod   st_File	= stFile,	/* file name */
669*3d8817e4Smiod   st_RegReloc	= stRegReloc,	/* register relocation */
670*3d8817e4Smiod   st_Forward	= stForward,	/* forwarding address */
671*3d8817e4Smiod   st_StaticProc	= stStaticProc,	/* load time only static procs */
672*3d8817e4Smiod   st_Constant	= stConstant,	/* const */
673*3d8817e4Smiod   st_Str	= stStr,	/* string */
674*3d8817e4Smiod   st_Number	= stNumber,	/* pure number (ie. 4 NOR 2+2) */
675*3d8817e4Smiod   st_Expr	= stExpr,	/* 2+2 vs. 4 */
676*3d8817e4Smiod   st_Type	= stType,	/* post-coercion SER */
677*3d8817e4Smiod   st_Max	= stMax		/* max type+1 */
678*3d8817e4Smiod } st_t;
679*3d8817e4Smiod 
680*3d8817e4Smiod /* Redefinition of type qualifiers.  */
681*3d8817e4Smiod 
682*3d8817e4Smiod typedef enum tq {
683*3d8817e4Smiod   tq_Nil	= tqNil,	/* bt is what you see */
684*3d8817e4Smiod   tq_Ptr	= tqPtr,	/* pointer */
685*3d8817e4Smiod   tq_Proc	= tqProc,	/* procedure */
686*3d8817e4Smiod   tq_Array	= tqArray,	/* duh */
687*3d8817e4Smiod   tq_Far	= tqFar,	/* longer addressing - 8086/8 land */
688*3d8817e4Smiod   tq_Vol	= tqVol,	/* volatile */
689*3d8817e4Smiod   tq_Max	= tqMax		/* Max type qualifier+1 */
690*3d8817e4Smiod } tq_t;
691*3d8817e4Smiod 
692*3d8817e4Smiod /* Redefinition of basic types.  */
693*3d8817e4Smiod 
694*3d8817e4Smiod typedef enum bt {
695*3d8817e4Smiod   bt_Nil	= btNil,	/* undefined */
696*3d8817e4Smiod   bt_Adr	= btAdr,	/* address - integer same size as pointer */
697*3d8817e4Smiod   bt_Char	= btChar,	/* character */
698*3d8817e4Smiod   bt_UChar	= btUChar,	/* unsigned character */
699*3d8817e4Smiod   bt_Short	= btShort,	/* short */
700*3d8817e4Smiod   bt_UShort	= btUShort,	/* unsigned short */
701*3d8817e4Smiod   bt_Int	= btInt,	/* int */
702*3d8817e4Smiod   bt_UInt	= btUInt,	/* unsigned int */
703*3d8817e4Smiod   bt_Long	= btLong,	/* long */
704*3d8817e4Smiod   bt_ULong	= btULong,	/* unsigned long */
705*3d8817e4Smiod   bt_Float	= btFloat,	/* float (real) */
706*3d8817e4Smiod   bt_Double	= btDouble,	/* Double (real) */
707*3d8817e4Smiod   bt_Struct	= btStruct,	/* Structure (Record) */
708*3d8817e4Smiod   bt_Union	= btUnion,	/* Union (variant) */
709*3d8817e4Smiod   bt_Enum	= btEnum,	/* Enumerated */
710*3d8817e4Smiod   bt_Typedef	= btTypedef,	/* defined via a typedef, isymRef points */
711*3d8817e4Smiod   bt_Range	= btRange,	/* subrange of int */
712*3d8817e4Smiod   bt_Set	= btSet,	/* pascal sets */
713*3d8817e4Smiod   bt_Complex	= btComplex,	/* fortran complex */
714*3d8817e4Smiod   bt_DComplex	= btDComplex,	/* fortran double complex */
715*3d8817e4Smiod   bt_Indirect	= btIndirect,	/* forward or unnamed typedef */
716*3d8817e4Smiod   bt_FixedDec	= btFixedDec,	/* Fixed Decimal */
717*3d8817e4Smiod   bt_FloatDec	= btFloatDec,	/* Float Decimal */
718*3d8817e4Smiod   bt_String	= btString,	/* Varying Length Character String */
719*3d8817e4Smiod   bt_Bit	= btBit,	/* Aligned Bit String */
720*3d8817e4Smiod   bt_Picture	= btPicture,	/* Picture */
721*3d8817e4Smiod   bt_Void	= btVoid,	/* Void */
722*3d8817e4Smiod   bt_Max	= btMax		/* Max basic type+1 */
723*3d8817e4Smiod } bt_t;
724*3d8817e4Smiod 
725*3d8817e4Smiod #define N_TQ itqMax
726*3d8817e4Smiod 
727*3d8817e4Smiod /* States for whether to hash type or not.  */
728*3d8817e4Smiod typedef enum hash_state {
729*3d8817e4Smiod   hash_no	= 0,		/* Don't hash type */
730*3d8817e4Smiod   hash_yes	= 1,		/* OK to hash type, or use previous hash */
731*3d8817e4Smiod   hash_record	= 2		/* OK to record hash, but don't use prev.  */
732*3d8817e4Smiod } hash_state_t;
733*3d8817e4Smiod 
734*3d8817e4Smiod /* Types of different sized allocation requests.  */
735*3d8817e4Smiod enum alloc_type {
736*3d8817e4Smiod   alloc_type_none,		/* dummy value */
737*3d8817e4Smiod   alloc_type_scope,		/* nested scopes linked list */
738*3d8817e4Smiod   alloc_type_vlinks,		/* glue linking pages in varray */
739*3d8817e4Smiod   alloc_type_shash,		/* string hash element */
740*3d8817e4Smiod   alloc_type_thash,		/* type hash element */
741*3d8817e4Smiod   alloc_type_tag,		/* struct/union/tag element */
742*3d8817e4Smiod   alloc_type_forward,		/* element to hold unknown tag */
743*3d8817e4Smiod   alloc_type_thead,		/* head of type hash list */
744*3d8817e4Smiod   alloc_type_varray,		/* general varray allocation */
745*3d8817e4Smiod   alloc_type_lineno,		/* line number list */
746*3d8817e4Smiod   alloc_type_last		/* last+1 element for array bounds */
747*3d8817e4Smiod };
748*3d8817e4Smiod 
749*3d8817e4Smiod /* Types of auxiliary type information.  */
750*3d8817e4Smiod enum aux_type {
751*3d8817e4Smiod   aux_tir,			/* TIR type information */
752*3d8817e4Smiod   aux_rndx,			/* relative index into symbol table */
753*3d8817e4Smiod   aux_dnLow,			/* low dimension */
754*3d8817e4Smiod   aux_dnHigh,			/* high dimension */
755*3d8817e4Smiod   aux_isym,			/* symbol table index (end of proc) */
756*3d8817e4Smiod   aux_iss,			/* index into string space (not used) */
757*3d8817e4Smiod   aux_width,			/* width for non-default sized struc fields */
758*3d8817e4Smiod   aux_count			/* count of ranges for variant arm */
759*3d8817e4Smiod };
760*3d8817e4Smiod 
761*3d8817e4Smiod /* Structures to provide n-number of virtual arrays, each of which can
762*3d8817e4Smiod    grow linearly, and which are written in the object file as
763*3d8817e4Smiod    sequential pages.  On systems with a BSD malloc, the
764*3d8817e4Smiod    MAX_CLUSTER_PAGES should be 1 less than a power of two, since
765*3d8817e4Smiod    malloc adds it's overhead, and rounds up to the next power of 2.
766*3d8817e4Smiod    Pages are linked together via a linked list.
767*3d8817e4Smiod 
768*3d8817e4Smiod    If PAGE_SIZE is > 4096, the string length in the shash_t structure
769*3d8817e4Smiod    can't be represented (assuming there are strings > 4096 bytes).  */
770*3d8817e4Smiod 
771*3d8817e4Smiod /* FIXME: Yes, there can be such strings while emitting C++ class debug
772*3d8817e4Smiod    info.  Templates are the offender here, the test case in question
773*3d8817e4Smiod    having a mangled class name of
774*3d8817e4Smiod 
775*3d8817e4Smiod      t7rb_tree4Z4xkeyZt4pair2ZC4xkeyZt7xsocket1Z4UserZt9select1st2Zt4pair\
776*3d8817e4Smiod      2ZC4xkeyZt7xsocket1Z4UserZ4xkeyZt4less1Z4xkey
777*3d8817e4Smiod 
778*3d8817e4Smiod    Repeat that a couple dozen times while listing the class members and
779*3d8817e4Smiod    you've got strings over 4k.  Hack around this for now by increasing
780*3d8817e4Smiod    the page size.  A proper solution would abandon this structure scheme
781*3d8817e4Smiod    certainly for very large strings, and possibly entirely.  */
782*3d8817e4Smiod 
783*3d8817e4Smiod #ifndef PAGE_SIZE
784*3d8817e4Smiod #define PAGE_SIZE (8*1024)	/* size of varray pages */
785*3d8817e4Smiod #endif
786*3d8817e4Smiod 
787*3d8817e4Smiod #define PAGE_USIZE ((unsigned long) PAGE_SIZE)
788*3d8817e4Smiod 
789*3d8817e4Smiod #ifndef MAX_CLUSTER_PAGES	/* # pages to get from system */
790*3d8817e4Smiod #define MAX_CLUSTER_PAGES 63
791*3d8817e4Smiod #endif
792*3d8817e4Smiod 
793*3d8817e4Smiod /* Linked list connecting separate page allocations.  */
794*3d8817e4Smiod typedef struct vlinks {
795*3d8817e4Smiod   struct vlinks	*prev;		/* previous set of pages */
796*3d8817e4Smiod   struct vlinks *next;		/* next set of pages */
797*3d8817e4Smiod   union  page   *datum;		/* start of page */
798*3d8817e4Smiod   unsigned long	 start_index;	/* starting index # of page */
799*3d8817e4Smiod } vlinks_t;
800*3d8817e4Smiod 
801*3d8817e4Smiod /* Virtual array header.  */
802*3d8817e4Smiod typedef struct varray {
803*3d8817e4Smiod   vlinks_t	*first;			/* first page link */
804*3d8817e4Smiod   vlinks_t	*last;			/* last page link */
805*3d8817e4Smiod   unsigned long	 num_allocated;		/* # objects allocated */
806*3d8817e4Smiod   unsigned short object_size;		/* size in bytes of each object */
807*3d8817e4Smiod   unsigned short objects_per_page;	/* # objects that can fit on a page */
808*3d8817e4Smiod   unsigned short objects_last_page;	/* # objects allocated on last page */
809*3d8817e4Smiod } varray_t;
810*3d8817e4Smiod 
811*3d8817e4Smiod #ifndef MALLOC_CHECK
812*3d8817e4Smiod #define OBJECTS_PER_PAGE(type) (PAGE_SIZE / sizeof (type))
813*3d8817e4Smiod #else
814*3d8817e4Smiod #define OBJECTS_PER_PAGE(type) ((sizeof (type) > 1) ? 1 : PAGE_SIZE)
815*3d8817e4Smiod #endif
816*3d8817e4Smiod 
817*3d8817e4Smiod #define INIT_VARRAY(type) {	/* macro to initialize a varray */	\
818*3d8817e4Smiod   (vlinks_t *)0,		/* first */				\
819*3d8817e4Smiod   (vlinks_t *)0,		/* last */				\
820*3d8817e4Smiod   0,				/* num_allocated */			\
821*3d8817e4Smiod   sizeof (type),		/* object_size */			\
822*3d8817e4Smiod   OBJECTS_PER_PAGE (type),	/* objects_per_page */			\
823*3d8817e4Smiod   OBJECTS_PER_PAGE (type),	/* objects_last_page */			\
824*3d8817e4Smiod }
825*3d8817e4Smiod 
826*3d8817e4Smiod /* Master type for indexes within the symbol table.  */
827*3d8817e4Smiod typedef unsigned long symint_t;
828*3d8817e4Smiod 
829*3d8817e4Smiod /* Linked list support for nested scopes (file, block, structure, etc.).  */
830*3d8817e4Smiod typedef struct scope {
831*3d8817e4Smiod   struct scope	*prev;		/* previous scope level */
832*3d8817e4Smiod   struct scope	*free;		/* free list pointer */
833*3d8817e4Smiod   struct localsym *lsym;	/* pointer to local symbol node */
834*3d8817e4Smiod   st_t		 type;		/* type of the node */
835*3d8817e4Smiod } scope_t;
836*3d8817e4Smiod 
837*3d8817e4Smiod /* For a local symbol we store a gas symbol as well as the debugging
838*3d8817e4Smiod    information we generate.  The gas symbol will be NULL if this is
839*3d8817e4Smiod    only a debugging symbol.  */
840*3d8817e4Smiod typedef struct localsym {
841*3d8817e4Smiod   const char *name;		/* symbol name */
842*3d8817e4Smiod   symbolS *as_sym;		/* symbol as seen by gas */
843*3d8817e4Smiod   bfd_vma addend;		/* addend to as_sym value */
844*3d8817e4Smiod   struct efdr *file_ptr;	/* file pointer */
845*3d8817e4Smiod   struct ecoff_proc *proc_ptr;	/* proc pointer */
846*3d8817e4Smiod   struct localsym *begin_ptr;	/* symbol at start of block */
847*3d8817e4Smiod   struct ecoff_aux *index_ptr;	/* index value to be filled in */
848*3d8817e4Smiod   struct forward *forward_ref;	/* forward references to this symbol */
849*3d8817e4Smiod   long sym_index;		/* final symbol index */
850*3d8817e4Smiod   EXTR ecoff_sym;		/* ECOFF debugging symbol */
851*3d8817e4Smiod } localsym_t;
852*3d8817e4Smiod 
853*3d8817e4Smiod /* For aux information we keep the type and the data.  */
854*3d8817e4Smiod typedef struct ecoff_aux {
855*3d8817e4Smiod   enum aux_type type;		/* aux type */
856*3d8817e4Smiod   AUXU data;			/* aux data */
857*3d8817e4Smiod } aux_t;
858*3d8817e4Smiod 
859*3d8817e4Smiod /* For a procedure we store the gas symbol as well as the PDR
860*3d8817e4Smiod    debugging information.  */
861*3d8817e4Smiod typedef struct ecoff_proc {
862*3d8817e4Smiod   localsym_t *sym;		/* associated symbol */
863*3d8817e4Smiod   PDR pdr;			/* ECOFF debugging info */
864*3d8817e4Smiod } proc_t;
865*3d8817e4Smiod 
866*3d8817e4Smiod /* Number of proc_t structures allocated.  */
867*3d8817e4Smiod static unsigned long proc_cnt;
868*3d8817e4Smiod 
869*3d8817e4Smiod /* Forward reference list for tags referenced, but not yet defined.  */
870*3d8817e4Smiod typedef struct forward {
871*3d8817e4Smiod   struct forward *next;		/* next forward reference */
872*3d8817e4Smiod   struct forward *free;		/* free list pointer */
873*3d8817e4Smiod   aux_t		 *ifd_ptr;	/* pointer to store file index */
874*3d8817e4Smiod   aux_t		 *index_ptr;	/* pointer to store symbol index */
875*3d8817e4Smiod } forward_t;
876*3d8817e4Smiod 
877*3d8817e4Smiod /* Linked list support for tags.  The first tag in the list is always
878*3d8817e4Smiod    the current tag for that block.  */
879*3d8817e4Smiod typedef struct tag {
880*3d8817e4Smiod   struct tag	 *free;		/* free list pointer */
881*3d8817e4Smiod   struct shash	 *hash_ptr;	/* pointer to the hash table head */
882*3d8817e4Smiod   struct tag	 *same_name;	/* tag with same name in outer scope */
883*3d8817e4Smiod   struct tag	 *same_block;	/* next tag defined in the same block.  */
884*3d8817e4Smiod   struct forward *forward_ref;	/* list of forward references */
885*3d8817e4Smiod   bt_t		  basic_type;	/* bt_Struct, bt_Union, or bt_Enum */
886*3d8817e4Smiod   symint_t	  ifd;		/* file # tag defined in */
887*3d8817e4Smiod   localsym_t	 *sym;		/* file's local symbols */
888*3d8817e4Smiod } tag_t;
889*3d8817e4Smiod 
890*3d8817e4Smiod /* Head of a block's linked list of tags.  */
891*3d8817e4Smiod typedef struct thead {
892*3d8817e4Smiod   struct thead	*prev;		/* previous block */
893*3d8817e4Smiod   struct thead	*free;		/* free list pointer */
894*3d8817e4Smiod   struct tag	*first_tag;	/* first tag in block defined */
895*3d8817e4Smiod } thead_t;
896*3d8817e4Smiod 
897*3d8817e4Smiod /* Union containing pointers to each the small structures which are freed up.  */
898*3d8817e4Smiod typedef union small_free {
899*3d8817e4Smiod   scope_t	*f_scope;	/* scope structure */
900*3d8817e4Smiod   thead_t	*f_thead;	/* tag head structure */
901*3d8817e4Smiod   tag_t		*f_tag;		/* tag element structure */
902*3d8817e4Smiod   forward_t	*f_forward;	/* forward tag reference */
903*3d8817e4Smiod } small_free_t;
904*3d8817e4Smiod 
905*3d8817e4Smiod /* String hash table entry.  */
906*3d8817e4Smiod 
907*3d8817e4Smiod typedef struct shash {
908*3d8817e4Smiod   char		*string;	/* string we are hashing */
909*3d8817e4Smiod   symint_t	 indx;		/* index within string table */
910*3d8817e4Smiod   EXTR		*esym_ptr;	/* global symbol pointer */
911*3d8817e4Smiod   localsym_t	*sym_ptr;	/* local symbol pointer */
912*3d8817e4Smiod   localsym_t	*end_ptr;	/* symbol pointer to end block */
913*3d8817e4Smiod   tag_t		*tag_ptr;	/* tag pointer */
914*3d8817e4Smiod   proc_t	*proc_ptr;	/* procedure descriptor pointer */
915*3d8817e4Smiod } shash_t;
916*3d8817e4Smiod 
917*3d8817e4Smiod /* Type hash table support.  The size of the hash table must fit
918*3d8817e4Smiod    within a page with the other extended file descriptor information.
919*3d8817e4Smiod    Because unique types which are hashed are fewer in number than
920*3d8817e4Smiod    strings, we use a smaller hash value.  */
921*3d8817e4Smiod 
922*3d8817e4Smiod #define HASHBITS 30
923*3d8817e4Smiod 
924*3d8817e4Smiod #ifndef THASH_SIZE
925*3d8817e4Smiod #define THASH_SIZE 113
926*3d8817e4Smiod #endif
927*3d8817e4Smiod 
928*3d8817e4Smiod typedef struct thash {
929*3d8817e4Smiod   struct thash	*next;		/* next hash value */
930*3d8817e4Smiod   AUXU		 type;		/* type we are hashing */
931*3d8817e4Smiod   symint_t	 indx;		/* index within string table */
932*3d8817e4Smiod } thash_t;
933*3d8817e4Smiod 
934*3d8817e4Smiod /* Extended file descriptor that contains all of the support necessary
935*3d8817e4Smiod    to add things to each file separately.  */
936*3d8817e4Smiod typedef struct efdr {
937*3d8817e4Smiod   FDR		 fdr;		/* File header to be written out */
938*3d8817e4Smiod   FDR		*orig_fdr;	/* original file header */
939*3d8817e4Smiod   char		*name;		/* filename */
940*3d8817e4Smiod   int		 fake;		/* whether this is faked .file */
941*3d8817e4Smiod   symint_t	 void_type;	/* aux. pointer to 'void' type */
942*3d8817e4Smiod   symint_t	 int_type;	/* aux. pointer to 'int' type */
943*3d8817e4Smiod   scope_t	*cur_scope;	/* current nested scopes */
944*3d8817e4Smiod   symint_t	 file_index;	/* current file number */
945*3d8817e4Smiod   int		 nested_scopes;	/* # nested scopes */
946*3d8817e4Smiod   varray_t	 strings;	/* local strings */
947*3d8817e4Smiod   varray_t	 symbols;	/* local symbols */
948*3d8817e4Smiod   varray_t	 procs;		/* procedures */
949*3d8817e4Smiod   varray_t	 aux_syms;	/* auxiliary symbols */
950*3d8817e4Smiod   struct efdr	*next_file;	/* next file descriptor */
951*3d8817e4Smiod 				/* string/type hash tables */
952*3d8817e4Smiod   struct hash_control *str_hash;	/* string hash table */
953*3d8817e4Smiod   thash_t	*thash_head[THASH_SIZE];
954*3d8817e4Smiod } efdr_t;
955*3d8817e4Smiod 
956*3d8817e4Smiod /* Pre-initialized extended file structure.  */
957*3d8817e4Smiod static const efdr_t init_file = {
958*3d8817e4Smiod   {			/* FDR structure */
959*3d8817e4Smiod     0,			/* adr:		memory address of beginning of file */
960*3d8817e4Smiod     0,			/* rss:		file name (of source, if known) */
961*3d8817e4Smiod     0,			/* issBase:	file's string space */
962*3d8817e4Smiod     0,			/* cbSs:	number of bytes in the ss */
963*3d8817e4Smiod     0,			/* isymBase:	beginning of symbols */
964*3d8817e4Smiod     0,			/* csym:	count file's of symbols */
965*3d8817e4Smiod     0,			/* ilineBase:	file's line symbols */
966*3d8817e4Smiod     0,			/* cline:	count of file's line symbols */
967*3d8817e4Smiod     0,			/* ioptBase:	file's optimization entries */
968*3d8817e4Smiod     0,			/* copt:	count of file's optimization entries */
969*3d8817e4Smiod     0,			/* ipdFirst:	start of procedures for this file */
970*3d8817e4Smiod     0,			/* cpd:		count of procedures for this file */
971*3d8817e4Smiod     0,			/* iauxBase:	file's auxiliary entries */
972*3d8817e4Smiod     0,			/* caux:	count of file's auxiliary entries */
973*3d8817e4Smiod     0,			/* rfdBase:	index into the file indirect table */
974*3d8817e4Smiod     0,			/* crfd:	count file indirect entries */
975*3d8817e4Smiod     langC,		/* lang:	language for this file */
976*3d8817e4Smiod     1,			/* fMerge:	whether this file can be merged */
977*3d8817e4Smiod     0,			/* fReadin:	true if read in (not just created) */
978*3d8817e4Smiod     TARGET_BYTES_BIG_ENDIAN,  /* fBigendian:	if 1, compiled on big endian machine */
979*3d8817e4Smiod     GLEVEL_2,		/* glevel:	level this file was compiled with */
980*3d8817e4Smiod     0,			/* reserved:	reserved for future use */
981*3d8817e4Smiod     0,			/* cbLineOffset: byte offset from header for this file ln's */
982*3d8817e4Smiod     0,			/* cbLine:	size of lines for this file */
983*3d8817e4Smiod   },
984*3d8817e4Smiod 
985*3d8817e4Smiod   (FDR *)0,		/* orig_fdr:	original file header pointer */
986*3d8817e4Smiod   (char *)0,		/* name:	pointer to filename */
987*3d8817e4Smiod   0,			/* fake:	whether this is a faked .file */
988*3d8817e4Smiod   0,			/* void_type:	ptr to aux node for void type */
989*3d8817e4Smiod   0,			/* int_type:	ptr to aux node for int type */
990*3d8817e4Smiod   (scope_t *)0,		/* cur_scope:	current scope being processed */
991*3d8817e4Smiod   0,			/* file_index:	current file # */
992*3d8817e4Smiod   0,			/* nested_scopes: # nested scopes */
993*3d8817e4Smiod   INIT_VARRAY (char),	/* strings:	local string varray */
994*3d8817e4Smiod   INIT_VARRAY (localsym_t),	/* symbols:	local symbols varray */
995*3d8817e4Smiod   INIT_VARRAY (proc_t),	/* procs:	procedure varray */
996*3d8817e4Smiod   INIT_VARRAY (aux_t),	/* aux_syms:	auxiliary symbols varray */
997*3d8817e4Smiod 
998*3d8817e4Smiod   (struct efdr *)0,	/* next_file:	next file structure */
999*3d8817e4Smiod 
1000*3d8817e4Smiod   (struct hash_control *)0,	/* str_hash:	string hash table */
1001*3d8817e4Smiod   { 0 },		/* thash_head:	type hash table */
1002*3d8817e4Smiod };
1003*3d8817e4Smiod 
1004*3d8817e4Smiod static efdr_t *first_file;			/* first file descriptor */
1005*3d8817e4Smiod static efdr_t **last_file_ptr = &first_file;	/* file descriptor tail */
1006*3d8817e4Smiod 
1007*3d8817e4Smiod /* Line number information is kept in a list until the assembly is
1008*3d8817e4Smiod    finished.  */
1009*3d8817e4Smiod typedef struct lineno_list {
1010*3d8817e4Smiod   struct lineno_list *next;	/* next element in list */
1011*3d8817e4Smiod   efdr_t *file;			/* file this line is in */
1012*3d8817e4Smiod   proc_t *proc;			/* procedure this line is in */
1013*3d8817e4Smiod   fragS *frag;			/* fragment this line number is in */
1014*3d8817e4Smiod   unsigned long paddr;		/* offset within fragment */
1015*3d8817e4Smiod   long lineno;			/* actual line number */
1016*3d8817e4Smiod } lineno_list_t;
1017*3d8817e4Smiod 
1018*3d8817e4Smiod static lineno_list_t *first_lineno;
1019*3d8817e4Smiod static lineno_list_t *last_lineno;
1020*3d8817e4Smiod static lineno_list_t **last_lineno_ptr = &first_lineno;
1021*3d8817e4Smiod 
1022*3d8817e4Smiod /* Sometimes there will be some .loc statements before a .ent.  We
1023*3d8817e4Smiod    keep them in this list so that we can fill in the procedure pointer
1024*3d8817e4Smiod    after we see the .ent.  */
1025*3d8817e4Smiod static lineno_list_t *noproc_lineno;
1026*3d8817e4Smiod 
1027*3d8817e4Smiod /* Union of various things that are held in pages.  */
1028*3d8817e4Smiod typedef union page {
1029*3d8817e4Smiod   char		byte	[ PAGE_SIZE ];
1030*3d8817e4Smiod   unsigned char	ubyte	[ PAGE_SIZE ];
1031*3d8817e4Smiod   efdr_t	file	[ PAGE_SIZE / sizeof (efdr_t)	     ];
1032*3d8817e4Smiod   FDR		ofile	[ PAGE_SIZE / sizeof (FDR)	     ];
1033*3d8817e4Smiod   proc_t	proc	[ PAGE_SIZE / sizeof (proc_t)	     ];
1034*3d8817e4Smiod   localsym_t	sym	[ PAGE_SIZE / sizeof (localsym_t)    ];
1035*3d8817e4Smiod   aux_t		aux	[ PAGE_SIZE / sizeof (aux_t)	     ];
1036*3d8817e4Smiod   DNR		dense	[ PAGE_SIZE / sizeof (DNR)	     ];
1037*3d8817e4Smiod   scope_t	scope	[ PAGE_SIZE / sizeof (scope_t)	     ];
1038*3d8817e4Smiod   vlinks_t	vlinks	[ PAGE_SIZE / sizeof (vlinks_t)	     ];
1039*3d8817e4Smiod   shash_t	shash	[ PAGE_SIZE / sizeof (shash_t)	     ];
1040*3d8817e4Smiod   thash_t	thash	[ PAGE_SIZE / sizeof (thash_t)	     ];
1041*3d8817e4Smiod   tag_t		tag	[ PAGE_SIZE / sizeof (tag_t)	     ];
1042*3d8817e4Smiod   forward_t	forward	[ PAGE_SIZE / sizeof (forward_t)     ];
1043*3d8817e4Smiod   thead_t	thead	[ PAGE_SIZE / sizeof (thead_t)	     ];
1044*3d8817e4Smiod   lineno_list_t	lineno	[ PAGE_SIZE / sizeof (lineno_list_t) ];
1045*3d8817e4Smiod } page_type;
1046*3d8817e4Smiod 
1047*3d8817e4Smiod /* Structure holding allocation information for small sized structures.  */
1048*3d8817e4Smiod typedef struct alloc_info {
1049*3d8817e4Smiod   char		*alloc_name;	/* name of this allocation type (must be first) */
1050*3d8817e4Smiod   page_type	*cur_page;	/* current page being allocated from */
1051*3d8817e4Smiod   small_free_t	 free_list;	/* current free list if any */
1052*3d8817e4Smiod   int		 unallocated;	/* number of elements unallocated on page */
1053*3d8817e4Smiod   int		 total_alloc;	/* total number of allocations */
1054*3d8817e4Smiod   int		 total_free;	/* total number of frees */
1055*3d8817e4Smiod   int		 total_pages;	/* total number of pages allocated */
1056*3d8817e4Smiod } alloc_info_t;
1057*3d8817e4Smiod 
1058*3d8817e4Smiod /* Type information collected together.  */
1059*3d8817e4Smiod typedef struct type_info {
1060*3d8817e4Smiod   bt_t	      basic_type;		/* basic type */
1061*3d8817e4Smiod   int	      orig_type;		/* original COFF-based type */
1062*3d8817e4Smiod   int	      num_tq;			/* # type qualifiers */
1063*3d8817e4Smiod   int	      num_dims;			/* # dimensions */
1064*3d8817e4Smiod   int	      num_sizes;		/* # sizes */
1065*3d8817e4Smiod   int	      extra_sizes;		/* # extra sizes not tied with dims */
1066*3d8817e4Smiod   tag_t *     tag_ptr;			/* tag pointer */
1067*3d8817e4Smiod   int	      bitfield;			/* symbol is a bitfield */
1068*3d8817e4Smiod   tq_t	      type_qualifiers[N_TQ];	/* type qualifiers (ptr, func, array)*/
1069*3d8817e4Smiod   symint_t    dimensions     [N_TQ];	/* dimensions for each array */
1070*3d8817e4Smiod   symint_t    sizes	     [N_TQ+2];	/* sizes of each array slice + size of
1071*3d8817e4Smiod 					   struct/union/enum + bitfield size */
1072*3d8817e4Smiod } type_info_t;
1073*3d8817e4Smiod 
1074*3d8817e4Smiod /* Pre-initialized type_info struct.  */
1075*3d8817e4Smiod static const type_info_t type_info_init = {
1076*3d8817e4Smiod   bt_Nil,				/* basic type */
1077*3d8817e4Smiod   T_NULL,				/* original COFF-based type */
1078*3d8817e4Smiod   0,					/* # type qualifiers */
1079*3d8817e4Smiod   0,					/* # dimensions */
1080*3d8817e4Smiod   0,					/* # sizes */
1081*3d8817e4Smiod   0,					/* sizes not tied with dims */
1082*3d8817e4Smiod   NULL,					/* ptr to tag */
1083*3d8817e4Smiod   0,					/* bitfield */
1084*3d8817e4Smiod   {					/* type qualifiers */
1085*3d8817e4Smiod     tq_Nil,
1086*3d8817e4Smiod     tq_Nil,
1087*3d8817e4Smiod     tq_Nil,
1088*3d8817e4Smiod     tq_Nil,
1089*3d8817e4Smiod     tq_Nil,
1090*3d8817e4Smiod     tq_Nil,
1091*3d8817e4Smiod   },
1092*3d8817e4Smiod   {					/* dimensions */
1093*3d8817e4Smiod     0,
1094*3d8817e4Smiod     0,
1095*3d8817e4Smiod     0,
1096*3d8817e4Smiod     0,
1097*3d8817e4Smiod     0,
1098*3d8817e4Smiod     0
1099*3d8817e4Smiod   },
1100*3d8817e4Smiod   {					/* sizes */
1101*3d8817e4Smiod     0,
1102*3d8817e4Smiod     0,
1103*3d8817e4Smiod     0,
1104*3d8817e4Smiod     0,
1105*3d8817e4Smiod     0,
1106*3d8817e4Smiod     0,
1107*3d8817e4Smiod     0,
1108*3d8817e4Smiod     0,
1109*3d8817e4Smiod   },
1110*3d8817e4Smiod };
1111*3d8817e4Smiod 
1112*3d8817e4Smiod /* Global hash table for the tags table and global table for file
1113*3d8817e4Smiod    descriptors.  */
1114*3d8817e4Smiod 
1115*3d8817e4Smiod static varray_t file_desc = INIT_VARRAY (efdr_t);
1116*3d8817e4Smiod 
1117*3d8817e4Smiod static struct hash_control *tag_hash;
1118*3d8817e4Smiod 
1119*3d8817e4Smiod /* Static types for int and void.  Also, remember the last function's
1120*3d8817e4Smiod    type (which is set up when we encounter the declaration for the
1121*3d8817e4Smiod    function, and used when the end block for the function is emitted.  */
1122*3d8817e4Smiod 
1123*3d8817e4Smiod static type_info_t int_type_info;
1124*3d8817e4Smiod static type_info_t void_type_info;
1125*3d8817e4Smiod static type_info_t last_func_type_info;
1126*3d8817e4Smiod static symbolS *last_func_sym_value;
1127*3d8817e4Smiod 
1128*3d8817e4Smiod /* Convert COFF basic type to ECOFF basic type.  The T_NULL type
1129*3d8817e4Smiod    really should use bt_Void, but this causes the current ecoff GDB to
1130*3d8817e4Smiod    issue unsupported type messages, and the Ultrix 4.00 dbx (aka MIPS
1131*3d8817e4Smiod    2.0) doesn't understand it, even though the compiler generates it.
1132*3d8817e4Smiod    Maybe this will be fixed in 2.10 or 2.20 of the MIPS compiler
1133*3d8817e4Smiod    suite, but for now go with what works.
1134*3d8817e4Smiod 
1135*3d8817e4Smiod    It would make sense for the .type and .scl directives to use the
1136*3d8817e4Smiod    ECOFF numbers directly, rather than using the COFF numbers and
1137*3d8817e4Smiod    mapping them.  Unfortunately, this is historically what mips-tfile
1138*3d8817e4Smiod    expects, and changing gcc now would be a considerable pain (the
1139*3d8817e4Smiod    native compiler generates debugging information internally, rather
1140*3d8817e4Smiod    than via the assembler, so it will never use .type or .scl).  */
1141*3d8817e4Smiod 
1142*3d8817e4Smiod static const bt_t map_coff_types[] = {
1143*3d8817e4Smiod   bt_Nil,			/* T_NULL */
1144*3d8817e4Smiod   bt_Nil,			/* T_ARG */
1145*3d8817e4Smiod   bt_Char,			/* T_CHAR */
1146*3d8817e4Smiod   bt_Short,			/* T_SHORT */
1147*3d8817e4Smiod   bt_Int,			/* T_INT */
1148*3d8817e4Smiod   bt_Long,			/* T_LONG */
1149*3d8817e4Smiod   bt_Float,			/* T_FLOAT */
1150*3d8817e4Smiod   bt_Double,			/* T_DOUBLE */
1151*3d8817e4Smiod   bt_Struct,			/* T_STRUCT */
1152*3d8817e4Smiod   bt_Union,			/* T_UNION */
1153*3d8817e4Smiod   bt_Enum,			/* T_ENUM */
1154*3d8817e4Smiod   bt_Enum,			/* T_MOE */
1155*3d8817e4Smiod   bt_UChar,			/* T_UCHAR */
1156*3d8817e4Smiod   bt_UShort,			/* T_USHORT */
1157*3d8817e4Smiod   bt_UInt,			/* T_UINT */
1158*3d8817e4Smiod   bt_ULong			/* T_ULONG */
1159*3d8817e4Smiod };
1160*3d8817e4Smiod 
1161*3d8817e4Smiod /* Convert COFF storage class to ECOFF storage class.  */
1162*3d8817e4Smiod static const sc_t map_coff_storage[] = {
1163*3d8817e4Smiod   sc_Nil,			/*   0: C_NULL */
1164*3d8817e4Smiod   sc_Abs,			/*   1: C_AUTO	  auto var */
1165*3d8817e4Smiod   sc_Undefined,			/*   2: C_EXT	  external */
1166*3d8817e4Smiod   sc_Data,			/*   3: C_STAT	  static */
1167*3d8817e4Smiod   sc_Register,			/*   4: C_REG	  register */
1168*3d8817e4Smiod   sc_Undefined,			/*   5: C_EXTDEF  ??? */
1169*3d8817e4Smiod   sc_Text,			/*   6: C_LABEL	  label */
1170*3d8817e4Smiod   sc_Text,			/*   7: C_ULABEL  user label */
1171*3d8817e4Smiod   sc_Info,			/*   8: C_MOS	  member of struct */
1172*3d8817e4Smiod   sc_Abs,			/*   9: C_ARG	  argument */
1173*3d8817e4Smiod   sc_Info,			/*  10: C_STRTAG  struct tag */
1174*3d8817e4Smiod   sc_Info,			/*  11: C_MOU	  member of union */
1175*3d8817e4Smiod   sc_Info,			/*  12: C_UNTAG   union tag */
1176*3d8817e4Smiod   sc_Info,			/*  13: C_TPDEF	  typedef */
1177*3d8817e4Smiod   sc_Data,			/*  14: C_USTATIC ??? */
1178*3d8817e4Smiod   sc_Info,			/*  15: C_ENTAG	  enum tag */
1179*3d8817e4Smiod   sc_Info,			/*  16: C_MOE	  member of enum */
1180*3d8817e4Smiod   sc_Register,			/*  17: C_REGPARM register parameter */
1181*3d8817e4Smiod   sc_Bits,			/*  18; C_FIELD	  bitfield */
1182*3d8817e4Smiod   sc_Nil,			/*  19 */
1183*3d8817e4Smiod   sc_Nil,			/*  20 */
1184*3d8817e4Smiod   sc_Nil,			/*  21 */
1185*3d8817e4Smiod   sc_Nil,			/*  22 */
1186*3d8817e4Smiod   sc_Nil,			/*  23 */
1187*3d8817e4Smiod   sc_Nil,			/*  24 */
1188*3d8817e4Smiod   sc_Nil,			/*  25 */
1189*3d8817e4Smiod   sc_Nil,			/*  26 */
1190*3d8817e4Smiod   sc_Nil,			/*  27 */
1191*3d8817e4Smiod   sc_Nil,			/*  28 */
1192*3d8817e4Smiod   sc_Nil,			/*  29 */
1193*3d8817e4Smiod   sc_Nil,			/*  30 */
1194*3d8817e4Smiod   sc_Nil,			/*  31 */
1195*3d8817e4Smiod   sc_Nil,			/*  32 */
1196*3d8817e4Smiod   sc_Nil,			/*  33 */
1197*3d8817e4Smiod   sc_Nil,			/*  34 */
1198*3d8817e4Smiod   sc_Nil,			/*  35 */
1199*3d8817e4Smiod   sc_Nil,			/*  36 */
1200*3d8817e4Smiod   sc_Nil,			/*  37 */
1201*3d8817e4Smiod   sc_Nil,			/*  38 */
1202*3d8817e4Smiod   sc_Nil,			/*  39 */
1203*3d8817e4Smiod   sc_Nil,			/*  40 */
1204*3d8817e4Smiod   sc_Nil,			/*  41 */
1205*3d8817e4Smiod   sc_Nil,			/*  42 */
1206*3d8817e4Smiod   sc_Nil,			/*  43 */
1207*3d8817e4Smiod   sc_Nil,			/*  44 */
1208*3d8817e4Smiod   sc_Nil,			/*  45 */
1209*3d8817e4Smiod   sc_Nil,			/*  46 */
1210*3d8817e4Smiod   sc_Nil,			/*  47 */
1211*3d8817e4Smiod   sc_Nil,			/*  48 */
1212*3d8817e4Smiod   sc_Nil,			/*  49 */
1213*3d8817e4Smiod   sc_Nil,			/*  50 */
1214*3d8817e4Smiod   sc_Nil,			/*  51 */
1215*3d8817e4Smiod   sc_Nil,			/*  52 */
1216*3d8817e4Smiod   sc_Nil,			/*  53 */
1217*3d8817e4Smiod   sc_Nil,			/*  54 */
1218*3d8817e4Smiod   sc_Nil,			/*  55 */
1219*3d8817e4Smiod   sc_Nil,			/*  56 */
1220*3d8817e4Smiod   sc_Nil,			/*  57 */
1221*3d8817e4Smiod   sc_Nil,			/*  58 */
1222*3d8817e4Smiod   sc_Nil,			/*  59 */
1223*3d8817e4Smiod   sc_Nil,			/*  60 */
1224*3d8817e4Smiod   sc_Nil,			/*  61 */
1225*3d8817e4Smiod   sc_Nil,			/*  62 */
1226*3d8817e4Smiod   sc_Nil,			/*  63 */
1227*3d8817e4Smiod   sc_Nil,			/*  64 */
1228*3d8817e4Smiod   sc_Nil,			/*  65 */
1229*3d8817e4Smiod   sc_Nil,			/*  66 */
1230*3d8817e4Smiod   sc_Nil,			/*  67 */
1231*3d8817e4Smiod   sc_Nil,			/*  68 */
1232*3d8817e4Smiod   sc_Nil,			/*  69 */
1233*3d8817e4Smiod   sc_Nil,			/*  70 */
1234*3d8817e4Smiod   sc_Nil,			/*  71 */
1235*3d8817e4Smiod   sc_Nil,			/*  72 */
1236*3d8817e4Smiod   sc_Nil,			/*  73 */
1237*3d8817e4Smiod   sc_Nil,			/*  74 */
1238*3d8817e4Smiod   sc_Nil,			/*  75 */
1239*3d8817e4Smiod   sc_Nil,			/*  76 */
1240*3d8817e4Smiod   sc_Nil,			/*  77 */
1241*3d8817e4Smiod   sc_Nil,			/*  78 */
1242*3d8817e4Smiod   sc_Nil,			/*  79 */
1243*3d8817e4Smiod   sc_Nil,			/*  80 */
1244*3d8817e4Smiod   sc_Nil,			/*  81 */
1245*3d8817e4Smiod   sc_Nil,			/*  82 */
1246*3d8817e4Smiod   sc_Nil,			/*  83 */
1247*3d8817e4Smiod   sc_Nil,			/*  84 */
1248*3d8817e4Smiod   sc_Nil,			/*  85 */
1249*3d8817e4Smiod   sc_Nil,			/*  86 */
1250*3d8817e4Smiod   sc_Nil,			/*  87 */
1251*3d8817e4Smiod   sc_Nil,			/*  88 */
1252*3d8817e4Smiod   sc_Nil,			/*  89 */
1253*3d8817e4Smiod   sc_Nil,			/*  90 */
1254*3d8817e4Smiod   sc_Nil,			/*  91 */
1255*3d8817e4Smiod   sc_Nil,			/*  92 */
1256*3d8817e4Smiod   sc_Nil,			/*  93 */
1257*3d8817e4Smiod   sc_Nil,			/*  94 */
1258*3d8817e4Smiod   sc_Nil,			/*  95 */
1259*3d8817e4Smiod   sc_Nil,			/*  96 */
1260*3d8817e4Smiod   sc_Nil,			/*  97 */
1261*3d8817e4Smiod   sc_Nil,			/*  98 */
1262*3d8817e4Smiod   sc_Nil,			/*  99 */
1263*3d8817e4Smiod   sc_Text,			/* 100: C_BLOCK  block start/end */
1264*3d8817e4Smiod   sc_Text,			/* 101: C_FCN	 function start/end */
1265*3d8817e4Smiod   sc_Info,			/* 102: C_EOS	 end of struct/union/enum */
1266*3d8817e4Smiod   sc_Nil,			/* 103: C_FILE	 file start */
1267*3d8817e4Smiod   sc_Nil,			/* 104: C_LINE	 line number */
1268*3d8817e4Smiod   sc_Nil,			/* 105: C_ALIAS	 combined type info */
1269*3d8817e4Smiod   sc_Nil,			/* 106: C_HIDDEN ??? */
1270*3d8817e4Smiod };
1271*3d8817e4Smiod 
1272*3d8817e4Smiod /* Convert COFF storage class to ECOFF symbol type.  */
1273*3d8817e4Smiod static const st_t map_coff_sym_type[] = {
1274*3d8817e4Smiod   st_Nil,			/*   0: C_NULL */
1275*3d8817e4Smiod   st_Local,			/*   1: C_AUTO	  auto var */
1276*3d8817e4Smiod   st_Global,			/*   2: C_EXT	  external */
1277*3d8817e4Smiod   st_Static,			/*   3: C_STAT	  static */
1278*3d8817e4Smiod   st_Local,			/*   4: C_REG	  register */
1279*3d8817e4Smiod   st_Global,			/*   5: C_EXTDEF  ??? */
1280*3d8817e4Smiod   st_Label,			/*   6: C_LABEL	  label */
1281*3d8817e4Smiod   st_Label,			/*   7: C_ULABEL  user label */
1282*3d8817e4Smiod   st_Member,			/*   8: C_MOS	  member of struct */
1283*3d8817e4Smiod   st_Param,			/*   9: C_ARG	  argument */
1284*3d8817e4Smiod   st_Block,			/*  10: C_STRTAG  struct tag */
1285*3d8817e4Smiod   st_Member,			/*  11: C_MOU	  member of union */
1286*3d8817e4Smiod   st_Block,			/*  12: C_UNTAG   union tag */
1287*3d8817e4Smiod   st_Typedef,			/*  13: C_TPDEF	  typedef */
1288*3d8817e4Smiod   st_Static,			/*  14: C_USTATIC ??? */
1289*3d8817e4Smiod   st_Block,			/*  15: C_ENTAG	  enum tag */
1290*3d8817e4Smiod   st_Member,			/*  16: C_MOE	  member of enum */
1291*3d8817e4Smiod   st_Param,			/*  17: C_REGPARM register parameter */
1292*3d8817e4Smiod   st_Member,			/*  18; C_FIELD	  bitfield */
1293*3d8817e4Smiod   st_Nil,			/*  19 */
1294*3d8817e4Smiod   st_Nil,			/*  20 */
1295*3d8817e4Smiod   st_Nil,			/*  21 */
1296*3d8817e4Smiod   st_Nil,			/*  22 */
1297*3d8817e4Smiod   st_Nil,			/*  23 */
1298*3d8817e4Smiod   st_Nil,			/*  24 */
1299*3d8817e4Smiod   st_Nil,			/*  25 */
1300*3d8817e4Smiod   st_Nil,			/*  26 */
1301*3d8817e4Smiod   st_Nil,			/*  27 */
1302*3d8817e4Smiod   st_Nil,			/*  28 */
1303*3d8817e4Smiod   st_Nil,			/*  29 */
1304*3d8817e4Smiod   st_Nil,			/*  30 */
1305*3d8817e4Smiod   st_Nil,			/*  31 */
1306*3d8817e4Smiod   st_Nil,			/*  32 */
1307*3d8817e4Smiod   st_Nil,			/*  33 */
1308*3d8817e4Smiod   st_Nil,			/*  34 */
1309*3d8817e4Smiod   st_Nil,			/*  35 */
1310*3d8817e4Smiod   st_Nil,			/*  36 */
1311*3d8817e4Smiod   st_Nil,			/*  37 */
1312*3d8817e4Smiod   st_Nil,			/*  38 */
1313*3d8817e4Smiod   st_Nil,			/*  39 */
1314*3d8817e4Smiod   st_Nil,			/*  40 */
1315*3d8817e4Smiod   st_Nil,			/*  41 */
1316*3d8817e4Smiod   st_Nil,			/*  42 */
1317*3d8817e4Smiod   st_Nil,			/*  43 */
1318*3d8817e4Smiod   st_Nil,			/*  44 */
1319*3d8817e4Smiod   st_Nil,			/*  45 */
1320*3d8817e4Smiod   st_Nil,			/*  46 */
1321*3d8817e4Smiod   st_Nil,			/*  47 */
1322*3d8817e4Smiod   st_Nil,			/*  48 */
1323*3d8817e4Smiod   st_Nil,			/*  49 */
1324*3d8817e4Smiod   st_Nil,			/*  50 */
1325*3d8817e4Smiod   st_Nil,			/*  51 */
1326*3d8817e4Smiod   st_Nil,			/*  52 */
1327*3d8817e4Smiod   st_Nil,			/*  53 */
1328*3d8817e4Smiod   st_Nil,			/*  54 */
1329*3d8817e4Smiod   st_Nil,			/*  55 */
1330*3d8817e4Smiod   st_Nil,			/*  56 */
1331*3d8817e4Smiod   st_Nil,			/*  57 */
1332*3d8817e4Smiod   st_Nil,			/*  58 */
1333*3d8817e4Smiod   st_Nil,			/*  59 */
1334*3d8817e4Smiod   st_Nil,			/*  60 */
1335*3d8817e4Smiod   st_Nil,			/*  61 */
1336*3d8817e4Smiod   st_Nil,			/*  62 */
1337*3d8817e4Smiod   st_Nil,			/*  63 */
1338*3d8817e4Smiod   st_Nil,			/*  64 */
1339*3d8817e4Smiod   st_Nil,			/*  65 */
1340*3d8817e4Smiod   st_Nil,			/*  66 */
1341*3d8817e4Smiod   st_Nil,			/*  67 */
1342*3d8817e4Smiod   st_Nil,			/*  68 */
1343*3d8817e4Smiod   st_Nil,			/*  69 */
1344*3d8817e4Smiod   st_Nil,			/*  70 */
1345*3d8817e4Smiod   st_Nil,			/*  71 */
1346*3d8817e4Smiod   st_Nil,			/*  72 */
1347*3d8817e4Smiod   st_Nil,			/*  73 */
1348*3d8817e4Smiod   st_Nil,			/*  74 */
1349*3d8817e4Smiod   st_Nil,			/*  75 */
1350*3d8817e4Smiod   st_Nil,			/*  76 */
1351*3d8817e4Smiod   st_Nil,			/*  77 */
1352*3d8817e4Smiod   st_Nil,			/*  78 */
1353*3d8817e4Smiod   st_Nil,			/*  79 */
1354*3d8817e4Smiod   st_Nil,			/*  80 */
1355*3d8817e4Smiod   st_Nil,			/*  81 */
1356*3d8817e4Smiod   st_Nil,			/*  82 */
1357*3d8817e4Smiod   st_Nil,			/*  83 */
1358*3d8817e4Smiod   st_Nil,			/*  84 */
1359*3d8817e4Smiod   st_Nil,			/*  85 */
1360*3d8817e4Smiod   st_Nil,			/*  86 */
1361*3d8817e4Smiod   st_Nil,			/*  87 */
1362*3d8817e4Smiod   st_Nil,			/*  88 */
1363*3d8817e4Smiod   st_Nil,			/*  89 */
1364*3d8817e4Smiod   st_Nil,			/*  90 */
1365*3d8817e4Smiod   st_Nil,			/*  91 */
1366*3d8817e4Smiod   st_Nil,			/*  92 */
1367*3d8817e4Smiod   st_Nil,			/*  93 */
1368*3d8817e4Smiod   st_Nil,			/*  94 */
1369*3d8817e4Smiod   st_Nil,			/*  95 */
1370*3d8817e4Smiod   st_Nil,			/*  96 */
1371*3d8817e4Smiod   st_Nil,			/*  97 */
1372*3d8817e4Smiod   st_Nil,			/*  98 */
1373*3d8817e4Smiod   st_Nil,			/*  99 */
1374*3d8817e4Smiod   st_Block,			/* 100: C_BLOCK  block start/end */
1375*3d8817e4Smiod   st_Proc,			/* 101: C_FCN	 function start/end */
1376*3d8817e4Smiod   st_End,			/* 102: C_EOS	 end of struct/union/enum */
1377*3d8817e4Smiod   st_File,			/* 103: C_FILE	 file start */
1378*3d8817e4Smiod   st_Nil,			/* 104: C_LINE	 line number */
1379*3d8817e4Smiod   st_Nil,			/* 105: C_ALIAS	 combined type info */
1380*3d8817e4Smiod   st_Nil,			/* 106: C_HIDDEN ??? */
1381*3d8817e4Smiod };
1382*3d8817e4Smiod 
1383*3d8817e4Smiod /* Keep track of different sized allocation requests.  */
1384*3d8817e4Smiod static alloc_info_t alloc_counts[(int) alloc_type_last];
1385*3d8817e4Smiod 
1386*3d8817e4Smiod /* Record whether we have seen any debugging information.  */
1387*3d8817e4Smiod int ecoff_debugging_seen = 0;
1388*3d8817e4Smiod 
1389*3d8817e4Smiod /* Various statics.  */
1390*3d8817e4Smiod static efdr_t  *cur_file_ptr	= (efdr_t *) 0;	/* current file desc. header */
1391*3d8817e4Smiod static proc_t  *cur_proc_ptr	= (proc_t *) 0;	/* current procedure header */
1392*3d8817e4Smiod static proc_t  *first_proc_ptr  = (proc_t *) 0; /* first procedure header */
1393*3d8817e4Smiod static thead_t *top_tag_head	= (thead_t *) 0; /* top level tag head */
1394*3d8817e4Smiod static thead_t *cur_tag_head	= (thead_t *) 0; /* current tag head */
1395*3d8817e4Smiod #ifdef ECOFF_DEBUG
1396*3d8817e4Smiod static int	debug		= 0; 		/* trace functions */
1397*3d8817e4Smiod #endif
1398*3d8817e4Smiod static int	stabs_seen	= 0;		/* != 0 if stabs have been seen */
1399*3d8817e4Smiod 
1400*3d8817e4Smiod static int current_file_idx;
1401*3d8817e4Smiod static const char *current_stabs_filename;
1402*3d8817e4Smiod 
1403*3d8817e4Smiod /* Pseudo symbol to use when putting stabs into the symbol table.  */
1404*3d8817e4Smiod #ifndef STABS_SYMBOL
1405*3d8817e4Smiod #define STABS_SYMBOL "@stabs"
1406*3d8817e4Smiod #endif
1407*3d8817e4Smiod 
1408*3d8817e4Smiod static char stabs_symbol[] = STABS_SYMBOL;
1409*3d8817e4Smiod 
1410*3d8817e4Smiod /* Prototypes for functions defined in this file.  */
1411*3d8817e4Smiod 
1412*3d8817e4Smiod static void add_varray_page (varray_t *vp);
1413*3d8817e4Smiod static symint_t add_string (varray_t *vp,
1414*3d8817e4Smiod 			    struct hash_control *hash_tbl,
1415*3d8817e4Smiod 			    const char *str,
1416*3d8817e4Smiod 			    shash_t **ret_hash);
1417*3d8817e4Smiod static localsym_t *add_ecoff_symbol (const char *str, st_t type,
1418*3d8817e4Smiod 				     sc_t storage, symbolS *sym,
1419*3d8817e4Smiod 				     bfd_vma addend, symint_t value,
1420*3d8817e4Smiod 				     symint_t indx);
1421*3d8817e4Smiod static symint_t add_aux_sym_symint (symint_t aux_word);
1422*3d8817e4Smiod static symint_t add_aux_sym_rndx (int file_index, symint_t sym_index);
1423*3d8817e4Smiod static symint_t add_aux_sym_tir (type_info_t *t,
1424*3d8817e4Smiod 				 hash_state_t state,
1425*3d8817e4Smiod 				 thash_t **hash_tbl);
1426*3d8817e4Smiod static tag_t *get_tag (const char *tag, localsym_t *sym, bt_t basic_type);
1427*3d8817e4Smiod static void add_unknown_tag (tag_t *ptag);
1428*3d8817e4Smiod static void add_procedure (char *func);
1429*3d8817e4Smiod static void add_file (const char *file_name, int indx, int fake);
1430*3d8817e4Smiod #ifdef ECOFF_DEBUG
1431*3d8817e4Smiod static char *sc_to_string (sc_t storage_class);
1432*3d8817e4Smiod static char *st_to_string (st_t symbol_type);
1433*3d8817e4Smiod #endif
1434*3d8817e4Smiod static void mark_stabs (int);
1435*3d8817e4Smiod static char *ecoff_add_bytes (char **buf, char **bufend,
1436*3d8817e4Smiod 			      char *bufptr, unsigned long need);
1437*3d8817e4Smiod static unsigned long ecoff_padding_adjust
1438*3d8817e4Smiod   (const struct ecoff_debug_swap *backend, char **buf, char **bufend,
1439*3d8817e4Smiod    unsigned long offset, char **bufptrptr);
1440*3d8817e4Smiod static unsigned long ecoff_build_lineno
1441*3d8817e4Smiod   (const struct ecoff_debug_swap *backend, char **buf, char **bufend,
1442*3d8817e4Smiod    unsigned long offset, long *linecntptr);
1443*3d8817e4Smiod static unsigned long ecoff_build_symbols
1444*3d8817e4Smiod   (const struct ecoff_debug_swap *backend, char **buf, char **bufend,
1445*3d8817e4Smiod    unsigned long offset);
1446*3d8817e4Smiod static unsigned long ecoff_build_procs
1447*3d8817e4Smiod   (const struct ecoff_debug_swap *backend, char **buf, char **bufend,
1448*3d8817e4Smiod    unsigned long offset);
1449*3d8817e4Smiod static unsigned long ecoff_build_aux
1450*3d8817e4Smiod   (const struct ecoff_debug_swap *backend, char **buf, char **bufend,
1451*3d8817e4Smiod    unsigned long offset);
1452*3d8817e4Smiod static unsigned long ecoff_build_strings (char **buf, char **bufend,
1453*3d8817e4Smiod 					  unsigned long offset,
1454*3d8817e4Smiod 					  varray_t *vp);
1455*3d8817e4Smiod static unsigned long ecoff_build_ss
1456*3d8817e4Smiod   (const struct ecoff_debug_swap *backend, char **buf, char **bufend,
1457*3d8817e4Smiod    unsigned long offset);
1458*3d8817e4Smiod static unsigned long ecoff_build_fdr
1459*3d8817e4Smiod   (const struct ecoff_debug_swap *backend, char **buf, char **bufend,
1460*3d8817e4Smiod    unsigned long offset);
1461*3d8817e4Smiod static void ecoff_setup_ext (void);
1462*3d8817e4Smiod static page_type *allocate_cluster (unsigned long npages);
1463*3d8817e4Smiod static page_type *allocate_page (void);
1464*3d8817e4Smiod static scope_t *allocate_scope (void);
1465*3d8817e4Smiod static void free_scope (scope_t *ptr);
1466*3d8817e4Smiod static vlinks_t *allocate_vlinks (void);
1467*3d8817e4Smiod static shash_t *allocate_shash (void);
1468*3d8817e4Smiod static thash_t *allocate_thash (void);
1469*3d8817e4Smiod static tag_t *allocate_tag (void);
1470*3d8817e4Smiod static void free_tag (tag_t *ptr);
1471*3d8817e4Smiod static forward_t *allocate_forward (void);
1472*3d8817e4Smiod static thead_t *allocate_thead (void);
1473*3d8817e4Smiod static void free_thead (thead_t *ptr);
1474*3d8817e4Smiod static lineno_list_t *allocate_lineno_list (void);
1475*3d8817e4Smiod 
1476*3d8817e4Smiod /* This function should be called when the assembler starts up.  */
1477*3d8817e4Smiod 
1478*3d8817e4Smiod void
ecoff_read_begin_hook(void)1479*3d8817e4Smiod ecoff_read_begin_hook (void)
1480*3d8817e4Smiod {
1481*3d8817e4Smiod   tag_hash = hash_new ();
1482*3d8817e4Smiod   top_tag_head = allocate_thead ();
1483*3d8817e4Smiod   top_tag_head->first_tag = (tag_t *) NULL;
1484*3d8817e4Smiod   top_tag_head->free = (thead_t *) NULL;
1485*3d8817e4Smiod   top_tag_head->prev = cur_tag_head;
1486*3d8817e4Smiod   cur_tag_head = top_tag_head;
1487*3d8817e4Smiod }
1488*3d8817e4Smiod 
1489*3d8817e4Smiod /* This function should be called when a symbol is created.  */
1490*3d8817e4Smiod 
1491*3d8817e4Smiod void
ecoff_symbol_new_hook(symbolS * symbolP)1492*3d8817e4Smiod ecoff_symbol_new_hook (symbolS *symbolP)
1493*3d8817e4Smiod {
1494*3d8817e4Smiod   OBJ_SYMFIELD_TYPE *obj;
1495*3d8817e4Smiod 
1496*3d8817e4Smiod   /* Make sure that we have a file pointer, but only if we have seen a
1497*3d8817e4Smiod      file.  If we haven't seen a file, then this is a probably special
1498*3d8817e4Smiod      symbol created by md_begin which may required special handling at
1499*3d8817e4Smiod      some point.  Creating a dummy file with a dummy name is certainly
1500*3d8817e4Smiod      wrong.  */
1501*3d8817e4Smiod   if (cur_file_ptr == (efdr_t *) NULL
1502*3d8817e4Smiod       && seen_at_least_1_file ())
1503*3d8817e4Smiod     add_file ((const char *) NULL, 0, 1);
1504*3d8817e4Smiod   obj = symbol_get_obj (symbolP);
1505*3d8817e4Smiod   obj->ecoff_file = cur_file_ptr;
1506*3d8817e4Smiod   obj->ecoff_symbol = NULL;
1507*3d8817e4Smiod   obj->ecoff_extern_size = 0;
1508*3d8817e4Smiod }
1509*3d8817e4Smiod 
1510*3d8817e4Smiod /* Add a page to a varray object.  */
1511*3d8817e4Smiod 
1512*3d8817e4Smiod static void
add_varray_page(varray_t * vp)1513*3d8817e4Smiod add_varray_page (varray_t *vp /* varray to add page to */)
1514*3d8817e4Smiod {
1515*3d8817e4Smiod   vlinks_t *new_links = allocate_vlinks ();
1516*3d8817e4Smiod 
1517*3d8817e4Smiod #ifdef MALLOC_CHECK
1518*3d8817e4Smiod   if (vp->object_size > 1)
1519*3d8817e4Smiod     new_links->datum = (page_type *) xcalloc (1, vp->object_size);
1520*3d8817e4Smiod   else
1521*3d8817e4Smiod #endif
1522*3d8817e4Smiod     new_links->datum = allocate_page ();
1523*3d8817e4Smiod 
1524*3d8817e4Smiod   alloc_counts[(int) alloc_type_varray].total_alloc++;
1525*3d8817e4Smiod   alloc_counts[(int) alloc_type_varray].total_pages++;
1526*3d8817e4Smiod 
1527*3d8817e4Smiod   new_links->start_index = vp->num_allocated;
1528*3d8817e4Smiod   vp->objects_last_page = 0;
1529*3d8817e4Smiod 
1530*3d8817e4Smiod   if (vp->first == (vlinks_t *) NULL)		/* first allocation? */
1531*3d8817e4Smiod     vp->first = vp->last = new_links;
1532*3d8817e4Smiod   else
1533*3d8817e4Smiod     {						/* 2nd or greater allocation */
1534*3d8817e4Smiod       new_links->prev = vp->last;
1535*3d8817e4Smiod       vp->last->next = new_links;
1536*3d8817e4Smiod       vp->last = new_links;
1537*3d8817e4Smiod     }
1538*3d8817e4Smiod }
1539*3d8817e4Smiod 
1540*3d8817e4Smiod /* Add a string (and null pad) to one of the string tables.  */
1541*3d8817e4Smiod 
1542*3d8817e4Smiod static symint_t
add_string(varray_t * vp,struct hash_control * hash_tbl,const char * str,shash_t ** ret_hash)1543*3d8817e4Smiod add_string (varray_t *vp,			/* string obstack */
1544*3d8817e4Smiod 	    struct hash_control *hash_tbl,	/* ptr to hash table */
1545*3d8817e4Smiod 	    const char *str,			/* string */
1546*3d8817e4Smiod 	    shash_t **ret_hash			/* return hash pointer */)
1547*3d8817e4Smiod {
1548*3d8817e4Smiod   register unsigned long len = strlen (str);
1549*3d8817e4Smiod   register shash_t *hash_ptr;
1550*3d8817e4Smiod 
1551*3d8817e4Smiod   if (len >= PAGE_USIZE)
1552*3d8817e4Smiod     as_fatal (_("string too big (%lu bytes)"), len);
1553*3d8817e4Smiod 
1554*3d8817e4Smiod   hash_ptr = (shash_t *) hash_find (hash_tbl, str);
1555*3d8817e4Smiod   if (hash_ptr == (shash_t *) NULL)
1556*3d8817e4Smiod     {
1557*3d8817e4Smiod       register const char *err;
1558*3d8817e4Smiod 
1559*3d8817e4Smiod       if (vp->objects_last_page + len >= PAGE_USIZE)
1560*3d8817e4Smiod 	{
1561*3d8817e4Smiod 	  vp->num_allocated =
1562*3d8817e4Smiod 	    ((vp->num_allocated + PAGE_USIZE - 1) / PAGE_USIZE) * PAGE_USIZE;
1563*3d8817e4Smiod 	  add_varray_page (vp);
1564*3d8817e4Smiod 	}
1565*3d8817e4Smiod 
1566*3d8817e4Smiod       hash_ptr = allocate_shash ();
1567*3d8817e4Smiod       hash_ptr->indx = vp->num_allocated;
1568*3d8817e4Smiod 
1569*3d8817e4Smiod       hash_ptr->string = &vp->last->datum->byte[vp->objects_last_page];
1570*3d8817e4Smiod 
1571*3d8817e4Smiod       vp->objects_last_page += len + 1;
1572*3d8817e4Smiod       vp->num_allocated += len + 1;
1573*3d8817e4Smiod 
1574*3d8817e4Smiod       strcpy (hash_ptr->string, str);
1575*3d8817e4Smiod 
1576*3d8817e4Smiod       err = hash_insert (hash_tbl, str, (char *) hash_ptr);
1577*3d8817e4Smiod       if (err)
1578*3d8817e4Smiod 	as_fatal (_("inserting \"%s\" into string hash table: %s"),
1579*3d8817e4Smiod 		  str, err);
1580*3d8817e4Smiod     }
1581*3d8817e4Smiod 
1582*3d8817e4Smiod   if (ret_hash != (shash_t **) NULL)
1583*3d8817e4Smiod     *ret_hash = hash_ptr;
1584*3d8817e4Smiod 
1585*3d8817e4Smiod   return hash_ptr->indx;
1586*3d8817e4Smiod }
1587*3d8817e4Smiod 
1588*3d8817e4Smiod /* Add debugging information for a symbol.  */
1589*3d8817e4Smiod 
1590*3d8817e4Smiod static localsym_t *
add_ecoff_symbol(const char * str,st_t type,sc_t storage,symbolS * sym_value,bfd_vma addend,symint_t value,symint_t indx)1591*3d8817e4Smiod add_ecoff_symbol (const char *str,	/* symbol name */
1592*3d8817e4Smiod 		  st_t type,		/* symbol type */
1593*3d8817e4Smiod 		  sc_t storage,		/* storage class */
1594*3d8817e4Smiod 		  symbolS *sym_value,	/* associated symbol.  */
1595*3d8817e4Smiod 		  bfd_vma addend,	/* addend to sym_value.  */
1596*3d8817e4Smiod 		  symint_t value,	/* value of symbol */
1597*3d8817e4Smiod 		  symint_t indx		/* index to local/aux. syms */)
1598*3d8817e4Smiod {
1599*3d8817e4Smiod   localsym_t *psym;
1600*3d8817e4Smiod   register scope_t *pscope;
1601*3d8817e4Smiod   register thead_t *ptag_head;
1602*3d8817e4Smiod   register tag_t *ptag;
1603*3d8817e4Smiod   register tag_t *ptag_next;
1604*3d8817e4Smiod   register varray_t *vp;
1605*3d8817e4Smiod   register int scope_delta = 0;
1606*3d8817e4Smiod   shash_t *hash_ptr = (shash_t *) NULL;
1607*3d8817e4Smiod 
1608*3d8817e4Smiod   if (cur_file_ptr == (efdr_t *) NULL)
1609*3d8817e4Smiod     as_fatal (_("no current file pointer"));
1610*3d8817e4Smiod 
1611*3d8817e4Smiod   vp = &cur_file_ptr->symbols;
1612*3d8817e4Smiod 
1613*3d8817e4Smiod   if (vp->objects_last_page == vp->objects_per_page)
1614*3d8817e4Smiod     add_varray_page (vp);
1615*3d8817e4Smiod 
1616*3d8817e4Smiod   psym = &vp->last->datum->sym[vp->objects_last_page++];
1617*3d8817e4Smiod 
1618*3d8817e4Smiod   if (str == (const char *) NULL && sym_value != (symbolS *) NULL)
1619*3d8817e4Smiod     psym->name = S_GET_NAME (sym_value);
1620*3d8817e4Smiod   else
1621*3d8817e4Smiod     psym->name = str;
1622*3d8817e4Smiod   psym->as_sym = sym_value;
1623*3d8817e4Smiod   if (sym_value != (symbolS *) NULL)
1624*3d8817e4Smiod     symbol_get_obj (sym_value)->ecoff_symbol = psym;
1625*3d8817e4Smiod   psym->addend = addend;
1626*3d8817e4Smiod   psym->file_ptr = cur_file_ptr;
1627*3d8817e4Smiod   psym->proc_ptr = cur_proc_ptr;
1628*3d8817e4Smiod   psym->begin_ptr = (localsym_t *) NULL;
1629*3d8817e4Smiod   psym->index_ptr = (aux_t *) NULL;
1630*3d8817e4Smiod   psym->forward_ref = (forward_t *) NULL;
1631*3d8817e4Smiod   psym->sym_index = -1;
1632*3d8817e4Smiod   memset (&psym->ecoff_sym, 0, sizeof (EXTR));
1633*3d8817e4Smiod   psym->ecoff_sym.asym.value = value;
1634*3d8817e4Smiod   psym->ecoff_sym.asym.st = (unsigned) type;
1635*3d8817e4Smiod   psym->ecoff_sym.asym.sc = (unsigned) storage;
1636*3d8817e4Smiod   psym->ecoff_sym.asym.index = indx;
1637*3d8817e4Smiod 
1638*3d8817e4Smiod   /* If there is an associated symbol, we wait until the end of the
1639*3d8817e4Smiod      assembly before deciding where to put the name (it may be just an
1640*3d8817e4Smiod      external symbol).  Otherwise, this is just a debugging symbol and
1641*3d8817e4Smiod      the name should go with the current file.  */
1642*3d8817e4Smiod   if (sym_value == (symbolS *) NULL)
1643*3d8817e4Smiod     psym->ecoff_sym.asym.iss = ((str == (const char *) NULL)
1644*3d8817e4Smiod 				? 0
1645*3d8817e4Smiod 				: add_string (&cur_file_ptr->strings,
1646*3d8817e4Smiod 					      cur_file_ptr->str_hash,
1647*3d8817e4Smiod 					      str,
1648*3d8817e4Smiod 					      &hash_ptr));
1649*3d8817e4Smiod 
1650*3d8817e4Smiod   ++vp->num_allocated;
1651*3d8817e4Smiod 
1652*3d8817e4Smiod   if (ECOFF_IS_STAB (&psym->ecoff_sym.asym))
1653*3d8817e4Smiod     return psym;
1654*3d8817e4Smiod 
1655*3d8817e4Smiod   /* Save the symbol within the hash table if this is a static
1656*3d8817e4Smiod      item, and it has a name.  */
1657*3d8817e4Smiod   if (hash_ptr != (shash_t *) NULL
1658*3d8817e4Smiod       && (type == st_Global || type == st_Static || type == st_Label
1659*3d8817e4Smiod 	  || type == st_Proc || type == st_StaticProc))
1660*3d8817e4Smiod     hash_ptr->sym_ptr = psym;
1661*3d8817e4Smiod 
1662*3d8817e4Smiod   /* push or pop a scope if appropriate.  */
1663*3d8817e4Smiod   switch (type)
1664*3d8817e4Smiod     {
1665*3d8817e4Smiod     default:
1666*3d8817e4Smiod       break;
1667*3d8817e4Smiod 
1668*3d8817e4Smiod     case st_File:			/* beginning of file */
1669*3d8817e4Smiod     case st_Proc:			/* procedure */
1670*3d8817e4Smiod     case st_StaticProc:			/* static procedure */
1671*3d8817e4Smiod     case st_Block:			/* begin scope */
1672*3d8817e4Smiod       pscope = allocate_scope ();
1673*3d8817e4Smiod       pscope->prev = cur_file_ptr->cur_scope;
1674*3d8817e4Smiod       pscope->lsym = psym;
1675*3d8817e4Smiod       pscope->type = type;
1676*3d8817e4Smiod       cur_file_ptr->cur_scope = pscope;
1677*3d8817e4Smiod 
1678*3d8817e4Smiod       if (type != st_File)
1679*3d8817e4Smiod 	scope_delta = 1;
1680*3d8817e4Smiod 
1681*3d8817e4Smiod       /* For every block type except file, struct, union, or
1682*3d8817e4Smiod          enumeration blocks, push a level on the tag stack.  We omit
1683*3d8817e4Smiod          file types, so that tags can span file boundaries.  */
1684*3d8817e4Smiod       if (type != st_File && storage != sc_Info)
1685*3d8817e4Smiod 	{
1686*3d8817e4Smiod 	  ptag_head = allocate_thead ();
1687*3d8817e4Smiod 	  ptag_head->first_tag = 0;
1688*3d8817e4Smiod 	  ptag_head->prev = cur_tag_head;
1689*3d8817e4Smiod 	  cur_tag_head = ptag_head;
1690*3d8817e4Smiod 	}
1691*3d8817e4Smiod       break;
1692*3d8817e4Smiod 
1693*3d8817e4Smiod     case st_End:
1694*3d8817e4Smiod       pscope = cur_file_ptr->cur_scope;
1695*3d8817e4Smiod       if (pscope == (scope_t *) NULL)
1696*3d8817e4Smiod 	as_fatal (_("too many st_End's"));
1697*3d8817e4Smiod       else
1698*3d8817e4Smiod 	{
1699*3d8817e4Smiod 	  st_t begin_type = (st_t) pscope->lsym->ecoff_sym.asym.st;
1700*3d8817e4Smiod 
1701*3d8817e4Smiod 	  psym->begin_ptr = pscope->lsym;
1702*3d8817e4Smiod 
1703*3d8817e4Smiod 	  if (begin_type != st_File)
1704*3d8817e4Smiod 	    scope_delta = -1;
1705*3d8817e4Smiod 
1706*3d8817e4Smiod 	  /* Except for file, structure, union, or enumeration end
1707*3d8817e4Smiod 	     blocks remove all tags created within this scope.  */
1708*3d8817e4Smiod 	  if (begin_type != st_File && storage != sc_Info)
1709*3d8817e4Smiod 	    {
1710*3d8817e4Smiod 	      ptag_head = cur_tag_head;
1711*3d8817e4Smiod 	      cur_tag_head = ptag_head->prev;
1712*3d8817e4Smiod 
1713*3d8817e4Smiod 	      for (ptag = ptag_head->first_tag;
1714*3d8817e4Smiod 		   ptag != (tag_t *) NULL;
1715*3d8817e4Smiod 		   ptag = ptag_next)
1716*3d8817e4Smiod 		{
1717*3d8817e4Smiod 		  if (ptag->forward_ref != (forward_t *) NULL)
1718*3d8817e4Smiod 		    add_unknown_tag (ptag);
1719*3d8817e4Smiod 
1720*3d8817e4Smiod 		  ptag_next = ptag->same_block;
1721*3d8817e4Smiod 		  ptag->hash_ptr->tag_ptr = ptag->same_name;
1722*3d8817e4Smiod 		  free_tag (ptag);
1723*3d8817e4Smiod 		}
1724*3d8817e4Smiod 
1725*3d8817e4Smiod 	      free_thead (ptag_head);
1726*3d8817e4Smiod 	    }
1727*3d8817e4Smiod 
1728*3d8817e4Smiod 	  cur_file_ptr->cur_scope = pscope->prev;
1729*3d8817e4Smiod 
1730*3d8817e4Smiod 	  /* block begin gets next sym #.  This is set when we know
1731*3d8817e4Smiod 	     the symbol index value.  */
1732*3d8817e4Smiod 
1733*3d8817e4Smiod 	  /* Functions push two or more aux words as follows:
1734*3d8817e4Smiod 	     1st word: index+1 of the end symbol (filled in later).
1735*3d8817e4Smiod 	     2nd word: type of the function (plus any aux words needed).
1736*3d8817e4Smiod 	     Also, tie the external pointer back to the function begin symbol.  */
1737*3d8817e4Smiod 	  if (begin_type != st_File && begin_type != st_Block)
1738*3d8817e4Smiod 	    {
1739*3d8817e4Smiod 	      symint_t ty;
1740*3d8817e4Smiod 	      varray_t *svp = &cur_file_ptr->aux_syms;
1741*3d8817e4Smiod 
1742*3d8817e4Smiod 	      pscope->lsym->ecoff_sym.asym.index = add_aux_sym_symint (0);
1743*3d8817e4Smiod 	      pscope->lsym->index_ptr =
1744*3d8817e4Smiod 		&svp->last->datum->aux[svp->objects_last_page - 1];
1745*3d8817e4Smiod 	      ty = add_aux_sym_tir (&last_func_type_info,
1746*3d8817e4Smiod 				    hash_no,
1747*3d8817e4Smiod 				    &cur_file_ptr->thash_head[0]);
1748*3d8817e4Smiod 
1749*3d8817e4Smiod /* This seems to be unnecessary.  I'm not even sure what it is
1750*3d8817e4Smiod  * intended to do.  It's from mips-tfile.
1751*3d8817e4Smiod  *	      if (last_func_sym_value != (symbolS *) NULL)
1752*3d8817e4Smiod  *		{
1753*3d8817e4Smiod  *		  last_func_sym_value->ifd = cur_file_ptr->file_index;
1754*3d8817e4Smiod  *		  last_func_sym_value->index = ty;
1755*3d8817e4Smiod  *		}
1756*3d8817e4Smiod  */
1757*3d8817e4Smiod 	    }
1758*3d8817e4Smiod 
1759*3d8817e4Smiod 	  free_scope (pscope);
1760*3d8817e4Smiod 	}
1761*3d8817e4Smiod     }
1762*3d8817e4Smiod 
1763*3d8817e4Smiod   cur_file_ptr->nested_scopes += scope_delta;
1764*3d8817e4Smiod 
1765*3d8817e4Smiod #ifdef ECOFF_DEBUG
1766*3d8817e4Smiod   if (debug && type != st_File
1767*3d8817e4Smiod       && (debug > 2 || type == st_Block || type == st_End
1768*3d8817e4Smiod 	  || type == st_Proc || type == st_StaticProc))
1769*3d8817e4Smiod     {
1770*3d8817e4Smiod       char *sc_str = sc_to_string (storage);
1771*3d8817e4Smiod       char *st_str = st_to_string (type);
1772*3d8817e4Smiod       int depth = cur_file_ptr->nested_scopes + (scope_delta < 0);
1773*3d8817e4Smiod 
1774*3d8817e4Smiod       fprintf (stderr,
1775*3d8817e4Smiod 	       "\tlsym\tv= %10ld, depth= %2d, sc= %-12s",
1776*3d8817e4Smiod 	       value, depth, sc_str);
1777*3d8817e4Smiod 
1778*3d8817e4Smiod       if (str_start && str_end_p1 - str_start > 0)
1779*3d8817e4Smiod 	fprintf (stderr, " st= %-11s name= %.*s\n",
1780*3d8817e4Smiod 		 st_str, str_end_p1 - str_start, str_start);
1781*3d8817e4Smiod       else
1782*3d8817e4Smiod 	{
1783*3d8817e4Smiod 	  unsigned long len = strlen (st_str);
1784*3d8817e4Smiod 	  fprintf (stderr, " st= %.*s\n", len - 1, st_str);
1785*3d8817e4Smiod 	}
1786*3d8817e4Smiod     }
1787*3d8817e4Smiod #endif
1788*3d8817e4Smiod 
1789*3d8817e4Smiod   return psym;
1790*3d8817e4Smiod }
1791*3d8817e4Smiod 
1792*3d8817e4Smiod /* Add an auxiliary symbol (passing a symint).  This is actually used
1793*3d8817e4Smiod    for integral aux types, not just symints.  */
1794*3d8817e4Smiod 
1795*3d8817e4Smiod static symint_t
add_aux_sym_symint(symint_t aux_word)1796*3d8817e4Smiod add_aux_sym_symint (symint_t aux_word /* auxiliary information word */)
1797*3d8817e4Smiod {
1798*3d8817e4Smiod   register varray_t *vp;
1799*3d8817e4Smiod   register aux_t *aux_ptr;
1800*3d8817e4Smiod 
1801*3d8817e4Smiod   if (cur_file_ptr == (efdr_t *) NULL)
1802*3d8817e4Smiod     as_fatal (_("no current file pointer"));
1803*3d8817e4Smiod 
1804*3d8817e4Smiod   vp = &cur_file_ptr->aux_syms;
1805*3d8817e4Smiod 
1806*3d8817e4Smiod   if (vp->objects_last_page == vp->objects_per_page)
1807*3d8817e4Smiod     add_varray_page (vp);
1808*3d8817e4Smiod 
1809*3d8817e4Smiod   aux_ptr = &vp->last->datum->aux[vp->objects_last_page++];
1810*3d8817e4Smiod   aux_ptr->type = aux_isym;
1811*3d8817e4Smiod   aux_ptr->data.isym = aux_word;
1812*3d8817e4Smiod 
1813*3d8817e4Smiod   return vp->num_allocated++;
1814*3d8817e4Smiod }
1815*3d8817e4Smiod 
1816*3d8817e4Smiod /* Add an auxiliary symbol (passing a file/symbol index combo).  */
1817*3d8817e4Smiod 
1818*3d8817e4Smiod static symint_t
add_aux_sym_rndx(int file_index,symint_t sym_index)1819*3d8817e4Smiod add_aux_sym_rndx (int file_index, symint_t sym_index)
1820*3d8817e4Smiod {
1821*3d8817e4Smiod   register varray_t *vp;
1822*3d8817e4Smiod   register aux_t *aux_ptr;
1823*3d8817e4Smiod 
1824*3d8817e4Smiod   if (cur_file_ptr == (efdr_t *) NULL)
1825*3d8817e4Smiod     as_fatal (_("no current file pointer"));
1826*3d8817e4Smiod 
1827*3d8817e4Smiod   vp = &cur_file_ptr->aux_syms;
1828*3d8817e4Smiod 
1829*3d8817e4Smiod   if (vp->objects_last_page == vp->objects_per_page)
1830*3d8817e4Smiod     add_varray_page (vp);
1831*3d8817e4Smiod 
1832*3d8817e4Smiod   aux_ptr = &vp->last->datum->aux[vp->objects_last_page++];
1833*3d8817e4Smiod   aux_ptr->type = aux_rndx;
1834*3d8817e4Smiod   aux_ptr->data.rndx.rfd   = file_index;
1835*3d8817e4Smiod   aux_ptr->data.rndx.index = sym_index;
1836*3d8817e4Smiod 
1837*3d8817e4Smiod   return vp->num_allocated++;
1838*3d8817e4Smiod }
1839*3d8817e4Smiod 
1840*3d8817e4Smiod /* Add an auxiliary symbol (passing the basic type and possibly
1841*3d8817e4Smiod    type qualifiers).  */
1842*3d8817e4Smiod 
1843*3d8817e4Smiod static symint_t
add_aux_sym_tir(type_info_t * t,hash_state_t state,thash_t ** hash_tbl)1844*3d8817e4Smiod add_aux_sym_tir (type_info_t *t,	/* current type information */
1845*3d8817e4Smiod 		 hash_state_t state,	/* whether to hash type or not */
1846*3d8817e4Smiod 		 thash_t **hash_tbl	/* pointer to hash table to use */)
1847*3d8817e4Smiod {
1848*3d8817e4Smiod   register varray_t *vp;
1849*3d8817e4Smiod   register aux_t *aux_ptr;
1850*3d8817e4Smiod   static AUXU init_aux;
1851*3d8817e4Smiod   symint_t ret;
1852*3d8817e4Smiod   int i;
1853*3d8817e4Smiod   AUXU aux;
1854*3d8817e4Smiod 
1855*3d8817e4Smiod   if (cur_file_ptr == (efdr_t *) NULL)
1856*3d8817e4Smiod     as_fatal (_("no current file pointer"));
1857*3d8817e4Smiod 
1858*3d8817e4Smiod   vp = &cur_file_ptr->aux_syms;
1859*3d8817e4Smiod 
1860*3d8817e4Smiod   aux = init_aux;
1861*3d8817e4Smiod   aux.ti.bt = (int) t->basic_type;
1862*3d8817e4Smiod   aux.ti.continued = 0;
1863*3d8817e4Smiod   aux.ti.fBitfield = t->bitfield;
1864*3d8817e4Smiod 
1865*3d8817e4Smiod   aux.ti.tq0 = (int) t->type_qualifiers[0];
1866*3d8817e4Smiod   aux.ti.tq1 = (int) t->type_qualifiers[1];
1867*3d8817e4Smiod   aux.ti.tq2 = (int) t->type_qualifiers[2];
1868*3d8817e4Smiod   aux.ti.tq3 = (int) t->type_qualifiers[3];
1869*3d8817e4Smiod   aux.ti.tq4 = (int) t->type_qualifiers[4];
1870*3d8817e4Smiod   aux.ti.tq5 = (int) t->type_qualifiers[5];
1871*3d8817e4Smiod 
1872*3d8817e4Smiod   /* For anything that adds additional information, we must not hash,
1873*3d8817e4Smiod      so check here, and reset our state.  */
1874*3d8817e4Smiod 
1875*3d8817e4Smiod   if (state != hash_no
1876*3d8817e4Smiod       && (t->type_qualifiers[0] == tq_Array
1877*3d8817e4Smiod 	  || t->type_qualifiers[1] == tq_Array
1878*3d8817e4Smiod 	  || t->type_qualifiers[2] == tq_Array
1879*3d8817e4Smiod 	  || t->type_qualifiers[3] == tq_Array
1880*3d8817e4Smiod 	  || t->type_qualifiers[4] == tq_Array
1881*3d8817e4Smiod 	  || t->type_qualifiers[5] == tq_Array
1882*3d8817e4Smiod 	  || t->basic_type == bt_Struct
1883*3d8817e4Smiod 	  || t->basic_type == bt_Union
1884*3d8817e4Smiod 	  || t->basic_type == bt_Enum
1885*3d8817e4Smiod 	  || t->bitfield
1886*3d8817e4Smiod 	  || t->num_dims > 0))
1887*3d8817e4Smiod     state = hash_no;
1888*3d8817e4Smiod 
1889*3d8817e4Smiod   /* See if we can hash this type, and save some space, but some types
1890*3d8817e4Smiod      can't be hashed (because they contain arrays or continuations),
1891*3d8817e4Smiod      and others can be put into the hash list, but cannot use existing
1892*3d8817e4Smiod      types because other aux entries precede this one.  */
1893*3d8817e4Smiod 
1894*3d8817e4Smiod   if (state != hash_no)
1895*3d8817e4Smiod     {
1896*3d8817e4Smiod       register thash_t *hash_ptr;
1897*3d8817e4Smiod       register symint_t hi;
1898*3d8817e4Smiod 
1899*3d8817e4Smiod       hi = aux.isym & ((1 << HASHBITS) - 1);
1900*3d8817e4Smiod       hi %= THASH_SIZE;
1901*3d8817e4Smiod 
1902*3d8817e4Smiod       for (hash_ptr = hash_tbl[hi];
1903*3d8817e4Smiod 	   hash_ptr != (thash_t *)0;
1904*3d8817e4Smiod 	   hash_ptr = hash_ptr->next)
1905*3d8817e4Smiod 	{
1906*3d8817e4Smiod 	  if (aux.isym == hash_ptr->type.isym)
1907*3d8817e4Smiod 	    break;
1908*3d8817e4Smiod 	}
1909*3d8817e4Smiod 
1910*3d8817e4Smiod       if (hash_ptr != (thash_t *) NULL && state == hash_yes)
1911*3d8817e4Smiod 	return hash_ptr->indx;
1912*3d8817e4Smiod 
1913*3d8817e4Smiod       if (hash_ptr == (thash_t *) NULL)
1914*3d8817e4Smiod 	{
1915*3d8817e4Smiod 	  hash_ptr = allocate_thash ();
1916*3d8817e4Smiod 	  hash_ptr->next = hash_tbl[hi];
1917*3d8817e4Smiod 	  hash_ptr->type = aux;
1918*3d8817e4Smiod 	  hash_ptr->indx = vp->num_allocated;
1919*3d8817e4Smiod 	  hash_tbl[hi] = hash_ptr;
1920*3d8817e4Smiod 	}
1921*3d8817e4Smiod     }
1922*3d8817e4Smiod 
1923*3d8817e4Smiod   /* Everything is set up, add the aux symbol.  */
1924*3d8817e4Smiod   if (vp->objects_last_page == vp->objects_per_page)
1925*3d8817e4Smiod     add_varray_page (vp);
1926*3d8817e4Smiod 
1927*3d8817e4Smiod   aux_ptr = &vp->last->datum->aux[vp->objects_last_page++];
1928*3d8817e4Smiod   aux_ptr->type = aux_tir;
1929*3d8817e4Smiod   aux_ptr->data = aux;
1930*3d8817e4Smiod 
1931*3d8817e4Smiod   ret = vp->num_allocated++;
1932*3d8817e4Smiod 
1933*3d8817e4Smiod   /* Add bitfield length if it exists.
1934*3d8817e4Smiod 
1935*3d8817e4Smiod      NOTE:  Mips documentation claims bitfield goes at the end of the
1936*3d8817e4Smiod      AUX record, but the DECstation compiler emits it here.
1937*3d8817e4Smiod      (This would only make a difference for enum bitfields.)
1938*3d8817e4Smiod 
1939*3d8817e4Smiod      Also note:  We use the last size given since gcc may emit 2
1940*3d8817e4Smiod      for an enum bitfield.  */
1941*3d8817e4Smiod 
1942*3d8817e4Smiod   if (t->bitfield)
1943*3d8817e4Smiod     (void) add_aux_sym_symint ((symint_t) t->sizes[t->num_sizes - 1]);
1944*3d8817e4Smiod 
1945*3d8817e4Smiod   /* Add tag information if needed.  Structure, union, and enum
1946*3d8817e4Smiod      references add 2 aux symbols: a [file index, symbol index]
1947*3d8817e4Smiod      pointer to the structure type, and the current file index.  */
1948*3d8817e4Smiod 
1949*3d8817e4Smiod   if (t->basic_type == bt_Struct
1950*3d8817e4Smiod       || t->basic_type == bt_Union
1951*3d8817e4Smiod       || t->basic_type == bt_Enum)
1952*3d8817e4Smiod     {
1953*3d8817e4Smiod       register symint_t file_index = t->tag_ptr->ifd;
1954*3d8817e4Smiod       register localsym_t *sym = t->tag_ptr->sym;
1955*3d8817e4Smiod       register forward_t *forward_ref = allocate_forward ();
1956*3d8817e4Smiod 
1957*3d8817e4Smiod       if (sym != (localsym_t *) NULL)
1958*3d8817e4Smiod 	{
1959*3d8817e4Smiod 	  forward_ref->next = sym->forward_ref;
1960*3d8817e4Smiod 	  sym->forward_ref = forward_ref;
1961*3d8817e4Smiod 	}
1962*3d8817e4Smiod       else
1963*3d8817e4Smiod 	{
1964*3d8817e4Smiod 	  forward_ref->next = t->tag_ptr->forward_ref;
1965*3d8817e4Smiod 	  t->tag_ptr->forward_ref = forward_ref;
1966*3d8817e4Smiod 	}
1967*3d8817e4Smiod 
1968*3d8817e4Smiod       (void) add_aux_sym_rndx (ST_RFDESCAPE, indexNil);
1969*3d8817e4Smiod       forward_ref->index_ptr
1970*3d8817e4Smiod 	= &vp->last->datum->aux[vp->objects_last_page - 1];
1971*3d8817e4Smiod 
1972*3d8817e4Smiod       (void) add_aux_sym_symint (file_index);
1973*3d8817e4Smiod       forward_ref->ifd_ptr
1974*3d8817e4Smiod 	= &vp->last->datum->aux[vp->objects_last_page - 1];
1975*3d8817e4Smiod     }
1976*3d8817e4Smiod 
1977*3d8817e4Smiod   /* Add information about array bounds if they exist.  */
1978*3d8817e4Smiod   for (i = 0; i < t->num_dims; i++)
1979*3d8817e4Smiod     {
1980*3d8817e4Smiod       (void) add_aux_sym_rndx (ST_RFDESCAPE,
1981*3d8817e4Smiod 			       cur_file_ptr->int_type);
1982*3d8817e4Smiod 
1983*3d8817e4Smiod       (void) add_aux_sym_symint (cur_file_ptr->file_index);	/* file index*/
1984*3d8817e4Smiod       (void) add_aux_sym_symint ((symint_t) 0);			/* low bound */
1985*3d8817e4Smiod       (void) add_aux_sym_symint (t->dimensions[i] - 1);		/* high bound*/
1986*3d8817e4Smiod       (void) add_aux_sym_symint ((t->dimensions[i] == 0)	/* stride */
1987*3d8817e4Smiod 				 ? 0
1988*3d8817e4Smiod 				 : (t->sizes[i] * 8) / t->dimensions[i]);
1989*3d8817e4Smiod     };
1990*3d8817e4Smiod 
1991*3d8817e4Smiod   /* NOTE:  Mips documentation claims that the bitfield width goes here.
1992*3d8817e4Smiod      But it needs to be emitted earlier.  */
1993*3d8817e4Smiod 
1994*3d8817e4Smiod   return ret;
1995*3d8817e4Smiod }
1996*3d8817e4Smiod 
1997*3d8817e4Smiod /* Add a tag to the tag table (unless it already exists).  */
1998*3d8817e4Smiod 
1999*3d8817e4Smiod static tag_t *
get_tag(const char * tag,localsym_t * sym,bt_t basic_type)2000*3d8817e4Smiod get_tag (const char *tag,	/* tag name */
2001*3d8817e4Smiod 	 localsym_t *sym,	/* tag start block */
2002*3d8817e4Smiod 	 bt_t basic_type	/* bt_Struct, bt_Union, or bt_Enum */)
2003*3d8817e4Smiod {
2004*3d8817e4Smiod   shash_t *hash_ptr;
2005*3d8817e4Smiod   const char *err;
2006*3d8817e4Smiod   tag_t *tag_ptr;
2007*3d8817e4Smiod 
2008*3d8817e4Smiod   if (cur_file_ptr == (efdr_t *) NULL)
2009*3d8817e4Smiod     as_fatal (_("no current file pointer"));
2010*3d8817e4Smiod 
2011*3d8817e4Smiod   hash_ptr = (shash_t *) hash_find (tag_hash, tag);
2012*3d8817e4Smiod 
2013*3d8817e4Smiod   if (hash_ptr != (shash_t *) NULL
2014*3d8817e4Smiod       && hash_ptr->tag_ptr != (tag_t *) NULL)
2015*3d8817e4Smiod     {
2016*3d8817e4Smiod       tag_ptr = hash_ptr->tag_ptr;
2017*3d8817e4Smiod       if (sym != (localsym_t *) NULL)
2018*3d8817e4Smiod 	{
2019*3d8817e4Smiod 	  tag_ptr->basic_type = basic_type;
2020*3d8817e4Smiod 	  tag_ptr->ifd        = cur_file_ptr->file_index;
2021*3d8817e4Smiod 	  tag_ptr->sym        = sym;
2022*3d8817e4Smiod 	}
2023*3d8817e4Smiod       return tag_ptr;
2024*3d8817e4Smiod     }
2025*3d8817e4Smiod 
2026*3d8817e4Smiod   if (hash_ptr == (shash_t *) NULL)
2027*3d8817e4Smiod     {
2028*3d8817e4Smiod       char *perm;
2029*3d8817e4Smiod 
2030*3d8817e4Smiod       perm = xstrdup (tag);
2031*3d8817e4Smiod       hash_ptr = allocate_shash ();
2032*3d8817e4Smiod       err = hash_insert (tag_hash, perm, (char *) hash_ptr);
2033*3d8817e4Smiod       if (err)
2034*3d8817e4Smiod 	as_fatal (_("inserting \"%s\" into tag hash table: %s"),
2035*3d8817e4Smiod 		  tag, err);
2036*3d8817e4Smiod       hash_ptr->string = perm;
2037*3d8817e4Smiod     }
2038*3d8817e4Smiod 
2039*3d8817e4Smiod   tag_ptr = allocate_tag ();
2040*3d8817e4Smiod   tag_ptr->forward_ref	= (forward_t *) NULL;
2041*3d8817e4Smiod   tag_ptr->hash_ptr	= hash_ptr;
2042*3d8817e4Smiod   tag_ptr->same_name	= hash_ptr->tag_ptr;
2043*3d8817e4Smiod   tag_ptr->basic_type	= basic_type;
2044*3d8817e4Smiod   tag_ptr->sym		= sym;
2045*3d8817e4Smiod   tag_ptr->ifd		= ((sym == (localsym_t *) NULL)
2046*3d8817e4Smiod 			   ? (symint_t) -1
2047*3d8817e4Smiod 			   : cur_file_ptr->file_index);
2048*3d8817e4Smiod   tag_ptr->same_block	= cur_tag_head->first_tag;
2049*3d8817e4Smiod 
2050*3d8817e4Smiod   cur_tag_head->first_tag = tag_ptr;
2051*3d8817e4Smiod   hash_ptr->tag_ptr	  = tag_ptr;
2052*3d8817e4Smiod 
2053*3d8817e4Smiod   return tag_ptr;
2054*3d8817e4Smiod }
2055*3d8817e4Smiod 
2056*3d8817e4Smiod /* Add an unknown {struct, union, enum} tag.  */
2057*3d8817e4Smiod 
2058*3d8817e4Smiod static void
add_unknown_tag(tag_t * ptag)2059*3d8817e4Smiod add_unknown_tag (tag_t *ptag /* pointer to tag information */)
2060*3d8817e4Smiod {
2061*3d8817e4Smiod   shash_t *hash_ptr	= ptag->hash_ptr;
2062*3d8817e4Smiod   char *name		= hash_ptr->string;
2063*3d8817e4Smiod   localsym_t *sym;
2064*3d8817e4Smiod   forward_t **pf;
2065*3d8817e4Smiod 
2066*3d8817e4Smiod #ifdef ECOFF_DEBUG
2067*3d8817e4Smiod   if (debug > 1)
2068*3d8817e4Smiod     {
2069*3d8817e4Smiod       char *agg_type = "{unknown aggregate type}";
2070*3d8817e4Smiod       switch (ptag->basic_type)
2071*3d8817e4Smiod 	{
2072*3d8817e4Smiod 	case bt_Struct:	agg_type = "struct";	break;
2073*3d8817e4Smiod 	case bt_Union:	agg_type = "union";	break;
2074*3d8817e4Smiod 	case bt_Enum:	agg_type = "enum";	break;
2075*3d8817e4Smiod 	default:				break;
2076*3d8817e4Smiod 	}
2077*3d8817e4Smiod 
2078*3d8817e4Smiod       fprintf (stderr, "unknown %s %.*s found\n", agg_type,
2079*3d8817e4Smiod 	       hash_ptr->len, name_start);
2080*3d8817e4Smiod     }
2081*3d8817e4Smiod #endif
2082*3d8817e4Smiod 
2083*3d8817e4Smiod   sym = add_ecoff_symbol (name,
2084*3d8817e4Smiod 			  st_Block,
2085*3d8817e4Smiod 			  sc_Info,
2086*3d8817e4Smiod 			  (symbolS *) NULL,
2087*3d8817e4Smiod 			  (bfd_vma) 0,
2088*3d8817e4Smiod 			  (symint_t) 0,
2089*3d8817e4Smiod 			  (symint_t) 0);
2090*3d8817e4Smiod 
2091*3d8817e4Smiod   (void) add_ecoff_symbol (name,
2092*3d8817e4Smiod 			   st_End,
2093*3d8817e4Smiod 			   sc_Info,
2094*3d8817e4Smiod 			   (symbolS *) NULL,
2095*3d8817e4Smiod 			   (bfd_vma) 0,
2096*3d8817e4Smiod 			   (symint_t) 0,
2097*3d8817e4Smiod 			   (symint_t) 0);
2098*3d8817e4Smiod 
2099*3d8817e4Smiod   for (pf = &sym->forward_ref; *pf != (forward_t *) NULL; pf = &(*pf)->next)
2100*3d8817e4Smiod     ;
2101*3d8817e4Smiod   *pf = ptag->forward_ref;
2102*3d8817e4Smiod }
2103*3d8817e4Smiod 
2104*3d8817e4Smiod /* Add a procedure to the current file's list of procedures, and record
2105*3d8817e4Smiod    this is the current procedure.  */
2106*3d8817e4Smiod 
2107*3d8817e4Smiod static void
add_procedure(char * func)2108*3d8817e4Smiod add_procedure (char *func /* func name */)
2109*3d8817e4Smiod {
2110*3d8817e4Smiod   register varray_t *vp;
2111*3d8817e4Smiod   register proc_t *new_proc_ptr;
2112*3d8817e4Smiod   symbolS *sym;
2113*3d8817e4Smiod 
2114*3d8817e4Smiod #ifdef ECOFF_DEBUG
2115*3d8817e4Smiod   if (debug)
2116*3d8817e4Smiod     fputc ('\n', stderr);
2117*3d8817e4Smiod #endif
2118*3d8817e4Smiod 
2119*3d8817e4Smiod   if (cur_file_ptr == (efdr_t *) NULL)
2120*3d8817e4Smiod     as_fatal (_("no current file pointer"));
2121*3d8817e4Smiod 
2122*3d8817e4Smiod   vp = &cur_file_ptr->procs;
2123*3d8817e4Smiod 
2124*3d8817e4Smiod   if (vp->objects_last_page == vp->objects_per_page)
2125*3d8817e4Smiod     add_varray_page (vp);
2126*3d8817e4Smiod 
2127*3d8817e4Smiod   cur_proc_ptr = new_proc_ptr = &vp->last->datum->proc[vp->objects_last_page++];
2128*3d8817e4Smiod 
2129*3d8817e4Smiod   if (first_proc_ptr == (proc_t *) NULL)
2130*3d8817e4Smiod     first_proc_ptr = new_proc_ptr;
2131*3d8817e4Smiod 
2132*3d8817e4Smiod   vp->num_allocated++;
2133*3d8817e4Smiod 
2134*3d8817e4Smiod   new_proc_ptr->pdr.isym = -1;
2135*3d8817e4Smiod   new_proc_ptr->pdr.iline = -1;
2136*3d8817e4Smiod   new_proc_ptr->pdr.lnLow = -1;
2137*3d8817e4Smiod   new_proc_ptr->pdr.lnHigh = -1;
2138*3d8817e4Smiod 
2139*3d8817e4Smiod   /* Set the BSF_FUNCTION flag for the symbol.  */
2140*3d8817e4Smiod   sym = symbol_find_or_make (func);
2141*3d8817e4Smiod   symbol_get_bfdsym (sym)->flags |= BSF_FUNCTION;
2142*3d8817e4Smiod 
2143*3d8817e4Smiod   /* Push the start of the function.  */
2144*3d8817e4Smiod   new_proc_ptr->sym = add_ecoff_symbol ((const char *) NULL, st_Proc, sc_Text,
2145*3d8817e4Smiod 					sym, (bfd_vma) 0, (symint_t) 0,
2146*3d8817e4Smiod 					(symint_t) 0);
2147*3d8817e4Smiod 
2148*3d8817e4Smiod   ++proc_cnt;
2149*3d8817e4Smiod 
2150*3d8817e4Smiod   /* Fill in the linenos preceding the .ent, if any.  */
2151*3d8817e4Smiod   if (noproc_lineno != (lineno_list_t *) NULL)
2152*3d8817e4Smiod     {
2153*3d8817e4Smiod       lineno_list_t *l;
2154*3d8817e4Smiod 
2155*3d8817e4Smiod       for (l = noproc_lineno; l != (lineno_list_t *) NULL; l = l->next)
2156*3d8817e4Smiod 	l->proc = new_proc_ptr;
2157*3d8817e4Smiod       *last_lineno_ptr = noproc_lineno;
2158*3d8817e4Smiod       while (*last_lineno_ptr != NULL)
2159*3d8817e4Smiod 	{
2160*3d8817e4Smiod 	  last_lineno = *last_lineno_ptr;
2161*3d8817e4Smiod 	  last_lineno_ptr = &last_lineno->next;
2162*3d8817e4Smiod 	}
2163*3d8817e4Smiod       noproc_lineno = (lineno_list_t *) NULL;
2164*3d8817e4Smiod     }
2165*3d8817e4Smiod }
2166*3d8817e4Smiod 
2167*3d8817e4Smiod symbolS *
ecoff_get_cur_proc_sym(void)2168*3d8817e4Smiod ecoff_get_cur_proc_sym (void)
2169*3d8817e4Smiod {
2170*3d8817e4Smiod   return (cur_proc_ptr ? cur_proc_ptr->sym->as_sym : NULL);
2171*3d8817e4Smiod }
2172*3d8817e4Smiod 
2173*3d8817e4Smiod /* Add a new filename, and set up all of the file relative
2174*3d8817e4Smiod    virtual arrays (strings, symbols, aux syms, etc.).  Record
2175*3d8817e4Smiod    where the current file structure lives.  */
2176*3d8817e4Smiod 
2177*3d8817e4Smiod static void
add_file(const char * file_name,int indx ATTRIBUTE_UNUSED,int fake)2178*3d8817e4Smiod add_file (const char *file_name, int indx ATTRIBUTE_UNUSED, int fake)
2179*3d8817e4Smiod {
2180*3d8817e4Smiod   register int first_ch;
2181*3d8817e4Smiod   register efdr_t *fil_ptr;
2182*3d8817e4Smiod 
2183*3d8817e4Smiod #ifdef ECOFF_DEBUG
2184*3d8817e4Smiod   if (debug)
2185*3d8817e4Smiod     fprintf (stderr, "\tfile\t%.*s\n", len, file_start);
2186*3d8817e4Smiod #endif
2187*3d8817e4Smiod 
2188*3d8817e4Smiod   /* If the file name is NULL, then no .file symbol appeared, and we
2189*3d8817e4Smiod      want to use the actual file name.  */
2190*3d8817e4Smiod   if (file_name == (const char *) NULL)
2191*3d8817e4Smiod     {
2192*3d8817e4Smiod       char *file;
2193*3d8817e4Smiod 
2194*3d8817e4Smiod       if (first_file != (efdr_t *) NULL)
2195*3d8817e4Smiod 	as_fatal (_("fake .file after real one"));
2196*3d8817e4Smiod       as_where (&file, (unsigned int *) NULL);
2197*3d8817e4Smiod       file_name = (const char *) file;
2198*3d8817e4Smiod 
2199*3d8817e4Smiod       /* Automatically generate ECOFF debugging information, since I
2200*3d8817e4Smiod          think that's what other ECOFF assemblers do.  We don't do
2201*3d8817e4Smiod          this if we see a .file directive with a string, since that
2202*3d8817e4Smiod          implies that some sort of debugging information is being
2203*3d8817e4Smiod          provided.  */
2204*3d8817e4Smiod       if (! symbol_table_frozen && debug_type == DEBUG_UNSPECIFIED)
2205*3d8817e4Smiod 	debug_type = DEBUG_ECOFF;
2206*3d8817e4Smiod     }
2207*3d8817e4Smiod   else if (debug_type == DEBUG_UNSPECIFIED)
2208*3d8817e4Smiod     debug_type = DEBUG_NONE;
2209*3d8817e4Smiod 
2210*3d8817e4Smiod #ifndef NO_LISTING
2211*3d8817e4Smiod   if (listing)
2212*3d8817e4Smiod     listing_source_file (file_name);
2213*3d8817e4Smiod #endif
2214*3d8817e4Smiod 
2215*3d8817e4Smiod   current_stabs_filename = file_name;
2216*3d8817e4Smiod 
2217*3d8817e4Smiod   /* If we're creating stabs, then we don't actually make a new FDR.
2218*3d8817e4Smiod      Instead, we just create a stabs symbol.  */
2219*3d8817e4Smiod   if (stabs_seen)
2220*3d8817e4Smiod     {
2221*3d8817e4Smiod       (void) add_ecoff_symbol (file_name, st_Nil, sc_Nil,
2222*3d8817e4Smiod 			       symbol_new ("L0\001", now_seg,
2223*3d8817e4Smiod 					   (valueT) frag_now_fix (),
2224*3d8817e4Smiod 					   frag_now),
2225*3d8817e4Smiod 			       (bfd_vma) 0, 0, ECOFF_MARK_STAB (N_SOL));
2226*3d8817e4Smiod       return;
2227*3d8817e4Smiod     }
2228*3d8817e4Smiod 
2229*3d8817e4Smiod   first_ch = *file_name;
2230*3d8817e4Smiod 
2231*3d8817e4Smiod   /* FIXME: We can't safely merge files which have line number
2232*3d8817e4Smiod      information (fMerge will be zero in this case).  Otherwise, we
2233*3d8817e4Smiod      get incorrect line number debugging info.  See for instance
2234*3d8817e4Smiod      ecoff_build_lineno, which will end up setting all file->fdr.*
2235*3d8817e4Smiod      fields multiple times, resulting in incorrect debug info.  In
2236*3d8817e4Smiod      order to make this work right, all line number and symbol info
2237*3d8817e4Smiod      for the same source file has to be adjacent in the object file,
2238*3d8817e4Smiod      so that a single file descriptor can be used to point to them.
2239*3d8817e4Smiod      This would require maintaining file specific lists of line
2240*3d8817e4Smiod      numbers and symbols for each file, so that they can be merged
2241*3d8817e4Smiod      together (or output together) when two .file pseudo-ops are
2242*3d8817e4Smiod      merged into one file descriptor.  */
2243*3d8817e4Smiod 
2244*3d8817e4Smiod   /* See if the file has already been created.  */
2245*3d8817e4Smiod   for (fil_ptr = first_file;
2246*3d8817e4Smiod        fil_ptr != (efdr_t *) NULL;
2247*3d8817e4Smiod        fil_ptr = fil_ptr->next_file)
2248*3d8817e4Smiod     {
2249*3d8817e4Smiod       if (first_ch == fil_ptr->name[0]
2250*3d8817e4Smiod 	  && strcmp (file_name, fil_ptr->name) == 0
2251*3d8817e4Smiod 	  && fil_ptr->fdr.fMerge)
2252*3d8817e4Smiod 	{
2253*3d8817e4Smiod 	  cur_file_ptr = fil_ptr;
2254*3d8817e4Smiod 	  if (! fake)
2255*3d8817e4Smiod 	    cur_file_ptr->fake = 0;
2256*3d8817e4Smiod 	  break;
2257*3d8817e4Smiod 	}
2258*3d8817e4Smiod     }
2259*3d8817e4Smiod 
2260*3d8817e4Smiod   /* If this is a new file, create it.  */
2261*3d8817e4Smiod   if (fil_ptr == (efdr_t *) NULL)
2262*3d8817e4Smiod     {
2263*3d8817e4Smiod       if (file_desc.objects_last_page == file_desc.objects_per_page)
2264*3d8817e4Smiod 	add_varray_page (&file_desc);
2265*3d8817e4Smiod 
2266*3d8817e4Smiod       fil_ptr = cur_file_ptr =
2267*3d8817e4Smiod 	&file_desc.last->datum->file[file_desc.objects_last_page++];
2268*3d8817e4Smiod       *fil_ptr = init_file;
2269*3d8817e4Smiod 
2270*3d8817e4Smiod       fil_ptr->file_index = current_file_idx++;
2271*3d8817e4Smiod       ++file_desc.num_allocated;
2272*3d8817e4Smiod 
2273*3d8817e4Smiod       fil_ptr->fake = fake;
2274*3d8817e4Smiod 
2275*3d8817e4Smiod       /* Allocate the string hash table.  */
2276*3d8817e4Smiod       fil_ptr->str_hash = hash_new ();
2277*3d8817e4Smiod 
2278*3d8817e4Smiod       /* Make sure 0 byte in string table is null  */
2279*3d8817e4Smiod       add_string (&fil_ptr->strings,
2280*3d8817e4Smiod 		  fil_ptr->str_hash,
2281*3d8817e4Smiod 		  "",
2282*3d8817e4Smiod 		  (shash_t **)0);
2283*3d8817e4Smiod 
2284*3d8817e4Smiod       if (strlen (file_name) > PAGE_USIZE - 2)
2285*3d8817e4Smiod 	as_fatal (_("filename goes over one page boundary"));
2286*3d8817e4Smiod 
2287*3d8817e4Smiod       /* Push the start of the filename. We assume that the filename
2288*3d8817e4Smiod          will be stored at string offset 1.  */
2289*3d8817e4Smiod       (void) add_ecoff_symbol (file_name, st_File, sc_Text,
2290*3d8817e4Smiod 			       (symbolS *) NULL, (bfd_vma) 0,
2291*3d8817e4Smiod 			       (symint_t) 0, (symint_t) 0);
2292*3d8817e4Smiod       fil_ptr->fdr.rss = 1;
2293*3d8817e4Smiod       fil_ptr->name = &fil_ptr->strings.last->datum->byte[1];
2294*3d8817e4Smiod 
2295*3d8817e4Smiod       /* Update the linked list of file descriptors.  */
2296*3d8817e4Smiod       *last_file_ptr = fil_ptr;
2297*3d8817e4Smiod       last_file_ptr = &fil_ptr->next_file;
2298*3d8817e4Smiod 
2299*3d8817e4Smiod       /* Add void & int types to the file (void should be first to catch
2300*3d8817e4Smiod          errant 0's within the index fields).  */
2301*3d8817e4Smiod       fil_ptr->void_type = add_aux_sym_tir (&void_type_info,
2302*3d8817e4Smiod 					    hash_yes,
2303*3d8817e4Smiod 					    &cur_file_ptr->thash_head[0]);
2304*3d8817e4Smiod 
2305*3d8817e4Smiod       fil_ptr->int_type = add_aux_sym_tir (&int_type_info,
2306*3d8817e4Smiod 					   hash_yes,
2307*3d8817e4Smiod 					   &cur_file_ptr->thash_head[0]);
2308*3d8817e4Smiod     }
2309*3d8817e4Smiod }
2310*3d8817e4Smiod 
2311*3d8817e4Smiod /* This function is called when the assembler notices a preprocessor
2312*3d8817e4Smiod    directive switching to a new file.  This will not happen in
2313*3d8817e4Smiod    compiler output, only in hand coded assembler.  */
2314*3d8817e4Smiod 
2315*3d8817e4Smiod void
ecoff_new_file(const char * name,int appfile ATTRIBUTE_UNUSED)2316*3d8817e4Smiod ecoff_new_file (const char *name, int appfile ATTRIBUTE_UNUSED)
2317*3d8817e4Smiod {
2318*3d8817e4Smiod   if (cur_file_ptr != NULL && strcmp (cur_file_ptr->name, name) == 0)
2319*3d8817e4Smiod     return;
2320*3d8817e4Smiod   add_file (name, 0, 0);
2321*3d8817e4Smiod 
2322*3d8817e4Smiod   /* This is a hand coded assembler file, so automatically turn on
2323*3d8817e4Smiod      debugging information.  */
2324*3d8817e4Smiod   if (debug_type == DEBUG_UNSPECIFIED)
2325*3d8817e4Smiod     debug_type = DEBUG_ECOFF;
2326*3d8817e4Smiod }
2327*3d8817e4Smiod 
2328*3d8817e4Smiod #ifdef ECOFF_DEBUG
2329*3d8817e4Smiod 
2330*3d8817e4Smiod /* Convert storage class to string.  */
2331*3d8817e4Smiod 
2332*3d8817e4Smiod static char *
sc_to_string(storage_class)2333*3d8817e4Smiod sc_to_string (storage_class)
2334*3d8817e4Smiod      sc_t storage_class;
2335*3d8817e4Smiod {
2336*3d8817e4Smiod   switch (storage_class)
2337*3d8817e4Smiod     {
2338*3d8817e4Smiod     case sc_Nil:	 return "Nil,";
2339*3d8817e4Smiod     case sc_Text:	 return "Text,";
2340*3d8817e4Smiod     case sc_Data:	 return "Data,";
2341*3d8817e4Smiod     case sc_Bss:	 return "Bss,";
2342*3d8817e4Smiod     case sc_Register:	 return "Register,";
2343*3d8817e4Smiod     case sc_Abs:	 return "Abs,";
2344*3d8817e4Smiod     case sc_Undefined:	 return "Undefined,";
2345*3d8817e4Smiod     case sc_CdbLocal:	 return "CdbLocal,";
2346*3d8817e4Smiod     case sc_Bits:	 return "Bits,";
2347*3d8817e4Smiod     case sc_CdbSystem:	 return "CdbSystem,";
2348*3d8817e4Smiod     case sc_RegImage:	 return "RegImage,";
2349*3d8817e4Smiod     case sc_Info:	 return "Info,";
2350*3d8817e4Smiod     case sc_UserStruct:	 return "UserStruct,";
2351*3d8817e4Smiod     case sc_SData:	 return "SData,";
2352*3d8817e4Smiod     case sc_SBss:	 return "SBss,";
2353*3d8817e4Smiod     case sc_RData:	 return "RData,";
2354*3d8817e4Smiod     case sc_Var:	 return "Var,";
2355*3d8817e4Smiod     case sc_Common:	 return "Common,";
2356*3d8817e4Smiod     case sc_SCommon:	 return "SCommon,";
2357*3d8817e4Smiod     case sc_VarRegister: return "VarRegister,";
2358*3d8817e4Smiod     case sc_Variant:	 return "Variant,";
2359*3d8817e4Smiod     case sc_SUndefined:	 return "SUndefined,";
2360*3d8817e4Smiod     case sc_Init:	 return "Init,";
2361*3d8817e4Smiod     case sc_Max:	 return "Max,";
2362*3d8817e4Smiod     }
2363*3d8817e4Smiod 
2364*3d8817e4Smiod   return "???,";
2365*3d8817e4Smiod }
2366*3d8817e4Smiod 
2367*3d8817e4Smiod #endif /* DEBUG */
2368*3d8817e4Smiod 
2369*3d8817e4Smiod #ifdef ECOFF_DEBUG
2370*3d8817e4Smiod 
2371*3d8817e4Smiod /* Convert symbol type to string.  */
2372*3d8817e4Smiod 
2373*3d8817e4Smiod static char *
st_to_string(symbol_type)2374*3d8817e4Smiod st_to_string (symbol_type)
2375*3d8817e4Smiod      st_t symbol_type;
2376*3d8817e4Smiod {
2377*3d8817e4Smiod   switch (symbol_type)
2378*3d8817e4Smiod     {
2379*3d8817e4Smiod     case st_Nil:	return "Nil,";
2380*3d8817e4Smiod     case st_Global:	return "Global,";
2381*3d8817e4Smiod     case st_Static:	return "Static,";
2382*3d8817e4Smiod     case st_Param:	return "Param,";
2383*3d8817e4Smiod     case st_Local:	return "Local,";
2384*3d8817e4Smiod     case st_Label:	return "Label,";
2385*3d8817e4Smiod     case st_Proc:	return "Proc,";
2386*3d8817e4Smiod     case st_Block:	return "Block,";
2387*3d8817e4Smiod     case st_End:	return "End,";
2388*3d8817e4Smiod     case st_Member:	return "Member,";
2389*3d8817e4Smiod     case st_Typedef:	return "Typedef,";
2390*3d8817e4Smiod     case st_File:	return "File,";
2391*3d8817e4Smiod     case st_RegReloc:	return "RegReloc,";
2392*3d8817e4Smiod     case st_Forward:	return "Forward,";
2393*3d8817e4Smiod     case st_StaticProc:	return "StaticProc,";
2394*3d8817e4Smiod     case st_Constant:	return "Constant,";
2395*3d8817e4Smiod     case st_Str:	return "String,";
2396*3d8817e4Smiod     case st_Number:	return "Number,";
2397*3d8817e4Smiod     case st_Expr:	return "Expr,";
2398*3d8817e4Smiod     case st_Type:	return "Type,";
2399*3d8817e4Smiod     case st_Max:	return "Max,";
2400*3d8817e4Smiod     }
2401*3d8817e4Smiod 
2402*3d8817e4Smiod   return "???,";
2403*3d8817e4Smiod }
2404*3d8817e4Smiod 
2405*3d8817e4Smiod #endif /* DEBUG */
2406*3d8817e4Smiod 
2407*3d8817e4Smiod /* Parse .begin directives which have a label as the first argument
2408*3d8817e4Smiod    which gives the location of the start of the block.  */
2409*3d8817e4Smiod 
2410*3d8817e4Smiod void
ecoff_directive_begin(int ignore ATTRIBUTE_UNUSED)2411*3d8817e4Smiod ecoff_directive_begin (int ignore ATTRIBUTE_UNUSED)
2412*3d8817e4Smiod {
2413*3d8817e4Smiod   char *name;
2414*3d8817e4Smiod   char name_end;
2415*3d8817e4Smiod 
2416*3d8817e4Smiod   if (cur_file_ptr == (efdr_t *) NULL)
2417*3d8817e4Smiod     {
2418*3d8817e4Smiod       as_warn (_(".begin directive without a preceding .file directive"));
2419*3d8817e4Smiod       demand_empty_rest_of_line ();
2420*3d8817e4Smiod       return;
2421*3d8817e4Smiod     }
2422*3d8817e4Smiod 
2423*3d8817e4Smiod   if (cur_proc_ptr == (proc_t *) NULL)
2424*3d8817e4Smiod     {
2425*3d8817e4Smiod       as_warn (_(".begin directive without a preceding .ent directive"));
2426*3d8817e4Smiod       demand_empty_rest_of_line ();
2427*3d8817e4Smiod       return;
2428*3d8817e4Smiod     }
2429*3d8817e4Smiod 
2430*3d8817e4Smiod   name = input_line_pointer;
2431*3d8817e4Smiod   name_end = get_symbol_end ();
2432*3d8817e4Smiod 
2433*3d8817e4Smiod   (void) add_ecoff_symbol ((const char *) NULL, st_Block, sc_Text,
2434*3d8817e4Smiod 			   symbol_find_or_make (name),
2435*3d8817e4Smiod 			   (bfd_vma) 0, (symint_t) 0, (symint_t) 0);
2436*3d8817e4Smiod 
2437*3d8817e4Smiod   *input_line_pointer = name_end;
2438*3d8817e4Smiod 
2439*3d8817e4Smiod   /* The line number follows, but we don't use it.  */
2440*3d8817e4Smiod   (void) get_absolute_expression ();
2441*3d8817e4Smiod   demand_empty_rest_of_line ();
2442*3d8817e4Smiod }
2443*3d8817e4Smiod 
2444*3d8817e4Smiod /* Parse .bend directives which have a label as the first argument
2445*3d8817e4Smiod    which gives the location of the end of the block.  */
2446*3d8817e4Smiod 
2447*3d8817e4Smiod void
ecoff_directive_bend(int ignore ATTRIBUTE_UNUSED)2448*3d8817e4Smiod ecoff_directive_bend (int ignore ATTRIBUTE_UNUSED)
2449*3d8817e4Smiod {
2450*3d8817e4Smiod   char *name;
2451*3d8817e4Smiod   char name_end;
2452*3d8817e4Smiod   symbolS *endsym;
2453*3d8817e4Smiod 
2454*3d8817e4Smiod   if (cur_file_ptr == (efdr_t *) NULL)
2455*3d8817e4Smiod     {
2456*3d8817e4Smiod       as_warn (_(".bend directive without a preceding .file directive"));
2457*3d8817e4Smiod       demand_empty_rest_of_line ();
2458*3d8817e4Smiod       return;
2459*3d8817e4Smiod     }
2460*3d8817e4Smiod 
2461*3d8817e4Smiod   if (cur_proc_ptr == (proc_t *) NULL)
2462*3d8817e4Smiod     {
2463*3d8817e4Smiod       as_warn (_(".bend directive without a preceding .ent directive"));
2464*3d8817e4Smiod       demand_empty_rest_of_line ();
2465*3d8817e4Smiod       return;
2466*3d8817e4Smiod     }
2467*3d8817e4Smiod 
2468*3d8817e4Smiod   name = input_line_pointer;
2469*3d8817e4Smiod   name_end = get_symbol_end ();
2470*3d8817e4Smiod 
2471*3d8817e4Smiod   /* The value is the distance between the .bend directive and the
2472*3d8817e4Smiod      corresponding symbol.  We fill in the offset when we write out
2473*3d8817e4Smiod      the symbol.  */
2474*3d8817e4Smiod   endsym = symbol_find (name);
2475*3d8817e4Smiod   if (endsym == (symbolS *) NULL)
2476*3d8817e4Smiod     as_warn (_(".bend directive names unknown symbol"));
2477*3d8817e4Smiod   else
2478*3d8817e4Smiod     (void) add_ecoff_symbol ((const char *) NULL, st_End, sc_Text, endsym,
2479*3d8817e4Smiod 			     (bfd_vma) 0, (symint_t) 0, (symint_t) 0);
2480*3d8817e4Smiod 
2481*3d8817e4Smiod   *input_line_pointer = name_end;
2482*3d8817e4Smiod 
2483*3d8817e4Smiod   /* The line number follows, but we don't use it.  */
2484*3d8817e4Smiod   (void) get_absolute_expression ();
2485*3d8817e4Smiod   demand_empty_rest_of_line ();
2486*3d8817e4Smiod }
2487*3d8817e4Smiod 
2488*3d8817e4Smiod /* COFF debugging information is provided as a series of directives
2489*3d8817e4Smiod    (.def, .scl, etc.).  We build up information as we read the
2490*3d8817e4Smiod    directives in the following static variables, and file it away when
2491*3d8817e4Smiod    we reach the .endef directive.  */
2492*3d8817e4Smiod static char *coff_sym_name;
2493*3d8817e4Smiod static type_info_t coff_type;
2494*3d8817e4Smiod static sc_t coff_storage_class;
2495*3d8817e4Smiod static st_t coff_symbol_typ;
2496*3d8817e4Smiod static int coff_is_function;
2497*3d8817e4Smiod static char *coff_tag;
2498*3d8817e4Smiod static valueT coff_value;
2499*3d8817e4Smiod static symbolS *coff_sym_value;
2500*3d8817e4Smiod static bfd_vma coff_sym_addend;
2501*3d8817e4Smiod static int coff_inside_enumeration;
2502*3d8817e4Smiod 
2503*3d8817e4Smiod /* Handle a .def directive: start defining a symbol.  */
2504*3d8817e4Smiod 
2505*3d8817e4Smiod void
ecoff_directive_def(int ignore ATTRIBUTE_UNUSED)2506*3d8817e4Smiod ecoff_directive_def (int ignore ATTRIBUTE_UNUSED)
2507*3d8817e4Smiod {
2508*3d8817e4Smiod   char *name;
2509*3d8817e4Smiod   char name_end;
2510*3d8817e4Smiod 
2511*3d8817e4Smiod   ecoff_debugging_seen = 1;
2512*3d8817e4Smiod 
2513*3d8817e4Smiod   SKIP_WHITESPACE ();
2514*3d8817e4Smiod 
2515*3d8817e4Smiod   name = input_line_pointer;
2516*3d8817e4Smiod   name_end = get_symbol_end ();
2517*3d8817e4Smiod 
2518*3d8817e4Smiod   if (coff_sym_name != (char *) NULL)
2519*3d8817e4Smiod     as_warn (_(".def pseudo-op used inside of .def/.endef; ignored"));
2520*3d8817e4Smiod   else if (*name == '\0')
2521*3d8817e4Smiod     as_warn (_("empty symbol name in .def; ignored"));
2522*3d8817e4Smiod   else
2523*3d8817e4Smiod     {
2524*3d8817e4Smiod       if (coff_sym_name != (char *) NULL)
2525*3d8817e4Smiod 	free (coff_sym_name);
2526*3d8817e4Smiod       if (coff_tag != (char *) NULL)
2527*3d8817e4Smiod 	free (coff_tag);
2528*3d8817e4Smiod 
2529*3d8817e4Smiod       coff_sym_name = xstrdup (name);
2530*3d8817e4Smiod       coff_type = type_info_init;
2531*3d8817e4Smiod       coff_storage_class = sc_Nil;
2532*3d8817e4Smiod       coff_symbol_typ = st_Nil;
2533*3d8817e4Smiod       coff_is_function = 0;
2534*3d8817e4Smiod       coff_tag = (char *) NULL;
2535*3d8817e4Smiod       coff_value = 0;
2536*3d8817e4Smiod       coff_sym_value = (symbolS *) NULL;
2537*3d8817e4Smiod       coff_sym_addend = 0;
2538*3d8817e4Smiod     }
2539*3d8817e4Smiod 
2540*3d8817e4Smiod   *input_line_pointer = name_end;
2541*3d8817e4Smiod 
2542*3d8817e4Smiod   demand_empty_rest_of_line ();
2543*3d8817e4Smiod }
2544*3d8817e4Smiod 
2545*3d8817e4Smiod /* Handle a .dim directive, used to give dimensions for an array.  The
2546*3d8817e4Smiod    arguments are comma separated numbers.  mips-tfile assumes that
2547*3d8817e4Smiod    there will not be more than 6 dimensions, and gdb won't read any
2548*3d8817e4Smiod    more than that anyhow, so I will also make that assumption.  */
2549*3d8817e4Smiod 
2550*3d8817e4Smiod void
ecoff_directive_dim(int ignore ATTRIBUTE_UNUSED)2551*3d8817e4Smiod ecoff_directive_dim (int ignore ATTRIBUTE_UNUSED)
2552*3d8817e4Smiod {
2553*3d8817e4Smiod   int dimens[N_TQ];
2554*3d8817e4Smiod   int i;
2555*3d8817e4Smiod 
2556*3d8817e4Smiod   if (coff_sym_name == (char *) NULL)
2557*3d8817e4Smiod     {
2558*3d8817e4Smiod       as_warn (_(".dim pseudo-op used outside of .def/.endef; ignored"));
2559*3d8817e4Smiod       demand_empty_rest_of_line ();
2560*3d8817e4Smiod       return;
2561*3d8817e4Smiod     }
2562*3d8817e4Smiod 
2563*3d8817e4Smiod   for (i = 0; i < N_TQ; i++)
2564*3d8817e4Smiod     {
2565*3d8817e4Smiod       SKIP_WHITESPACE ();
2566*3d8817e4Smiod       dimens[i] = get_absolute_expression ();
2567*3d8817e4Smiod       if (*input_line_pointer == ',')
2568*3d8817e4Smiod 	++input_line_pointer;
2569*3d8817e4Smiod       else
2570*3d8817e4Smiod 	{
2571*3d8817e4Smiod 	  if (*input_line_pointer != '\n'
2572*3d8817e4Smiod 	      && *input_line_pointer != ';')
2573*3d8817e4Smiod 	    as_warn (_("badly formed .dim directive"));
2574*3d8817e4Smiod 	  break;
2575*3d8817e4Smiod 	}
2576*3d8817e4Smiod     }
2577*3d8817e4Smiod 
2578*3d8817e4Smiod   if (i == N_TQ)
2579*3d8817e4Smiod     --i;
2580*3d8817e4Smiod 
2581*3d8817e4Smiod   /* The dimensions are stored away in reverse order.  */
2582*3d8817e4Smiod   for (; i >= 0; i--)
2583*3d8817e4Smiod     {
2584*3d8817e4Smiod       if (coff_type.num_dims >= N_TQ)
2585*3d8817e4Smiod 	{
2586*3d8817e4Smiod 	  as_warn (_("too many .dim entries"));
2587*3d8817e4Smiod 	  break;
2588*3d8817e4Smiod 	}
2589*3d8817e4Smiod       coff_type.dimensions[coff_type.num_dims] = dimens[i];
2590*3d8817e4Smiod       ++coff_type.num_dims;
2591*3d8817e4Smiod     }
2592*3d8817e4Smiod 
2593*3d8817e4Smiod   demand_empty_rest_of_line ();
2594*3d8817e4Smiod }
2595*3d8817e4Smiod 
2596*3d8817e4Smiod /* Handle a .scl directive, which sets the COFF storage class of the
2597*3d8817e4Smiod    symbol.  */
2598*3d8817e4Smiod 
2599*3d8817e4Smiod void
ecoff_directive_scl(int ignore ATTRIBUTE_UNUSED)2600*3d8817e4Smiod ecoff_directive_scl (int ignore ATTRIBUTE_UNUSED)
2601*3d8817e4Smiod {
2602*3d8817e4Smiod   long val;
2603*3d8817e4Smiod 
2604*3d8817e4Smiod   if (coff_sym_name == (char *) NULL)
2605*3d8817e4Smiod     {
2606*3d8817e4Smiod       as_warn (_(".scl pseudo-op used outside of .def/.endef; ignored"));
2607*3d8817e4Smiod       demand_empty_rest_of_line ();
2608*3d8817e4Smiod       return;
2609*3d8817e4Smiod     }
2610*3d8817e4Smiod 
2611*3d8817e4Smiod   val = get_absolute_expression ();
2612*3d8817e4Smiod 
2613*3d8817e4Smiod   coff_symbol_typ = map_coff_sym_type[val];
2614*3d8817e4Smiod   coff_storage_class = map_coff_storage[val];
2615*3d8817e4Smiod 
2616*3d8817e4Smiod   demand_empty_rest_of_line ();
2617*3d8817e4Smiod }
2618*3d8817e4Smiod 
2619*3d8817e4Smiod /* Handle a .size directive.  For some reason mips-tfile.c thinks that
2620*3d8817e4Smiod    .size can have multiple arguments.  We humor it, although gcc will
2621*3d8817e4Smiod    never generate more than one argument.  */
2622*3d8817e4Smiod 
2623*3d8817e4Smiod void
ecoff_directive_size(int ignore ATTRIBUTE_UNUSED)2624*3d8817e4Smiod ecoff_directive_size (int ignore ATTRIBUTE_UNUSED)
2625*3d8817e4Smiod {
2626*3d8817e4Smiod   int sizes[N_TQ];
2627*3d8817e4Smiod   int i;
2628*3d8817e4Smiod 
2629*3d8817e4Smiod   if (coff_sym_name == (char *) NULL)
2630*3d8817e4Smiod     {
2631*3d8817e4Smiod       as_warn (_(".size pseudo-op used outside of .def/.endef; ignored"));
2632*3d8817e4Smiod       demand_empty_rest_of_line ();
2633*3d8817e4Smiod       return;
2634*3d8817e4Smiod     }
2635*3d8817e4Smiod 
2636*3d8817e4Smiod   for (i = 0; i < N_TQ; i++)
2637*3d8817e4Smiod     {
2638*3d8817e4Smiod       SKIP_WHITESPACE ();
2639*3d8817e4Smiod       sizes[i] = get_absolute_expression ();
2640*3d8817e4Smiod       if (*input_line_pointer == ',')
2641*3d8817e4Smiod 	++input_line_pointer;
2642*3d8817e4Smiod       else
2643*3d8817e4Smiod 	{
2644*3d8817e4Smiod 	  if (*input_line_pointer != '\n'
2645*3d8817e4Smiod 	      && *input_line_pointer != ';')
2646*3d8817e4Smiod 	    as_warn (_("badly formed .size directive"));
2647*3d8817e4Smiod 	  break;
2648*3d8817e4Smiod 	}
2649*3d8817e4Smiod     }
2650*3d8817e4Smiod 
2651*3d8817e4Smiod   if (i == N_TQ)
2652*3d8817e4Smiod     --i;
2653*3d8817e4Smiod 
2654*3d8817e4Smiod   /* The sizes are stored away in reverse order.  */
2655*3d8817e4Smiod   for (; i >= 0; i--)
2656*3d8817e4Smiod     {
2657*3d8817e4Smiod       if (coff_type.num_sizes >= N_TQ)
2658*3d8817e4Smiod 	{
2659*3d8817e4Smiod 	  as_warn (_("too many .size entries"));
2660*3d8817e4Smiod 	  break;
2661*3d8817e4Smiod 	}
2662*3d8817e4Smiod       coff_type.sizes[coff_type.num_sizes] = sizes[i];
2663*3d8817e4Smiod       ++coff_type.num_sizes;
2664*3d8817e4Smiod     }
2665*3d8817e4Smiod 
2666*3d8817e4Smiod   demand_empty_rest_of_line ();
2667*3d8817e4Smiod }
2668*3d8817e4Smiod 
2669*3d8817e4Smiod /* Handle the .type directive, which gives the COFF type of the
2670*3d8817e4Smiod    symbol.  */
2671*3d8817e4Smiod 
2672*3d8817e4Smiod void
ecoff_directive_type(int ignore ATTRIBUTE_UNUSED)2673*3d8817e4Smiod ecoff_directive_type (int ignore ATTRIBUTE_UNUSED)
2674*3d8817e4Smiod {
2675*3d8817e4Smiod   long val;
2676*3d8817e4Smiod   tq_t *tq_ptr;
2677*3d8817e4Smiod   tq_t *tq_shft;
2678*3d8817e4Smiod 
2679*3d8817e4Smiod   if (coff_sym_name == (char *) NULL)
2680*3d8817e4Smiod     {
2681*3d8817e4Smiod       as_warn (_(".type pseudo-op used outside of .def/.endef; ignored"));
2682*3d8817e4Smiod       demand_empty_rest_of_line ();
2683*3d8817e4Smiod       return;
2684*3d8817e4Smiod     }
2685*3d8817e4Smiod 
2686*3d8817e4Smiod   val = get_absolute_expression ();
2687*3d8817e4Smiod 
2688*3d8817e4Smiod   coff_type.orig_type = BTYPE (val);
2689*3d8817e4Smiod   coff_type.basic_type = map_coff_types[coff_type.orig_type];
2690*3d8817e4Smiod 
2691*3d8817e4Smiod   tq_ptr = &coff_type.type_qualifiers[N_TQ];
2692*3d8817e4Smiod   while (val & ~N_BTMASK)
2693*3d8817e4Smiod     {
2694*3d8817e4Smiod       if (tq_ptr == &coff_type.type_qualifiers[0])
2695*3d8817e4Smiod 	{
2696*3d8817e4Smiod 	  /* FIXME: We could handle this by setting the continued bit.
2697*3d8817e4Smiod 	     There would still be a limit: the .type argument can not
2698*3d8817e4Smiod 	     be infinite.  */
2699*3d8817e4Smiod 	  as_warn (_("the type of %s is too complex; it will be simplified"),
2700*3d8817e4Smiod 		   coff_sym_name);
2701*3d8817e4Smiod 	  break;
2702*3d8817e4Smiod 	}
2703*3d8817e4Smiod       if (ISPTR (val))
2704*3d8817e4Smiod 	*--tq_ptr = tq_Ptr;
2705*3d8817e4Smiod       else if (ISFCN (val))
2706*3d8817e4Smiod 	*--tq_ptr = tq_Proc;
2707*3d8817e4Smiod       else if (ISARY (val))
2708*3d8817e4Smiod 	*--tq_ptr = tq_Array;
2709*3d8817e4Smiod       else
2710*3d8817e4Smiod 	as_fatal (_("Unrecognized .type argument"));
2711*3d8817e4Smiod 
2712*3d8817e4Smiod       val = DECREF (val);
2713*3d8817e4Smiod     }
2714*3d8817e4Smiod 
2715*3d8817e4Smiod   tq_shft = &coff_type.type_qualifiers[0];
2716*3d8817e4Smiod   while (tq_ptr != &coff_type.type_qualifiers[N_TQ])
2717*3d8817e4Smiod     *tq_shft++ = *tq_ptr++;
2718*3d8817e4Smiod 
2719*3d8817e4Smiod   if (tq_shft != &coff_type.type_qualifiers[0] && tq_shft[-1] == tq_Proc)
2720*3d8817e4Smiod     {
2721*3d8817e4Smiod       /* If this is a function, ignore it, so that we don't get two
2722*3d8817e4Smiod          entries (one from the .ent, and one for the .def that
2723*3d8817e4Smiod          precedes it).  Save the type information so that the end
2724*3d8817e4Smiod          block can properly add it after the begin block index.  For
2725*3d8817e4Smiod          MIPS knows what reason, we must strip off the function type
2726*3d8817e4Smiod          at this point.  */
2727*3d8817e4Smiod       coff_is_function = 1;
2728*3d8817e4Smiod       tq_shft[-1] = tq_Nil;
2729*3d8817e4Smiod     }
2730*3d8817e4Smiod 
2731*3d8817e4Smiod   while (tq_shft != &coff_type.type_qualifiers[N_TQ])
2732*3d8817e4Smiod     *tq_shft++ = tq_Nil;
2733*3d8817e4Smiod 
2734*3d8817e4Smiod   demand_empty_rest_of_line ();
2735*3d8817e4Smiod }
2736*3d8817e4Smiod 
2737*3d8817e4Smiod /* Handle the .tag directive, which gives the name of a structure,
2738*3d8817e4Smiod    union or enum.  */
2739*3d8817e4Smiod 
2740*3d8817e4Smiod void
ecoff_directive_tag(int ignore ATTRIBUTE_UNUSED)2741*3d8817e4Smiod ecoff_directive_tag (int ignore ATTRIBUTE_UNUSED)
2742*3d8817e4Smiod {
2743*3d8817e4Smiod   char *name;
2744*3d8817e4Smiod   char name_end;
2745*3d8817e4Smiod 
2746*3d8817e4Smiod   if (coff_sym_name == (char *) NULL)
2747*3d8817e4Smiod     {
2748*3d8817e4Smiod       as_warn (_(".tag pseudo-op used outside of .def/.endef; ignored"));
2749*3d8817e4Smiod       demand_empty_rest_of_line ();
2750*3d8817e4Smiod       return;
2751*3d8817e4Smiod     }
2752*3d8817e4Smiod 
2753*3d8817e4Smiod   name = input_line_pointer;
2754*3d8817e4Smiod   name_end = get_symbol_end ();
2755*3d8817e4Smiod 
2756*3d8817e4Smiod   coff_tag = xstrdup (name);
2757*3d8817e4Smiod 
2758*3d8817e4Smiod   *input_line_pointer = name_end;
2759*3d8817e4Smiod 
2760*3d8817e4Smiod   demand_empty_rest_of_line ();
2761*3d8817e4Smiod }
2762*3d8817e4Smiod 
2763*3d8817e4Smiod /* Handle the .val directive, which gives the value of the symbol.  It
2764*3d8817e4Smiod    may be the name of a static or global symbol.  */
2765*3d8817e4Smiod 
2766*3d8817e4Smiod void
ecoff_directive_val(int ignore ATTRIBUTE_UNUSED)2767*3d8817e4Smiod ecoff_directive_val (int ignore ATTRIBUTE_UNUSED)
2768*3d8817e4Smiod {
2769*3d8817e4Smiod   expressionS exp;
2770*3d8817e4Smiod 
2771*3d8817e4Smiod   if (coff_sym_name == (char *) NULL)
2772*3d8817e4Smiod     {
2773*3d8817e4Smiod       as_warn (_(".val pseudo-op used outside of .def/.endef; ignored"));
2774*3d8817e4Smiod       demand_empty_rest_of_line ();
2775*3d8817e4Smiod       return;
2776*3d8817e4Smiod     }
2777*3d8817e4Smiod 
2778*3d8817e4Smiod   expression (&exp);
2779*3d8817e4Smiod   if (exp.X_op != O_constant && exp.X_op != O_symbol)
2780*3d8817e4Smiod     {
2781*3d8817e4Smiod       as_bad (_(".val expression is too copmlex"));
2782*3d8817e4Smiod       demand_empty_rest_of_line ();
2783*3d8817e4Smiod       return;
2784*3d8817e4Smiod     }
2785*3d8817e4Smiod 
2786*3d8817e4Smiod   if (exp.X_op == O_constant)
2787*3d8817e4Smiod     coff_value = exp.X_add_number;
2788*3d8817e4Smiod   else
2789*3d8817e4Smiod     {
2790*3d8817e4Smiod       coff_sym_value = exp.X_add_symbol;
2791*3d8817e4Smiod       coff_sym_addend = exp.X_add_number;
2792*3d8817e4Smiod     }
2793*3d8817e4Smiod 
2794*3d8817e4Smiod   demand_empty_rest_of_line ();
2795*3d8817e4Smiod }
2796*3d8817e4Smiod 
2797*3d8817e4Smiod /* Handle the .endef directive, which terminates processing of COFF
2798*3d8817e4Smiod    debugging information for a symbol.  */
2799*3d8817e4Smiod 
2800*3d8817e4Smiod void
ecoff_directive_endef(int ignore ATTRIBUTE_UNUSED)2801*3d8817e4Smiod ecoff_directive_endef (int ignore ATTRIBUTE_UNUSED)
2802*3d8817e4Smiod {
2803*3d8817e4Smiod   char *name;
2804*3d8817e4Smiod   symint_t indx;
2805*3d8817e4Smiod   localsym_t *sym;
2806*3d8817e4Smiod 
2807*3d8817e4Smiod   demand_empty_rest_of_line ();
2808*3d8817e4Smiod 
2809*3d8817e4Smiod   if (coff_sym_name == (char *) NULL)
2810*3d8817e4Smiod     {
2811*3d8817e4Smiod       as_warn (_(".endef pseudo-op used before .def; ignored"));
2812*3d8817e4Smiod       return;
2813*3d8817e4Smiod     }
2814*3d8817e4Smiod 
2815*3d8817e4Smiod   name = coff_sym_name;
2816*3d8817e4Smiod   coff_sym_name = (char *) NULL;
2817*3d8817e4Smiod 
2818*3d8817e4Smiod   /* If the symbol is a static or external, we have already gotten the
2819*3d8817e4Smiod      appropriate type and class, so make sure we don't override those
2820*3d8817e4Smiod      values.  This is needed because there are some type and classes
2821*3d8817e4Smiod      that are not in COFF, such as short data, etc.  */
2822*3d8817e4Smiod   if (coff_sym_value != (symbolS *) NULL)
2823*3d8817e4Smiod     {
2824*3d8817e4Smiod       coff_symbol_typ = st_Nil;
2825*3d8817e4Smiod       coff_storage_class = sc_Nil;
2826*3d8817e4Smiod     }
2827*3d8817e4Smiod 
2828*3d8817e4Smiod   coff_type.extra_sizes = coff_tag != (char *) NULL;
2829*3d8817e4Smiod   if (coff_type.num_dims > 0)
2830*3d8817e4Smiod     {
2831*3d8817e4Smiod       int diff = coff_type.num_dims - coff_type.num_sizes;
2832*3d8817e4Smiod       int i = coff_type.num_dims - 1;
2833*3d8817e4Smiod       int j;
2834*3d8817e4Smiod 
2835*3d8817e4Smiod       if (coff_type.num_sizes != 1 || diff < 0)
2836*3d8817e4Smiod 	{
2837*3d8817e4Smiod 	  as_warn (_("bad COFF debugging information"));
2838*3d8817e4Smiod 	  return;
2839*3d8817e4Smiod 	}
2840*3d8817e4Smiod 
2841*3d8817e4Smiod       /* If this is an array, make sure the same number of dimensions
2842*3d8817e4Smiod          and sizes were passed, creating extra sizes for multiply
2843*3d8817e4Smiod          dimensioned arrays if not passed.  */
2844*3d8817e4Smiod       coff_type.extra_sizes = 0;
2845*3d8817e4Smiod       if (diff)
2846*3d8817e4Smiod 	{
2847*3d8817e4Smiod 	  j = (sizeof (coff_type.sizes) / sizeof (coff_type.sizes[0])) - 1;
2848*3d8817e4Smiod 	  while (j >= 0)
2849*3d8817e4Smiod 	    {
2850*3d8817e4Smiod 	      coff_type.sizes[j] = (((j - diff) >= 0)
2851*3d8817e4Smiod 				    ? coff_type.sizes[j - diff]
2852*3d8817e4Smiod 				    : 0);
2853*3d8817e4Smiod 	      j--;
2854*3d8817e4Smiod 	    }
2855*3d8817e4Smiod 
2856*3d8817e4Smiod 	  coff_type.num_sizes = i + 1;
2857*3d8817e4Smiod 	  for (i--; i >= 0; i--)
2858*3d8817e4Smiod 	    coff_type.sizes[i] = (coff_type.dimensions[i + 1] == 0
2859*3d8817e4Smiod 				  ? 0
2860*3d8817e4Smiod 				  : (coff_type.sizes[i + 1]
2861*3d8817e4Smiod 				     / coff_type.dimensions[i + 1]));
2862*3d8817e4Smiod 	}
2863*3d8817e4Smiod     }
2864*3d8817e4Smiod   else if (coff_symbol_typ == st_Member
2865*3d8817e4Smiod 	   && coff_type.num_sizes - coff_type.extra_sizes == 1)
2866*3d8817e4Smiod     {
2867*3d8817e4Smiod       /* Is this a bitfield?  This is indicated by a structure member
2868*3d8817e4Smiod          having a size field that isn't an array.  */
2869*3d8817e4Smiod       coff_type.bitfield = 1;
2870*3d8817e4Smiod     }
2871*3d8817e4Smiod 
2872*3d8817e4Smiod   /* Except for enumeration members & begin/ending of scopes, put the
2873*3d8817e4Smiod      type word in the aux. symbol table.  */
2874*3d8817e4Smiod   if (coff_symbol_typ == st_Block || coff_symbol_typ == st_End)
2875*3d8817e4Smiod     indx = 0;
2876*3d8817e4Smiod   else if (coff_inside_enumeration)
2877*3d8817e4Smiod     indx = cur_file_ptr->void_type;
2878*3d8817e4Smiod   else
2879*3d8817e4Smiod     {
2880*3d8817e4Smiod       if (coff_type.basic_type == bt_Struct
2881*3d8817e4Smiod 	  || coff_type.basic_type == bt_Union
2882*3d8817e4Smiod 	  || coff_type.basic_type == bt_Enum)
2883*3d8817e4Smiod 	{
2884*3d8817e4Smiod 	  if (coff_tag == (char *) NULL)
2885*3d8817e4Smiod 	    {
2886*3d8817e4Smiod 	      as_warn (_("no tag specified for %s"), name);
2887*3d8817e4Smiod 	      return;
2888*3d8817e4Smiod 	    }
2889*3d8817e4Smiod 
2890*3d8817e4Smiod 	  coff_type.tag_ptr = get_tag (coff_tag, (localsym_t *) NULL,
2891*3d8817e4Smiod 				       coff_type.basic_type);
2892*3d8817e4Smiod 	}
2893*3d8817e4Smiod 
2894*3d8817e4Smiod       if (coff_is_function)
2895*3d8817e4Smiod 	{
2896*3d8817e4Smiod 	  last_func_type_info = coff_type;
2897*3d8817e4Smiod 	  last_func_sym_value = coff_sym_value;
2898*3d8817e4Smiod 	  return;
2899*3d8817e4Smiod 	}
2900*3d8817e4Smiod 
2901*3d8817e4Smiod       indx = add_aux_sym_tir (&coff_type,
2902*3d8817e4Smiod 			      hash_yes,
2903*3d8817e4Smiod 			      &cur_file_ptr->thash_head[0]);
2904*3d8817e4Smiod     }
2905*3d8817e4Smiod 
2906*3d8817e4Smiod   /* Do any last minute adjustments that are necessary.  */
2907*3d8817e4Smiod   switch (coff_symbol_typ)
2908*3d8817e4Smiod     {
2909*3d8817e4Smiod     default:
2910*3d8817e4Smiod       break;
2911*3d8817e4Smiod 
2912*3d8817e4Smiod       /* For the beginning of structs, unions, and enumerations, the
2913*3d8817e4Smiod          size info needs to be passed in the value field.  */
2914*3d8817e4Smiod     case st_Block:
2915*3d8817e4Smiod       if (coff_type.num_sizes - coff_type.num_dims - coff_type.extra_sizes
2916*3d8817e4Smiod 	  != 1)
2917*3d8817e4Smiod 	{
2918*3d8817e4Smiod 	  as_warn (_("bad COFF debugging information"));
2919*3d8817e4Smiod 	  return;
2920*3d8817e4Smiod 	}
2921*3d8817e4Smiod       else
2922*3d8817e4Smiod 	coff_value = coff_type.sizes[0];
2923*3d8817e4Smiod 
2924*3d8817e4Smiod       coff_inside_enumeration = (coff_type.orig_type == T_ENUM);
2925*3d8817e4Smiod       break;
2926*3d8817e4Smiod 
2927*3d8817e4Smiod       /* For the end of structs, unions, and enumerations, omit the
2928*3d8817e4Smiod          name which is always ".eos".  This needs to be done last, so
2929*3d8817e4Smiod          that any error reporting above gives the correct name.  */
2930*3d8817e4Smiod     case st_End:
2931*3d8817e4Smiod       free (name);
2932*3d8817e4Smiod       name = (char *) NULL;
2933*3d8817e4Smiod       coff_value = 0;
2934*3d8817e4Smiod       coff_inside_enumeration = 0;
2935*3d8817e4Smiod       break;
2936*3d8817e4Smiod 
2937*3d8817e4Smiod       /* Members of structures and unions that aren't bitfields, need
2938*3d8817e4Smiod          to adjust the value from a byte offset to a bit offset.
2939*3d8817e4Smiod          Members of enumerations do not have the value adjusted, and
2940*3d8817e4Smiod          can be distinguished by indx == indexNil.  For enumerations,
2941*3d8817e4Smiod          update the maximum enumeration value.  */
2942*3d8817e4Smiod     case st_Member:
2943*3d8817e4Smiod       if (! coff_type.bitfield && ! coff_inside_enumeration)
2944*3d8817e4Smiod 	coff_value *= 8;
2945*3d8817e4Smiod 
2946*3d8817e4Smiod       break;
2947*3d8817e4Smiod     }
2948*3d8817e4Smiod 
2949*3d8817e4Smiod   /* Add the symbol.  */
2950*3d8817e4Smiod   sym = add_ecoff_symbol (name,
2951*3d8817e4Smiod 			  coff_symbol_typ,
2952*3d8817e4Smiod 			  coff_storage_class,
2953*3d8817e4Smiod 			  coff_sym_value,
2954*3d8817e4Smiod 			  coff_sym_addend,
2955*3d8817e4Smiod 			  (symint_t) coff_value,
2956*3d8817e4Smiod 			  indx);
2957*3d8817e4Smiod 
2958*3d8817e4Smiod   /* deal with struct, union, and enum tags.  */
2959*3d8817e4Smiod   if (coff_symbol_typ == st_Block)
2960*3d8817e4Smiod     {
2961*3d8817e4Smiod       /* Create or update the tag information.  */
2962*3d8817e4Smiod       tag_t *tag_ptr = get_tag (name,
2963*3d8817e4Smiod 				sym,
2964*3d8817e4Smiod 				coff_type.basic_type);
2965*3d8817e4Smiod       forward_t **pf;
2966*3d8817e4Smiod 
2967*3d8817e4Smiod       /* Remember any forward references.  */
2968*3d8817e4Smiod       for (pf = &sym->forward_ref;
2969*3d8817e4Smiod 	   *pf != (forward_t *) NULL;
2970*3d8817e4Smiod 	   pf = &(*pf)->next)
2971*3d8817e4Smiod 	;
2972*3d8817e4Smiod       *pf = tag_ptr->forward_ref;
2973*3d8817e4Smiod       tag_ptr->forward_ref = (forward_t *) NULL;
2974*3d8817e4Smiod     }
2975*3d8817e4Smiod }
2976*3d8817e4Smiod 
2977*3d8817e4Smiod /* Parse .end directives.  */
2978*3d8817e4Smiod 
2979*3d8817e4Smiod void
ecoff_directive_end(int ignore ATTRIBUTE_UNUSED)2980*3d8817e4Smiod ecoff_directive_end (int ignore ATTRIBUTE_UNUSED)
2981*3d8817e4Smiod {
2982*3d8817e4Smiod   char *name;
2983*3d8817e4Smiod   char name_end;
2984*3d8817e4Smiod   symbolS *ent;
2985*3d8817e4Smiod 
2986*3d8817e4Smiod   if (cur_file_ptr == (efdr_t *) NULL)
2987*3d8817e4Smiod     {
2988*3d8817e4Smiod       as_warn (_(".end directive without a preceding .file directive"));
2989*3d8817e4Smiod       demand_empty_rest_of_line ();
2990*3d8817e4Smiod       return;
2991*3d8817e4Smiod     }
2992*3d8817e4Smiod 
2993*3d8817e4Smiod   if (cur_proc_ptr == (proc_t *) NULL)
2994*3d8817e4Smiod     {
2995*3d8817e4Smiod       as_warn (_(".end directive without a preceding .ent directive"));
2996*3d8817e4Smiod       demand_empty_rest_of_line ();
2997*3d8817e4Smiod       return;
2998*3d8817e4Smiod     }
2999*3d8817e4Smiod 
3000*3d8817e4Smiod   name = input_line_pointer;
3001*3d8817e4Smiod   name_end = get_symbol_end ();
3002*3d8817e4Smiod 
3003*3d8817e4Smiod   if (name == input_line_pointer)
3004*3d8817e4Smiod     {
3005*3d8817e4Smiod       as_warn (_(".end directive has no name"));
3006*3d8817e4Smiod       *input_line_pointer = name_end;
3007*3d8817e4Smiod       demand_empty_rest_of_line ();
3008*3d8817e4Smiod       return;
3009*3d8817e4Smiod     }
3010*3d8817e4Smiod 
3011*3d8817e4Smiod   /* The value is the distance between the .end directive and the
3012*3d8817e4Smiod      corresponding symbol.  We create a fake symbol to hold the
3013*3d8817e4Smiod      current location, and put in the offset when we write out the
3014*3d8817e4Smiod      symbol.  */
3015*3d8817e4Smiod   ent = symbol_find (name);
3016*3d8817e4Smiod   if (ent == (symbolS *) NULL)
3017*3d8817e4Smiod     as_warn (_(".end directive names unknown symbol"));
3018*3d8817e4Smiod   else
3019*3d8817e4Smiod     (void) add_ecoff_symbol ((const char *) NULL, st_End, sc_Text,
3020*3d8817e4Smiod 			     symbol_new ("L0\001", now_seg,
3021*3d8817e4Smiod 					 (valueT) frag_now_fix (),
3022*3d8817e4Smiod 					 frag_now),
3023*3d8817e4Smiod 			     (bfd_vma) 0, (symint_t) 0, (symint_t) 0);
3024*3d8817e4Smiod 
3025*3d8817e4Smiod   cur_proc_ptr = (proc_t *) NULL;
3026*3d8817e4Smiod 
3027*3d8817e4Smiod   *input_line_pointer = name_end;
3028*3d8817e4Smiod   demand_empty_rest_of_line ();
3029*3d8817e4Smiod }
3030*3d8817e4Smiod 
3031*3d8817e4Smiod /* Parse .ent directives.  */
3032*3d8817e4Smiod 
3033*3d8817e4Smiod void
ecoff_directive_ent(int ignore ATTRIBUTE_UNUSED)3034*3d8817e4Smiod ecoff_directive_ent (int ignore ATTRIBUTE_UNUSED)
3035*3d8817e4Smiod {
3036*3d8817e4Smiod   char *name;
3037*3d8817e4Smiod   char name_end;
3038*3d8817e4Smiod 
3039*3d8817e4Smiod   if (cur_file_ptr == (efdr_t *) NULL)
3040*3d8817e4Smiod     add_file ((const char *) NULL, 0, 1);
3041*3d8817e4Smiod 
3042*3d8817e4Smiod   if (cur_proc_ptr != (proc_t *) NULL)
3043*3d8817e4Smiod     {
3044*3d8817e4Smiod       as_warn (_("second .ent directive found before .end directive"));
3045*3d8817e4Smiod       demand_empty_rest_of_line ();
3046*3d8817e4Smiod       return;
3047*3d8817e4Smiod     }
3048*3d8817e4Smiod 
3049*3d8817e4Smiod   name = input_line_pointer;
3050*3d8817e4Smiod   name_end = get_symbol_end ();
3051*3d8817e4Smiod 
3052*3d8817e4Smiod   if (name == input_line_pointer)
3053*3d8817e4Smiod     {
3054*3d8817e4Smiod       as_warn (_(".ent directive has no name"));
3055*3d8817e4Smiod       *input_line_pointer = name_end;
3056*3d8817e4Smiod       demand_empty_rest_of_line ();
3057*3d8817e4Smiod       return;
3058*3d8817e4Smiod     }
3059*3d8817e4Smiod 
3060*3d8817e4Smiod   add_procedure (name);
3061*3d8817e4Smiod 
3062*3d8817e4Smiod   *input_line_pointer = name_end;
3063*3d8817e4Smiod 
3064*3d8817e4Smiod   /* The .ent directive is sometimes followed by a number.  I'm not
3065*3d8817e4Smiod      really sure what the number means.  I don't see any way to store
3066*3d8817e4Smiod      the information in the PDR.  The Irix 4 assembler seems to ignore
3067*3d8817e4Smiod      the information.  */
3068*3d8817e4Smiod   SKIP_WHITESPACE ();
3069*3d8817e4Smiod   if (*input_line_pointer == ',')
3070*3d8817e4Smiod     {
3071*3d8817e4Smiod       ++input_line_pointer;
3072*3d8817e4Smiod       SKIP_WHITESPACE ();
3073*3d8817e4Smiod     }
3074*3d8817e4Smiod   if (ISDIGIT (*input_line_pointer)
3075*3d8817e4Smiod       || *input_line_pointer == '-')
3076*3d8817e4Smiod     (void) get_absolute_expression ();
3077*3d8817e4Smiod 
3078*3d8817e4Smiod   demand_empty_rest_of_line ();
3079*3d8817e4Smiod }
3080*3d8817e4Smiod 
3081*3d8817e4Smiod /* Parse .extern directives.  */
3082*3d8817e4Smiod 
3083*3d8817e4Smiod void
ecoff_directive_extern(int ignore ATTRIBUTE_UNUSED)3084*3d8817e4Smiod ecoff_directive_extern (int ignore ATTRIBUTE_UNUSED)
3085*3d8817e4Smiod {
3086*3d8817e4Smiod   char *name;
3087*3d8817e4Smiod   int c;
3088*3d8817e4Smiod   symbolS *symbolp;
3089*3d8817e4Smiod   valueT size;
3090*3d8817e4Smiod 
3091*3d8817e4Smiod   name = input_line_pointer;
3092*3d8817e4Smiod   c = get_symbol_end ();
3093*3d8817e4Smiod   symbolp = symbol_find_or_make (name);
3094*3d8817e4Smiod   *input_line_pointer = c;
3095*3d8817e4Smiod 
3096*3d8817e4Smiod   S_SET_EXTERNAL (symbolp);
3097*3d8817e4Smiod 
3098*3d8817e4Smiod   if (*input_line_pointer == ',')
3099*3d8817e4Smiod     ++input_line_pointer;
3100*3d8817e4Smiod   size = get_absolute_expression ();
3101*3d8817e4Smiod 
3102*3d8817e4Smiod   symbol_get_obj (symbolp)->ecoff_extern_size = size;
3103*3d8817e4Smiod }
3104*3d8817e4Smiod 
3105*3d8817e4Smiod /* Parse .file directives.  */
3106*3d8817e4Smiod 
3107*3d8817e4Smiod void
ecoff_directive_file(int ignore ATTRIBUTE_UNUSED)3108*3d8817e4Smiod ecoff_directive_file (int ignore ATTRIBUTE_UNUSED)
3109*3d8817e4Smiod {
3110*3d8817e4Smiod   int indx;
3111*3d8817e4Smiod   char *name;
3112*3d8817e4Smiod   int len;
3113*3d8817e4Smiod 
3114*3d8817e4Smiod   if (cur_proc_ptr != (proc_t *) NULL)
3115*3d8817e4Smiod     {
3116*3d8817e4Smiod       as_warn (_("no way to handle .file within .ent/.end section"));
3117*3d8817e4Smiod       demand_empty_rest_of_line ();
3118*3d8817e4Smiod       return;
3119*3d8817e4Smiod     }
3120*3d8817e4Smiod 
3121*3d8817e4Smiod   indx = (int) get_absolute_expression ();
3122*3d8817e4Smiod 
3123*3d8817e4Smiod   /* FIXME: we don't have to save the name here.  */
3124*3d8817e4Smiod   name = demand_copy_C_string (&len);
3125*3d8817e4Smiod 
3126*3d8817e4Smiod   add_file (name, indx - 1, 0);
3127*3d8817e4Smiod 
3128*3d8817e4Smiod   demand_empty_rest_of_line ();
3129*3d8817e4Smiod }
3130*3d8817e4Smiod 
3131*3d8817e4Smiod /* Parse .fmask directives.  */
3132*3d8817e4Smiod 
3133*3d8817e4Smiod void
ecoff_directive_fmask(int ignore ATTRIBUTE_UNUSED)3134*3d8817e4Smiod ecoff_directive_fmask (int ignore ATTRIBUTE_UNUSED)
3135*3d8817e4Smiod {
3136*3d8817e4Smiod   long val;
3137*3d8817e4Smiod 
3138*3d8817e4Smiod   if (cur_proc_ptr == (proc_t *) NULL)
3139*3d8817e4Smiod     {
3140*3d8817e4Smiod       as_warn (_(".fmask outside of .ent"));
3141*3d8817e4Smiod       demand_empty_rest_of_line ();
3142*3d8817e4Smiod       return;
3143*3d8817e4Smiod     }
3144*3d8817e4Smiod 
3145*3d8817e4Smiod   if (get_absolute_expression_and_terminator (&val) != ',')
3146*3d8817e4Smiod     {
3147*3d8817e4Smiod       as_warn (_("bad .fmask directive"));
3148*3d8817e4Smiod       --input_line_pointer;
3149*3d8817e4Smiod       demand_empty_rest_of_line ();
3150*3d8817e4Smiod       return;
3151*3d8817e4Smiod     }
3152*3d8817e4Smiod 
3153*3d8817e4Smiod   cur_proc_ptr->pdr.fregmask = val;
3154*3d8817e4Smiod   cur_proc_ptr->pdr.fregoffset = get_absolute_expression ();
3155*3d8817e4Smiod 
3156*3d8817e4Smiod   demand_empty_rest_of_line ();
3157*3d8817e4Smiod }
3158*3d8817e4Smiod 
3159*3d8817e4Smiod /* Parse .frame directives.  */
3160*3d8817e4Smiod 
3161*3d8817e4Smiod void
ecoff_directive_frame(int ignore ATTRIBUTE_UNUSED)3162*3d8817e4Smiod ecoff_directive_frame (int ignore ATTRIBUTE_UNUSED)
3163*3d8817e4Smiod {
3164*3d8817e4Smiod   long val;
3165*3d8817e4Smiod 
3166*3d8817e4Smiod   if (cur_proc_ptr == (proc_t *) NULL)
3167*3d8817e4Smiod     {
3168*3d8817e4Smiod       as_warn (_(".frame outside of .ent"));
3169*3d8817e4Smiod       demand_empty_rest_of_line ();
3170*3d8817e4Smiod       return;
3171*3d8817e4Smiod     }
3172*3d8817e4Smiod 
3173*3d8817e4Smiod   cur_proc_ptr->pdr.framereg = tc_get_register (1);
3174*3d8817e4Smiod 
3175*3d8817e4Smiod   SKIP_WHITESPACE ();
3176*3d8817e4Smiod   if (*input_line_pointer++ != ','
3177*3d8817e4Smiod       || get_absolute_expression_and_terminator (&val) != ',')
3178*3d8817e4Smiod     {
3179*3d8817e4Smiod       as_warn (_("bad .frame directive"));
3180*3d8817e4Smiod       --input_line_pointer;
3181*3d8817e4Smiod       demand_empty_rest_of_line ();
3182*3d8817e4Smiod       return;
3183*3d8817e4Smiod     }
3184*3d8817e4Smiod 
3185*3d8817e4Smiod   cur_proc_ptr->pdr.frameoffset = val;
3186*3d8817e4Smiod 
3187*3d8817e4Smiod   cur_proc_ptr->pdr.pcreg = tc_get_register (0);
3188*3d8817e4Smiod 
3189*3d8817e4Smiod   /* Alpha-OSF1 adds "the offset of saved $a0 from $sp", according to
3190*3d8817e4Smiod      Sandro.  I don't yet know where this value should be stored, if
3191*3d8817e4Smiod      anywhere.  Don't call demand_empty_rest_of_line ().  */
3192*3d8817e4Smiod   s_ignore (42);
3193*3d8817e4Smiod }
3194*3d8817e4Smiod 
3195*3d8817e4Smiod /* Parse .mask directives.  */
3196*3d8817e4Smiod 
3197*3d8817e4Smiod void
ecoff_directive_mask(int ignore ATTRIBUTE_UNUSED)3198*3d8817e4Smiod ecoff_directive_mask (int ignore ATTRIBUTE_UNUSED)
3199*3d8817e4Smiod {
3200*3d8817e4Smiod   long val;
3201*3d8817e4Smiod 
3202*3d8817e4Smiod   if (cur_proc_ptr == (proc_t *) NULL)
3203*3d8817e4Smiod     {
3204*3d8817e4Smiod       as_warn (_(".mask outside of .ent"));
3205*3d8817e4Smiod       demand_empty_rest_of_line ();
3206*3d8817e4Smiod       return;
3207*3d8817e4Smiod     }
3208*3d8817e4Smiod 
3209*3d8817e4Smiod   if (get_absolute_expression_and_terminator (&val) != ',')
3210*3d8817e4Smiod     {
3211*3d8817e4Smiod       as_warn (_("bad .mask directive"));
3212*3d8817e4Smiod       --input_line_pointer;
3213*3d8817e4Smiod       demand_empty_rest_of_line ();
3214*3d8817e4Smiod       return;
3215*3d8817e4Smiod     }
3216*3d8817e4Smiod 
3217*3d8817e4Smiod   cur_proc_ptr->pdr.regmask = val;
3218*3d8817e4Smiod   cur_proc_ptr->pdr.regoffset = get_absolute_expression ();
3219*3d8817e4Smiod 
3220*3d8817e4Smiod   demand_empty_rest_of_line ();
3221*3d8817e4Smiod }
3222*3d8817e4Smiod 
3223*3d8817e4Smiod /* Parse .loc directives.  */
3224*3d8817e4Smiod 
3225*3d8817e4Smiod void
ecoff_directive_loc(int ignore ATTRIBUTE_UNUSED)3226*3d8817e4Smiod ecoff_directive_loc (int ignore ATTRIBUTE_UNUSED)
3227*3d8817e4Smiod {
3228*3d8817e4Smiod   lineno_list_t *list;
3229*3d8817e4Smiod   symint_t lineno;
3230*3d8817e4Smiod 
3231*3d8817e4Smiod   if (cur_file_ptr == (efdr_t *) NULL)
3232*3d8817e4Smiod     {
3233*3d8817e4Smiod       as_warn (_(".loc before .file"));
3234*3d8817e4Smiod       demand_empty_rest_of_line ();
3235*3d8817e4Smiod       return;
3236*3d8817e4Smiod     }
3237*3d8817e4Smiod 
3238*3d8817e4Smiod   if (now_seg != text_section)
3239*3d8817e4Smiod     {
3240*3d8817e4Smiod       as_warn (_(".loc outside of .text"));
3241*3d8817e4Smiod       demand_empty_rest_of_line ();
3242*3d8817e4Smiod       return;
3243*3d8817e4Smiod     }
3244*3d8817e4Smiod 
3245*3d8817e4Smiod   /* Skip the file number.  */
3246*3d8817e4Smiod   SKIP_WHITESPACE ();
3247*3d8817e4Smiod   get_absolute_expression ();
3248*3d8817e4Smiod   SKIP_WHITESPACE ();
3249*3d8817e4Smiod 
3250*3d8817e4Smiod   lineno = get_absolute_expression ();
3251*3d8817e4Smiod 
3252*3d8817e4Smiod #ifndef NO_LISTING
3253*3d8817e4Smiod   if (listing)
3254*3d8817e4Smiod     listing_source_line (lineno);
3255*3d8817e4Smiod #endif
3256*3d8817e4Smiod 
3257*3d8817e4Smiod   /* If we're building stabs, then output a special label rather than
3258*3d8817e4Smiod      ECOFF line number info.  */
3259*3d8817e4Smiod   if (stabs_seen)
3260*3d8817e4Smiod     {
3261*3d8817e4Smiod       (void) add_ecoff_symbol ((char *) NULL, st_Label, sc_Text,
3262*3d8817e4Smiod 			       symbol_new ("L0\001", now_seg,
3263*3d8817e4Smiod 					   (valueT) frag_now_fix (),
3264*3d8817e4Smiod 					   frag_now),
3265*3d8817e4Smiod 			       (bfd_vma) 0, 0, lineno);
3266*3d8817e4Smiod       return;
3267*3d8817e4Smiod     }
3268*3d8817e4Smiod 
3269*3d8817e4Smiod   list = allocate_lineno_list ();
3270*3d8817e4Smiod 
3271*3d8817e4Smiod   list->next = (lineno_list_t *) NULL;
3272*3d8817e4Smiod   list->file = cur_file_ptr;
3273*3d8817e4Smiod   list->proc = cur_proc_ptr;
3274*3d8817e4Smiod   list->frag = frag_now;
3275*3d8817e4Smiod   list->paddr = frag_now_fix ();
3276*3d8817e4Smiod   list->lineno = lineno;
3277*3d8817e4Smiod 
3278*3d8817e4Smiod   /* We don't want to merge files which have line numbers.  */
3279*3d8817e4Smiod   cur_file_ptr->fdr.fMerge = 0;
3280*3d8817e4Smiod 
3281*3d8817e4Smiod   /* A .loc directive will sometimes appear before a .ent directive,
3282*3d8817e4Smiod      which means that cur_proc_ptr will be NULL here.  Arrange to
3283*3d8817e4Smiod      patch this up.  */
3284*3d8817e4Smiod   if (cur_proc_ptr == (proc_t *) NULL)
3285*3d8817e4Smiod     {
3286*3d8817e4Smiod       lineno_list_t **pl;
3287*3d8817e4Smiod 
3288*3d8817e4Smiod       pl = &noproc_lineno;
3289*3d8817e4Smiod       while (*pl != (lineno_list_t *) NULL)
3290*3d8817e4Smiod 	pl = &(*pl)->next;
3291*3d8817e4Smiod       *pl = list;
3292*3d8817e4Smiod     }
3293*3d8817e4Smiod   else
3294*3d8817e4Smiod     {
3295*3d8817e4Smiod       last_lineno = list;
3296*3d8817e4Smiod       *last_lineno_ptr = list;
3297*3d8817e4Smiod       last_lineno_ptr = &list->next;
3298*3d8817e4Smiod     }
3299*3d8817e4Smiod }
3300*3d8817e4Smiod 
3301*3d8817e4Smiod /* The MIPS assembler sometimes inserts nop instructions in the
3302*3d8817e4Smiod    instruction stream.  When this happens, we must patch up the .loc
3303*3d8817e4Smiod    information so that it points to the instruction after the nop.  */
3304*3d8817e4Smiod 
3305*3d8817e4Smiod void
ecoff_fix_loc(fragS * old_frag,unsigned long old_frag_offset)3306*3d8817e4Smiod ecoff_fix_loc (fragS *old_frag, unsigned long old_frag_offset)
3307*3d8817e4Smiod {
3308*3d8817e4Smiod   if (last_lineno != NULL
3309*3d8817e4Smiod       && last_lineno->frag == old_frag
3310*3d8817e4Smiod       && last_lineno->paddr == old_frag_offset)
3311*3d8817e4Smiod     {
3312*3d8817e4Smiod       last_lineno->frag = frag_now;
3313*3d8817e4Smiod       last_lineno->paddr = frag_now_fix ();
3314*3d8817e4Smiod     }
3315*3d8817e4Smiod }
3316*3d8817e4Smiod 
3317*3d8817e4Smiod /* Make sure the @stabs symbol is emitted.  */
3318*3d8817e4Smiod 
3319*3d8817e4Smiod static void
mark_stabs(int ignore ATTRIBUTE_UNUSED)3320*3d8817e4Smiod mark_stabs (int ignore ATTRIBUTE_UNUSED)
3321*3d8817e4Smiod {
3322*3d8817e4Smiod   if (! stabs_seen)
3323*3d8817e4Smiod     {
3324*3d8817e4Smiod       /* Add a dummy @stabs dymbol.  */
3325*3d8817e4Smiod       stabs_seen = 1;
3326*3d8817e4Smiod       (void) add_ecoff_symbol (stabs_symbol, stNil, scInfo,
3327*3d8817e4Smiod 			       (symbolS *) NULL,
3328*3d8817e4Smiod 			       (bfd_vma) 0, (symint_t) -1,
3329*3d8817e4Smiod 			       ECOFF_MARK_STAB (0));
3330*3d8817e4Smiod     }
3331*3d8817e4Smiod }
3332*3d8817e4Smiod 
3333*3d8817e4Smiod /* Parse .weakext directives.  */
3334*3d8817e4Smiod #ifndef TC_MIPS
3335*3d8817e4Smiod /* For TC_MIPS use the version in tc-mips.c.  */
3336*3d8817e4Smiod void
ecoff_directive_weakext(int ignore ATTRIBUTE_UNUSED)3337*3d8817e4Smiod ecoff_directive_weakext (int ignore ATTRIBUTE_UNUSED)
3338*3d8817e4Smiod {
3339*3d8817e4Smiod   char *name;
3340*3d8817e4Smiod   int c;
3341*3d8817e4Smiod   symbolS *symbolP;
3342*3d8817e4Smiod   expressionS exp;
3343*3d8817e4Smiod 
3344*3d8817e4Smiod   name = input_line_pointer;
3345*3d8817e4Smiod   c = get_symbol_end ();
3346*3d8817e4Smiod   symbolP = symbol_find_or_make (name);
3347*3d8817e4Smiod   *input_line_pointer = c;
3348*3d8817e4Smiod 
3349*3d8817e4Smiod   SKIP_WHITESPACE ();
3350*3d8817e4Smiod 
3351*3d8817e4Smiod   if (*input_line_pointer == ',')
3352*3d8817e4Smiod     {
3353*3d8817e4Smiod       if (S_IS_DEFINED (symbolP))
3354*3d8817e4Smiod 	{
3355*3d8817e4Smiod 	  as_bad (_("symbol `%s' is already defined"),
3356*3d8817e4Smiod 		  S_GET_NAME (symbolP));
3357*3d8817e4Smiod 	  ignore_rest_of_line ();
3358*3d8817e4Smiod 	  return;
3359*3d8817e4Smiod 	}
3360*3d8817e4Smiod 
3361*3d8817e4Smiod       ++input_line_pointer;
3362*3d8817e4Smiod       SKIP_WHITESPACE ();
3363*3d8817e4Smiod       if (! is_end_of_line[(unsigned char) *input_line_pointer])
3364*3d8817e4Smiod 	{
3365*3d8817e4Smiod 	  expression (&exp);
3366*3d8817e4Smiod 	  if (exp.X_op != O_symbol)
3367*3d8817e4Smiod 	    {
3368*3d8817e4Smiod 	      as_bad (_("bad .weakext directive"));
3369*3d8817e4Smiod 	      ignore_rest_of_line ();
3370*3d8817e4Smiod 	      return;
3371*3d8817e4Smiod 	    }
3372*3d8817e4Smiod 	  symbol_set_value_expression (symbolP, &exp);
3373*3d8817e4Smiod 	}
3374*3d8817e4Smiod     }
3375*3d8817e4Smiod 
3376*3d8817e4Smiod   S_SET_WEAK (symbolP);
3377*3d8817e4Smiod 
3378*3d8817e4Smiod   demand_empty_rest_of_line ();
3379*3d8817e4Smiod }
3380*3d8817e4Smiod #endif /* not TC_MIPS */
3381*3d8817e4Smiod 
3382*3d8817e4Smiod /* Handle .stabs directives.  The actual parsing routine is done by a
3383*3d8817e4Smiod    generic routine.  This routine is called via OBJ_PROCESS_STAB.
3384*3d8817e4Smiod    When this is called, input_line_pointer will be pointing at the
3385*3d8817e4Smiod    value field of the stab.
3386*3d8817e4Smiod 
3387*3d8817e4Smiod    .stabs directives have five fields:
3388*3d8817e4Smiod 	"string"	a string, encoding the type information.
3389*3d8817e4Smiod 	code		a numeric code, defined in <stab.h>
3390*3d8817e4Smiod 	0		a zero
3391*3d8817e4Smiod 	desc		a zero or line number
3392*3d8817e4Smiod 	value		a numeric value or an address.
3393*3d8817e4Smiod 
3394*3d8817e4Smiod     If the value is relocatable, we transform this into:
3395*3d8817e4Smiod 	iss		points as an index into string space
3396*3d8817e4Smiod 	value		value from lookup of the name
3397*3d8817e4Smiod 	st		st from lookup of the name
3398*3d8817e4Smiod 	sc		sc from lookup of the name
3399*3d8817e4Smiod 	index		code|CODE_MASK
3400*3d8817e4Smiod 
3401*3d8817e4Smiod     If the value is not relocatable, we transform this into:
3402*3d8817e4Smiod 	iss		points as an index into string space
3403*3d8817e4Smiod 	value		value
3404*3d8817e4Smiod 	st		st_Nil
3405*3d8817e4Smiod 	sc		sc_Nil
3406*3d8817e4Smiod 	index		code|CODE_MASK
3407*3d8817e4Smiod 
3408*3d8817e4Smiod     .stabn directives have four fields (string is null):
3409*3d8817e4Smiod 	code		a numeric code, defined in <stab.h>
3410*3d8817e4Smiod 	0		a zero
3411*3d8817e4Smiod 	desc		a zero or a line number
3412*3d8817e4Smiod 	value		a numeric value or an address.  */
3413*3d8817e4Smiod 
3414*3d8817e4Smiod void
ecoff_stab(segT sec ATTRIBUTE_UNUSED,int what,const char * string,int type,int other,int desc)3415*3d8817e4Smiod ecoff_stab (segT sec ATTRIBUTE_UNUSED,
3416*3d8817e4Smiod 	    int what,
3417*3d8817e4Smiod 	    const char *string,
3418*3d8817e4Smiod 	    int type,
3419*3d8817e4Smiod 	    int other,
3420*3d8817e4Smiod 	    int desc)
3421*3d8817e4Smiod {
3422*3d8817e4Smiod   efdr_t *save_file_ptr = cur_file_ptr;
3423*3d8817e4Smiod   symbolS *sym;
3424*3d8817e4Smiod   symint_t value;
3425*3d8817e4Smiod   bfd_vma addend;
3426*3d8817e4Smiod   st_t st;
3427*3d8817e4Smiod   sc_t sc;
3428*3d8817e4Smiod   symint_t indx;
3429*3d8817e4Smiod   localsym_t *hold = NULL;
3430*3d8817e4Smiod 
3431*3d8817e4Smiod   ecoff_debugging_seen = 1;
3432*3d8817e4Smiod 
3433*3d8817e4Smiod   /* We don't handle .stabd.  */
3434*3d8817e4Smiod   if (what != 's' && what != 'n')
3435*3d8817e4Smiod     {
3436*3d8817e4Smiod       as_bad (_(".stab%c is not supported"), what);
3437*3d8817e4Smiod       return;
3438*3d8817e4Smiod     }
3439*3d8817e4Smiod 
3440*3d8817e4Smiod   /* A .stabn uses a null name, not an empty string.  */
3441*3d8817e4Smiod   if (what == 'n')
3442*3d8817e4Smiod     string = NULL;
3443*3d8817e4Smiod 
3444*3d8817e4Smiod   /* We ignore the other field.  */
3445*3d8817e4Smiod   if (other != 0)
3446*3d8817e4Smiod     as_warn (_(".stab%c: ignoring non-zero other field"), what);
3447*3d8817e4Smiod 
3448*3d8817e4Smiod   /* Make sure we have a current file.  */
3449*3d8817e4Smiod   if (cur_file_ptr == (efdr_t *) NULL)
3450*3d8817e4Smiod     {
3451*3d8817e4Smiod       add_file ((const char *) NULL, 0, 1);
3452*3d8817e4Smiod       save_file_ptr = cur_file_ptr;
3453*3d8817e4Smiod     }
3454*3d8817e4Smiod 
3455*3d8817e4Smiod   /* For stabs in ECOFF, the first symbol must be @stabs.  This is a
3456*3d8817e4Smiod      signal to gdb.  */
3457*3d8817e4Smiod   if (stabs_seen == 0)
3458*3d8817e4Smiod     mark_stabs (0);
3459*3d8817e4Smiod 
3460*3d8817e4Smiod   /* Line number stabs are handled differently, since they have two
3461*3d8817e4Smiod      values, the line number and the address of the label.  We use the
3462*3d8817e4Smiod      index field (aka desc) to hold the line number, and the value
3463*3d8817e4Smiod      field to hold the address.  The symbol type is st_Label, which
3464*3d8817e4Smiod      should be different from the other stabs, so that gdb can
3465*3d8817e4Smiod      recognize it.  */
3466*3d8817e4Smiod   if (type == N_SLINE)
3467*3d8817e4Smiod     {
3468*3d8817e4Smiod       SYMR dummy_symr;
3469*3d8817e4Smiod       char *name;
3470*3d8817e4Smiod       char name_end;
3471*3d8817e4Smiod 
3472*3d8817e4Smiod #ifndef NO_LISTING
3473*3d8817e4Smiod       if (listing)
3474*3d8817e4Smiod 	listing_source_line ((unsigned int) desc);
3475*3d8817e4Smiod #endif
3476*3d8817e4Smiod 
3477*3d8817e4Smiod       dummy_symr.index = desc;
3478*3d8817e4Smiod       if (dummy_symr.index != desc)
3479*3d8817e4Smiod 	{
3480*3d8817e4Smiod 	  as_warn (_("line number (%d) for .stab%c directive cannot fit in index field (20 bits)"),
3481*3d8817e4Smiod 		   desc, what);
3482*3d8817e4Smiod 	  return;
3483*3d8817e4Smiod 	}
3484*3d8817e4Smiod 
3485*3d8817e4Smiod       name = input_line_pointer;
3486*3d8817e4Smiod       name_end = get_symbol_end ();
3487*3d8817e4Smiod 
3488*3d8817e4Smiod       sym = symbol_find_or_make (name);
3489*3d8817e4Smiod       *input_line_pointer = name_end;
3490*3d8817e4Smiod 
3491*3d8817e4Smiod       value = 0;
3492*3d8817e4Smiod       addend = 0;
3493*3d8817e4Smiod       st = st_Label;
3494*3d8817e4Smiod       sc = sc_Text;
3495*3d8817e4Smiod       indx = desc;
3496*3d8817e4Smiod     }
3497*3d8817e4Smiod   else
3498*3d8817e4Smiod     {
3499*3d8817e4Smiod #ifndef NO_LISTING
3500*3d8817e4Smiod       if (listing && (type == N_SO || type == N_SOL))
3501*3d8817e4Smiod 	listing_source_file (string);
3502*3d8817e4Smiod #endif
3503*3d8817e4Smiod 
3504*3d8817e4Smiod       if (ISDIGIT (*input_line_pointer)
3505*3d8817e4Smiod 	  || *input_line_pointer == '-'
3506*3d8817e4Smiod 	  || *input_line_pointer == '+')
3507*3d8817e4Smiod 	{
3508*3d8817e4Smiod 	  st = st_Nil;
3509*3d8817e4Smiod 	  sc = sc_Nil;
3510*3d8817e4Smiod 	  sym = (symbolS *) NULL;
3511*3d8817e4Smiod 	  value = get_absolute_expression ();
3512*3d8817e4Smiod 	  addend = 0;
3513*3d8817e4Smiod 	}
3514*3d8817e4Smiod       else if (! is_name_beginner ((unsigned char) *input_line_pointer))
3515*3d8817e4Smiod 	{
3516*3d8817e4Smiod 	  as_warn (_("illegal .stab%c directive, bad character"), what);
3517*3d8817e4Smiod 	  return;
3518*3d8817e4Smiod 	}
3519*3d8817e4Smiod       else
3520*3d8817e4Smiod 	{
3521*3d8817e4Smiod 	  expressionS exp;
3522*3d8817e4Smiod 
3523*3d8817e4Smiod 	  sc = sc_Nil;
3524*3d8817e4Smiod 	  st = st_Nil;
3525*3d8817e4Smiod 
3526*3d8817e4Smiod 	  expression (&exp);
3527*3d8817e4Smiod 	  if (exp.X_op == O_constant)
3528*3d8817e4Smiod 	    {
3529*3d8817e4Smiod 	      sym = NULL;
3530*3d8817e4Smiod 	      value = exp.X_add_number;
3531*3d8817e4Smiod 	      addend = 0;
3532*3d8817e4Smiod 	    }
3533*3d8817e4Smiod 	  else if (exp.X_op == O_symbol)
3534*3d8817e4Smiod 	    {
3535*3d8817e4Smiod 	      sym = exp.X_add_symbol;
3536*3d8817e4Smiod 	      value = 0;
3537*3d8817e4Smiod 	      addend = exp.X_add_number;
3538*3d8817e4Smiod 	    }
3539*3d8817e4Smiod 	  else
3540*3d8817e4Smiod 	    {
3541*3d8817e4Smiod 	      sym = make_expr_symbol (&exp);
3542*3d8817e4Smiod 	      value = 0;
3543*3d8817e4Smiod 	      addend = 0;
3544*3d8817e4Smiod 	    }
3545*3d8817e4Smiod 	}
3546*3d8817e4Smiod 
3547*3d8817e4Smiod       indx = ECOFF_MARK_STAB (type);
3548*3d8817e4Smiod     }
3549*3d8817e4Smiod 
3550*3d8817e4Smiod   /* Don't store the stabs symbol we are creating as the type of the
3551*3d8817e4Smiod      ECOFF symbol.  We want to compute the type of the ECOFF symbol
3552*3d8817e4Smiod      independently.  */
3553*3d8817e4Smiod   if (sym != (symbolS *) NULL)
3554*3d8817e4Smiod     hold = symbol_get_obj (sym)->ecoff_symbol;
3555*3d8817e4Smiod 
3556*3d8817e4Smiod   (void) add_ecoff_symbol (string, st, sc, sym, addend, value, indx);
3557*3d8817e4Smiod 
3558*3d8817e4Smiod   if (sym != (symbolS *) NULL)
3559*3d8817e4Smiod     symbol_get_obj (sym)->ecoff_symbol = hold;
3560*3d8817e4Smiod 
3561*3d8817e4Smiod   /* Restore normal file type.  */
3562*3d8817e4Smiod   cur_file_ptr = save_file_ptr;
3563*3d8817e4Smiod }
3564*3d8817e4Smiod 
3565*3d8817e4Smiod /* Frob an ECOFF symbol.  Small common symbols go into a special
3566*3d8817e4Smiod    .scommon section rather than bfd_com_section.  */
3567*3d8817e4Smiod 
3568*3d8817e4Smiod void
ecoff_frob_symbol(symbolS * sym)3569*3d8817e4Smiod ecoff_frob_symbol (symbolS *sym)
3570*3d8817e4Smiod {
3571*3d8817e4Smiod   if (S_IS_COMMON (sym)
3572*3d8817e4Smiod       && S_GET_VALUE (sym) > 0
3573*3d8817e4Smiod       && S_GET_VALUE (sym) <= bfd_get_gp_size (stdoutput))
3574*3d8817e4Smiod     {
3575*3d8817e4Smiod       static asection scom_section;
3576*3d8817e4Smiod       static asymbol scom_symbol;
3577*3d8817e4Smiod 
3578*3d8817e4Smiod       /* We must construct a fake section similar to bfd_com_section
3579*3d8817e4Smiod          but with the name .scommon.  */
3580*3d8817e4Smiod       if (scom_section.name == NULL)
3581*3d8817e4Smiod 	{
3582*3d8817e4Smiod 	  scom_section = bfd_com_section;
3583*3d8817e4Smiod 	  scom_section.name = ".scommon";
3584*3d8817e4Smiod 	  scom_section.output_section = &scom_section;
3585*3d8817e4Smiod 	  scom_section.symbol = &scom_symbol;
3586*3d8817e4Smiod 	  scom_section.symbol_ptr_ptr = &scom_section.symbol;
3587*3d8817e4Smiod 	  scom_symbol = *bfd_com_section.symbol;
3588*3d8817e4Smiod 	  scom_symbol.name = ".scommon";
3589*3d8817e4Smiod 	  scom_symbol.section = &scom_section;
3590*3d8817e4Smiod 	}
3591*3d8817e4Smiod       S_SET_SEGMENT (sym, &scom_section);
3592*3d8817e4Smiod     }
3593*3d8817e4Smiod 
3594*3d8817e4Smiod   /* Double check weak symbols.  */
3595*3d8817e4Smiod   if (S_IS_WEAK (sym))
3596*3d8817e4Smiod     {
3597*3d8817e4Smiod       if (S_IS_COMMON (sym))
3598*3d8817e4Smiod 	as_bad (_("symbol `%s' can not be both weak and common"),
3599*3d8817e4Smiod 		S_GET_NAME (sym));
3600*3d8817e4Smiod     }
3601*3d8817e4Smiod }
3602*3d8817e4Smiod 
3603*3d8817e4Smiod /* Add bytes to the symbolic information buffer.  */
3604*3d8817e4Smiod 
3605*3d8817e4Smiod static char *
ecoff_add_bytes(char ** buf,char ** bufend,char * bufptr,unsigned long need)3606*3d8817e4Smiod ecoff_add_bytes (char **buf,
3607*3d8817e4Smiod 		 char **bufend,
3608*3d8817e4Smiod 		 char *bufptr,
3609*3d8817e4Smiod 		 unsigned long need)
3610*3d8817e4Smiod {
3611*3d8817e4Smiod   unsigned long at;
3612*3d8817e4Smiod   unsigned long want;
3613*3d8817e4Smiod 
3614*3d8817e4Smiod   at = bufptr - *buf;
3615*3d8817e4Smiod   need -= *bufend - bufptr;
3616*3d8817e4Smiod   if (need < PAGE_SIZE)
3617*3d8817e4Smiod     need = PAGE_SIZE;
3618*3d8817e4Smiod   want = (*bufend - *buf) + need;
3619*3d8817e4Smiod   *buf = xrealloc (*buf, want);
3620*3d8817e4Smiod   *bufend = *buf + want;
3621*3d8817e4Smiod   return *buf + at;
3622*3d8817e4Smiod }
3623*3d8817e4Smiod 
3624*3d8817e4Smiod /* Adjust the symbolic information buffer to the alignment required
3625*3d8817e4Smiod    for the ECOFF target debugging information.  */
3626*3d8817e4Smiod 
3627*3d8817e4Smiod static unsigned long
ecoff_padding_adjust(const struct ecoff_debug_swap * backend,char ** buf,char ** bufend,unsigned long offset,char ** bufptrptr)3628*3d8817e4Smiod ecoff_padding_adjust (const struct ecoff_debug_swap *backend,
3629*3d8817e4Smiod 		      char **buf,
3630*3d8817e4Smiod 		      char **bufend,
3631*3d8817e4Smiod 		      unsigned long offset,
3632*3d8817e4Smiod 		      char **bufptrptr)
3633*3d8817e4Smiod {
3634*3d8817e4Smiod   bfd_size_type align;
3635*3d8817e4Smiod 
3636*3d8817e4Smiod   align = backend->debug_align;
3637*3d8817e4Smiod   if ((offset & (align - 1)) != 0)
3638*3d8817e4Smiod     {
3639*3d8817e4Smiod       unsigned long add;
3640*3d8817e4Smiod 
3641*3d8817e4Smiod       add = align - (offset & (align - 1));
3642*3d8817e4Smiod       if ((unsigned long) (*bufend - (*buf + offset)) < add)
3643*3d8817e4Smiod 	(void) ecoff_add_bytes (buf, bufend, *buf + offset, add);
3644*3d8817e4Smiod       memset (*buf + offset, 0, add);
3645*3d8817e4Smiod       offset += add;
3646*3d8817e4Smiod       if (bufptrptr != (char **) NULL)
3647*3d8817e4Smiod 	*bufptrptr = *buf + offset;
3648*3d8817e4Smiod     }
3649*3d8817e4Smiod 
3650*3d8817e4Smiod   return offset;
3651*3d8817e4Smiod }
3652*3d8817e4Smiod 
3653*3d8817e4Smiod /* Build the line number information.  */
3654*3d8817e4Smiod 
3655*3d8817e4Smiod static unsigned long
ecoff_build_lineno(const struct ecoff_debug_swap * backend,char ** buf,char ** bufend,unsigned long offset,long * linecntptr)3656*3d8817e4Smiod ecoff_build_lineno (const struct ecoff_debug_swap *backend,
3657*3d8817e4Smiod 		    char **buf,
3658*3d8817e4Smiod 		    char **bufend,
3659*3d8817e4Smiod 		    unsigned long offset,
3660*3d8817e4Smiod 		    long *linecntptr)
3661*3d8817e4Smiod {
3662*3d8817e4Smiod   char *bufptr;
3663*3d8817e4Smiod   register lineno_list_t *l;
3664*3d8817e4Smiod   lineno_list_t *last;
3665*3d8817e4Smiod   efdr_t *file;
3666*3d8817e4Smiod   proc_t *proc;
3667*3d8817e4Smiod   unsigned long c;
3668*3d8817e4Smiod   long iline;
3669*3d8817e4Smiod   long totcount;
3670*3d8817e4Smiod   lineno_list_t first;
3671*3d8817e4Smiod   lineno_list_t *local_first_lineno = first_lineno;
3672*3d8817e4Smiod 
3673*3d8817e4Smiod   if (linecntptr != (long *) NULL)
3674*3d8817e4Smiod     *linecntptr = 0;
3675*3d8817e4Smiod 
3676*3d8817e4Smiod   bufptr = *buf + offset;
3677*3d8817e4Smiod 
3678*3d8817e4Smiod   file = (efdr_t *) NULL;
3679*3d8817e4Smiod   proc = (proc_t *) NULL;
3680*3d8817e4Smiod   last = (lineno_list_t *) NULL;
3681*3d8817e4Smiod   c = offset;
3682*3d8817e4Smiod   iline = 0;
3683*3d8817e4Smiod   totcount = 0;
3684*3d8817e4Smiod 
3685*3d8817e4Smiod   /* FIXME?  Now that MIPS embedded-PIC is gone, it may be safe to
3686*3d8817e4Smiod      remove this code.  */
3687*3d8817e4Smiod   /* For some reason the address of the first procedure is ignored
3688*3d8817e4Smiod      when reading line numbers.  This doesn't matter if the address of
3689*3d8817e4Smiod      the first procedure is 0, but when gcc is generating MIPS
3690*3d8817e4Smiod      embedded PIC code, it will put strings in the .text section
3691*3d8817e4Smiod      before the first procedure.  We cope by inserting a dummy line if
3692*3d8817e4Smiod      the address of the first procedure is not 0.  Hopefully this
3693*3d8817e4Smiod      won't screw things up too badly.
3694*3d8817e4Smiod 
3695*3d8817e4Smiod      Don't do this for ECOFF assembly source line numbers.  They work
3696*3d8817e4Smiod      without this extra attention.  */
3697*3d8817e4Smiod   if (debug_type != DEBUG_ECOFF
3698*3d8817e4Smiod       && first_proc_ptr != (proc_t *) NULL
3699*3d8817e4Smiod       && local_first_lineno != (lineno_list_t *) NULL
3700*3d8817e4Smiod       && ((S_GET_VALUE (first_proc_ptr->sym->as_sym)
3701*3d8817e4Smiod 	   + bfd_get_section_vma (stdoutput,
3702*3d8817e4Smiod 				  S_GET_SEGMENT (first_proc_ptr->sym->as_sym)))
3703*3d8817e4Smiod 	  != 0))
3704*3d8817e4Smiod     {
3705*3d8817e4Smiod       first.file = local_first_lineno->file;
3706*3d8817e4Smiod       first.proc = local_first_lineno->proc;
3707*3d8817e4Smiod       first.frag = &zero_address_frag;
3708*3d8817e4Smiod       first.paddr = 0;
3709*3d8817e4Smiod       first.lineno = 0;
3710*3d8817e4Smiod 
3711*3d8817e4Smiod       first.next = local_first_lineno;
3712*3d8817e4Smiod       local_first_lineno = &first;
3713*3d8817e4Smiod     }
3714*3d8817e4Smiod 
3715*3d8817e4Smiod   for (l = local_first_lineno; l != (lineno_list_t *) NULL; l = l->next)
3716*3d8817e4Smiod     {
3717*3d8817e4Smiod       long count;
3718*3d8817e4Smiod       long delta;
3719*3d8817e4Smiod 
3720*3d8817e4Smiod       /* Get the offset to the memory address of the next line number
3721*3d8817e4Smiod          (in words).  Do this first, so that we can skip ahead to the
3722*3d8817e4Smiod          next useful line number entry.  */
3723*3d8817e4Smiod       if (l->next == (lineno_list_t *) NULL)
3724*3d8817e4Smiod 	{
3725*3d8817e4Smiod 	  /* We want a count of zero, but it will be decremented
3726*3d8817e4Smiod 	     before it is used.  */
3727*3d8817e4Smiod 	  count = 1;
3728*3d8817e4Smiod 	}
3729*3d8817e4Smiod       else if (l->next->frag->fr_address + l->next->paddr
3730*3d8817e4Smiod 	       > l->frag->fr_address + l->paddr)
3731*3d8817e4Smiod 	{
3732*3d8817e4Smiod 	  count = ((l->next->frag->fr_address + l->next->paddr
3733*3d8817e4Smiod 		    - (l->frag->fr_address + l->paddr))
3734*3d8817e4Smiod 		   >> 2);
3735*3d8817e4Smiod 	}
3736*3d8817e4Smiod       else
3737*3d8817e4Smiod 	{
3738*3d8817e4Smiod 	  /* Don't change last, so we still get the right delta.  */
3739*3d8817e4Smiod 	  continue;
3740*3d8817e4Smiod 	}
3741*3d8817e4Smiod 
3742*3d8817e4Smiod       if (l->file != file || l->proc != proc)
3743*3d8817e4Smiod 	{
3744*3d8817e4Smiod 	  if (l->proc != proc && proc != (proc_t *) NULL)
3745*3d8817e4Smiod 	    proc->pdr.lnHigh = last->lineno;
3746*3d8817e4Smiod 	  if (l->file != file && file != (efdr_t *) NULL)
3747*3d8817e4Smiod 	    {
3748*3d8817e4Smiod 	      file->fdr.cbLine = c - file->fdr.cbLineOffset;
3749*3d8817e4Smiod 	      file->fdr.cline = totcount + count;
3750*3d8817e4Smiod 	      if (linecntptr != (long *) NULL)
3751*3d8817e4Smiod 		*linecntptr += totcount + count;
3752*3d8817e4Smiod 	      totcount = 0;
3753*3d8817e4Smiod 	    }
3754*3d8817e4Smiod 
3755*3d8817e4Smiod 	  if (l->file != file)
3756*3d8817e4Smiod 	    {
3757*3d8817e4Smiod 	      efdr_t *last_file = file;
3758*3d8817e4Smiod 
3759*3d8817e4Smiod 	      file = l->file;
3760*3d8817e4Smiod 	      if (last_file != (efdr_t *) NULL)
3761*3d8817e4Smiod 		file->fdr.ilineBase
3762*3d8817e4Smiod 		  = last_file->fdr.ilineBase + last_file->fdr.cline;
3763*3d8817e4Smiod 	      else
3764*3d8817e4Smiod 		file->fdr.ilineBase = 0;
3765*3d8817e4Smiod 	      file->fdr.cbLineOffset = c;
3766*3d8817e4Smiod 	    }
3767*3d8817e4Smiod 	  if (l->proc != proc)
3768*3d8817e4Smiod 	    {
3769*3d8817e4Smiod 	      proc = l->proc;
3770*3d8817e4Smiod 	      if (proc != (proc_t *) NULL)
3771*3d8817e4Smiod 		{
3772*3d8817e4Smiod 		  proc->pdr.lnLow = l->lineno;
3773*3d8817e4Smiod 		  proc->pdr.cbLineOffset = c - file->fdr.cbLineOffset;
3774*3d8817e4Smiod 		  proc->pdr.iline = totcount;
3775*3d8817e4Smiod 		}
3776*3d8817e4Smiod 	    }
3777*3d8817e4Smiod 
3778*3d8817e4Smiod 	  last = (lineno_list_t *) NULL;
3779*3d8817e4Smiod 	}
3780*3d8817e4Smiod 
3781*3d8817e4Smiod       totcount += count;
3782*3d8817e4Smiod 
3783*3d8817e4Smiod       /* Get the offset to this line number.  */
3784*3d8817e4Smiod       if (last == (lineno_list_t *) NULL)
3785*3d8817e4Smiod 	delta = 0;
3786*3d8817e4Smiod       else
3787*3d8817e4Smiod 	delta = l->lineno - last->lineno;
3788*3d8817e4Smiod 
3789*3d8817e4Smiod       /* Put in the offset to this line number.  */
3790*3d8817e4Smiod       while (delta != 0)
3791*3d8817e4Smiod 	{
3792*3d8817e4Smiod 	  int setcount;
3793*3d8817e4Smiod 
3794*3d8817e4Smiod 	  /* 1 is added to each count read.  */
3795*3d8817e4Smiod 	  --count;
3796*3d8817e4Smiod 	  /* We can only adjust the word count by up to 15 words at a
3797*3d8817e4Smiod 	     time.  */
3798*3d8817e4Smiod 	  if (count <= 0x0f)
3799*3d8817e4Smiod 	    {
3800*3d8817e4Smiod 	      setcount = count;
3801*3d8817e4Smiod 	      count = 0;
3802*3d8817e4Smiod 	    }
3803*3d8817e4Smiod 	  else
3804*3d8817e4Smiod 	    {
3805*3d8817e4Smiod 	      setcount = 0x0f;
3806*3d8817e4Smiod 	      count -= 0x0f;
3807*3d8817e4Smiod 	    }
3808*3d8817e4Smiod 	  if (delta >= -7 && delta <= 7)
3809*3d8817e4Smiod 	    {
3810*3d8817e4Smiod 	      if (bufptr >= *bufend)
3811*3d8817e4Smiod 		bufptr = ecoff_add_bytes (buf, bufend, bufptr, (long) 1);
3812*3d8817e4Smiod 	      *bufptr++ = setcount + (delta << 4);
3813*3d8817e4Smiod 	      delta = 0;
3814*3d8817e4Smiod 	      ++c;
3815*3d8817e4Smiod 	    }
3816*3d8817e4Smiod 	  else
3817*3d8817e4Smiod 	    {
3818*3d8817e4Smiod 	      int set;
3819*3d8817e4Smiod 
3820*3d8817e4Smiod 	      if (*bufend - bufptr < 3)
3821*3d8817e4Smiod 		bufptr = ecoff_add_bytes (buf, bufend, bufptr, (long) 3);
3822*3d8817e4Smiod 	      *bufptr++ = setcount + (8 << 4);
3823*3d8817e4Smiod 	      if (delta < -0x8000)
3824*3d8817e4Smiod 		{
3825*3d8817e4Smiod 		  set = -0x8000;
3826*3d8817e4Smiod 		  delta += 0x8000;
3827*3d8817e4Smiod 		}
3828*3d8817e4Smiod 	      else if (delta > 0x7fff)
3829*3d8817e4Smiod 		{
3830*3d8817e4Smiod 		  set = 0x7fff;
3831*3d8817e4Smiod 		  delta -= 0x7fff;
3832*3d8817e4Smiod 		}
3833*3d8817e4Smiod 	      else
3834*3d8817e4Smiod 		{
3835*3d8817e4Smiod 		  set = delta;
3836*3d8817e4Smiod 		  delta = 0;
3837*3d8817e4Smiod 		}
3838*3d8817e4Smiod 	      *bufptr++ = set >> 8;
3839*3d8817e4Smiod 	      *bufptr++ = set & 0xffff;
3840*3d8817e4Smiod 	      c += 3;
3841*3d8817e4Smiod 	    }
3842*3d8817e4Smiod 	}
3843*3d8817e4Smiod 
3844*3d8817e4Smiod       /* Finish adjusting the count.  */
3845*3d8817e4Smiod       while (count > 0)
3846*3d8817e4Smiod 	{
3847*3d8817e4Smiod 	  if (bufptr >= *bufend)
3848*3d8817e4Smiod 	    bufptr = ecoff_add_bytes (buf, bufend, bufptr, (long) 1);
3849*3d8817e4Smiod 	  /* 1 is added to each count read.  */
3850*3d8817e4Smiod 	  --count;
3851*3d8817e4Smiod 	  if (count > 0x0f)
3852*3d8817e4Smiod 	    {
3853*3d8817e4Smiod 	      *bufptr++ = 0x0f;
3854*3d8817e4Smiod 	      count -= 0x0f;
3855*3d8817e4Smiod 	    }
3856*3d8817e4Smiod 	  else
3857*3d8817e4Smiod 	    {
3858*3d8817e4Smiod 	      *bufptr++ = count;
3859*3d8817e4Smiod 	      count = 0;
3860*3d8817e4Smiod 	    }
3861*3d8817e4Smiod 	  ++c;
3862*3d8817e4Smiod 	}
3863*3d8817e4Smiod 
3864*3d8817e4Smiod       ++iline;
3865*3d8817e4Smiod       last = l;
3866*3d8817e4Smiod     }
3867*3d8817e4Smiod 
3868*3d8817e4Smiod   if (proc != (proc_t *) NULL)
3869*3d8817e4Smiod     proc->pdr.lnHigh = last->lineno;
3870*3d8817e4Smiod   if (file != (efdr_t *) NULL)
3871*3d8817e4Smiod     {
3872*3d8817e4Smiod       file->fdr.cbLine = c - file->fdr.cbLineOffset;
3873*3d8817e4Smiod       file->fdr.cline = totcount;
3874*3d8817e4Smiod     }
3875*3d8817e4Smiod 
3876*3d8817e4Smiod   if (linecntptr != (long *) NULL)
3877*3d8817e4Smiod     *linecntptr += totcount;
3878*3d8817e4Smiod 
3879*3d8817e4Smiod   c = ecoff_padding_adjust (backend, buf, bufend, c, &bufptr);
3880*3d8817e4Smiod 
3881*3d8817e4Smiod   return c;
3882*3d8817e4Smiod }
3883*3d8817e4Smiod 
3884*3d8817e4Smiod /* Build and swap out the symbols.  */
3885*3d8817e4Smiod 
3886*3d8817e4Smiod static unsigned long
ecoff_build_symbols(const struct ecoff_debug_swap * backend,char ** buf,char ** bufend,unsigned long offset)3887*3d8817e4Smiod ecoff_build_symbols (const struct ecoff_debug_swap *backend,
3888*3d8817e4Smiod 		     char **buf,
3889*3d8817e4Smiod 		     char **bufend,
3890*3d8817e4Smiod 		     unsigned long offset)
3891*3d8817e4Smiod {
3892*3d8817e4Smiod   const bfd_size_type external_sym_size = backend->external_sym_size;
3893*3d8817e4Smiod   void (* const swap_sym_out) (bfd *, const SYMR *, PTR)
3894*3d8817e4Smiod     = backend->swap_sym_out;
3895*3d8817e4Smiod   char *sym_out;
3896*3d8817e4Smiod   long isym;
3897*3d8817e4Smiod   vlinks_t *file_link;
3898*3d8817e4Smiod 
3899*3d8817e4Smiod   sym_out = *buf + offset;
3900*3d8817e4Smiod 
3901*3d8817e4Smiod   isym = 0;
3902*3d8817e4Smiod 
3903*3d8817e4Smiod   /* The symbols are stored by file.  */
3904*3d8817e4Smiod   for (file_link = file_desc.first;
3905*3d8817e4Smiod        file_link != (vlinks_t *) NULL;
3906*3d8817e4Smiod        file_link = file_link->next)
3907*3d8817e4Smiod     {
3908*3d8817e4Smiod       int ifilesym;
3909*3d8817e4Smiod       int fil_cnt;
3910*3d8817e4Smiod       efdr_t *fil_ptr;
3911*3d8817e4Smiod       efdr_t *fil_end;
3912*3d8817e4Smiod 
3913*3d8817e4Smiod       if (file_link->next == (vlinks_t *) NULL)
3914*3d8817e4Smiod 	fil_cnt = file_desc.objects_last_page;
3915*3d8817e4Smiod       else
3916*3d8817e4Smiod 	fil_cnt = file_desc.objects_per_page;
3917*3d8817e4Smiod       fil_ptr = file_link->datum->file;
3918*3d8817e4Smiod       fil_end = fil_ptr + fil_cnt;
3919*3d8817e4Smiod       for (; fil_ptr < fil_end; fil_ptr++)
3920*3d8817e4Smiod 	{
3921*3d8817e4Smiod 	  vlinks_t *sym_link;
3922*3d8817e4Smiod 
3923*3d8817e4Smiod 	  fil_ptr->fdr.isymBase = isym;
3924*3d8817e4Smiod 	  ifilesym = isym;
3925*3d8817e4Smiod 	  for (sym_link = fil_ptr->symbols.first;
3926*3d8817e4Smiod 	       sym_link != (vlinks_t *) NULL;
3927*3d8817e4Smiod 	       sym_link = sym_link->next)
3928*3d8817e4Smiod 	    {
3929*3d8817e4Smiod 	      int sym_cnt;
3930*3d8817e4Smiod 	      localsym_t *sym_ptr;
3931*3d8817e4Smiod 	      localsym_t *sym_end;
3932*3d8817e4Smiod 
3933*3d8817e4Smiod 	      if (sym_link->next == (vlinks_t *) NULL)
3934*3d8817e4Smiod 		sym_cnt = fil_ptr->symbols.objects_last_page;
3935*3d8817e4Smiod 	      else
3936*3d8817e4Smiod 		sym_cnt = fil_ptr->symbols.objects_per_page;
3937*3d8817e4Smiod 	      sym_ptr = sym_link->datum->sym;
3938*3d8817e4Smiod 	      sym_end = sym_ptr + sym_cnt;
3939*3d8817e4Smiod 	      for (; sym_ptr < sym_end; sym_ptr++)
3940*3d8817e4Smiod 		{
3941*3d8817e4Smiod 		  int local;
3942*3d8817e4Smiod 		  symbolS *as_sym;
3943*3d8817e4Smiod 		  forward_t *f;
3944*3d8817e4Smiod 
3945*3d8817e4Smiod 		  know (sym_ptr->file_ptr == fil_ptr);
3946*3d8817e4Smiod 
3947*3d8817e4Smiod 		  /* If there is no associated gas symbol, then this
3948*3d8817e4Smiod 		     is a pure debugging symbol.  We have already
3949*3d8817e4Smiod 		     added the name (if any) to fil_ptr->strings.
3950*3d8817e4Smiod 		     Otherwise we must decide whether this is an
3951*3d8817e4Smiod 		     external or a local symbol (actually, it may be
3952*3d8817e4Smiod 		     both if the local provides additional debugging
3953*3d8817e4Smiod 		     information for the external).  */
3954*3d8817e4Smiod 		  local = 1;
3955*3d8817e4Smiod 		  as_sym = sym_ptr->as_sym;
3956*3d8817e4Smiod 		  if (as_sym != (symbolS *) NULL)
3957*3d8817e4Smiod 		    {
3958*3d8817e4Smiod 		      symint_t indx;
3959*3d8817e4Smiod 
3960*3d8817e4Smiod 		      /* The value of a block start symbol is the
3961*3d8817e4Smiod 		         offset from the start of the procedure.  For
3962*3d8817e4Smiod 		         other symbols we just use the gas value (but
3963*3d8817e4Smiod 		         we must offset it by the vma of the section,
3964*3d8817e4Smiod 		         just as BFD does, because BFD will not see
3965*3d8817e4Smiod 		         this value).  */
3966*3d8817e4Smiod 		      if (sym_ptr->ecoff_sym.asym.st == (int) st_Block
3967*3d8817e4Smiod 			  && sym_ptr->ecoff_sym.asym.sc == (int) sc_Text)
3968*3d8817e4Smiod 			{
3969*3d8817e4Smiod 			  symbolS *begin_sym;
3970*3d8817e4Smiod 
3971*3d8817e4Smiod 			  know (sym_ptr->proc_ptr != (proc_t *) NULL);
3972*3d8817e4Smiod 			  begin_sym = sym_ptr->proc_ptr->sym->as_sym;
3973*3d8817e4Smiod 			  if (S_GET_SEGMENT (as_sym)
3974*3d8817e4Smiod 			      != S_GET_SEGMENT (begin_sym))
3975*3d8817e4Smiod 			    as_warn (_(".begin/.bend in different segments"));
3976*3d8817e4Smiod 			  sym_ptr->ecoff_sym.asym.value =
3977*3d8817e4Smiod 			    S_GET_VALUE (as_sym) - S_GET_VALUE (begin_sym);
3978*3d8817e4Smiod 			}
3979*3d8817e4Smiod 		      else
3980*3d8817e4Smiod 			sym_ptr->ecoff_sym.asym.value =
3981*3d8817e4Smiod 			  (S_GET_VALUE (as_sym)
3982*3d8817e4Smiod 			   + bfd_get_section_vma (stdoutput,
3983*3d8817e4Smiod 						  S_GET_SEGMENT (as_sym))
3984*3d8817e4Smiod 			   + sym_ptr->addend);
3985*3d8817e4Smiod 
3986*3d8817e4Smiod 		      sym_ptr->ecoff_sym.weakext = S_IS_WEAK (as_sym);
3987*3d8817e4Smiod 
3988*3d8817e4Smiod 		      /* Set st_Proc to st_StaticProc for local
3989*3d8817e4Smiod 			 functions.  */
3990*3d8817e4Smiod 		      if (sym_ptr->ecoff_sym.asym.st == st_Proc
3991*3d8817e4Smiod 			  && S_IS_DEFINED (as_sym)
3992*3d8817e4Smiod 			  && ! S_IS_EXTERNAL (as_sym)
3993*3d8817e4Smiod 			  && ! S_IS_WEAK (as_sym))
3994*3d8817e4Smiod 			sym_ptr->ecoff_sym.asym.st = st_StaticProc;
3995*3d8817e4Smiod 
3996*3d8817e4Smiod 		      /* Get the type and storage class based on where
3997*3d8817e4Smiod 		         the symbol actually wound up.  Traditionally,
3998*3d8817e4Smiod 		         N_LBRAC and N_RBRAC are *not* relocated.  */
3999*3d8817e4Smiod 		      indx = sym_ptr->ecoff_sym.asym.index;
4000*3d8817e4Smiod 		      if (sym_ptr->ecoff_sym.asym.st == st_Nil
4001*3d8817e4Smiod 			  && sym_ptr->ecoff_sym.asym.sc == sc_Nil
4002*3d8817e4Smiod 			  && (! ECOFF_IS_STAB (&sym_ptr->ecoff_sym.asym)
4003*3d8817e4Smiod 			      || ((ECOFF_UNMARK_STAB (indx) != N_LBRAC)
4004*3d8817e4Smiod 				  && (ECOFF_UNMARK_STAB (indx) != N_RBRAC))))
4005*3d8817e4Smiod 			{
4006*3d8817e4Smiod 			  segT seg;
4007*3d8817e4Smiod 			  const char *segname;
4008*3d8817e4Smiod 			  st_t st;
4009*3d8817e4Smiod 			  sc_t sc;
4010*3d8817e4Smiod 
4011*3d8817e4Smiod 			  seg = S_GET_SEGMENT (as_sym);
4012*3d8817e4Smiod 			  segname = segment_name (seg);
4013*3d8817e4Smiod 
4014*3d8817e4Smiod 			  if (! ECOFF_IS_STAB (&sym_ptr->ecoff_sym.asym)
4015*3d8817e4Smiod 			      && (S_IS_EXTERNAL (as_sym)
4016*3d8817e4Smiod 				  || S_IS_WEAK (as_sym)
4017*3d8817e4Smiod 				  || ! S_IS_DEFINED (as_sym)))
4018*3d8817e4Smiod 			    {
4019*3d8817e4Smiod 			      if ((symbol_get_bfdsym (as_sym)->flags
4020*3d8817e4Smiod 				   & BSF_FUNCTION) != 0)
4021*3d8817e4Smiod 				st = st_Proc;
4022*3d8817e4Smiod 			      else
4023*3d8817e4Smiod 				st = st_Global;
4024*3d8817e4Smiod 			    }
4025*3d8817e4Smiod 			  else if (seg == text_section)
4026*3d8817e4Smiod 			    st = st_Label;
4027*3d8817e4Smiod 			  else
4028*3d8817e4Smiod 			    st = st_Static;
4029*3d8817e4Smiod 
4030*3d8817e4Smiod 			  if (! S_IS_DEFINED (as_sym))
4031*3d8817e4Smiod 			    {
4032*3d8817e4Smiod 			      valueT s;
4033*3d8817e4Smiod 
4034*3d8817e4Smiod 			      s = symbol_get_obj (as_sym)->ecoff_extern_size;
4035*3d8817e4Smiod 			      if (s == 0
4036*3d8817e4Smiod 				  || s > bfd_get_gp_size (stdoutput))
4037*3d8817e4Smiod 				sc = sc_Undefined;
4038*3d8817e4Smiod 			      else
4039*3d8817e4Smiod 				{
4040*3d8817e4Smiod 				  sc = sc_SUndefined;
4041*3d8817e4Smiod 				  sym_ptr->ecoff_sym.asym.value = s;
4042*3d8817e4Smiod 				}
4043*3d8817e4Smiod #ifdef S_SET_SIZE
4044*3d8817e4Smiod 			      S_SET_SIZE (as_sym, s);
4045*3d8817e4Smiod #endif
4046*3d8817e4Smiod 			    }
4047*3d8817e4Smiod 			  else if (S_IS_COMMON (as_sym))
4048*3d8817e4Smiod 			    {
4049*3d8817e4Smiod 			      if (S_GET_VALUE (as_sym) > 0
4050*3d8817e4Smiod 				  && (S_GET_VALUE (as_sym)
4051*3d8817e4Smiod 				      <= bfd_get_gp_size (stdoutput)))
4052*3d8817e4Smiod 				sc = sc_SCommon;
4053*3d8817e4Smiod 			      else
4054*3d8817e4Smiod 				sc = sc_Common;
4055*3d8817e4Smiod 			    }
4056*3d8817e4Smiod 			  else if (seg == text_section)
4057*3d8817e4Smiod 			    sc = sc_Text;
4058*3d8817e4Smiod 			  else if (seg == data_section)
4059*3d8817e4Smiod 			    sc = sc_Data;
4060*3d8817e4Smiod 			  else if (strcmp (segname, ".rdata") == 0
4061*3d8817e4Smiod 				   || strcmp (segname, ".rodata") == 0)
4062*3d8817e4Smiod 			    sc = sc_RData;
4063*3d8817e4Smiod 			  else if (strcmp (segname, ".sdata") == 0)
4064*3d8817e4Smiod 			    sc = sc_SData;
4065*3d8817e4Smiod 			  else if (seg == bss_section)
4066*3d8817e4Smiod 			    sc = sc_Bss;
4067*3d8817e4Smiod 			  else if (strcmp (segname, ".sbss") == 0)
4068*3d8817e4Smiod 			    sc = sc_SBss;
4069*3d8817e4Smiod 			  else if (seg == &bfd_abs_section)
4070*3d8817e4Smiod 			    sc = sc_Abs;
4071*3d8817e4Smiod 			  else
4072*3d8817e4Smiod 			    {
4073*3d8817e4Smiod 			      /* This must be a user named section.
4074*3d8817e4Smiod 			         This is not possible in ECOFF, but it
4075*3d8817e4Smiod 			         is in ELF.  */
4076*3d8817e4Smiod 			      sc = sc_Data;
4077*3d8817e4Smiod 			    }
4078*3d8817e4Smiod 
4079*3d8817e4Smiod 			  sym_ptr->ecoff_sym.asym.st = (int) st;
4080*3d8817e4Smiod 			  sym_ptr->ecoff_sym.asym.sc = (int) sc;
4081*3d8817e4Smiod 			}
4082*3d8817e4Smiod 
4083*3d8817e4Smiod 		      /* This is just an external symbol if it is
4084*3d8817e4Smiod 		         outside a procedure and it has a type.
4085*3d8817e4Smiod 		         FIXME: g++ will generate symbols which have
4086*3d8817e4Smiod 		         different names in the debugging information
4087*3d8817e4Smiod 		         than the actual symbol.  Should we handle
4088*3d8817e4Smiod 		         them here?  */
4089*3d8817e4Smiod 		      if ((S_IS_EXTERNAL (as_sym)
4090*3d8817e4Smiod 			   || S_IS_WEAK (as_sym)
4091*3d8817e4Smiod 			   || ! S_IS_DEFINED (as_sym))
4092*3d8817e4Smiod 			  && sym_ptr->proc_ptr == (proc_t *) NULL
4093*3d8817e4Smiod 			  && sym_ptr->ecoff_sym.asym.st != (int) st_Nil
4094*3d8817e4Smiod 			  && ! ECOFF_IS_STAB (&sym_ptr->ecoff_sym.asym))
4095*3d8817e4Smiod 			local = 0;
4096*3d8817e4Smiod 
4097*3d8817e4Smiod 		      /* This is just an external symbol if it is a
4098*3d8817e4Smiod 		         common symbol.  */
4099*3d8817e4Smiod 		      if (S_IS_COMMON (as_sym))
4100*3d8817e4Smiod 			local = 0;
4101*3d8817e4Smiod 
4102*3d8817e4Smiod 		      /* If an st_end symbol has an associated gas
4103*3d8817e4Smiod 		         symbol, then it is a local label created for
4104*3d8817e4Smiod 		         a .bend or .end directive.  Stabs line
4105*3d8817e4Smiod 		         numbers will have \001 in the names.  */
4106*3d8817e4Smiod 		      if (local
4107*3d8817e4Smiod 			  && sym_ptr->ecoff_sym.asym.st != st_End
4108*3d8817e4Smiod 			  && strchr (sym_ptr->name, '\001') == 0)
4109*3d8817e4Smiod 			sym_ptr->ecoff_sym.asym.iss =
4110*3d8817e4Smiod 			  add_string (&fil_ptr->strings,
4111*3d8817e4Smiod 				      fil_ptr->str_hash,
4112*3d8817e4Smiod 				      sym_ptr->name,
4113*3d8817e4Smiod 				      (shash_t **) NULL);
4114*3d8817e4Smiod 		    }
4115*3d8817e4Smiod 
4116*3d8817e4Smiod 		  /* We now know the index of this symbol; fill in
4117*3d8817e4Smiod 		     locations that have been waiting for that
4118*3d8817e4Smiod 		     information.  */
4119*3d8817e4Smiod 		  if (sym_ptr->begin_ptr != (localsym_t *) NULL)
4120*3d8817e4Smiod 		    {
4121*3d8817e4Smiod 		      localsym_t *begin_ptr;
4122*3d8817e4Smiod 		      st_t begin_type;
4123*3d8817e4Smiod 
4124*3d8817e4Smiod 		      know (local);
4125*3d8817e4Smiod 		      begin_ptr = sym_ptr->begin_ptr;
4126*3d8817e4Smiod 		      know (begin_ptr->sym_index != -1);
4127*3d8817e4Smiod 		      sym_ptr->ecoff_sym.asym.index = begin_ptr->sym_index;
4128*3d8817e4Smiod 		      if (sym_ptr->ecoff_sym.asym.sc != (int) sc_Info)
4129*3d8817e4Smiod 			sym_ptr->ecoff_sym.asym.iss =
4130*3d8817e4Smiod 			  begin_ptr->ecoff_sym.asym.iss;
4131*3d8817e4Smiod 
4132*3d8817e4Smiod 		      begin_type = begin_ptr->ecoff_sym.asym.st;
4133*3d8817e4Smiod 		      if (begin_type == st_File
4134*3d8817e4Smiod 			  || begin_type == st_Block)
4135*3d8817e4Smiod 			{
4136*3d8817e4Smiod 			  begin_ptr->ecoff_sym.asym.index =
4137*3d8817e4Smiod 			    isym - ifilesym + 1;
4138*3d8817e4Smiod 			  (*swap_sym_out) (stdoutput,
4139*3d8817e4Smiod 					   &begin_ptr->ecoff_sym.asym,
4140*3d8817e4Smiod 					   (*buf
4141*3d8817e4Smiod 					    + offset
4142*3d8817e4Smiod 					    + (begin_ptr->sym_index
4143*3d8817e4Smiod 					       * external_sym_size)));
4144*3d8817e4Smiod 			}
4145*3d8817e4Smiod 		      else
4146*3d8817e4Smiod 			{
4147*3d8817e4Smiod 			  know (begin_ptr->index_ptr != (aux_t *) NULL);
4148*3d8817e4Smiod 			  begin_ptr->index_ptr->data.isym =
4149*3d8817e4Smiod 			    isym - ifilesym + 1;
4150*3d8817e4Smiod 			}
4151*3d8817e4Smiod 
4152*3d8817e4Smiod 		      /* The value of the symbol marking the end of a
4153*3d8817e4Smiod 		         procedure is the size of the procedure.  The
4154*3d8817e4Smiod 		         value of the symbol marking the end of a
4155*3d8817e4Smiod 		         block is the offset from the start of the
4156*3d8817e4Smiod 		         procedure to the block.  */
4157*3d8817e4Smiod 		      if (begin_type == st_Proc
4158*3d8817e4Smiod 			  || begin_type == st_StaticProc)
4159*3d8817e4Smiod 			{
4160*3d8817e4Smiod 			  know (as_sym != (symbolS *) NULL);
4161*3d8817e4Smiod 			  know (begin_ptr->as_sym != (symbolS *) NULL);
4162*3d8817e4Smiod 			  if (S_GET_SEGMENT (as_sym)
4163*3d8817e4Smiod 			      != S_GET_SEGMENT (begin_ptr->as_sym))
4164*3d8817e4Smiod 			    as_warn (_(".begin/.bend in different segments"));
4165*3d8817e4Smiod 			  sym_ptr->ecoff_sym.asym.value =
4166*3d8817e4Smiod 			    (S_GET_VALUE (as_sym)
4167*3d8817e4Smiod 			     - S_GET_VALUE (begin_ptr->as_sym));
4168*3d8817e4Smiod 
4169*3d8817e4Smiod 			  /* If the size is odd, this is probably a
4170*3d8817e4Smiod 			     mips16 function; force it to be even.  */
4171*3d8817e4Smiod 			  if ((sym_ptr->ecoff_sym.asym.value & 1) != 0)
4172*3d8817e4Smiod 			    ++sym_ptr->ecoff_sym.asym.value;
4173*3d8817e4Smiod 
4174*3d8817e4Smiod #ifdef S_SET_SIZE
4175*3d8817e4Smiod 			  S_SET_SIZE (begin_ptr->as_sym,
4176*3d8817e4Smiod 				      sym_ptr->ecoff_sym.asym.value);
4177*3d8817e4Smiod #endif
4178*3d8817e4Smiod 			}
4179*3d8817e4Smiod 		      else if (begin_type == st_Block
4180*3d8817e4Smiod 			       && sym_ptr->ecoff_sym.asym.sc != (int) sc_Info)
4181*3d8817e4Smiod 			{
4182*3d8817e4Smiod 			  symbolS *begin_sym;
4183*3d8817e4Smiod 
4184*3d8817e4Smiod 			  know (as_sym != (symbolS *) NULL);
4185*3d8817e4Smiod 			  know (sym_ptr->proc_ptr != (proc_t *) NULL);
4186*3d8817e4Smiod 			  begin_sym = sym_ptr->proc_ptr->sym->as_sym;
4187*3d8817e4Smiod 			  if (S_GET_SEGMENT (as_sym)
4188*3d8817e4Smiod 			      != S_GET_SEGMENT (begin_sym))
4189*3d8817e4Smiod 			    as_warn (_(".begin/.bend in different segments"));
4190*3d8817e4Smiod 			  sym_ptr->ecoff_sym.asym.value =
4191*3d8817e4Smiod 			    S_GET_VALUE (as_sym) - S_GET_VALUE (begin_sym);
4192*3d8817e4Smiod 			}
4193*3d8817e4Smiod 		    }
4194*3d8817e4Smiod 
4195*3d8817e4Smiod 		  for (f = sym_ptr->forward_ref;
4196*3d8817e4Smiod 		       f != (forward_t *) NULL;
4197*3d8817e4Smiod 		       f = f->next)
4198*3d8817e4Smiod 		    {
4199*3d8817e4Smiod 		      know (local);
4200*3d8817e4Smiod 		      f->ifd_ptr->data.isym = fil_ptr->file_index;
4201*3d8817e4Smiod 		      f->index_ptr->data.rndx.index = isym - ifilesym;
4202*3d8817e4Smiod 		    }
4203*3d8817e4Smiod 
4204*3d8817e4Smiod 		  if (local)
4205*3d8817e4Smiod 		    {
4206*3d8817e4Smiod 		      if ((bfd_size_type)(*bufend - sym_out) < external_sym_size)
4207*3d8817e4Smiod 			sym_out = ecoff_add_bytes (buf, bufend,
4208*3d8817e4Smiod 						   sym_out,
4209*3d8817e4Smiod 						   external_sym_size);
4210*3d8817e4Smiod 		      (*swap_sym_out) (stdoutput, &sym_ptr->ecoff_sym.asym,
4211*3d8817e4Smiod 				       sym_out);
4212*3d8817e4Smiod 		      sym_out += external_sym_size;
4213*3d8817e4Smiod 
4214*3d8817e4Smiod 		      sym_ptr->sym_index = isym;
4215*3d8817e4Smiod 
4216*3d8817e4Smiod 		      if (sym_ptr->proc_ptr != (proc_t *) NULL
4217*3d8817e4Smiod 			  && sym_ptr->proc_ptr->sym == sym_ptr)
4218*3d8817e4Smiod 			sym_ptr->proc_ptr->pdr.isym = isym - ifilesym;
4219*3d8817e4Smiod 
4220*3d8817e4Smiod 		      ++isym;
4221*3d8817e4Smiod 		    }
4222*3d8817e4Smiod 
4223*3d8817e4Smiod 		  /* Record the local symbol index and file number in
4224*3d8817e4Smiod 		     case this is an external symbol.  Note that this
4225*3d8817e4Smiod 		     destroys the asym.index field.  */
4226*3d8817e4Smiod 		  if (as_sym != (symbolS *) NULL
4227*3d8817e4Smiod 		      && symbol_get_obj (as_sym)->ecoff_symbol == sym_ptr)
4228*3d8817e4Smiod 		    {
4229*3d8817e4Smiod 		      if ((sym_ptr->ecoff_sym.asym.st == st_Proc
4230*3d8817e4Smiod 			   || sym_ptr->ecoff_sym.asym.st == st_StaticProc)
4231*3d8817e4Smiod 			  && local)
4232*3d8817e4Smiod 			sym_ptr->ecoff_sym.asym.index = isym - ifilesym - 1;
4233*3d8817e4Smiod 		      sym_ptr->ecoff_sym.ifd = fil_ptr->file_index;
4234*3d8817e4Smiod 
4235*3d8817e4Smiod 		      /* Don't try to merge an FDR which has an
4236*3d8817e4Smiod 		         external symbol attached to it.  */
4237*3d8817e4Smiod 		      if (S_IS_EXTERNAL (as_sym) || S_IS_WEAK (as_sym))
4238*3d8817e4Smiod 			fil_ptr->fdr.fMerge = 0;
4239*3d8817e4Smiod 		    }
4240*3d8817e4Smiod 		}
4241*3d8817e4Smiod 	    }
4242*3d8817e4Smiod 	  fil_ptr->fdr.csym = isym - fil_ptr->fdr.isymBase;
4243*3d8817e4Smiod 	}
4244*3d8817e4Smiod     }
4245*3d8817e4Smiod 
4246*3d8817e4Smiod   return offset + isym * external_sym_size;
4247*3d8817e4Smiod }
4248*3d8817e4Smiod 
4249*3d8817e4Smiod /* Swap out the procedure information.  */
4250*3d8817e4Smiod 
4251*3d8817e4Smiod static unsigned long
ecoff_build_procs(const struct ecoff_debug_swap * backend,char ** buf,char ** bufend,unsigned long offset)4252*3d8817e4Smiod ecoff_build_procs (const struct ecoff_debug_swap *backend,
4253*3d8817e4Smiod 		   char **buf,
4254*3d8817e4Smiod 		   char **bufend,
4255*3d8817e4Smiod 		   unsigned long offset)
4256*3d8817e4Smiod {
4257*3d8817e4Smiod   const bfd_size_type external_pdr_size = backend->external_pdr_size;
4258*3d8817e4Smiod   void (* const swap_pdr_out) (bfd *, const PDR *, PTR)
4259*3d8817e4Smiod     = backend->swap_pdr_out;
4260*3d8817e4Smiod   char *pdr_out;
4261*3d8817e4Smiod   long iproc;
4262*3d8817e4Smiod   vlinks_t *file_link;
4263*3d8817e4Smiod 
4264*3d8817e4Smiod   pdr_out = *buf + offset;
4265*3d8817e4Smiod 
4266*3d8817e4Smiod   iproc = 0;
4267*3d8817e4Smiod 
4268*3d8817e4Smiod   /* The procedures are stored by file.  */
4269*3d8817e4Smiod   for (file_link = file_desc.first;
4270*3d8817e4Smiod        file_link != (vlinks_t *) NULL;
4271*3d8817e4Smiod        file_link = file_link->next)
4272*3d8817e4Smiod     {
4273*3d8817e4Smiod       int fil_cnt;
4274*3d8817e4Smiod       efdr_t *fil_ptr;
4275*3d8817e4Smiod       efdr_t *fil_end;
4276*3d8817e4Smiod 
4277*3d8817e4Smiod       if (file_link->next == (vlinks_t *) NULL)
4278*3d8817e4Smiod 	fil_cnt = file_desc.objects_last_page;
4279*3d8817e4Smiod       else
4280*3d8817e4Smiod 	fil_cnt = file_desc.objects_per_page;
4281*3d8817e4Smiod       fil_ptr = file_link->datum->file;
4282*3d8817e4Smiod       fil_end = fil_ptr + fil_cnt;
4283*3d8817e4Smiod       for (; fil_ptr < fil_end; fil_ptr++)
4284*3d8817e4Smiod 	{
4285*3d8817e4Smiod 	  vlinks_t *proc_link;
4286*3d8817e4Smiod 	  int first;
4287*3d8817e4Smiod 
4288*3d8817e4Smiod 	  fil_ptr->fdr.ipdFirst = iproc;
4289*3d8817e4Smiod 	  first = 1;
4290*3d8817e4Smiod 	  for (proc_link = fil_ptr->procs.first;
4291*3d8817e4Smiod 	       proc_link != (vlinks_t *) NULL;
4292*3d8817e4Smiod 	       proc_link = proc_link->next)
4293*3d8817e4Smiod 	    {
4294*3d8817e4Smiod 	      int prc_cnt;
4295*3d8817e4Smiod 	      proc_t *proc_ptr;
4296*3d8817e4Smiod 	      proc_t *proc_end;
4297*3d8817e4Smiod 
4298*3d8817e4Smiod 	      if (proc_link->next == (vlinks_t *) NULL)
4299*3d8817e4Smiod 		prc_cnt = fil_ptr->procs.objects_last_page;
4300*3d8817e4Smiod 	      else
4301*3d8817e4Smiod 		prc_cnt = fil_ptr->procs.objects_per_page;
4302*3d8817e4Smiod 	      proc_ptr = proc_link->datum->proc;
4303*3d8817e4Smiod 	      proc_end = proc_ptr + prc_cnt;
4304*3d8817e4Smiod 	      for (; proc_ptr < proc_end; proc_ptr++)
4305*3d8817e4Smiod 		{
4306*3d8817e4Smiod 		  symbolS *adr_sym;
4307*3d8817e4Smiod 		  unsigned long adr;
4308*3d8817e4Smiod 
4309*3d8817e4Smiod 		  adr_sym = proc_ptr->sym->as_sym;
4310*3d8817e4Smiod 		  adr = (S_GET_VALUE (adr_sym)
4311*3d8817e4Smiod 			 + bfd_get_section_vma (stdoutput,
4312*3d8817e4Smiod 						S_GET_SEGMENT (adr_sym)));
4313*3d8817e4Smiod 		  if (first)
4314*3d8817e4Smiod 		    {
4315*3d8817e4Smiod 		      /* This code used to force the adr of the very
4316*3d8817e4Smiod 		         first fdr to be 0.  However, the native tools
4317*3d8817e4Smiod 		         don't do that, and I can't remember why it
4318*3d8817e4Smiod 		         used to work that way, so I took it out.  */
4319*3d8817e4Smiod 		      fil_ptr->fdr.adr = adr;
4320*3d8817e4Smiod 		      first = 0;
4321*3d8817e4Smiod 		    }
4322*3d8817e4Smiod 		  proc_ptr->pdr.adr = adr - fil_ptr->fdr.adr;
4323*3d8817e4Smiod 		  if ((bfd_size_type)(*bufend - pdr_out) < external_pdr_size)
4324*3d8817e4Smiod 		    pdr_out = ecoff_add_bytes (buf, bufend,
4325*3d8817e4Smiod 					       pdr_out,
4326*3d8817e4Smiod 					       external_pdr_size);
4327*3d8817e4Smiod 		  (*swap_pdr_out) (stdoutput, &proc_ptr->pdr, pdr_out);
4328*3d8817e4Smiod 		  pdr_out += external_pdr_size;
4329*3d8817e4Smiod 		  ++iproc;
4330*3d8817e4Smiod 		}
4331*3d8817e4Smiod 	    }
4332*3d8817e4Smiod 	  fil_ptr->fdr.cpd = iproc - fil_ptr->fdr.ipdFirst;
4333*3d8817e4Smiod 	}
4334*3d8817e4Smiod     }
4335*3d8817e4Smiod 
4336*3d8817e4Smiod   return offset + iproc * external_pdr_size;
4337*3d8817e4Smiod }
4338*3d8817e4Smiod 
4339*3d8817e4Smiod /* Swap out the aux information.  */
4340*3d8817e4Smiod 
4341*3d8817e4Smiod static unsigned long
ecoff_build_aux(const struct ecoff_debug_swap * backend,char ** buf,char ** bufend,unsigned long offset)4342*3d8817e4Smiod ecoff_build_aux (const struct ecoff_debug_swap *backend,
4343*3d8817e4Smiod 		 char **buf,
4344*3d8817e4Smiod 		 char **bufend,
4345*3d8817e4Smiod 		 unsigned long offset)
4346*3d8817e4Smiod {
4347*3d8817e4Smiod   int bigendian;
4348*3d8817e4Smiod   union aux_ext *aux_out;
4349*3d8817e4Smiod   long iaux;
4350*3d8817e4Smiod   vlinks_t *file_link;
4351*3d8817e4Smiod 
4352*3d8817e4Smiod   bigendian = bfd_big_endian (stdoutput);
4353*3d8817e4Smiod 
4354*3d8817e4Smiod   aux_out = (union aux_ext *) (*buf + offset);
4355*3d8817e4Smiod 
4356*3d8817e4Smiod   iaux = 0;
4357*3d8817e4Smiod 
4358*3d8817e4Smiod   /* The aux entries are stored by file.  */
4359*3d8817e4Smiod   for (file_link = file_desc.first;
4360*3d8817e4Smiod        file_link != (vlinks_t *) NULL;
4361*3d8817e4Smiod        file_link = file_link->next)
4362*3d8817e4Smiod     {
4363*3d8817e4Smiod       int fil_cnt;
4364*3d8817e4Smiod       efdr_t *fil_ptr;
4365*3d8817e4Smiod       efdr_t *fil_end;
4366*3d8817e4Smiod 
4367*3d8817e4Smiod       if (file_link->next == (vlinks_t *) NULL)
4368*3d8817e4Smiod 	fil_cnt = file_desc.objects_last_page;
4369*3d8817e4Smiod       else
4370*3d8817e4Smiod 	fil_cnt = file_desc.objects_per_page;
4371*3d8817e4Smiod       fil_ptr = file_link->datum->file;
4372*3d8817e4Smiod       fil_end = fil_ptr + fil_cnt;
4373*3d8817e4Smiod       for (; fil_ptr < fil_end; fil_ptr++)
4374*3d8817e4Smiod 	{
4375*3d8817e4Smiod 	  vlinks_t *aux_link;
4376*3d8817e4Smiod 
4377*3d8817e4Smiod 	  fil_ptr->fdr.fBigendian = bigendian;
4378*3d8817e4Smiod 	  fil_ptr->fdr.iauxBase = iaux;
4379*3d8817e4Smiod 	  for (aux_link = fil_ptr->aux_syms.first;
4380*3d8817e4Smiod 	       aux_link != (vlinks_t *) NULL;
4381*3d8817e4Smiod 	       aux_link = aux_link->next)
4382*3d8817e4Smiod 	    {
4383*3d8817e4Smiod 	      int aux_cnt;
4384*3d8817e4Smiod 	      aux_t *aux_ptr;
4385*3d8817e4Smiod 	      aux_t *aux_end;
4386*3d8817e4Smiod 
4387*3d8817e4Smiod 	      if (aux_link->next == (vlinks_t *) NULL)
4388*3d8817e4Smiod 		aux_cnt = fil_ptr->aux_syms.objects_last_page;
4389*3d8817e4Smiod 	      else
4390*3d8817e4Smiod 		aux_cnt = fil_ptr->aux_syms.objects_per_page;
4391*3d8817e4Smiod 	      aux_ptr = aux_link->datum->aux;
4392*3d8817e4Smiod 	      aux_end = aux_ptr + aux_cnt;
4393*3d8817e4Smiod 	      for (; aux_ptr < aux_end; aux_ptr++)
4394*3d8817e4Smiod 		{
4395*3d8817e4Smiod 		  if ((unsigned long) (*bufend - (char *) aux_out)
4396*3d8817e4Smiod 		      < sizeof (union aux_ext))
4397*3d8817e4Smiod 		    aux_out = ((union aux_ext *)
4398*3d8817e4Smiod 			       ecoff_add_bytes (buf, bufend,
4399*3d8817e4Smiod 						(char *) aux_out,
4400*3d8817e4Smiod 						sizeof (union aux_ext)));
4401*3d8817e4Smiod 		  switch (aux_ptr->type)
4402*3d8817e4Smiod 		    {
4403*3d8817e4Smiod 		    case aux_tir:
4404*3d8817e4Smiod 		      (*backend->swap_tir_out) (bigendian,
4405*3d8817e4Smiod 						&aux_ptr->data.ti,
4406*3d8817e4Smiod 						&aux_out->a_ti);
4407*3d8817e4Smiod 		      break;
4408*3d8817e4Smiod 		    case aux_rndx:
4409*3d8817e4Smiod 		      (*backend->swap_rndx_out) (bigendian,
4410*3d8817e4Smiod 						 &aux_ptr->data.rndx,
4411*3d8817e4Smiod 						 &aux_out->a_rndx);
4412*3d8817e4Smiod 		      break;
4413*3d8817e4Smiod 		    case aux_dnLow:
4414*3d8817e4Smiod 		      AUX_PUT_DNLOW (bigendian, aux_ptr->data.dnLow,
4415*3d8817e4Smiod 				     aux_out);
4416*3d8817e4Smiod 		      break;
4417*3d8817e4Smiod 		    case aux_dnHigh:
4418*3d8817e4Smiod 		      AUX_PUT_DNHIGH (bigendian, aux_ptr->data.dnHigh,
4419*3d8817e4Smiod 				      aux_out);
4420*3d8817e4Smiod 		      break;
4421*3d8817e4Smiod 		    case aux_isym:
4422*3d8817e4Smiod 		      AUX_PUT_ISYM (bigendian, aux_ptr->data.isym,
4423*3d8817e4Smiod 				    aux_out);
4424*3d8817e4Smiod 		      break;
4425*3d8817e4Smiod 		    case aux_iss:
4426*3d8817e4Smiod 		      AUX_PUT_ISS (bigendian, aux_ptr->data.iss,
4427*3d8817e4Smiod 				   aux_out);
4428*3d8817e4Smiod 		      break;
4429*3d8817e4Smiod 		    case aux_width:
4430*3d8817e4Smiod 		      AUX_PUT_WIDTH (bigendian, aux_ptr->data.width,
4431*3d8817e4Smiod 				     aux_out);
4432*3d8817e4Smiod 		      break;
4433*3d8817e4Smiod 		    case aux_count:
4434*3d8817e4Smiod 		      AUX_PUT_COUNT (bigendian, aux_ptr->data.count,
4435*3d8817e4Smiod 				     aux_out);
4436*3d8817e4Smiod 		      break;
4437*3d8817e4Smiod 		    }
4438*3d8817e4Smiod 
4439*3d8817e4Smiod 		  ++aux_out;
4440*3d8817e4Smiod 		  ++iaux;
4441*3d8817e4Smiod 		}
4442*3d8817e4Smiod 	    }
4443*3d8817e4Smiod 	  fil_ptr->fdr.caux = iaux - fil_ptr->fdr.iauxBase;
4444*3d8817e4Smiod 	}
4445*3d8817e4Smiod     }
4446*3d8817e4Smiod 
4447*3d8817e4Smiod   return ecoff_padding_adjust (backend, buf, bufend,
4448*3d8817e4Smiod 			       offset + iaux * sizeof (union aux_ext),
4449*3d8817e4Smiod 			       (char **) NULL);
4450*3d8817e4Smiod }
4451*3d8817e4Smiod 
4452*3d8817e4Smiod /* Copy out the strings from a varray_t.  This returns the number of
4453*3d8817e4Smiod    bytes copied, rather than the new offset.  */
4454*3d8817e4Smiod 
4455*3d8817e4Smiod static unsigned long
ecoff_build_strings(char ** buf,char ** bufend,unsigned long offset,varray_t * vp)4456*3d8817e4Smiod ecoff_build_strings (char **buf,
4457*3d8817e4Smiod 		     char **bufend,
4458*3d8817e4Smiod 		     unsigned long offset,
4459*3d8817e4Smiod 		     varray_t *vp)
4460*3d8817e4Smiod {
4461*3d8817e4Smiod   unsigned long istr;
4462*3d8817e4Smiod   char *str_out;
4463*3d8817e4Smiod   vlinks_t *str_link;
4464*3d8817e4Smiod 
4465*3d8817e4Smiod   str_out = *buf + offset;
4466*3d8817e4Smiod 
4467*3d8817e4Smiod   istr = 0;
4468*3d8817e4Smiod 
4469*3d8817e4Smiod   for (str_link = vp->first;
4470*3d8817e4Smiod        str_link != (vlinks_t *) NULL;
4471*3d8817e4Smiod        str_link = str_link->next)
4472*3d8817e4Smiod     {
4473*3d8817e4Smiod       unsigned long str_cnt;
4474*3d8817e4Smiod 
4475*3d8817e4Smiod       if (str_link->next == (vlinks_t *) NULL)
4476*3d8817e4Smiod 	str_cnt = vp->objects_last_page;
4477*3d8817e4Smiod       else
4478*3d8817e4Smiod 	str_cnt = vp->objects_per_page;
4479*3d8817e4Smiod 
4480*3d8817e4Smiod       if ((unsigned long)(*bufend - str_out) < str_cnt)
4481*3d8817e4Smiod 	str_out = ecoff_add_bytes (buf, bufend, str_out, str_cnt);
4482*3d8817e4Smiod 
4483*3d8817e4Smiod       memcpy (str_out, str_link->datum->byte, str_cnt);
4484*3d8817e4Smiod       str_out += str_cnt;
4485*3d8817e4Smiod       istr += str_cnt;
4486*3d8817e4Smiod     }
4487*3d8817e4Smiod 
4488*3d8817e4Smiod   return istr;
4489*3d8817e4Smiod }
4490*3d8817e4Smiod 
4491*3d8817e4Smiod /* Dump out the local strings.  */
4492*3d8817e4Smiod 
4493*3d8817e4Smiod static unsigned long
ecoff_build_ss(const struct ecoff_debug_swap * backend,char ** buf,char ** bufend,unsigned long offset)4494*3d8817e4Smiod ecoff_build_ss (const struct ecoff_debug_swap *backend,
4495*3d8817e4Smiod 		char **buf,
4496*3d8817e4Smiod 		char **bufend,
4497*3d8817e4Smiod 		unsigned long offset)
4498*3d8817e4Smiod {
4499*3d8817e4Smiod   long iss;
4500*3d8817e4Smiod   vlinks_t *file_link;
4501*3d8817e4Smiod 
4502*3d8817e4Smiod   iss = 0;
4503*3d8817e4Smiod 
4504*3d8817e4Smiod   for (file_link = file_desc.first;
4505*3d8817e4Smiod        file_link != (vlinks_t *) NULL;
4506*3d8817e4Smiod        file_link = file_link->next)
4507*3d8817e4Smiod     {
4508*3d8817e4Smiod       int fil_cnt;
4509*3d8817e4Smiod       efdr_t *fil_ptr;
4510*3d8817e4Smiod       efdr_t *fil_end;
4511*3d8817e4Smiod 
4512*3d8817e4Smiod       if (file_link->next == (vlinks_t *) NULL)
4513*3d8817e4Smiod 	fil_cnt = file_desc.objects_last_page;
4514*3d8817e4Smiod       else
4515*3d8817e4Smiod 	fil_cnt = file_desc.objects_per_page;
4516*3d8817e4Smiod       fil_ptr = file_link->datum->file;
4517*3d8817e4Smiod       fil_end = fil_ptr + fil_cnt;
4518*3d8817e4Smiod       for (; fil_ptr < fil_end; fil_ptr++)
4519*3d8817e4Smiod 	{
4520*3d8817e4Smiod 	  long ss_cnt;
4521*3d8817e4Smiod 
4522*3d8817e4Smiod 	  fil_ptr->fdr.issBase = iss;
4523*3d8817e4Smiod 	  ss_cnt = ecoff_build_strings (buf, bufend, offset + iss,
4524*3d8817e4Smiod 					&fil_ptr->strings);
4525*3d8817e4Smiod 	  fil_ptr->fdr.cbSs = ss_cnt;
4526*3d8817e4Smiod 	  iss += ss_cnt;
4527*3d8817e4Smiod 	}
4528*3d8817e4Smiod     }
4529*3d8817e4Smiod 
4530*3d8817e4Smiod   return ecoff_padding_adjust (backend, buf, bufend, offset + iss,
4531*3d8817e4Smiod 			       (char **) NULL);
4532*3d8817e4Smiod }
4533*3d8817e4Smiod 
4534*3d8817e4Smiod /* Swap out the file descriptors.  */
4535*3d8817e4Smiod 
4536*3d8817e4Smiod static unsigned long
ecoff_build_fdr(const struct ecoff_debug_swap * backend,char ** buf,char ** bufend,unsigned long offset)4537*3d8817e4Smiod ecoff_build_fdr (const struct ecoff_debug_swap *backend,
4538*3d8817e4Smiod 		 char **buf,
4539*3d8817e4Smiod 		 char **bufend,
4540*3d8817e4Smiod 		 unsigned long offset)
4541*3d8817e4Smiod {
4542*3d8817e4Smiod   const bfd_size_type external_fdr_size = backend->external_fdr_size;
4543*3d8817e4Smiod   void (* const swap_fdr_out) (bfd *, const FDR *, PTR)
4544*3d8817e4Smiod     = backend->swap_fdr_out;
4545*3d8817e4Smiod   long ifile;
4546*3d8817e4Smiod   char *fdr_out;
4547*3d8817e4Smiod   vlinks_t *file_link;
4548*3d8817e4Smiod 
4549*3d8817e4Smiod   ifile = 0;
4550*3d8817e4Smiod 
4551*3d8817e4Smiod   fdr_out = *buf + offset;
4552*3d8817e4Smiod 
4553*3d8817e4Smiod   for (file_link = file_desc.first;
4554*3d8817e4Smiod        file_link != (vlinks_t *) NULL;
4555*3d8817e4Smiod        file_link = file_link->next)
4556*3d8817e4Smiod     {
4557*3d8817e4Smiod       int fil_cnt;
4558*3d8817e4Smiod       efdr_t *fil_ptr;
4559*3d8817e4Smiod       efdr_t *fil_end;
4560*3d8817e4Smiod 
4561*3d8817e4Smiod       if (file_link->next == (vlinks_t *) NULL)
4562*3d8817e4Smiod 	fil_cnt = file_desc.objects_last_page;
4563*3d8817e4Smiod       else
4564*3d8817e4Smiod 	fil_cnt = file_desc.objects_per_page;
4565*3d8817e4Smiod       fil_ptr = file_link->datum->file;
4566*3d8817e4Smiod       fil_end = fil_ptr + fil_cnt;
4567*3d8817e4Smiod       for (; fil_ptr < fil_end; fil_ptr++)
4568*3d8817e4Smiod 	{
4569*3d8817e4Smiod 	  if ((bfd_size_type)(*bufend - fdr_out) < external_fdr_size)
4570*3d8817e4Smiod 	    fdr_out = ecoff_add_bytes (buf, bufend, fdr_out,
4571*3d8817e4Smiod 				       external_fdr_size);
4572*3d8817e4Smiod 	  (*swap_fdr_out) (stdoutput, &fil_ptr->fdr, fdr_out);
4573*3d8817e4Smiod 	  fdr_out += external_fdr_size;
4574*3d8817e4Smiod 	  ++ifile;
4575*3d8817e4Smiod 	}
4576*3d8817e4Smiod     }
4577*3d8817e4Smiod 
4578*3d8817e4Smiod   return offset + ifile * external_fdr_size;
4579*3d8817e4Smiod }
4580*3d8817e4Smiod 
4581*3d8817e4Smiod /* Set up the external symbols.  These are supposed to be handled by
4582*3d8817e4Smiod    the backend.  This routine just gets the right information and
4583*3d8817e4Smiod    calls a backend function to deal with it.  */
4584*3d8817e4Smiod 
4585*3d8817e4Smiod static void
ecoff_setup_ext(void)4586*3d8817e4Smiod ecoff_setup_ext (void)
4587*3d8817e4Smiod {
4588*3d8817e4Smiod   register symbolS *sym;
4589*3d8817e4Smiod 
4590*3d8817e4Smiod   for (sym = symbol_rootP; sym != (symbolS *) NULL; sym = symbol_next (sym))
4591*3d8817e4Smiod     {
4592*3d8817e4Smiod       if (symbol_get_obj (sym)->ecoff_symbol == NULL)
4593*3d8817e4Smiod 	continue;
4594*3d8817e4Smiod 
4595*3d8817e4Smiod       /* If this is a local symbol, then force the fields to zero.  */
4596*3d8817e4Smiod       if (! S_IS_EXTERNAL (sym)
4597*3d8817e4Smiod 	  && ! S_IS_WEAK (sym)
4598*3d8817e4Smiod 	  && S_IS_DEFINED (sym))
4599*3d8817e4Smiod 	{
4600*3d8817e4Smiod 	  struct localsym *lsym;
4601*3d8817e4Smiod 
4602*3d8817e4Smiod 	  lsym = symbol_get_obj (sym)->ecoff_symbol;
4603*3d8817e4Smiod 	  lsym->ecoff_sym.asym.value = 0;
4604*3d8817e4Smiod 	  lsym->ecoff_sym.asym.st = (int) st_Nil;
4605*3d8817e4Smiod 	  lsym->ecoff_sym.asym.sc = (int) sc_Nil;
4606*3d8817e4Smiod 	  lsym->ecoff_sym.asym.index = indexNil;
4607*3d8817e4Smiod 	}
4608*3d8817e4Smiod 
4609*3d8817e4Smiod       obj_ecoff_set_ext (sym, &symbol_get_obj (sym)->ecoff_symbol->ecoff_sym);
4610*3d8817e4Smiod     }
4611*3d8817e4Smiod }
4612*3d8817e4Smiod 
4613*3d8817e4Smiod /* Build the ECOFF debugging information.  */
4614*3d8817e4Smiod 
4615*3d8817e4Smiod unsigned long
ecoff_build_debug(HDRR * hdr,char ** bufp,const struct ecoff_debug_swap * backend)4616*3d8817e4Smiod ecoff_build_debug (HDRR *hdr,
4617*3d8817e4Smiod 		   char **bufp,
4618*3d8817e4Smiod 		   const struct ecoff_debug_swap *backend)
4619*3d8817e4Smiod {
4620*3d8817e4Smiod   const bfd_size_type external_pdr_size = backend->external_pdr_size;
4621*3d8817e4Smiod   tag_t *ptag;
4622*3d8817e4Smiod   tag_t *ptag_next;
4623*3d8817e4Smiod   efdr_t *fil_ptr;
4624*3d8817e4Smiod   int end_warning;
4625*3d8817e4Smiod   efdr_t *hold_file_ptr;
4626*3d8817e4Smiod   proc_t *hold_proc_ptr;
4627*3d8817e4Smiod   symbolS *sym;
4628*3d8817e4Smiod   char *buf;
4629*3d8817e4Smiod   char *bufend;
4630*3d8817e4Smiod   unsigned long offset;
4631*3d8817e4Smiod 
4632*3d8817e4Smiod   /* Make sure we have a file.  */
4633*3d8817e4Smiod   if (first_file == (efdr_t *) NULL)
4634*3d8817e4Smiod     add_file ((const char *) NULL, 0, 1);
4635*3d8817e4Smiod 
4636*3d8817e4Smiod   /* Handle any top level tags.  */
4637*3d8817e4Smiod   for (ptag = top_tag_head->first_tag;
4638*3d8817e4Smiod        ptag != (tag_t *) NULL;
4639*3d8817e4Smiod        ptag = ptag_next)
4640*3d8817e4Smiod     {
4641*3d8817e4Smiod       if (ptag->forward_ref != (forward_t *) NULL)
4642*3d8817e4Smiod 	add_unknown_tag (ptag);
4643*3d8817e4Smiod 
4644*3d8817e4Smiod       ptag_next = ptag->same_block;
4645*3d8817e4Smiod       ptag->hash_ptr->tag_ptr = ptag->same_name;
4646*3d8817e4Smiod       free_tag (ptag);
4647*3d8817e4Smiod     }
4648*3d8817e4Smiod 
4649*3d8817e4Smiod   free_thead (top_tag_head);
4650*3d8817e4Smiod 
4651*3d8817e4Smiod   /* Look through the symbols.  Add debugging information for each
4652*3d8817e4Smiod      symbol that has not already received it.  */
4653*3d8817e4Smiod   hold_file_ptr = cur_file_ptr;
4654*3d8817e4Smiod   hold_proc_ptr = cur_proc_ptr;
4655*3d8817e4Smiod   cur_proc_ptr = (proc_t *) NULL;
4656*3d8817e4Smiod   for (sym = symbol_rootP; sym != (symbolS *) NULL; sym = symbol_next (sym))
4657*3d8817e4Smiod     {
4658*3d8817e4Smiod       if (symbol_get_obj (sym)->ecoff_symbol != NULL
4659*3d8817e4Smiod 	  || symbol_get_obj (sym)->ecoff_file == (efdr_t *) NULL
4660*3d8817e4Smiod 	  || (symbol_get_bfdsym (sym)->flags & BSF_SECTION_SYM) != 0)
4661*3d8817e4Smiod 	continue;
4662*3d8817e4Smiod 
4663*3d8817e4Smiod       cur_file_ptr = symbol_get_obj (sym)->ecoff_file;
4664*3d8817e4Smiod       add_ecoff_symbol ((const char *) NULL, st_Nil, sc_Nil, sym,
4665*3d8817e4Smiod 			(bfd_vma) 0, S_GET_VALUE (sym), indexNil);
4666*3d8817e4Smiod     }
4667*3d8817e4Smiod   cur_proc_ptr = hold_proc_ptr;
4668*3d8817e4Smiod   cur_file_ptr = hold_file_ptr;
4669*3d8817e4Smiod 
4670*3d8817e4Smiod   /* Output an ending symbol for all the files.  We have to do this
4671*3d8817e4Smiod      here for the last file, so we may as well do it for all of the
4672*3d8817e4Smiod      files.  */
4673*3d8817e4Smiod   end_warning = 0;
4674*3d8817e4Smiod   for (fil_ptr = first_file;
4675*3d8817e4Smiod        fil_ptr != (efdr_t *) NULL;
4676*3d8817e4Smiod        fil_ptr = fil_ptr->next_file)
4677*3d8817e4Smiod     {
4678*3d8817e4Smiod       cur_file_ptr = fil_ptr;
4679*3d8817e4Smiod       while (cur_file_ptr->cur_scope != (scope_t *) NULL
4680*3d8817e4Smiod 	     && cur_file_ptr->cur_scope->prev != (scope_t *) NULL)
4681*3d8817e4Smiod 	{
4682*3d8817e4Smiod 	  cur_file_ptr->cur_scope = cur_file_ptr->cur_scope->prev;
4683*3d8817e4Smiod 	  if (! end_warning && ! cur_file_ptr->fake)
4684*3d8817e4Smiod 	    {
4685*3d8817e4Smiod 	      as_warn (_("missing .end or .bend at end of file"));
4686*3d8817e4Smiod 	      end_warning = 1;
4687*3d8817e4Smiod 	    }
4688*3d8817e4Smiod 	}
4689*3d8817e4Smiod       if (cur_file_ptr->cur_scope != (scope_t *) NULL)
4690*3d8817e4Smiod 	(void) add_ecoff_symbol ((const char *) NULL,
4691*3d8817e4Smiod 				 st_End, sc_Text,
4692*3d8817e4Smiod 				 (symbolS *) NULL,
4693*3d8817e4Smiod 				 (bfd_vma) 0,
4694*3d8817e4Smiod 				 (symint_t) 0,
4695*3d8817e4Smiod 				 (symint_t) 0);
4696*3d8817e4Smiod     }
4697*3d8817e4Smiod 
4698*3d8817e4Smiod   /* Build the symbolic information.  */
4699*3d8817e4Smiod   offset = 0;
4700*3d8817e4Smiod   buf = xmalloc (PAGE_SIZE);
4701*3d8817e4Smiod   bufend = buf + PAGE_SIZE;
4702*3d8817e4Smiod 
4703*3d8817e4Smiod   /* Build the line number information.  */
4704*3d8817e4Smiod   hdr->cbLineOffset = offset;
4705*3d8817e4Smiod   offset = ecoff_build_lineno (backend, &buf, &bufend, offset,
4706*3d8817e4Smiod 			       &hdr->ilineMax);
4707*3d8817e4Smiod   hdr->cbLine = offset - hdr->cbLineOffset;
4708*3d8817e4Smiod 
4709*3d8817e4Smiod   /* We don't use dense numbers at all.  */
4710*3d8817e4Smiod   hdr->idnMax = 0;
4711*3d8817e4Smiod   hdr->cbDnOffset = 0;
4712*3d8817e4Smiod 
4713*3d8817e4Smiod   /* We can't build the PDR table until we have built the symbols,
4714*3d8817e4Smiod      because a PDR contains a symbol index.  However, we set aside
4715*3d8817e4Smiod      space at this point.  */
4716*3d8817e4Smiod   hdr->ipdMax = proc_cnt;
4717*3d8817e4Smiod   hdr->cbPdOffset = offset;
4718*3d8817e4Smiod   if ((bfd_size_type)(bufend - (buf + offset)) < proc_cnt * external_pdr_size)
4719*3d8817e4Smiod     (void) ecoff_add_bytes (&buf, &bufend, buf + offset,
4720*3d8817e4Smiod 			    proc_cnt * external_pdr_size);
4721*3d8817e4Smiod   offset += proc_cnt * external_pdr_size;
4722*3d8817e4Smiod 
4723*3d8817e4Smiod   /* Build the local symbols.  */
4724*3d8817e4Smiod   hdr->cbSymOffset = offset;
4725*3d8817e4Smiod   offset = ecoff_build_symbols (backend, &buf, &bufend, offset);
4726*3d8817e4Smiod   hdr->isymMax = (offset - hdr->cbSymOffset) / backend->external_sym_size;
4727*3d8817e4Smiod 
4728*3d8817e4Smiod   /* Building the symbols initializes the symbol index in the PDR's.
4729*3d8817e4Smiod      Now we can swap out the PDR's.  */
4730*3d8817e4Smiod   (void) ecoff_build_procs (backend, &buf, &bufend, hdr->cbPdOffset);
4731*3d8817e4Smiod 
4732*3d8817e4Smiod   /* We don't use optimization symbols.  */
4733*3d8817e4Smiod   hdr->ioptMax = 0;
4734*3d8817e4Smiod   hdr->cbOptOffset = 0;
4735*3d8817e4Smiod 
4736*3d8817e4Smiod   /* Swap out the auxiliary type information.  */
4737*3d8817e4Smiod   hdr->cbAuxOffset = offset;
4738*3d8817e4Smiod   offset = ecoff_build_aux (backend, &buf, &bufend, offset);
4739*3d8817e4Smiod   hdr->iauxMax = (offset - hdr->cbAuxOffset) / sizeof (union aux_ext);
4740*3d8817e4Smiod 
4741*3d8817e4Smiod   /* Copy out the local strings.  */
4742*3d8817e4Smiod   hdr->cbSsOffset = offset;
4743*3d8817e4Smiod   offset = ecoff_build_ss (backend, &buf, &bufend, offset);
4744*3d8817e4Smiod   hdr->issMax = offset - hdr->cbSsOffset;
4745*3d8817e4Smiod 
4746*3d8817e4Smiod   /* We don't use relative file descriptors.  */
4747*3d8817e4Smiod   hdr->crfd = 0;
4748*3d8817e4Smiod   hdr->cbRfdOffset = 0;
4749*3d8817e4Smiod 
4750*3d8817e4Smiod   /* Swap out the file descriptors.  */
4751*3d8817e4Smiod   hdr->cbFdOffset = offset;
4752*3d8817e4Smiod   offset = ecoff_build_fdr (backend, &buf, &bufend, offset);
4753*3d8817e4Smiod   hdr->ifdMax = (offset - hdr->cbFdOffset) / backend->external_fdr_size;
4754*3d8817e4Smiod 
4755*3d8817e4Smiod   /* Set up the external symbols, which are handled by the BFD back
4756*3d8817e4Smiod      end.  */
4757*3d8817e4Smiod   hdr->issExtMax = 0;
4758*3d8817e4Smiod   hdr->cbSsExtOffset = 0;
4759*3d8817e4Smiod   hdr->iextMax = 0;
4760*3d8817e4Smiod   hdr->cbExtOffset = 0;
4761*3d8817e4Smiod   ecoff_setup_ext ();
4762*3d8817e4Smiod 
4763*3d8817e4Smiod   know ((offset & (backend->debug_align - 1)) == 0);
4764*3d8817e4Smiod 
4765*3d8817e4Smiod   /* FIXME: This value should be determined from the .verstamp directive,
4766*3d8817e4Smiod      with reasonable defaults in config files.  */
4767*3d8817e4Smiod #ifdef TC_ALPHA
4768*3d8817e4Smiod   hdr->vstamp = 0x030b;
4769*3d8817e4Smiod #else
4770*3d8817e4Smiod   hdr->vstamp = 0x020b;
4771*3d8817e4Smiod #endif
4772*3d8817e4Smiod 
4773*3d8817e4Smiod   *bufp = buf;
4774*3d8817e4Smiod   return offset;
4775*3d8817e4Smiod }
4776*3d8817e4Smiod 
4777*3d8817e4Smiod /* Allocate a cluster of pages.  */
4778*3d8817e4Smiod 
4779*3d8817e4Smiod #ifndef MALLOC_CHECK
4780*3d8817e4Smiod 
4781*3d8817e4Smiod static page_type *
allocate_cluster(unsigned long npages)4782*3d8817e4Smiod allocate_cluster (unsigned long npages)
4783*3d8817e4Smiod {
4784*3d8817e4Smiod   register page_type *value = (page_type *) xmalloc (npages * PAGE_USIZE);
4785*3d8817e4Smiod 
4786*3d8817e4Smiod #ifdef ECOFF_DEBUG
4787*3d8817e4Smiod   if (debug > 3)
4788*3d8817e4Smiod     fprintf (stderr, "\talloc\tnpages = %d, value = 0x%.8x\n", npages, value);
4789*3d8817e4Smiod #endif
4790*3d8817e4Smiod 
4791*3d8817e4Smiod   memset (value, 0, npages * PAGE_USIZE);
4792*3d8817e4Smiod 
4793*3d8817e4Smiod   return value;
4794*3d8817e4Smiod }
4795*3d8817e4Smiod 
4796*3d8817e4Smiod static page_type *cluster_ptr = NULL;
4797*3d8817e4Smiod static unsigned long pages_left = 0;
4798*3d8817e4Smiod 
4799*3d8817e4Smiod #endif /* MALLOC_CHECK */
4800*3d8817e4Smiod 
4801*3d8817e4Smiod /* Allocate one page (which is initialized to 0).  */
4802*3d8817e4Smiod 
4803*3d8817e4Smiod static page_type *
allocate_page(void)4804*3d8817e4Smiod allocate_page (void)
4805*3d8817e4Smiod {
4806*3d8817e4Smiod #ifndef MALLOC_CHECK
4807*3d8817e4Smiod 
4808*3d8817e4Smiod   if (pages_left == 0)
4809*3d8817e4Smiod     {
4810*3d8817e4Smiod       pages_left = MAX_CLUSTER_PAGES;
4811*3d8817e4Smiod       cluster_ptr = allocate_cluster (pages_left);
4812*3d8817e4Smiod     }
4813*3d8817e4Smiod 
4814*3d8817e4Smiod   pages_left--;
4815*3d8817e4Smiod   return cluster_ptr++;
4816*3d8817e4Smiod 
4817*3d8817e4Smiod #else /* MALLOC_CHECK */
4818*3d8817e4Smiod 
4819*3d8817e4Smiod   page_type *ptr;
4820*3d8817e4Smiod 
4821*3d8817e4Smiod   ptr = xmalloc (PAGE_USIZE);
4822*3d8817e4Smiod   memset (ptr, 0, PAGE_USIZE);
4823*3d8817e4Smiod   return ptr;
4824*3d8817e4Smiod 
4825*3d8817e4Smiod #endif /* MALLOC_CHECK */
4826*3d8817e4Smiod }
4827*3d8817e4Smiod 
4828*3d8817e4Smiod /* Allocate scoping information.  */
4829*3d8817e4Smiod 
4830*3d8817e4Smiod static scope_t *
allocate_scope(void)4831*3d8817e4Smiod allocate_scope (void)
4832*3d8817e4Smiod {
4833*3d8817e4Smiod   register scope_t *ptr;
4834*3d8817e4Smiod   static scope_t initial_scope;
4835*3d8817e4Smiod 
4836*3d8817e4Smiod #ifndef MALLOC_CHECK
4837*3d8817e4Smiod 
4838*3d8817e4Smiod   ptr = alloc_counts[(int) alloc_type_scope].free_list.f_scope;
4839*3d8817e4Smiod   if (ptr != (scope_t *) NULL)
4840*3d8817e4Smiod     alloc_counts[(int) alloc_type_scope].free_list.f_scope = ptr->free;
4841*3d8817e4Smiod   else
4842*3d8817e4Smiod     {
4843*3d8817e4Smiod       register int unallocated	= alloc_counts[(int) alloc_type_scope].unallocated;
4844*3d8817e4Smiod       register page_type *cur_page	= alloc_counts[(int) alloc_type_scope].cur_page;
4845*3d8817e4Smiod 
4846*3d8817e4Smiod       if (unallocated == 0)
4847*3d8817e4Smiod 	{
4848*3d8817e4Smiod 	  unallocated = PAGE_SIZE / sizeof (scope_t);
4849*3d8817e4Smiod 	  alloc_counts[(int) alloc_type_scope].cur_page = cur_page = allocate_page ();
4850*3d8817e4Smiod 	  alloc_counts[(int) alloc_type_scope].total_pages++;
4851*3d8817e4Smiod 	}
4852*3d8817e4Smiod 
4853*3d8817e4Smiod       ptr = &cur_page->scope[--unallocated];
4854*3d8817e4Smiod       alloc_counts[(int) alloc_type_scope].unallocated = unallocated;
4855*3d8817e4Smiod     }
4856*3d8817e4Smiod 
4857*3d8817e4Smiod #else
4858*3d8817e4Smiod 
4859*3d8817e4Smiod   ptr = (scope_t *) xmalloc (sizeof (scope_t));
4860*3d8817e4Smiod 
4861*3d8817e4Smiod #endif
4862*3d8817e4Smiod 
4863*3d8817e4Smiod   alloc_counts[(int) alloc_type_scope].total_alloc++;
4864*3d8817e4Smiod   *ptr = initial_scope;
4865*3d8817e4Smiod   return ptr;
4866*3d8817e4Smiod }
4867*3d8817e4Smiod 
4868*3d8817e4Smiod /* Free scoping information.  */
4869*3d8817e4Smiod 
4870*3d8817e4Smiod static void
free_scope(scope_t * ptr)4871*3d8817e4Smiod free_scope (scope_t *ptr)
4872*3d8817e4Smiod {
4873*3d8817e4Smiod   alloc_counts[(int) alloc_type_scope].total_free++;
4874*3d8817e4Smiod 
4875*3d8817e4Smiod #ifndef MALLOC_CHECK
4876*3d8817e4Smiod   ptr->free = alloc_counts[(int) alloc_type_scope].free_list.f_scope;
4877*3d8817e4Smiod   alloc_counts[(int) alloc_type_scope].free_list.f_scope = ptr;
4878*3d8817e4Smiod #else
4879*3d8817e4Smiod   free ((PTR) ptr);
4880*3d8817e4Smiod #endif
4881*3d8817e4Smiod }
4882*3d8817e4Smiod 
4883*3d8817e4Smiod /* Allocate links for pages in a virtual array.  */
4884*3d8817e4Smiod 
4885*3d8817e4Smiod static vlinks_t *
allocate_vlinks(void)4886*3d8817e4Smiod allocate_vlinks (void)
4887*3d8817e4Smiod {
4888*3d8817e4Smiod   register vlinks_t *ptr;
4889*3d8817e4Smiod   static vlinks_t initial_vlinks;
4890*3d8817e4Smiod 
4891*3d8817e4Smiod #ifndef MALLOC_CHECK
4892*3d8817e4Smiod 
4893*3d8817e4Smiod   register int unallocated = alloc_counts[(int) alloc_type_vlinks].unallocated;
4894*3d8817e4Smiod   register page_type *cur_page = alloc_counts[(int) alloc_type_vlinks].cur_page;
4895*3d8817e4Smiod 
4896*3d8817e4Smiod   if (unallocated == 0)
4897*3d8817e4Smiod     {
4898*3d8817e4Smiod       unallocated = PAGE_SIZE / sizeof (vlinks_t);
4899*3d8817e4Smiod       alloc_counts[(int) alloc_type_vlinks].cur_page = cur_page = allocate_page ();
4900*3d8817e4Smiod       alloc_counts[(int) alloc_type_vlinks].total_pages++;
4901*3d8817e4Smiod     }
4902*3d8817e4Smiod 
4903*3d8817e4Smiod   ptr = &cur_page->vlinks[--unallocated];
4904*3d8817e4Smiod   alloc_counts[(int) alloc_type_vlinks].unallocated = unallocated;
4905*3d8817e4Smiod 
4906*3d8817e4Smiod #else
4907*3d8817e4Smiod 
4908*3d8817e4Smiod   ptr = (vlinks_t *) xmalloc (sizeof (vlinks_t));
4909*3d8817e4Smiod 
4910*3d8817e4Smiod #endif
4911*3d8817e4Smiod 
4912*3d8817e4Smiod   alloc_counts[(int) alloc_type_vlinks].total_alloc++;
4913*3d8817e4Smiod   *ptr = initial_vlinks;
4914*3d8817e4Smiod   return ptr;
4915*3d8817e4Smiod }
4916*3d8817e4Smiod 
4917*3d8817e4Smiod /* Allocate string hash buckets.  */
4918*3d8817e4Smiod 
4919*3d8817e4Smiod static shash_t *
allocate_shash(void)4920*3d8817e4Smiod allocate_shash (void)
4921*3d8817e4Smiod {
4922*3d8817e4Smiod   register shash_t *ptr;
4923*3d8817e4Smiod   static shash_t initial_shash;
4924*3d8817e4Smiod 
4925*3d8817e4Smiod #ifndef MALLOC_CHECK
4926*3d8817e4Smiod 
4927*3d8817e4Smiod   register int unallocated = alloc_counts[(int) alloc_type_shash].unallocated;
4928*3d8817e4Smiod   register page_type *cur_page = alloc_counts[(int) alloc_type_shash].cur_page;
4929*3d8817e4Smiod 
4930*3d8817e4Smiod   if (unallocated == 0)
4931*3d8817e4Smiod     {
4932*3d8817e4Smiod       unallocated = PAGE_SIZE / sizeof (shash_t);
4933*3d8817e4Smiod       alloc_counts[(int) alloc_type_shash].cur_page = cur_page = allocate_page ();
4934*3d8817e4Smiod       alloc_counts[(int) alloc_type_shash].total_pages++;
4935*3d8817e4Smiod     }
4936*3d8817e4Smiod 
4937*3d8817e4Smiod   ptr = &cur_page->shash[--unallocated];
4938*3d8817e4Smiod   alloc_counts[(int) alloc_type_shash].unallocated = unallocated;
4939*3d8817e4Smiod 
4940*3d8817e4Smiod #else
4941*3d8817e4Smiod 
4942*3d8817e4Smiod   ptr = (shash_t *) xmalloc (sizeof (shash_t));
4943*3d8817e4Smiod 
4944*3d8817e4Smiod #endif
4945*3d8817e4Smiod 
4946*3d8817e4Smiod   alloc_counts[(int) alloc_type_shash].total_alloc++;
4947*3d8817e4Smiod   *ptr = initial_shash;
4948*3d8817e4Smiod   return ptr;
4949*3d8817e4Smiod }
4950*3d8817e4Smiod 
4951*3d8817e4Smiod /* Allocate type hash buckets.  */
4952*3d8817e4Smiod 
4953*3d8817e4Smiod static thash_t *
allocate_thash(void)4954*3d8817e4Smiod allocate_thash (void)
4955*3d8817e4Smiod {
4956*3d8817e4Smiod   register thash_t *ptr;
4957*3d8817e4Smiod   static thash_t initial_thash;
4958*3d8817e4Smiod 
4959*3d8817e4Smiod #ifndef MALLOC_CHECK
4960*3d8817e4Smiod 
4961*3d8817e4Smiod   register int unallocated = alloc_counts[(int) alloc_type_thash].unallocated;
4962*3d8817e4Smiod   register page_type *cur_page = alloc_counts[(int) alloc_type_thash].cur_page;
4963*3d8817e4Smiod 
4964*3d8817e4Smiod   if (unallocated == 0)
4965*3d8817e4Smiod     {
4966*3d8817e4Smiod       unallocated = PAGE_SIZE / sizeof (thash_t);
4967*3d8817e4Smiod       alloc_counts[(int) alloc_type_thash].cur_page = cur_page = allocate_page ();
4968*3d8817e4Smiod       alloc_counts[(int) alloc_type_thash].total_pages++;
4969*3d8817e4Smiod     }
4970*3d8817e4Smiod 
4971*3d8817e4Smiod   ptr = &cur_page->thash[--unallocated];
4972*3d8817e4Smiod   alloc_counts[(int) alloc_type_thash].unallocated = unallocated;
4973*3d8817e4Smiod 
4974*3d8817e4Smiod #else
4975*3d8817e4Smiod 
4976*3d8817e4Smiod   ptr = (thash_t *) xmalloc (sizeof (thash_t));
4977*3d8817e4Smiod 
4978*3d8817e4Smiod #endif
4979*3d8817e4Smiod 
4980*3d8817e4Smiod   alloc_counts[(int) alloc_type_thash].total_alloc++;
4981*3d8817e4Smiod   *ptr = initial_thash;
4982*3d8817e4Smiod   return ptr;
4983*3d8817e4Smiod }
4984*3d8817e4Smiod 
4985*3d8817e4Smiod /* Allocate structure, union, or enum tag information.  */
4986*3d8817e4Smiod 
4987*3d8817e4Smiod static tag_t *
allocate_tag(void)4988*3d8817e4Smiod allocate_tag (void)
4989*3d8817e4Smiod {
4990*3d8817e4Smiod   register tag_t *ptr;
4991*3d8817e4Smiod   static tag_t initial_tag;
4992*3d8817e4Smiod 
4993*3d8817e4Smiod #ifndef MALLOC_CHECK
4994*3d8817e4Smiod 
4995*3d8817e4Smiod   ptr = alloc_counts[(int) alloc_type_tag].free_list.f_tag;
4996*3d8817e4Smiod   if (ptr != (tag_t *) NULL)
4997*3d8817e4Smiod     alloc_counts[(int) alloc_type_tag].free_list.f_tag = ptr->free;
4998*3d8817e4Smiod   else
4999*3d8817e4Smiod     {
5000*3d8817e4Smiod       register int unallocated = alloc_counts[(int) alloc_type_tag].unallocated;
5001*3d8817e4Smiod       register page_type *cur_page = alloc_counts[(int) alloc_type_tag].cur_page;
5002*3d8817e4Smiod 
5003*3d8817e4Smiod       if (unallocated == 0)
5004*3d8817e4Smiod 	{
5005*3d8817e4Smiod 	  unallocated = PAGE_SIZE / sizeof (tag_t);
5006*3d8817e4Smiod 	  alloc_counts[(int) alloc_type_tag].cur_page = cur_page = allocate_page ();
5007*3d8817e4Smiod 	  alloc_counts[(int) alloc_type_tag].total_pages++;
5008*3d8817e4Smiod 	}
5009*3d8817e4Smiod 
5010*3d8817e4Smiod       ptr = &cur_page->tag[--unallocated];
5011*3d8817e4Smiod       alloc_counts[(int) alloc_type_tag].unallocated = unallocated;
5012*3d8817e4Smiod     }
5013*3d8817e4Smiod 
5014*3d8817e4Smiod #else
5015*3d8817e4Smiod 
5016*3d8817e4Smiod   ptr = (tag_t *) xmalloc (sizeof (tag_t));
5017*3d8817e4Smiod 
5018*3d8817e4Smiod #endif
5019*3d8817e4Smiod 
5020*3d8817e4Smiod   alloc_counts[(int) alloc_type_tag].total_alloc++;
5021*3d8817e4Smiod   *ptr = initial_tag;
5022*3d8817e4Smiod   return ptr;
5023*3d8817e4Smiod }
5024*3d8817e4Smiod 
5025*3d8817e4Smiod /* Free scoping information.  */
5026*3d8817e4Smiod 
5027*3d8817e4Smiod static void
free_tag(tag_t * ptr)5028*3d8817e4Smiod free_tag (tag_t *ptr)
5029*3d8817e4Smiod {
5030*3d8817e4Smiod   alloc_counts[(int) alloc_type_tag].total_free++;
5031*3d8817e4Smiod 
5032*3d8817e4Smiod #ifndef MALLOC_CHECK
5033*3d8817e4Smiod   ptr->free = alloc_counts[(int) alloc_type_tag].free_list.f_tag;
5034*3d8817e4Smiod   alloc_counts[(int) alloc_type_tag].free_list.f_tag = ptr;
5035*3d8817e4Smiod #else
5036*3d8817e4Smiod   free ((PTR_T) ptr);
5037*3d8817e4Smiod #endif
5038*3d8817e4Smiod }
5039*3d8817e4Smiod 
5040*3d8817e4Smiod /* Allocate forward reference to a yet unknown tag.  */
5041*3d8817e4Smiod 
5042*3d8817e4Smiod static forward_t *
allocate_forward(void)5043*3d8817e4Smiod allocate_forward (void)
5044*3d8817e4Smiod {
5045*3d8817e4Smiod   register forward_t *ptr;
5046*3d8817e4Smiod   static forward_t initial_forward;
5047*3d8817e4Smiod 
5048*3d8817e4Smiod #ifndef MALLOC_CHECK
5049*3d8817e4Smiod 
5050*3d8817e4Smiod   register int unallocated = alloc_counts[(int) alloc_type_forward].unallocated;
5051*3d8817e4Smiod   register page_type *cur_page = alloc_counts[(int) alloc_type_forward].cur_page;
5052*3d8817e4Smiod 
5053*3d8817e4Smiod   if (unallocated == 0)
5054*3d8817e4Smiod     {
5055*3d8817e4Smiod       unallocated = PAGE_SIZE / sizeof (forward_t);
5056*3d8817e4Smiod       alloc_counts[(int) alloc_type_forward].cur_page = cur_page = allocate_page ();
5057*3d8817e4Smiod       alloc_counts[(int) alloc_type_forward].total_pages++;
5058*3d8817e4Smiod     }
5059*3d8817e4Smiod 
5060*3d8817e4Smiod   ptr = &cur_page->forward[--unallocated];
5061*3d8817e4Smiod   alloc_counts[(int) alloc_type_forward].unallocated = unallocated;
5062*3d8817e4Smiod 
5063*3d8817e4Smiod #else
5064*3d8817e4Smiod 
5065*3d8817e4Smiod   ptr = (forward_t *) xmalloc (sizeof (forward_t));
5066*3d8817e4Smiod 
5067*3d8817e4Smiod #endif
5068*3d8817e4Smiod 
5069*3d8817e4Smiod   alloc_counts[(int) alloc_type_forward].total_alloc++;
5070*3d8817e4Smiod   *ptr = initial_forward;
5071*3d8817e4Smiod   return ptr;
5072*3d8817e4Smiod }
5073*3d8817e4Smiod 
5074*3d8817e4Smiod /* Allocate head of type hash list.  */
5075*3d8817e4Smiod 
5076*3d8817e4Smiod static thead_t *
allocate_thead(void)5077*3d8817e4Smiod allocate_thead (void)
5078*3d8817e4Smiod {
5079*3d8817e4Smiod   register thead_t *ptr;
5080*3d8817e4Smiod   static thead_t initial_thead;
5081*3d8817e4Smiod 
5082*3d8817e4Smiod #ifndef MALLOC_CHECK
5083*3d8817e4Smiod 
5084*3d8817e4Smiod   ptr = alloc_counts[(int) alloc_type_thead].free_list.f_thead;
5085*3d8817e4Smiod   if (ptr != (thead_t *) NULL)
5086*3d8817e4Smiod     alloc_counts[(int) alloc_type_thead].free_list.f_thead = ptr->free;
5087*3d8817e4Smiod   else
5088*3d8817e4Smiod     {
5089*3d8817e4Smiod       register int unallocated = alloc_counts[(int) alloc_type_thead].unallocated;
5090*3d8817e4Smiod       register page_type *cur_page = alloc_counts[(int) alloc_type_thead].cur_page;
5091*3d8817e4Smiod 
5092*3d8817e4Smiod       if (unallocated == 0)
5093*3d8817e4Smiod 	{
5094*3d8817e4Smiod 	  unallocated = PAGE_SIZE / sizeof (thead_t);
5095*3d8817e4Smiod 	  alloc_counts[(int) alloc_type_thead].cur_page = cur_page = allocate_page ();
5096*3d8817e4Smiod 	  alloc_counts[(int) alloc_type_thead].total_pages++;
5097*3d8817e4Smiod 	}
5098*3d8817e4Smiod 
5099*3d8817e4Smiod       ptr = &cur_page->thead[--unallocated];
5100*3d8817e4Smiod       alloc_counts[(int) alloc_type_thead].unallocated = unallocated;
5101*3d8817e4Smiod     }
5102*3d8817e4Smiod 
5103*3d8817e4Smiod #else
5104*3d8817e4Smiod 
5105*3d8817e4Smiod   ptr = (thead_t *) xmalloc (sizeof (thead_t));
5106*3d8817e4Smiod 
5107*3d8817e4Smiod #endif
5108*3d8817e4Smiod 
5109*3d8817e4Smiod   alloc_counts[(int) alloc_type_thead].total_alloc++;
5110*3d8817e4Smiod   *ptr = initial_thead;
5111*3d8817e4Smiod   return ptr;
5112*3d8817e4Smiod }
5113*3d8817e4Smiod 
5114*3d8817e4Smiod /* Free scoping information.  */
5115*3d8817e4Smiod 
5116*3d8817e4Smiod static void
free_thead(thead_t * ptr)5117*3d8817e4Smiod free_thead (thead_t *ptr)
5118*3d8817e4Smiod {
5119*3d8817e4Smiod   alloc_counts[(int) alloc_type_thead].total_free++;
5120*3d8817e4Smiod 
5121*3d8817e4Smiod #ifndef MALLOC_CHECK
5122*3d8817e4Smiod   ptr->free = (thead_t *) alloc_counts[(int) alloc_type_thead].free_list.f_thead;
5123*3d8817e4Smiod   alloc_counts[(int) alloc_type_thead].free_list.f_thead = ptr;
5124*3d8817e4Smiod #else
5125*3d8817e4Smiod   free ((PTR_T) ptr);
5126*3d8817e4Smiod #endif
5127*3d8817e4Smiod }
5128*3d8817e4Smiod 
5129*3d8817e4Smiod static lineno_list_t *
allocate_lineno_list(void)5130*3d8817e4Smiod allocate_lineno_list (void)
5131*3d8817e4Smiod {
5132*3d8817e4Smiod   register lineno_list_t *ptr;
5133*3d8817e4Smiod   static lineno_list_t initial_lineno_list;
5134*3d8817e4Smiod 
5135*3d8817e4Smiod #ifndef MALLOC_CHECK
5136*3d8817e4Smiod 
5137*3d8817e4Smiod   register int unallocated = alloc_counts[(int) alloc_type_lineno].unallocated;
5138*3d8817e4Smiod   register page_type *cur_page = alloc_counts[(int) alloc_type_lineno].cur_page;
5139*3d8817e4Smiod 
5140*3d8817e4Smiod   if (unallocated == 0)
5141*3d8817e4Smiod     {
5142*3d8817e4Smiod       unallocated = PAGE_SIZE / sizeof (lineno_list_t);
5143*3d8817e4Smiod       alloc_counts[(int) alloc_type_lineno].cur_page = cur_page = allocate_page ();
5144*3d8817e4Smiod       alloc_counts[(int) alloc_type_lineno].total_pages++;
5145*3d8817e4Smiod     }
5146*3d8817e4Smiod 
5147*3d8817e4Smiod   ptr = &cur_page->lineno[--unallocated];
5148*3d8817e4Smiod   alloc_counts[(int) alloc_type_lineno].unallocated = unallocated;
5149*3d8817e4Smiod 
5150*3d8817e4Smiod #else
5151*3d8817e4Smiod 
5152*3d8817e4Smiod   ptr = (lineno_list_t *) xmalloc (sizeof (lineno_list_t));
5153*3d8817e4Smiod 
5154*3d8817e4Smiod #endif
5155*3d8817e4Smiod 
5156*3d8817e4Smiod   alloc_counts[(int) alloc_type_lineno].total_alloc++;
5157*3d8817e4Smiod   *ptr = initial_lineno_list;
5158*3d8817e4Smiod   return ptr;
5159*3d8817e4Smiod }
5160*3d8817e4Smiod 
5161*3d8817e4Smiod void
ecoff_set_gp_prolog_size(int sz)5162*3d8817e4Smiod ecoff_set_gp_prolog_size (int sz)
5163*3d8817e4Smiod {
5164*3d8817e4Smiod   if (cur_proc_ptr == 0)
5165*3d8817e4Smiod     return;
5166*3d8817e4Smiod 
5167*3d8817e4Smiod   cur_proc_ptr->pdr.gp_prologue = sz;
5168*3d8817e4Smiod   if (cur_proc_ptr->pdr.gp_prologue != sz)
5169*3d8817e4Smiod     {
5170*3d8817e4Smiod       as_warn (_("GP prologue size exceeds field size, using 0 instead"));
5171*3d8817e4Smiod       cur_proc_ptr->pdr.gp_prologue = 0;
5172*3d8817e4Smiod     }
5173*3d8817e4Smiod 
5174*3d8817e4Smiod   cur_proc_ptr->pdr.gp_used = 1;
5175*3d8817e4Smiod }
5176*3d8817e4Smiod 
5177*3d8817e4Smiod int
ecoff_no_current_file(void)5178*3d8817e4Smiod ecoff_no_current_file (void)
5179*3d8817e4Smiod {
5180*3d8817e4Smiod   return cur_file_ptr == (efdr_t *) NULL;
5181*3d8817e4Smiod }
5182*3d8817e4Smiod 
5183*3d8817e4Smiod void
ecoff_generate_asm_lineno(void)5184*3d8817e4Smiod ecoff_generate_asm_lineno (void)
5185*3d8817e4Smiod {
5186*3d8817e4Smiod   unsigned int lineno;
5187*3d8817e4Smiod   char *filename;
5188*3d8817e4Smiod   lineno_list_t *list;
5189*3d8817e4Smiod 
5190*3d8817e4Smiod   as_where (&filename, &lineno);
5191*3d8817e4Smiod 
5192*3d8817e4Smiod   if (current_stabs_filename == (char *) NULL
5193*3d8817e4Smiod       || strcmp (current_stabs_filename, filename))
5194*3d8817e4Smiod     add_file (filename, 0, 1);
5195*3d8817e4Smiod 
5196*3d8817e4Smiod   list = allocate_lineno_list ();
5197*3d8817e4Smiod 
5198*3d8817e4Smiod   list->next = (lineno_list_t *) NULL;
5199*3d8817e4Smiod   list->file = cur_file_ptr;
5200*3d8817e4Smiod   list->proc = cur_proc_ptr;
5201*3d8817e4Smiod   list->frag = frag_now;
5202*3d8817e4Smiod   list->paddr = frag_now_fix ();
5203*3d8817e4Smiod   list->lineno = lineno;
5204*3d8817e4Smiod 
5205*3d8817e4Smiod   /* We don't want to merge files which have line numbers.  */
5206*3d8817e4Smiod   cur_file_ptr->fdr.fMerge = 0;
5207*3d8817e4Smiod 
5208*3d8817e4Smiod   /* A .loc directive will sometimes appear before a .ent directive,
5209*3d8817e4Smiod      which means that cur_proc_ptr will be NULL here.  Arrange to
5210*3d8817e4Smiod      patch this up.  */
5211*3d8817e4Smiod   if (cur_proc_ptr == (proc_t *) NULL)
5212*3d8817e4Smiod     {
5213*3d8817e4Smiod       lineno_list_t **pl;
5214*3d8817e4Smiod 
5215*3d8817e4Smiod       pl = &noproc_lineno;
5216*3d8817e4Smiod       while (*pl != (lineno_list_t *) NULL)
5217*3d8817e4Smiod 	pl = &(*pl)->next;
5218*3d8817e4Smiod       *pl = list;
5219*3d8817e4Smiod     }
5220*3d8817e4Smiod   else
5221*3d8817e4Smiod     {
5222*3d8817e4Smiod       last_lineno = list;
5223*3d8817e4Smiod       *last_lineno_ptr = list;
5224*3d8817e4Smiod       last_lineno_ptr = &list->next;
5225*3d8817e4Smiod     }
5226*3d8817e4Smiod }
5227*3d8817e4Smiod 
5228*3d8817e4Smiod #else
5229*3d8817e4Smiod 
5230*3d8817e4Smiod void
ecoff_generate_asm_lineno(void)5231*3d8817e4Smiod ecoff_generate_asm_lineno (void)
5232*3d8817e4Smiod {
5233*3d8817e4Smiod }
5234*3d8817e4Smiod 
5235*3d8817e4Smiod #endif /* ECOFF_DEBUGGING */
5236