1/* Read coff symbol tables and convert to internal format, for GDB.
2   Copyright 1987, 1988, 1989, 1990, 1991, 1992, 1993, 1994, 1995, 1996,
3   1997, 1998, 1999, 2000, 2001, 2002, 2003, 2004
4   Free Software Foundation, Inc.
5   Contributed by David D. Johnson, Brown University (ddj@cs.brown.edu).
6
7   This file is part of GDB.
8
9   This program is free software; you can redistribute it and/or modify
10   it under the terms of the GNU General Public License as published by
11   the Free Software Foundation; either version 2 of the License, or
12   (at your option) any later version.
13
14   This program is distributed in the hope that it will be useful,
15   but WITHOUT ANY WARRANTY; without even the implied warranty of
16   MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
17   GNU General Public License for more details.
18
19   You should have received a copy of the GNU General Public License
20   along with this program; if not, write to the Free Software
21   Foundation, Inc., 59 Temple Place - Suite 330,
22   Boston, MA 02111-1307, USA.  */
23
24#include "defs.h"
25#include "symtab.h"
26#include "gdbtypes.h"
27#include "demangle.h"
28#include "breakpoint.h"
29
30#include "bfd.h"
31#include "gdb_obstack.h"
32
33#include "gdb_string.h"
34#include <ctype.h>
35
36#include "coff/internal.h"	/* Internal format of COFF symbols in BFD */
37#include "libcoff.h"		/* FIXME secret internal data from BFD */
38#include "objfiles.h"
39#include "buildsym.h"
40#include "gdb-stabs.h"
41#include "stabsread.h"
42#include "complaints.h"
43#include "target.h"
44#include "gdb_assert.h"
45#include "block.h"
46#include "dictionary.h"
47
48#include "coff-pe-read.h"
49
50extern void _initialize_coffread (void);
51
52struct coff_symfile_info
53  {
54    file_ptr min_lineno_offset;	/* Where in file lowest line#s are */
55    file_ptr max_lineno_offset;	/* 1+last byte of line#s in file */
56
57    CORE_ADDR textaddr;		/* Addr of .text section. */
58    unsigned int textsize;	/* Size of .text section. */
59    struct stab_section_list *stabsects;	/* .stab sections.  */
60    asection *stabstrsect;	/* Section pointer for .stab section */
61    char *stabstrdata;
62  };
63
64/* Translate an external name string into a user-visible name.  */
65#define	EXTERNAL_NAME(string, abfd) \
66	(string[0] == bfd_get_symbol_leading_char(abfd)? string+1: string)
67
68/* To be an sdb debug type, type must have at least a basic or primary
69   derived type.  Using this rather than checking against T_NULL is
70   said to prevent core dumps if we try to operate on Michael Bloom
71   dbx-in-coff file.  */
72
73#define SDB_TYPE(type) (BTYPE(type) | (type & N_TMASK))
74
75/* Core address of start and end of text of current source file.
76   This comes from a ".text" symbol where x_nlinno > 0.  */
77
78static CORE_ADDR current_source_start_addr;
79static CORE_ADDR current_source_end_addr;
80
81/* The addresses of the symbol table stream and number of symbols
82   of the object file we are reading (as copied into core).  */
83
84static bfd *nlist_bfd_global;
85static int nlist_nsyms_global;
86
87
88/* Pointers to scratch storage, used for reading raw symbols and auxents.  */
89
90static char *temp_sym;
91static char *temp_aux;
92
93/* Local variables that hold the shift and mask values for the
94   COFF file that we are currently reading.  These come back to us
95   from BFD, and are referenced by their macro names, as well as
96   internally to the BTYPE, ISPTR, ISFCN, ISARY, ISTAG, and DECREF
97   macros from include/coff/internal.h .  */
98
99static unsigned local_n_btmask;
100static unsigned local_n_btshft;
101static unsigned local_n_tmask;
102static unsigned local_n_tshift;
103
104#define	N_BTMASK	local_n_btmask
105#define	N_BTSHFT	local_n_btshft
106#define	N_TMASK		local_n_tmask
107#define	N_TSHIFT	local_n_tshift
108
109/* Local variables that hold the sizes in the file of various COFF structures.
110   (We only need to know this to read them from the file -- BFD will then
111   translate the data in them, into `internal_xxx' structs in the right
112   byte order, alignment, etc.)  */
113
114static unsigned local_linesz;
115static unsigned local_symesz;
116static unsigned local_auxesz;
117
118/* This is set if this is a PE format file.  */
119
120static int pe_file;
121
122/* Chain of typedefs of pointers to empty struct/union types.
123   They are chained thru the SYMBOL_VALUE_CHAIN.  */
124
125static struct symbol *opaque_type_chain[HASHSIZE];
126
127/* Simplified internal version of coff symbol table information */
128
129struct coff_symbol
130  {
131    char *c_name;
132    int c_symnum;		/* symbol number of this entry */
133    int c_naux;			/* 0 if syment only, 1 if syment + auxent, etc */
134    long c_value;
135    int c_sclass;
136    int c_secnum;
137    unsigned int c_type;
138  };
139
140extern void stabsread_clear_cache (void);
141
142static struct type *coff_read_struct_type (int, int, int);
143
144static struct type *decode_base_type (struct coff_symbol *,
145				      unsigned int, union internal_auxent *);
146
147static struct type *decode_type (struct coff_symbol *, unsigned int,
148				 union internal_auxent *);
149
150static struct type *decode_function_type (struct coff_symbol *,
151					  unsigned int,
152					  union internal_auxent *);
153
154static struct type *coff_read_enum_type (int, int, int);
155
156static struct symbol *process_coff_symbol (struct coff_symbol *,
157					   union internal_auxent *,
158					   struct objfile *);
159
160static void patch_opaque_types (struct symtab *);
161
162static void enter_linenos (long, int, int, struct objfile *);
163
164static void free_linetab (void);
165
166static void free_linetab_cleanup (void *ignore);
167
168static int init_lineno (bfd *, long, int);
169
170static char *getsymname (struct internal_syment *);
171
172static char *coff_getfilename (union internal_auxent *);
173
174static void free_stringtab (void);
175
176static void free_stringtab_cleanup (void *ignore);
177
178static int init_stringtab (bfd *, long);
179
180static void read_one_sym (struct coff_symbol *,
181			  struct internal_syment *, union internal_auxent *);
182
183static void coff_symtab_read (long, unsigned int, struct objfile *);
184
185/* We are called once per section from coff_symfile_read.  We
186   need to examine each section we are passed, check to see
187   if it is something we are interested in processing, and
188   if so, stash away some access information for the section.
189
190   FIXME: The section names should not be hardwired strings (what
191   should they be?  I don't think most object file formats have enough
192   section flags to specify what kind of debug section it is
193   -kingdon).  */
194
195static void
196coff_locate_sections (bfd *abfd, asection *sectp, void *csip)
197{
198  struct coff_symfile_info *csi;
199  const char *name;
200
201  csi = (struct coff_symfile_info *) csip;
202  name = bfd_get_section_name (abfd, sectp);
203  if (DEPRECATED_STREQ (name, ".text"))
204    {
205      csi->textaddr = bfd_section_vma (abfd, sectp);
206      csi->textsize += bfd_section_size (abfd, sectp);
207    }
208  else if (strncmp (name, ".text", sizeof ".text" - 1) == 0)
209    {
210      csi->textsize += bfd_section_size (abfd, sectp);
211    }
212  else if (DEPRECATED_STREQ (name, ".stabstr"))
213    {
214      csi->stabstrsect = sectp;
215    }
216  else if (strncmp (name, ".stab", sizeof ".stab" - 1) == 0)
217    {
218      const char *s;
219
220      /* We can have multiple .stab sections if linked with
221         --split-by-reloc.  */
222      for (s = name + sizeof ".stab" - 1; *s != '\0'; s++)
223	if (!isdigit (*s))
224	  break;
225      if (*s == '\0')
226	{
227	  struct stab_section_list *n, **pn;
228
229	  n = ((struct stab_section_list *)
230	       xmalloc (sizeof (struct stab_section_list)));
231	  n->section = sectp;
232	  n->next = NULL;
233	  for (pn = &csi->stabsects; *pn != NULL; pn = &(*pn)->next)
234	    ;
235	  *pn = n;
236
237	  /* This will be run after coffstab_build_psymtabs is called
238	     in coff_symfile_read, at which point we no longer need
239	     the information.  */
240	  make_cleanup (xfree, n);
241	}
242    }
243}
244
245/* Return the section_offsets* that CS points to.  */
246static int cs_to_section (struct coff_symbol *, struct objfile *);
247
248struct find_targ_sec_arg
249  {
250    int targ_index;
251    asection **resultp;
252  };
253
254static void
255find_targ_sec (bfd *abfd, asection *sect, void *obj)
256{
257  struct find_targ_sec_arg *args = (struct find_targ_sec_arg *) obj;
258  if (sect->target_index == args->targ_index)
259    *args->resultp = sect;
260}
261
262/* Return the section number (SECT_OFF_*) that CS points to.  */
263static int
264cs_to_section (struct coff_symbol *cs, struct objfile *objfile)
265{
266  asection *sect = NULL;
267  struct find_targ_sec_arg args;
268  int off = SECT_OFF_TEXT (objfile);
269
270  args.targ_index = cs->c_secnum;
271  args.resultp = &sect;
272  bfd_map_over_sections (objfile->obfd, find_targ_sec, &args);
273  if (sect != NULL)
274    {
275      /* This is the section.  Figure out what SECT_OFF_* code it is.  */
276      if (bfd_get_section_flags (abfd, sect) & SEC_CODE)
277	off = SECT_OFF_TEXT (objfile);
278      else if (bfd_get_section_flags (abfd, sect) & SEC_LOAD)
279	off = SECT_OFF_DATA (objfile);
280      else
281	/* Just return the bfd section index. */
282	off = sect->index;
283    }
284  return off;
285}
286
287/* Return the address of the section of a COFF symbol.  */
288
289static CORE_ADDR cs_section_address (struct coff_symbol *, bfd *);
290
291static CORE_ADDR
292cs_section_address (struct coff_symbol *cs, bfd *abfd)
293{
294  asection *sect = NULL;
295  struct find_targ_sec_arg args;
296  CORE_ADDR addr = 0;
297
298  args.targ_index = cs->c_secnum;
299  args.resultp = &sect;
300  bfd_map_over_sections (abfd, find_targ_sec, &args);
301  if (sect != NULL)
302    addr = bfd_get_section_vma (objfile->obfd, sect);
303  return addr;
304}
305
306/* Look up a coff type-number index.  Return the address of the slot
307   where the type for that index is stored.
308   The type-number is in INDEX.
309
310   This can be used for finding the type associated with that index
311   or for associating a new type with the index.  */
312
313static struct type **
314coff_lookup_type (int index)
315{
316  if (index >= type_vector_length)
317    {
318      int old_vector_length = type_vector_length;
319
320      type_vector_length *= 2;
321      if (index /* is still */  >= type_vector_length)
322	type_vector_length = index * 2;
323
324      type_vector = (struct type **)
325	xrealloc ((char *) type_vector,
326		  type_vector_length * sizeof (struct type *));
327      memset (&type_vector[old_vector_length], 0,
328	 (type_vector_length - old_vector_length) * sizeof (struct type *));
329    }
330  return &type_vector[index];
331}
332
333/* Make sure there is a type allocated for type number index
334   and return the type object.
335   This can create an empty (zeroed) type object.  */
336
337static struct type *
338coff_alloc_type (int index)
339{
340  struct type **type_addr = coff_lookup_type (index);
341  struct type *type = *type_addr;
342
343  /* If we are referring to a type not known at all yet,
344     allocate an empty type for it.
345     We will fill it in later if we find out how.  */
346  if (type == NULL)
347    {
348      type = alloc_type (current_objfile);
349      *type_addr = type;
350    }
351  return type;
352}
353
354/* Start a new symtab for a new source file.
355   This is called when a COFF ".file" symbol is seen;
356   it indicates the start of data for one original source file.  */
357
358static void
359coff_start_symtab (char *name)
360{
361  start_symtab (
362  /* We fill in the filename later.  start_symtab puts
363     this pointer into last_source_file and we put it in
364     subfiles->name, which end_symtab frees; that's why
365     it must be malloc'd.  */
366		 savestring (name, strlen (name)),
367  /* We never know the directory name for COFF.  */
368		 NULL,
369  /* The start address is irrelevant, since we set
370     last_source_start_addr in coff_end_symtab.  */
371		 0);
372  record_debugformat ("COFF");
373}
374
375/* Save the vital information from when starting to read a file,
376   for use when closing off the current file.
377   NAME is the file name the symbols came from, START_ADDR is the first
378   text address for the file, and SIZE is the number of bytes of text.  */
379
380static void
381complete_symtab (char *name, CORE_ADDR start_addr, unsigned int size)
382{
383  if (last_source_file != NULL)
384    xfree (last_source_file);
385  last_source_file = savestring (name, strlen (name));
386  current_source_start_addr = start_addr;
387  current_source_end_addr = start_addr + size;
388}
389
390/* Finish the symbol definitions for one main source file,
391   close off all the lexical contexts for that file
392   (creating struct block's for them), then make the
393   struct symtab for that file and put it in the list of all such. */
394
395static void
396coff_end_symtab (struct objfile *objfile)
397{
398  struct symtab *symtab;
399
400  last_source_start_addr = current_source_start_addr;
401
402  symtab = end_symtab (current_source_end_addr, objfile, SECT_OFF_TEXT (objfile));
403
404  if (symtab != NULL)
405    free_named_symtabs (symtab->filename);
406
407  /* Reinitialize for beginning of new file. */
408  last_source_file = NULL;
409}
410
411static void
412record_minimal_symbol (char *name, CORE_ADDR address,
413		       enum minimal_symbol_type type, struct objfile *objfile)
414{
415  /* We don't want TDESC entry points in the minimal symbol table */
416  if (name[0] == '@')
417    return;
418
419  prim_record_minimal_symbol (name, address, type, objfile);
420}
421
422/* coff_symfile_init ()
423   is the coff-specific initialization routine for reading symbols.
424   It is passed a struct objfile which contains, among other things,
425   the BFD for the file whose symbols are being read, and a slot for
426   a pointer to "private data" which we fill with cookies and other
427   treats for coff_symfile_read ().
428
429   We will only be called if this is a COFF or COFF-like file.
430   BFD handles figuring out the format of the file, and code in symtab.c
431   uses BFD's determination to vector to us.
432
433   The ultimate result is a new symtab (or, FIXME, eventually a psymtab).  */
434
435static void
436coff_symfile_init (struct objfile *objfile)
437{
438  /* Allocate struct to keep track of stab reading. */
439  objfile->sym_stab_info = (struct dbx_symfile_info *)
440    xmalloc (sizeof (struct dbx_symfile_info));
441
442  memset (objfile->sym_stab_info, 0,
443	  sizeof (struct dbx_symfile_info));
444
445  /* Allocate struct to keep track of the symfile */
446  objfile->sym_private = xmalloc (sizeof (struct coff_symfile_info));
447
448  memset (objfile->sym_private, 0, sizeof (struct coff_symfile_info));
449
450  /* COFF objects may be reordered, so set OBJF_REORDERED.  If we
451     find this causes a significant slowdown in gdb then we could
452     set it in the debug symbol readers only when necessary.  */
453  objfile->flags |= OBJF_REORDERED;
454
455  init_entry_point_info (objfile);
456}
457
458/* This function is called for every section; it finds the outer limits
459   of the line table (minimum and maximum file offset) so that the
460   mainline code can read the whole thing for efficiency.  */
461
462static void
463find_linenos (bfd *abfd, struct bfd_section *asect, void *vpinfo)
464{
465  struct coff_symfile_info *info;
466  int size, count;
467  file_ptr offset, maxoff;
468
469/* WARNING WILL ROBINSON!  ACCESSING BFD-PRIVATE DATA HERE!  FIXME!  */
470  count = asect->lineno_count;
471/* End of warning */
472
473  if (count == 0)
474    return;
475  size = count * local_linesz;
476
477  info = (struct coff_symfile_info *) vpinfo;
478/* WARNING WILL ROBINSON!  ACCESSING BFD-PRIVATE DATA HERE!  FIXME!  */
479  offset = asect->line_filepos;
480/* End of warning */
481
482  if (offset < info->min_lineno_offset || info->min_lineno_offset == 0)
483    info->min_lineno_offset = offset;
484
485  maxoff = offset + size;
486  if (maxoff > info->max_lineno_offset)
487    info->max_lineno_offset = maxoff;
488}
489
490
491/* The BFD for this file -- only good while we're actively reading
492   symbols into a psymtab or a symtab.  */
493
494static bfd *symfile_bfd;
495
496/* Read a symbol file, after initialization by coff_symfile_init.  */
497
498static void
499coff_symfile_read (struct objfile *objfile, int mainline)
500{
501  struct coff_symfile_info *info;
502  struct dbx_symfile_info *dbxinfo;
503  bfd *abfd = objfile->obfd;
504  coff_data_type *cdata = coff_data (abfd);
505  char *name = bfd_get_filename (abfd);
506  int val;
507  unsigned int num_symbols;
508  int symtab_offset;
509  int stringtab_offset;
510  struct cleanup *back_to, *cleanup_minimal_symbols;
511  int stabstrsize;
512  int len;
513  char * target;
514
515  info = (struct coff_symfile_info *) objfile->sym_private;
516  dbxinfo = objfile->sym_stab_info;
517  symfile_bfd = abfd;		/* Kludge for swap routines */
518
519/* WARNING WILL ROBINSON!  ACCESSING BFD-PRIVATE DATA HERE!  FIXME!  */
520  num_symbols = bfd_get_symcount (abfd);	/* How many syms */
521  symtab_offset = cdata->sym_filepos;	/* Symbol table file offset */
522  stringtab_offset = symtab_offset +	/* String table file offset */
523    num_symbols * cdata->local_symesz;
524
525  /* Set a few file-statics that give us specific information about
526     the particular COFF file format we're reading.  */
527  local_n_btmask = cdata->local_n_btmask;
528  local_n_btshft = cdata->local_n_btshft;
529  local_n_tmask = cdata->local_n_tmask;
530  local_n_tshift = cdata->local_n_tshift;
531  local_linesz = cdata->local_linesz;
532  local_symesz = cdata->local_symesz;
533  local_auxesz = cdata->local_auxesz;
534
535  /* Allocate space for raw symbol and aux entries, based on their
536     space requirements as reported by BFD.  */
537  temp_sym = (char *) xmalloc
538    (cdata->local_symesz + cdata->local_auxesz);
539  temp_aux = temp_sym + cdata->local_symesz;
540  back_to = make_cleanup (free_current_contents, &temp_sym);
541
542  /* We need to know whether this is a PE file, because in PE files,
543     unlike standard COFF files, symbol values are stored as offsets
544     from the section address, rather than as absolute addresses.
545     FIXME: We should use BFD to read the symbol table, and thus avoid
546     this problem.  */
547  pe_file =
548    strncmp (bfd_get_target (objfile->obfd), "pe", 2) == 0
549    || strncmp (bfd_get_target (objfile->obfd), "epoc-pe", 7) == 0;
550
551/* End of warning */
552
553  info->min_lineno_offset = 0;
554  info->max_lineno_offset = 0;
555
556  /* Only read line number information if we have symbols.
557
558     On Windows NT, some of the system's DLL's have sections with
559     PointerToLinenumbers fields that are non-zero, but point at
560     random places within the image file.  (In the case I found,
561     KERNEL32.DLL's .text section has a line number info pointer that
562     points into the middle of the string `lib\\i386\kernel32.dll'.)
563
564     However, these DLL's also have no symbols.  The line number
565     tables are meaningless without symbols.  And in fact, GDB never
566     uses the line number information unless there are symbols.  So we
567     can avoid spurious error messages (and maybe run a little
568     faster!) by not even reading the line number table unless we have
569     symbols.  */
570  if (num_symbols > 0)
571    {
572      /* Read the line number table, all at once.  */
573      bfd_map_over_sections (abfd, find_linenos, (void *) info);
574
575      make_cleanup (free_linetab_cleanup, 0 /*ignore*/);
576      val = init_lineno (abfd, info->min_lineno_offset,
577                         info->max_lineno_offset - info->min_lineno_offset);
578      if (val < 0)
579        error ("\"%s\": error reading line numbers\n", name);
580    }
581
582  /* Now read the string table, all at once.  */
583
584  make_cleanup (free_stringtab_cleanup, 0 /*ignore*/);
585  val = init_stringtab (abfd, stringtab_offset);
586  if (val < 0)
587    error ("\"%s\": can't get string table", name);
588
589  init_minimal_symbol_collection ();
590  cleanup_minimal_symbols = make_cleanup_discard_minimal_symbols ();
591
592  /* Now that the executable file is positioned at symbol table,
593     process it and define symbols accordingly.  */
594
595  coff_symtab_read ((long) symtab_offset, num_symbols, objfile);
596
597  /* Install any minimal symbols that have been collected as the current
598     minimal symbols for this objfile.  */
599
600  install_minimal_symbols (objfile);
601
602  /* Free the installed minimal symbol data.  */
603  do_cleanups (cleanup_minimal_symbols);
604
605  /* If we are reinitializing, or if we have not loaded syms yet,
606     empty the psymtab.  "mainline" is cleared so the *_read_psymtab
607     functions do not all re-initialize it.  */
608  if (mainline)
609    {
610      init_psymbol_list (objfile, 0);
611      mainline = 0;
612    }
613
614  bfd_map_over_sections (abfd, coff_locate_sections, (void *) info);
615
616  if (info->stabsects)
617    {
618      if (!info->stabstrsect)
619	{
620	  error (("The debugging information in `%s' is corrupted.\n"
621		  "The file has a `.stabs' section, but no `.stabstr' "
622		  "section."),
623		 name);
624	}
625
626      /* FIXME: dubious.  Why can't we use something normal like
627         bfd_get_section_contents?  */
628      bfd_seek (abfd, abfd->where, 0);
629
630      stabstrsize = bfd_section_size (abfd, info->stabstrsect);
631
632      coffstab_build_psymtabs (objfile,
633			       mainline,
634			       info->textaddr, info->textsize,
635			       info->stabsects,
636			       info->stabstrsect->filepos, stabstrsize);
637    }
638  if (dwarf2_has_info (objfile))
639    {
640      /* DWARF2 sections.  */
641      dwarf2_build_psymtabs (objfile, mainline);
642    }
643
644  dwarf2_build_frame_info (objfile);
645
646  do_cleanups (back_to);
647}
648
649static void
650coff_new_init (struct objfile *ignore)
651{
652}
653
654/* Perform any local cleanups required when we are done with a particular
655   objfile.  I.E, we are in the process of discarding all symbol information
656   for an objfile, freeing up all memory held for it, and unlinking the
657   objfile struct from the global list of known objfiles. */
658
659static void
660coff_symfile_finish (struct objfile *objfile)
661{
662  if (objfile->sym_private != NULL)
663    {
664      xfree (objfile->sym_private);
665    }
666
667  /* Let stabs reader clean up */
668  stabsread_clear_cache ();
669}
670
671
672/* Given pointers to a symbol table in coff style exec file,
673   analyze them and create struct symtab's describing the symbols.
674   NSYMS is the number of symbols in the symbol table.
675   We read them one at a time using read_one_sym ().  */
676
677static void
678coff_symtab_read (long symtab_offset, unsigned int nsyms,
679		  struct objfile *objfile)
680{
681  struct context_stack *new;
682  struct coff_symbol coff_symbol;
683  struct coff_symbol *cs = &coff_symbol;
684  static struct internal_syment main_sym;
685  static union internal_auxent main_aux;
686  struct coff_symbol fcn_cs_saved;
687  static struct internal_syment fcn_sym_saved;
688  static union internal_auxent fcn_aux_saved;
689  struct symtab *s;
690  /* A .file is open.  */
691  int in_source_file = 0;
692  int next_file_symnum = -1;
693  /* Name of the current file.  */
694  char *filestring = "";
695  int depth = 0;
696  int fcn_first_line = 0;
697  CORE_ADDR fcn_first_line_addr = 0;
698  int fcn_last_line = 0;
699  int fcn_start_addr = 0;
700  long fcn_line_ptr = 0;
701  int val;
702  CORE_ADDR tmpaddr;
703
704  /* Work around a stdio bug in SunOS4.1.1 (this makes me nervous....
705     it's hard to know I've really worked around it.  The fix should be
706     harmless, anyway).  The symptom of the bug is that the first
707     fread (in read_one_sym), will (in my example) actually get data
708     from file offset 268, when the fseek was to 264 (and ftell shows
709     264).  This causes all hell to break loose.  I was unable to
710     reproduce this on a short test program which operated on the same
711     file, performing (I think) the same sequence of operations.
712
713     It stopped happening when I put in this (former) rewind().
714
715     FIXME: Find out if this has been reported to Sun, whether it has
716     been fixed in a later release, etc.  */
717
718  bfd_seek (objfile->obfd, 0, 0);
719
720  /* Position to read the symbol table. */
721  val = bfd_seek (objfile->obfd, (long) symtab_offset, 0);
722  if (val < 0)
723    perror_with_name (objfile->name);
724
725  current_objfile = objfile;
726  nlist_bfd_global = objfile->obfd;
727  nlist_nsyms_global = nsyms;
728  last_source_file = NULL;
729  memset (opaque_type_chain, 0, sizeof opaque_type_chain);
730
731  if (type_vector)		/* Get rid of previous one */
732    xfree (type_vector);
733  type_vector_length = 160;
734  type_vector = (struct type **)
735    xmalloc (type_vector_length * sizeof (struct type *));
736  memset (type_vector, 0, type_vector_length * sizeof (struct type *));
737
738  coff_start_symtab ("");
739
740  symnum = 0;
741  while (symnum < nsyms)
742    {
743      QUIT;			/* Make this command interruptable.  */
744
745      read_one_sym (cs, &main_sym, &main_aux);
746
747      if (cs->c_symnum == next_file_symnum && cs->c_sclass != C_FILE)
748	{
749	  if (last_source_file)
750	    coff_end_symtab (objfile);
751
752	  coff_start_symtab ("_globals_");
753	  complete_symtab ("_globals_", 0, 0);
754	  /* done with all files, everything from here on out is globals */
755	}
756
757      /* Special case for file with type declarations only, no text.  */
758      if (!last_source_file && SDB_TYPE (cs->c_type)
759	  && cs->c_secnum == N_DEBUG)
760	complete_symtab (filestring, 0, 0);
761
762      /* Typedefs should not be treated as symbol definitions.  */
763      if (ISFCN (cs->c_type) && cs->c_sclass != C_TPDEF)
764	{
765	  /* Record all functions -- external and static -- in minsyms. */
766	  tmpaddr = cs->c_value + ANOFFSET (objfile->section_offsets, SECT_OFF_TEXT (objfile));
767	  record_minimal_symbol (cs->c_name, tmpaddr, mst_text, objfile);
768
769	  fcn_line_ptr = main_aux.x_sym.x_fcnary.x_fcn.x_lnnoptr;
770	  fcn_start_addr = tmpaddr;
771	  fcn_cs_saved = *cs;
772	  fcn_sym_saved = main_sym;
773	  fcn_aux_saved = main_aux;
774	  continue;
775	}
776
777      switch (cs->c_sclass)
778	{
779	case C_EFCN:
780	case C_EXTDEF:
781	case C_ULABEL:
782	case C_USTATIC:
783	case C_LINE:
784	case C_ALIAS:
785	case C_HIDDEN:
786	  complaint (&symfile_complaints, "Bad n_sclass for symbol %s",
787		     cs->c_name);
788	  break;
789
790	case C_FILE:
791	  /* c_value field contains symnum of next .file entry in table
792	     or symnum of first global after last .file.  */
793	  next_file_symnum = cs->c_value;
794	  if (cs->c_naux > 0)
795	    filestring = coff_getfilename (&main_aux);
796	  else
797	    filestring = "";
798
799	  /* Complete symbol table for last object file
800	     containing debugging information.  */
801	  if (last_source_file)
802	    {
803	      coff_end_symtab (objfile);
804	      coff_start_symtab (filestring);
805	    }
806	  in_source_file = 1;
807	  break;
808
809	  /* C_LABEL is used for labels and static functions.  Including
810	     it here allows gdb to see static functions when no debug
811	     info is available.  */
812	case C_LABEL:
813	  /* However, labels within a function can make weird backtraces,
814	     so filter them out (from phdm@macqel.be). */
815	  if (within_function)
816	    break;
817	case C_STAT:
818	case C_THUMBLABEL:
819	case C_THUMBSTAT:
820	case C_THUMBSTATFUNC:
821	  if (cs->c_name[0] == '.')
822	    {
823	      if (DEPRECATED_STREQ (cs->c_name, ".text"))
824		{
825		  /* FIXME:  don't wire in ".text" as section name
826		     or symbol name! */
827		  /* Check for in_source_file deals with case of
828		     a file with debugging symbols
829		     followed by a later file with no symbols.  */
830		  if (in_source_file)
831		    complete_symtab (filestring,
832		    cs->c_value + ANOFFSET (objfile->section_offsets, SECT_OFF_TEXT (objfile)),
833				     main_aux.x_scn.x_scnlen);
834		  in_source_file = 0;
835		}
836	      /* flush rest of '.' symbols */
837	      break;
838	    }
839	  else if (!SDB_TYPE (cs->c_type)
840		   && cs->c_name[0] == 'L'
841		   && (strncmp (cs->c_name, "LI%", 3) == 0
842		       || strncmp (cs->c_name, "LF%", 3) == 0
843		       || strncmp (cs->c_name, "LC%", 3) == 0
844		       || strncmp (cs->c_name, "LP%", 3) == 0
845		       || strncmp (cs->c_name, "LPB%", 4) == 0
846		       || strncmp (cs->c_name, "LBB%", 4) == 0
847		       || strncmp (cs->c_name, "LBE%", 4) == 0
848		       || strncmp (cs->c_name, "LPBX%", 5) == 0))
849	    /* At least on a 3b1, gcc generates swbeg and string labels
850	       that look like this.  Ignore them.  */
851	    break;
852	  /* fall in for static symbols that don't start with '.' */
853	case C_THUMBEXT:
854	case C_THUMBEXTFUNC:
855	case C_EXT:
856	  {
857	    /* Record it in the minimal symbols regardless of
858	       SDB_TYPE.  This parallels what we do for other debug
859	       formats, and probably is needed to make
860	       print_address_symbolic work right without the (now
861	       gone) "set fast-symbolic-addr off" kludge.  */
862
863	    enum minimal_symbol_type ms_type;
864	    int sec;
865
866	    if (cs->c_secnum == N_UNDEF)
867	      {
868		/* This is a common symbol.  See if the target
869		   environment knows where it has been relocated to.  */
870		CORE_ADDR reladdr;
871		if (target_lookup_symbol (cs->c_name, &reladdr))
872		  {
873		    /* Error in lookup; ignore symbol.  */
874		    break;
875		  }
876		tmpaddr = reladdr;
877		/* The address has already been relocated; make sure that
878		   objfile_relocate doesn't relocate it again.  */
879		sec = -2;
880		ms_type = cs->c_sclass == C_EXT
881		  || cs->c_sclass == C_THUMBEXT ?
882		  mst_bss : mst_file_bss;
883	      }
884 	    else if (cs->c_secnum == N_ABS)
885 	      {
886 		/* Use the correct minimal symbol type (and don't
887 		   relocate) for absolute values. */
888 		ms_type = mst_abs;
889 		sec = cs_to_section (cs, objfile);
890 		tmpaddr = cs->c_value;
891 	      }
892	    else
893	      {
894		sec = cs_to_section (cs, objfile);
895		tmpaddr = cs->c_value;
896 		/* Statics in a PE file also get relocated */
897 		if (cs->c_sclass == C_EXT
898 		    || cs->c_sclass == C_THUMBEXTFUNC
899 		    || cs->c_sclass == C_THUMBEXT
900 		    || (pe_file && (cs->c_sclass == C_STAT)))
901		  tmpaddr += ANOFFSET (objfile->section_offsets, sec);
902
903		if (sec == SECT_OFF_TEXT (objfile))
904		  {
905		    ms_type =
906		      cs->c_sclass == C_EXT || cs->c_sclass == C_THUMBEXTFUNC
907		      || cs->c_sclass == C_THUMBEXT ?
908		      mst_text : mst_file_text;
909		    tmpaddr = SMASH_TEXT_ADDRESS (tmpaddr);
910		  }
911		else if (sec == SECT_OFF_DATA (objfile))
912		  {
913		    ms_type =
914		      cs->c_sclass == C_EXT || cs->c_sclass == C_THUMBEXT ?
915		      mst_data : mst_file_data;
916		  }
917		else if (sec == SECT_OFF_BSS (objfile))
918		  {
919		    ms_type =
920		      cs->c_sclass == C_EXT || cs->c_sclass == C_THUMBEXT ?
921		      mst_data : mst_file_data;
922		  }
923		else
924		  ms_type = mst_unknown;
925	      }
926
927	    if (cs->c_name[0] != '@' /* Skip tdesc symbols */ )
928	      {
929		struct minimal_symbol *msym;
930		msym = prim_record_minimal_symbol_and_info
931		  (cs->c_name, tmpaddr, ms_type, NULL,
932		   sec, NULL, objfile);
933		if (msym)
934		  COFF_MAKE_MSYMBOL_SPECIAL (cs->c_sclass, msym);
935	      }
936	    if (SDB_TYPE (cs->c_type))
937	      {
938		struct symbol *sym;
939		sym = process_coff_symbol
940		  (cs, &main_aux, objfile);
941		SYMBOL_VALUE (sym) = tmpaddr;
942		SYMBOL_SECTION (sym) = sec;
943	      }
944	  }
945	  break;
946
947	case C_FCN:
948	  if (DEPRECATED_STREQ (cs->c_name, ".bf"))
949	    {
950	      within_function = 1;
951
952	      /* value contains address of first non-init type code */
953	      /* main_aux.x_sym.x_misc.x_lnsz.x_lnno
954	         contains line number of '{' } */
955	      if (cs->c_naux != 1)
956		complaint (&symfile_complaints,
957			   "`.bf' symbol %d has no aux entry", cs->c_symnum);
958	      fcn_first_line = main_aux.x_sym.x_misc.x_lnsz.x_lnno;
959	      fcn_first_line_addr = cs->c_value;
960
961	      /* Might want to check that locals are 0 and
962	         context_stack_depth is zero, and complain if not.  */
963
964	      depth = 0;
965	      new = push_context (depth, fcn_start_addr);
966	      fcn_cs_saved.c_name = getsymname (&fcn_sym_saved);
967	      new->name =
968		process_coff_symbol (&fcn_cs_saved, &fcn_aux_saved, objfile);
969	    }
970	  else if (DEPRECATED_STREQ (cs->c_name, ".ef"))
971	    {
972	      if (!within_function)
973		error ("Bad coff function information\n");
974	      /* the value of .ef is the address of epilogue code;
975	         not useful for gdb.  */
976	      /* { main_aux.x_sym.x_misc.x_lnsz.x_lnno
977	         contains number of lines to '}' */
978
979	      if (context_stack_depth <= 0)
980		{		/* We attempted to pop an empty context stack */
981		  complaint (&symfile_complaints,
982			     "`.ef' symbol without matching `.bf' symbol ignored starting at symnum %d",
983			     cs->c_symnum);
984		  within_function = 0;
985		  break;
986		}
987
988	      new = pop_context ();
989	      /* Stack must be empty now.  */
990	      if (context_stack_depth > 0 || new == NULL)
991		{
992		  complaint (&symfile_complaints,
993			     "Unmatched .ef symbol(s) ignored starting at symnum %d",
994			     cs->c_symnum);
995		  within_function = 0;
996		  break;
997		}
998	      if (cs->c_naux != 1)
999		{
1000		  complaint (&symfile_complaints,
1001			     "`.ef' symbol %d has no aux entry", cs->c_symnum);
1002		  fcn_last_line = 0x7FFFFFFF;
1003		}
1004	      else
1005		{
1006		  fcn_last_line = main_aux.x_sym.x_misc.x_lnsz.x_lnno;
1007		}
1008	      /* fcn_first_line is the line number of the opening '{'.
1009	         Do not record it - because it would affect gdb's idea
1010	         of the line number of the first statement of the function -
1011	         except for one-line functions, for which it is also the line
1012	         number of all the statements and of the closing '}', and
1013	         for which we do not have any other statement-line-number. */
1014	      if (fcn_last_line == 1)
1015		record_line (current_subfile, fcn_first_line,
1016			     fcn_first_line_addr);
1017	      else
1018		enter_linenos (fcn_line_ptr, fcn_first_line, fcn_last_line,
1019			       objfile);
1020
1021	      finish_block (new->name, &local_symbols, new->old_blocks,
1022			    new->start_addr,
1023#if defined (FUNCTION_EPILOGUE_SIZE)
1024	      /* This macro should be defined only on
1025	         machines where the
1026	         fcn_aux_saved.x_sym.x_misc.x_fsize
1027	         field is always zero.
1028	         So use the .bf record information that
1029	         points to the epilogue and add the size
1030	         of the epilogue.  */
1031			    cs->c_value
1032			    + FUNCTION_EPILOGUE_SIZE
1033			    + ANOFFSET (objfile->section_offsets, SECT_OFF_TEXT (objfile)),
1034#else
1035			    fcn_cs_saved.c_value
1036			    + fcn_aux_saved.x_sym.x_misc.x_fsize
1037			    + ANOFFSET (objfile->section_offsets, SECT_OFF_TEXT (objfile)),
1038#endif
1039			    objfile
1040		);
1041	      within_function = 0;
1042	    }
1043	  break;
1044
1045	case C_BLOCK:
1046	  if (DEPRECATED_STREQ (cs->c_name, ".bb"))
1047	    {
1048	      tmpaddr = cs->c_value;
1049	      tmpaddr += ANOFFSET (objfile->section_offsets, SECT_OFF_TEXT (objfile));
1050	      push_context (++depth, tmpaddr);
1051	    }
1052	  else if (DEPRECATED_STREQ (cs->c_name, ".eb"))
1053	    {
1054	      if (context_stack_depth <= 0)
1055		{		/* We attempted to pop an empty context stack */
1056		  complaint (&symfile_complaints,
1057			     "`.eb' symbol without matching `.bb' symbol ignored starting at symnum %d",
1058			     cs->c_symnum);
1059		  break;
1060		}
1061
1062	      new = pop_context ();
1063	      if (depth-- != new->depth)
1064		{
1065		  complaint (&symfile_complaints,
1066			     "Mismatched .eb symbol ignored starting at symnum %d",
1067			     symnum);
1068		  break;
1069		}
1070	      if (local_symbols && context_stack_depth > 0)
1071		{
1072		  tmpaddr =
1073		    cs->c_value + ANOFFSET (objfile->section_offsets, SECT_OFF_TEXT (objfile));
1074		  /* Make a block for the local symbols within.  */
1075		  finish_block (0, &local_symbols, new->old_blocks,
1076				new->start_addr, tmpaddr, objfile);
1077		}
1078	      /* Now pop locals of block just finished.  */
1079	      local_symbols = new->locals;
1080	    }
1081	  break;
1082
1083	default:
1084	  process_coff_symbol (cs, &main_aux, objfile);
1085	  break;
1086	}
1087    }
1088
1089  if ((nsyms == 0) && (pe_file))
1090    {
1091      /* We've got no debugging symbols, but it's is a portable
1092	 executable, so try to read the export table */
1093      read_pe_exported_syms (objfile);
1094    }
1095
1096  if (last_source_file)
1097    coff_end_symtab (objfile);
1098
1099  /* Patch up any opaque types (references to types that are not defined
1100     in the file where they are referenced, e.g. "struct foo *bar").  */
1101  ALL_OBJFILE_SYMTABS (objfile, s)
1102    patch_opaque_types (s);
1103
1104  current_objfile = NULL;
1105}
1106
1107/* Routines for reading headers and symbols from executable.  */
1108
1109/* Read the next symbol, swap it, and return it in both internal_syment
1110   form, and coff_symbol form.  Also return its first auxent, if any,
1111   in internal_auxent form, and skip any other auxents.  */
1112
1113static void
1114read_one_sym (struct coff_symbol *cs,
1115	      struct internal_syment *sym,
1116	      union internal_auxent *aux)
1117{
1118  int i;
1119
1120  cs->c_symnum = symnum;
1121  bfd_bread (temp_sym, local_symesz, nlist_bfd_global);
1122  bfd_coff_swap_sym_in (symfile_bfd, temp_sym, (char *) sym);
1123  cs->c_naux = sym->n_numaux & 0xff;
1124  if (cs->c_naux >= 1)
1125    {
1126      bfd_bread (temp_aux, local_auxesz, nlist_bfd_global);
1127      bfd_coff_swap_aux_in (symfile_bfd, temp_aux, sym->n_type, sym->n_sclass,
1128			    0, cs->c_naux, (char *) aux);
1129      /* If more than one aux entry, read past it (only the first aux
1130         is important). */
1131      for (i = 1; i < cs->c_naux; i++)
1132	bfd_bread (temp_aux, local_auxesz, nlist_bfd_global);
1133    }
1134  cs->c_name = getsymname (sym);
1135  cs->c_value = sym->n_value;
1136  cs->c_sclass = (sym->n_sclass & 0xff);
1137  cs->c_secnum = sym->n_scnum;
1138  cs->c_type = (unsigned) sym->n_type;
1139  if (!SDB_TYPE (cs->c_type))
1140    cs->c_type = 0;
1141
1142#if 0
1143  if (cs->c_sclass & 128)
1144    printf ("thumb symbol %s, class 0x%x\n", cs->c_name, cs->c_sclass);
1145#endif
1146
1147  symnum += 1 + cs->c_naux;
1148
1149  /* The PE file format stores symbol values as offsets within the
1150     section, rather than as absolute addresses.  We correct that
1151     here, if the symbol has an appropriate storage class.  FIXME: We
1152     should use BFD to read the symbols, rather than duplicating the
1153     work here.  */
1154  if (pe_file)
1155    {
1156      switch (cs->c_sclass)
1157	{
1158	case C_EXT:
1159	case C_THUMBEXT:
1160	case C_THUMBEXTFUNC:
1161	case C_SECTION:
1162	case C_NT_WEAK:
1163	case C_STAT:
1164	case C_THUMBSTAT:
1165	case C_THUMBSTATFUNC:
1166	case C_LABEL:
1167	case C_THUMBLABEL:
1168	case C_BLOCK:
1169	case C_FCN:
1170	case C_EFCN:
1171	  if (cs->c_secnum != 0)
1172	    cs->c_value += cs_section_address (cs, symfile_bfd);
1173	  break;
1174	}
1175    }
1176}
1177
1178/* Support for string table handling */
1179
1180static char *stringtab = NULL;
1181
1182static int
1183init_stringtab (bfd *abfd, long offset)
1184{
1185  long length;
1186  int val;
1187  unsigned char lengthbuf[4];
1188
1189  free_stringtab ();
1190
1191  /* If the file is stripped, the offset might be zero, indicating no
1192     string table.  Just return with `stringtab' set to null. */
1193  if (offset == 0)
1194    return 0;
1195
1196  if (bfd_seek (abfd, offset, 0) < 0)
1197    return -1;
1198
1199  val = bfd_bread ((char *) lengthbuf, sizeof lengthbuf, abfd);
1200  length = bfd_h_get_32 (symfile_bfd, lengthbuf);
1201
1202  /* If no string table is needed, then the file may end immediately
1203     after the symbols.  Just return with `stringtab' set to null. */
1204  if (val != sizeof lengthbuf || length < sizeof lengthbuf)
1205    return 0;
1206
1207  stringtab = (char *) xmalloc (length);
1208  /* This is in target format (probably not very useful, and not currently
1209     used), not host format.  */
1210  memcpy (stringtab, lengthbuf, sizeof lengthbuf);
1211  if (length == sizeof length)	/* Empty table -- just the count */
1212    return 0;
1213
1214  val = bfd_bread (stringtab + sizeof lengthbuf, length - sizeof lengthbuf,
1215		   abfd);
1216  if (val != length - sizeof lengthbuf || stringtab[length - 1] != '\0')
1217    return -1;
1218
1219  return 0;
1220}
1221
1222static void
1223free_stringtab (void)
1224{
1225  if (stringtab)
1226    xfree (stringtab);
1227  stringtab = NULL;
1228}
1229
1230static void
1231free_stringtab_cleanup (void *ignore)
1232{
1233  free_stringtab ();
1234}
1235
1236static char *
1237getsymname (struct internal_syment *symbol_entry)
1238{
1239  static char buffer[SYMNMLEN + 1];
1240  char *result;
1241
1242  if (symbol_entry->_n._n_n._n_zeroes == 0)
1243    {
1244      /* FIXME: Probably should be detecting corrupt symbol files by
1245         seeing whether offset points to within the stringtab.  */
1246      result = stringtab + symbol_entry->_n._n_n._n_offset;
1247    }
1248  else
1249    {
1250      strncpy (buffer, symbol_entry->_n._n_name, SYMNMLEN);
1251      buffer[SYMNMLEN] = '\0';
1252      result = buffer;
1253    }
1254  return result;
1255}
1256
1257/* Extract the file name from the aux entry of a C_FILE symbol.  Return
1258   only the last component of the name.  Result is in static storage and
1259   is only good for temporary use.  */
1260
1261static char *
1262coff_getfilename (union internal_auxent *aux_entry)
1263{
1264  static char buffer[BUFSIZ];
1265  char *temp;
1266  char *result;
1267
1268  if (aux_entry->x_file.x_n.x_zeroes == 0)
1269    strcpy (buffer, stringtab + aux_entry->x_file.x_n.x_offset);
1270  else
1271    {
1272      strncpy (buffer, aux_entry->x_file.x_fname, FILNMLEN);
1273      buffer[FILNMLEN] = '\0';
1274    }
1275  result = buffer;
1276
1277  /* FIXME: We should not be throwing away the information about what
1278     directory.  It should go into dirname of the symtab, or some such
1279     place.  */
1280  if ((temp = strrchr (result, '/')) != NULL)
1281    result = temp + 1;
1282  return (result);
1283}
1284
1285/* Support for line number handling.  */
1286
1287static char *linetab = NULL;
1288static long linetab_offset;
1289static unsigned long linetab_size;
1290
1291/* Read in all the line numbers for fast lookups later.  Leave them in
1292   external (unswapped) format in memory; we'll swap them as we enter
1293   them into GDB's data structures.  */
1294
1295static int
1296init_lineno (bfd *abfd, long offset, int size)
1297{
1298  int val;
1299
1300  linetab_offset = offset;
1301  linetab_size = size;
1302
1303  free_linetab ();
1304
1305  if (size == 0)
1306    return 0;
1307
1308  if (bfd_seek (abfd, offset, 0) < 0)
1309    return -1;
1310
1311  /* Allocate the desired table, plus a sentinel */
1312  linetab = (char *) xmalloc (size + local_linesz);
1313
1314  val = bfd_bread (linetab, size, abfd);
1315  if (val != size)
1316    return -1;
1317
1318  /* Terminate it with an all-zero sentinel record */
1319  memset (linetab + size, 0, local_linesz);
1320
1321  return 0;
1322}
1323
1324static void
1325free_linetab (void)
1326{
1327  if (linetab)
1328    xfree (linetab);
1329  linetab = NULL;
1330}
1331
1332static void
1333free_linetab_cleanup (void *ignore)
1334{
1335  free_linetab ();
1336}
1337
1338#if !defined (L_LNNO32)
1339#define L_LNNO32(lp) ((lp)->l_lnno)
1340#endif
1341
1342static void
1343enter_linenos (long file_offset, int first_line,
1344	       int last_line, struct objfile *objfile)
1345{
1346  char *rawptr;
1347  struct internal_lineno lptr;
1348
1349  if (!linetab)
1350    return;
1351  if (file_offset < linetab_offset)
1352    {
1353      complaint (&symfile_complaints,
1354		 "Line number pointer %ld lower than start of line numbers",
1355		 file_offset);
1356      if (file_offset > linetab_size)	/* Too big to be an offset? */
1357	return;
1358      file_offset += linetab_offset;	/* Try reading at that linetab offset */
1359    }
1360
1361  rawptr = &linetab[file_offset - linetab_offset];
1362
1363  /* skip first line entry for each function */
1364  rawptr += local_linesz;
1365  /* line numbers start at one for the first line of the function */
1366  first_line--;
1367
1368  /* If the line number table is full (e.g. 64K lines in COFF debug
1369     info), the next function's L_LNNO32 might not be zero, so don't
1370     overstep the table's end in any case.  */
1371  while (rawptr <= &linetab[0] + linetab_size)
1372    {
1373      bfd_coff_swap_lineno_in (symfile_bfd, rawptr, &lptr);
1374      rawptr += local_linesz;
1375      /* The next function, or the sentinel, will have L_LNNO32 zero;
1376	 we exit. */
1377      if (L_LNNO32 (&lptr) && L_LNNO32 (&lptr) <= last_line)
1378	record_line (current_subfile, first_line + L_LNNO32 (&lptr),
1379		     lptr.l_addr.l_paddr
1380		     + ANOFFSET (objfile->section_offsets, SECT_OFF_TEXT (objfile)));
1381      else
1382	break;
1383    }
1384}
1385
1386static void
1387patch_type (struct type *type, struct type *real_type)
1388{
1389  struct type *target = TYPE_TARGET_TYPE (type);
1390  struct type *real_target = TYPE_TARGET_TYPE (real_type);
1391  int field_size = TYPE_NFIELDS (real_target) * sizeof (struct field);
1392
1393  TYPE_LENGTH (target) = TYPE_LENGTH (real_target);
1394  TYPE_NFIELDS (target) = TYPE_NFIELDS (real_target);
1395  TYPE_FIELDS (target) = (struct field *) TYPE_ALLOC (target, field_size);
1396
1397  memcpy (TYPE_FIELDS (target), TYPE_FIELDS (real_target), field_size);
1398
1399  if (TYPE_NAME (real_target))
1400    {
1401      if (TYPE_NAME (target))
1402	xfree (TYPE_NAME (target));
1403      TYPE_NAME (target) = concat (TYPE_NAME (real_target), NULL);
1404    }
1405}
1406
1407/* Patch up all appropriate typedef symbols in the opaque_type_chains
1408   so that they can be used to print out opaque data structures properly.  */
1409
1410static void
1411patch_opaque_types (struct symtab *s)
1412{
1413  struct block *b;
1414  struct dict_iterator iter;
1415  struct symbol *real_sym;
1416
1417  /* Go through the per-file symbols only */
1418  b = BLOCKVECTOR_BLOCK (BLOCKVECTOR (s), STATIC_BLOCK);
1419  ALL_BLOCK_SYMBOLS (b, iter, real_sym)
1420    {
1421      /* Find completed typedefs to use to fix opaque ones.
1422         Remove syms from the chain when their types are stored,
1423         but search the whole chain, as there may be several syms
1424         from different files with the same name.  */
1425      if (SYMBOL_CLASS (real_sym) == LOC_TYPEDEF &&
1426	  SYMBOL_DOMAIN (real_sym) == VAR_DOMAIN &&
1427	  TYPE_CODE (SYMBOL_TYPE (real_sym)) == TYPE_CODE_PTR &&
1428	  TYPE_LENGTH (TYPE_TARGET_TYPE (SYMBOL_TYPE (real_sym))) != 0)
1429	{
1430	  char *name = DEPRECATED_SYMBOL_NAME (real_sym);
1431	  int hash = hashname (name);
1432	  struct symbol *sym, *prev;
1433
1434	  prev = 0;
1435	  for (sym = opaque_type_chain[hash]; sym;)
1436	    {
1437	      if (name[0] == DEPRECATED_SYMBOL_NAME (sym)[0] &&
1438		  strcmp (name + 1, DEPRECATED_SYMBOL_NAME (sym) + 1) == 0)
1439		{
1440		  if (prev)
1441		    {
1442		      SYMBOL_VALUE_CHAIN (prev) = SYMBOL_VALUE_CHAIN (sym);
1443		    }
1444		  else
1445		    {
1446		      opaque_type_chain[hash] = SYMBOL_VALUE_CHAIN (sym);
1447		    }
1448
1449		  patch_type (SYMBOL_TYPE (sym), SYMBOL_TYPE (real_sym));
1450
1451		  if (prev)
1452		    {
1453		      sym = SYMBOL_VALUE_CHAIN (prev);
1454		    }
1455		  else
1456		    {
1457		      sym = opaque_type_chain[hash];
1458		    }
1459		}
1460	      else
1461		{
1462		  prev = sym;
1463		  sym = SYMBOL_VALUE_CHAIN (sym);
1464		}
1465	    }
1466	}
1467    }
1468}
1469
1470static struct symbol *
1471process_coff_symbol (struct coff_symbol *cs,
1472		     union internal_auxent *aux,
1473		     struct objfile *objfile)
1474{
1475  struct symbol *sym
1476  = (struct symbol *) obstack_alloc (&objfile->objfile_obstack,
1477				     sizeof (struct symbol));
1478  char *name;
1479
1480  memset (sym, 0, sizeof (struct symbol));
1481  name = cs->c_name;
1482  name = EXTERNAL_NAME (name, objfile->obfd);
1483  SYMBOL_LANGUAGE (sym) = language_auto;
1484  SYMBOL_SET_NAMES (sym, name, strlen (name), objfile);
1485
1486  /* default assumptions */
1487  SYMBOL_VALUE (sym) = cs->c_value;
1488  SYMBOL_DOMAIN (sym) = VAR_DOMAIN;
1489  SYMBOL_SECTION (sym) = cs_to_section (cs, objfile);
1490
1491  if (ISFCN (cs->c_type))
1492    {
1493      SYMBOL_VALUE (sym) += ANOFFSET (objfile->section_offsets, SECT_OFF_TEXT (objfile));
1494      SYMBOL_TYPE (sym) =
1495	lookup_function_type (decode_function_type (cs, cs->c_type, aux));
1496
1497      SYMBOL_CLASS (sym) = LOC_BLOCK;
1498      if (cs->c_sclass == C_STAT || cs->c_sclass == C_THUMBSTAT
1499	  || cs->c_sclass == C_THUMBSTATFUNC)
1500	add_symbol_to_list (sym, &file_symbols);
1501      else if (cs->c_sclass == C_EXT || cs->c_sclass == C_THUMBEXT
1502	       || cs->c_sclass == C_THUMBEXTFUNC)
1503	add_symbol_to_list (sym, &global_symbols);
1504    }
1505  else
1506    {
1507      SYMBOL_TYPE (sym) = decode_type (cs, cs->c_type, aux);
1508      switch (cs->c_sclass)
1509	{
1510	case C_NULL:
1511	  break;
1512
1513	case C_AUTO:
1514	  SYMBOL_CLASS (sym) = LOC_LOCAL;
1515	  add_symbol_to_list (sym, &local_symbols);
1516	  break;
1517
1518	case C_THUMBEXT:
1519	case C_THUMBEXTFUNC:
1520	case C_EXT:
1521	  SYMBOL_CLASS (sym) = LOC_STATIC;
1522	  SYMBOL_VALUE_ADDRESS (sym) = (CORE_ADDR) cs->c_value;
1523	  SYMBOL_VALUE_ADDRESS (sym) += ANOFFSET (objfile->section_offsets, SECT_OFF_TEXT (objfile));
1524	  add_symbol_to_list (sym, &global_symbols);
1525	  break;
1526
1527	case C_THUMBSTAT:
1528	case C_THUMBSTATFUNC:
1529	case C_STAT:
1530	  SYMBOL_CLASS (sym) = LOC_STATIC;
1531	  SYMBOL_VALUE_ADDRESS (sym) = (CORE_ADDR) cs->c_value;
1532	  SYMBOL_VALUE_ADDRESS (sym) += ANOFFSET (objfile->section_offsets, SECT_OFF_TEXT (objfile));
1533	  if (within_function)
1534	    {
1535	      /* Static symbol of local scope */
1536	      add_symbol_to_list (sym, &local_symbols);
1537	    }
1538	  else
1539	    {
1540	      /* Static symbol at top level of file */
1541	      add_symbol_to_list (sym, &file_symbols);
1542	    }
1543	  break;
1544
1545#ifdef C_GLBLREG		/* AMD coff */
1546	case C_GLBLREG:
1547#endif
1548	case C_REG:
1549	  SYMBOL_CLASS (sym) = LOC_REGISTER;
1550	  SYMBOL_VALUE (sym) = SDB_REG_TO_REGNUM (cs->c_value);
1551	  add_symbol_to_list (sym, &local_symbols);
1552	  break;
1553
1554	case C_THUMBLABEL:
1555	case C_LABEL:
1556	  break;
1557
1558	case C_ARG:
1559	  SYMBOL_CLASS (sym) = LOC_ARG;
1560	  add_symbol_to_list (sym, &local_symbols);
1561#if !defined (BELIEVE_PCC_PROMOTION)
1562	  if (TARGET_BYTE_ORDER == BFD_ENDIAN_BIG)
1563	    {
1564	      /* If PCC says a parameter is a short or a char,
1565	         aligned on an int boundary, realign it to the
1566	         "little end" of the int.  */
1567	      struct type *temptype;
1568	      temptype = lookup_fundamental_type (current_objfile,
1569						  FT_INTEGER);
1570	      if (TYPE_LENGTH (SYMBOL_TYPE (sym)) < TYPE_LENGTH (temptype)
1571		  && TYPE_CODE (SYMBOL_TYPE (sym)) == TYPE_CODE_INT
1572		  && 0 == SYMBOL_VALUE (sym) % TYPE_LENGTH (temptype))
1573		{
1574		  SYMBOL_VALUE (sym) +=
1575		    TYPE_LENGTH (temptype)
1576		    - TYPE_LENGTH (SYMBOL_TYPE (sym));
1577		}
1578	    }
1579#endif
1580	  break;
1581
1582	case C_REGPARM:
1583	  SYMBOL_CLASS (sym) = LOC_REGPARM;
1584	  SYMBOL_VALUE (sym) = SDB_REG_TO_REGNUM (cs->c_value);
1585	  add_symbol_to_list (sym, &local_symbols);
1586#if !defined (BELIEVE_PCC_PROMOTION)
1587	  /* FIXME:  This should retain the current type, since it's just
1588	     a register value.  gnu@adobe, 26Feb93 */
1589	  {
1590	    /* If PCC says a parameter is a short or a char,
1591	       it is really an int.  */
1592	    struct type *temptype;
1593	    temptype =
1594	      lookup_fundamental_type (current_objfile, FT_INTEGER);
1595	    if (TYPE_LENGTH (SYMBOL_TYPE (sym)) < TYPE_LENGTH (temptype)
1596		&& TYPE_CODE (SYMBOL_TYPE (sym)) == TYPE_CODE_INT)
1597	      {
1598		SYMBOL_TYPE (sym) =
1599		  (TYPE_UNSIGNED (SYMBOL_TYPE (sym))
1600		   ? lookup_fundamental_type (current_objfile,
1601					      FT_UNSIGNED_INTEGER)
1602		   : temptype);
1603	      }
1604	  }
1605#endif
1606	  break;
1607
1608	case C_TPDEF:
1609	  SYMBOL_CLASS (sym) = LOC_TYPEDEF;
1610	  SYMBOL_DOMAIN (sym) = VAR_DOMAIN;
1611
1612	  /* If type has no name, give it one */
1613	  if (TYPE_NAME (SYMBOL_TYPE (sym)) == 0)
1614	    {
1615	      if (TYPE_CODE (SYMBOL_TYPE (sym)) == TYPE_CODE_PTR
1616		  || TYPE_CODE (SYMBOL_TYPE (sym)) == TYPE_CODE_FUNC)
1617		{
1618		  /* If we are giving a name to a type such as "pointer to
1619		     foo" or "function returning foo", we better not set
1620		     the TYPE_NAME.  If the program contains "typedef char
1621		     *caddr_t;", we don't want all variables of type char
1622		     * to print as caddr_t.  This is not just a
1623		     consequence of GDB's type management; CC and GCC (at
1624		     least through version 2.4) both output variables of
1625		     either type char * or caddr_t with the type
1626		     refering to the C_TPDEF symbol for caddr_t.  If a future
1627		     compiler cleans this up it GDB is not ready for it
1628		     yet, but if it becomes ready we somehow need to
1629		     disable this check (without breaking the PCC/GCC2.4
1630		     case).
1631
1632		     Sigh.
1633
1634		     Fortunately, this check seems not to be necessary
1635		     for anything except pointers or functions.  */
1636		  ;
1637		}
1638	      else
1639		TYPE_NAME (SYMBOL_TYPE (sym)) =
1640		  concat (DEPRECATED_SYMBOL_NAME (sym), NULL);
1641	    }
1642
1643	  /* Keep track of any type which points to empty structured type,
1644	     so it can be filled from a definition from another file.  A
1645	     simple forward reference (TYPE_CODE_UNDEF) is not an
1646	     empty structured type, though; the forward references
1647	     work themselves out via the magic of coff_lookup_type.  */
1648	  if (TYPE_CODE (SYMBOL_TYPE (sym)) == TYPE_CODE_PTR &&
1649	      TYPE_LENGTH (TYPE_TARGET_TYPE (SYMBOL_TYPE (sym))) == 0 &&
1650	      TYPE_CODE (TYPE_TARGET_TYPE (SYMBOL_TYPE (sym))) !=
1651	      TYPE_CODE_UNDEF)
1652	    {
1653	      int i = hashname (DEPRECATED_SYMBOL_NAME (sym));
1654
1655	      SYMBOL_VALUE_CHAIN (sym) = opaque_type_chain[i];
1656	      opaque_type_chain[i] = sym;
1657	    }
1658	  add_symbol_to_list (sym, &file_symbols);
1659	  break;
1660
1661	case C_STRTAG:
1662	case C_UNTAG:
1663	case C_ENTAG:
1664	  SYMBOL_CLASS (sym) = LOC_TYPEDEF;
1665	  SYMBOL_DOMAIN (sym) = STRUCT_DOMAIN;
1666
1667	  /* Some compilers try to be helpful by inventing "fake"
1668	     names for anonymous enums, structures, and unions, like
1669	     "~0fake" or ".0fake".  Thanks, but no thanks... */
1670	  if (TYPE_TAG_NAME (SYMBOL_TYPE (sym)) == 0)
1671	    if (DEPRECATED_SYMBOL_NAME (sym) != NULL
1672		&& *DEPRECATED_SYMBOL_NAME (sym) != '~'
1673		&& *DEPRECATED_SYMBOL_NAME (sym) != '.')
1674	      TYPE_TAG_NAME (SYMBOL_TYPE (sym)) =
1675		concat (DEPRECATED_SYMBOL_NAME (sym), NULL);
1676
1677	  add_symbol_to_list (sym, &file_symbols);
1678	  break;
1679
1680	default:
1681	  break;
1682	}
1683    }
1684  return sym;
1685}
1686
1687/* Decode a coff type specifier;  return the type that is meant.  */
1688
1689static struct type *
1690decode_type (struct coff_symbol *cs, unsigned int c_type,
1691	     union internal_auxent *aux)
1692{
1693  struct type *type = 0;
1694  unsigned int new_c_type;
1695
1696  if (c_type & ~N_BTMASK)
1697    {
1698      new_c_type = DECREF (c_type);
1699      if (ISPTR (c_type))
1700	{
1701	  type = decode_type (cs, new_c_type, aux);
1702	  type = lookup_pointer_type (type);
1703	}
1704      else if (ISFCN (c_type))
1705	{
1706	  type = decode_type (cs, new_c_type, aux);
1707	  type = lookup_function_type (type);
1708	}
1709      else if (ISARY (c_type))
1710	{
1711	  int i, n;
1712	  unsigned short *dim;
1713	  struct type *base_type, *index_type, *range_type;
1714
1715	  /* Define an array type.  */
1716	  /* auxent refers to array, not base type */
1717	  if (aux->x_sym.x_tagndx.l == 0)
1718	    cs->c_naux = 0;
1719
1720	  /* shift the indices down */
1721	  dim = &aux->x_sym.x_fcnary.x_ary.x_dimen[0];
1722	  i = 1;
1723	  n = dim[0];
1724	  for (i = 0; *dim && i < DIMNUM - 1; i++, dim++)
1725	    *dim = *(dim + 1);
1726	  *dim = 0;
1727
1728	  base_type = decode_type (cs, new_c_type, aux);
1729	  index_type = lookup_fundamental_type (current_objfile, FT_INTEGER);
1730	  range_type =
1731	    create_range_type ((struct type *) NULL, index_type, 0, n - 1);
1732	  type =
1733	    create_array_type ((struct type *) NULL, base_type, range_type);
1734	}
1735      return type;
1736    }
1737
1738  /* Reference to existing type.  This only occurs with the
1739     struct, union, and enum types.  EPI a29k coff
1740     fakes us out by producing aux entries with a nonzero
1741     x_tagndx for definitions of structs, unions, and enums, so we
1742     have to check the c_sclass field.  SCO 3.2v4 cc gets confused
1743     with pointers to pointers to defined structs, and generates
1744     negative x_tagndx fields.  */
1745  if (cs->c_naux > 0 && aux->x_sym.x_tagndx.l != 0)
1746    {
1747      if (cs->c_sclass != C_STRTAG
1748	  && cs->c_sclass != C_UNTAG
1749	  && cs->c_sclass != C_ENTAG
1750	  && aux->x_sym.x_tagndx.l >= 0)
1751	{
1752	  type = coff_alloc_type (aux->x_sym.x_tagndx.l);
1753	  return type;
1754	}
1755      else
1756	{
1757	  complaint (&symfile_complaints,
1758		     "Symbol table entry for %s has bad tagndx value",
1759		     cs->c_name);
1760	  /* And fall through to decode_base_type... */
1761	}
1762    }
1763
1764  return decode_base_type (cs, BTYPE (c_type), aux);
1765}
1766
1767/* Decode a coff type specifier for function definition;
1768   return the type that the function returns.  */
1769
1770static struct type *
1771decode_function_type (struct coff_symbol *cs, unsigned int c_type,
1772		      union internal_auxent *aux)
1773{
1774  if (aux->x_sym.x_tagndx.l == 0)
1775    cs->c_naux = 0;		/* auxent refers to function, not base type */
1776
1777  return decode_type (cs, DECREF (c_type), aux);
1778}
1779
1780/* basic C types */
1781
1782static struct type *
1783decode_base_type (struct coff_symbol *cs, unsigned int c_type,
1784		  union internal_auxent *aux)
1785{
1786  struct type *type;
1787
1788  switch (c_type)
1789    {
1790    case T_NULL:
1791      /* shows up with "void (*foo)();" structure members */
1792      return lookup_fundamental_type (current_objfile, FT_VOID);
1793
1794#ifdef T_VOID
1795    case T_VOID:
1796      /* Intel 960 COFF has this symbol and meaning.  */
1797      return lookup_fundamental_type (current_objfile, FT_VOID);
1798#endif
1799
1800    case T_CHAR:
1801      return lookup_fundamental_type (current_objfile, FT_CHAR);
1802
1803    case T_SHORT:
1804      return lookup_fundamental_type (current_objfile, FT_SHORT);
1805
1806    case T_INT:
1807      return lookup_fundamental_type (current_objfile, FT_INTEGER);
1808
1809    case T_LONG:
1810      if (cs->c_sclass == C_FIELD
1811	  && aux->x_sym.x_misc.x_lnsz.x_size > TARGET_LONG_BIT)
1812	return lookup_fundamental_type (current_objfile, FT_LONG_LONG);
1813      else
1814	return lookup_fundamental_type (current_objfile, FT_LONG);
1815
1816    case T_FLOAT:
1817      return lookup_fundamental_type (current_objfile, FT_FLOAT);
1818
1819    case T_DOUBLE:
1820      return lookup_fundamental_type (current_objfile, FT_DBL_PREC_FLOAT);
1821
1822    case T_LNGDBL:
1823      return lookup_fundamental_type (current_objfile, FT_EXT_PREC_FLOAT);
1824
1825    case T_STRUCT:
1826      if (cs->c_naux != 1)
1827	{
1828	  /* anonymous structure type */
1829	  type = coff_alloc_type (cs->c_symnum);
1830	  TYPE_CODE (type) = TYPE_CODE_STRUCT;
1831	  TYPE_NAME (type) = NULL;
1832	  /* This used to set the tag to "<opaque>".  But I think setting it
1833	     to NULL is right, and the printing code can print it as
1834	     "struct {...}".  */
1835	  TYPE_TAG_NAME (type) = NULL;
1836	  INIT_CPLUS_SPECIFIC (type);
1837	  TYPE_LENGTH (type) = 0;
1838	  TYPE_FIELDS (type) = 0;
1839	  TYPE_NFIELDS (type) = 0;
1840	}
1841      else
1842	{
1843	  type = coff_read_struct_type (cs->c_symnum,
1844					aux->x_sym.x_misc.x_lnsz.x_size,
1845				      aux->x_sym.x_fcnary.x_fcn.x_endndx.l);
1846	}
1847      return type;
1848
1849    case T_UNION:
1850      if (cs->c_naux != 1)
1851	{
1852	  /* anonymous union type */
1853	  type = coff_alloc_type (cs->c_symnum);
1854	  TYPE_NAME (type) = NULL;
1855	  /* This used to set the tag to "<opaque>".  But I think setting it
1856	     to NULL is right, and the printing code can print it as
1857	     "union {...}".  */
1858	  TYPE_TAG_NAME (type) = NULL;
1859	  INIT_CPLUS_SPECIFIC (type);
1860	  TYPE_LENGTH (type) = 0;
1861	  TYPE_FIELDS (type) = 0;
1862	  TYPE_NFIELDS (type) = 0;
1863	}
1864      else
1865	{
1866	  type = coff_read_struct_type (cs->c_symnum,
1867					aux->x_sym.x_misc.x_lnsz.x_size,
1868				      aux->x_sym.x_fcnary.x_fcn.x_endndx.l);
1869	}
1870      TYPE_CODE (type) = TYPE_CODE_UNION;
1871      return type;
1872
1873    case T_ENUM:
1874      if (cs->c_naux != 1)
1875	{
1876	  /* anonymous enum type */
1877	  type = coff_alloc_type (cs->c_symnum);
1878	  TYPE_CODE (type) = TYPE_CODE_ENUM;
1879	  TYPE_NAME (type) = NULL;
1880	  /* This used to set the tag to "<opaque>".  But I think setting it
1881	     to NULL is right, and the printing code can print it as
1882	     "enum {...}".  */
1883	  TYPE_TAG_NAME (type) = NULL;
1884	  TYPE_LENGTH (type) = 0;
1885	  TYPE_FIELDS (type) = 0;
1886	  TYPE_NFIELDS (type) = 0;
1887	}
1888      else
1889	{
1890	  type = coff_read_enum_type (cs->c_symnum,
1891				      aux->x_sym.x_misc.x_lnsz.x_size,
1892				      aux->x_sym.x_fcnary.x_fcn.x_endndx.l);
1893	}
1894      return type;
1895
1896    case T_MOE:
1897      /* shouldn't show up here */
1898      break;
1899
1900    case T_UCHAR:
1901      return lookup_fundamental_type (current_objfile, FT_UNSIGNED_CHAR);
1902
1903    case T_USHORT:
1904      return lookup_fundamental_type (current_objfile, FT_UNSIGNED_SHORT);
1905
1906    case T_UINT:
1907      return lookup_fundamental_type (current_objfile, FT_UNSIGNED_INTEGER);
1908
1909    case T_ULONG:
1910      if (cs->c_sclass == C_FIELD
1911	  && aux->x_sym.x_misc.x_lnsz.x_size > TARGET_LONG_BIT)
1912	return lookup_fundamental_type (current_objfile, FT_UNSIGNED_LONG_LONG);
1913      else
1914	return lookup_fundamental_type (current_objfile, FT_UNSIGNED_LONG);
1915    }
1916  complaint (&symfile_complaints, "Unexpected type for symbol %s", cs->c_name);
1917  return lookup_fundamental_type (current_objfile, FT_VOID);
1918}
1919
1920/* This page contains subroutines of read_type.  */
1921
1922/* Read the description of a structure (or union type) and return an
1923   object describing the type.  */
1924
1925static struct type *
1926coff_read_struct_type (int index, int length, int lastsym)
1927{
1928  struct nextfield
1929    {
1930      struct nextfield *next;
1931      struct field field;
1932    };
1933
1934  struct type *type;
1935  struct nextfield *list = 0;
1936  struct nextfield *new;
1937  int nfields = 0;
1938  int n;
1939  char *name;
1940  struct coff_symbol member_sym;
1941  struct coff_symbol *ms = &member_sym;
1942  struct internal_syment sub_sym;
1943  union internal_auxent sub_aux;
1944  int done = 0;
1945
1946  type = coff_alloc_type (index);
1947  TYPE_CODE (type) = TYPE_CODE_STRUCT;
1948  INIT_CPLUS_SPECIFIC (type);
1949  TYPE_LENGTH (type) = length;
1950
1951  while (!done && symnum < lastsym && symnum < nlist_nsyms_global)
1952    {
1953      read_one_sym (ms, &sub_sym, &sub_aux);
1954      name = ms->c_name;
1955      name = EXTERNAL_NAME (name, current_objfile->obfd);
1956
1957      switch (ms->c_sclass)
1958	{
1959	case C_MOS:
1960	case C_MOU:
1961
1962	  /* Get space to record the next field's data.  */
1963	  new = (struct nextfield *) alloca (sizeof (struct nextfield));
1964	  new->next = list;
1965	  list = new;
1966
1967	  /* Save the data.  */
1968	  list->field.name =
1969	    obsavestring (name,
1970			  strlen (name),
1971			  &current_objfile->objfile_obstack);
1972	  FIELD_TYPE (list->field) = decode_type (ms, ms->c_type, &sub_aux);
1973	  FIELD_BITPOS (list->field) = 8 * ms->c_value;
1974	  FIELD_BITSIZE (list->field) = 0;
1975	  FIELD_STATIC_KIND (list->field) = 0;
1976	  nfields++;
1977	  break;
1978
1979	case C_FIELD:
1980
1981	  /* Get space to record the next field's data.  */
1982	  new = (struct nextfield *) alloca (sizeof (struct nextfield));
1983	  new->next = list;
1984	  list = new;
1985
1986	  /* Save the data.  */
1987	  list->field.name =
1988	    obsavestring (name,
1989			  strlen (name),
1990			  &current_objfile->objfile_obstack);
1991	  FIELD_TYPE (list->field) = decode_type (ms, ms->c_type, &sub_aux);
1992	  FIELD_BITPOS (list->field) = ms->c_value;
1993	  FIELD_BITSIZE (list->field) = sub_aux.x_sym.x_misc.x_lnsz.x_size;
1994	  FIELD_STATIC_KIND (list->field) = 0;
1995	  nfields++;
1996	  break;
1997
1998	case C_EOS:
1999	  done = 1;
2000	  break;
2001	}
2002    }
2003  /* Now create the vector of fields, and record how big it is.  */
2004
2005  TYPE_NFIELDS (type) = nfields;
2006  TYPE_FIELDS (type) = (struct field *)
2007    TYPE_ALLOC (type, sizeof (struct field) * nfields);
2008
2009  /* Copy the saved-up fields into the field vector.  */
2010
2011  for (n = nfields; list; list = list->next)
2012    TYPE_FIELD (type, --n) = list->field;
2013
2014  return type;
2015}
2016
2017/* Read a definition of an enumeration type,
2018   and create and return a suitable type object.
2019   Also defines the symbols that represent the values of the type.  */
2020
2021static struct type *
2022coff_read_enum_type (int index, int length, int lastsym)
2023{
2024  struct symbol *sym;
2025  struct type *type;
2026  int nsyms = 0;
2027  int done = 0;
2028  struct pending **symlist;
2029  struct coff_symbol member_sym;
2030  struct coff_symbol *ms = &member_sym;
2031  struct internal_syment sub_sym;
2032  union internal_auxent sub_aux;
2033  struct pending *osyms, *syms;
2034  int o_nsyms;
2035  int n;
2036  char *name;
2037  int unsigned_enum = 1;
2038
2039  type = coff_alloc_type (index);
2040  if (within_function)
2041    symlist = &local_symbols;
2042  else
2043    symlist = &file_symbols;
2044  osyms = *symlist;
2045  o_nsyms = osyms ? osyms->nsyms : 0;
2046
2047  while (!done && symnum < lastsym && symnum < nlist_nsyms_global)
2048    {
2049      read_one_sym (ms, &sub_sym, &sub_aux);
2050      name = ms->c_name;
2051      name = EXTERNAL_NAME (name, current_objfile->obfd);
2052
2053      switch (ms->c_sclass)
2054	{
2055	case C_MOE:
2056	  sym = (struct symbol *) obstack_alloc
2057	    (&current_objfile->objfile_obstack,
2058	     sizeof (struct symbol));
2059	  memset (sym, 0, sizeof (struct symbol));
2060
2061	  DEPRECATED_SYMBOL_NAME (sym) =
2062	    obsavestring (name, strlen (name),
2063			  &current_objfile->objfile_obstack);
2064	  SYMBOL_CLASS (sym) = LOC_CONST;
2065	  SYMBOL_DOMAIN (sym) = VAR_DOMAIN;
2066	  SYMBOL_VALUE (sym) = ms->c_value;
2067	  add_symbol_to_list (sym, symlist);
2068	  nsyms++;
2069	  break;
2070
2071	case C_EOS:
2072	  /* Sometimes the linker (on 386/ix 2.0.2 at least) screws
2073	     up the count of how many symbols to read.  So stop
2074	     on .eos.  */
2075	  done = 1;
2076	  break;
2077	}
2078    }
2079
2080  /* Now fill in the fields of the type-structure.  */
2081
2082  if (length > 0)
2083    TYPE_LENGTH (type) = length;
2084  else
2085    TYPE_LENGTH (type) = TARGET_INT_BIT / TARGET_CHAR_BIT;	/* Assume ints */
2086  TYPE_CODE (type) = TYPE_CODE_ENUM;
2087  TYPE_NFIELDS (type) = nsyms;
2088  TYPE_FIELDS (type) = (struct field *)
2089    TYPE_ALLOC (type, sizeof (struct field) * nsyms);
2090
2091  /* Find the symbols for the values and put them into the type.
2092     The symbols can be found in the symlist that we put them on
2093     to cause them to be defined.  osyms contains the old value
2094     of that symlist; everything up to there was defined by us.  */
2095  /* Note that we preserve the order of the enum constants, so
2096     that in something like "enum {FOO, LAST_THING=FOO}" we print
2097     FOO, not LAST_THING.  */
2098
2099  for (syms = *symlist, n = 0; syms; syms = syms->next)
2100    {
2101      int j = 0;
2102
2103      if (syms == osyms)
2104	j = o_nsyms;
2105      for (; j < syms->nsyms; j++, n++)
2106	{
2107	  struct symbol *xsym = syms->symbol[j];
2108	  SYMBOL_TYPE (xsym) = type;
2109	  TYPE_FIELD_NAME (type, n) = DEPRECATED_SYMBOL_NAME (xsym);
2110	  TYPE_FIELD_BITPOS (type, n) = SYMBOL_VALUE (xsym);
2111	  if (SYMBOL_VALUE (xsym) < 0)
2112	    unsigned_enum = 0;
2113	  TYPE_FIELD_BITSIZE (type, n) = 0;
2114	  TYPE_FIELD_STATIC_KIND (type, n) = 0;
2115	}
2116      if (syms == osyms)
2117	break;
2118    }
2119
2120  if (unsigned_enum)
2121    TYPE_FLAGS (type) |= TYPE_FLAG_UNSIGNED;
2122
2123  return type;
2124}
2125
2126/* Register our ability to parse symbols for coff BFD files. */
2127
2128static struct sym_fns coff_sym_fns =
2129{
2130  bfd_target_coff_flavour,
2131  coff_new_init,		/* sym_new_init: init anything gbl to entire symtab */
2132  coff_symfile_init,		/* sym_init: read initial info, setup for sym_read() */
2133  coff_symfile_read,		/* sym_read: read a symbol file into symtab */
2134  coff_symfile_finish,		/* sym_finish: finished with file, cleanup */
2135  default_symfile_offsets,	/* sym_offsets:  xlate external to internal form */
2136  NULL				/* next: pointer to next struct sym_fns */
2137};
2138
2139void
2140_initialize_coffread (void)
2141{
2142  add_symtab_fns (&coff_sym_fns);
2143}
2144