1 /* DWARF debugging format support for GDB.
2 Copyright (C) 1991 Free Software Foundation, Inc.
3 Written by Fred Fish at Cygnus Support, portions based on dbxread.c,
4 mipsread.c, coffread.c, and dwarfread.c from a Data General SVR4 gdb port.
6 This file is part of GDB.
8 This program is free software; you can redistribute it and/or modify
9 it under the terms of the GNU General Public License as published by
10 the Free Software Foundation; either version 2 of the License, or
11 (at your option) any later version.
13 This program is distributed in the hope that it will be useful,
14 but WITHOUT ANY WARRANTY; without even the implied warranty of
15 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
16 GNU General Public License for more details.
18 You should have received a copy of the GNU General Public License
19 along with this program; if not, write to the Free Software
20 Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. */
24 FIXME: Figure out how to get the frame pointer register number in the
25 execution environment of the target. Remove R_FP kludge
27 FIXME: Add generation of dependencies list to partial symtab code.
29 FIXME: Currently we ignore host/target byte ordering and integer size
30 differences. Should remap data from external form to an internal form
31 before trying to use it.
33 FIXME: Resolve minor differences between what information we put in the
34 partial symbol table and what dbxread puts in. For example, we don't yet
35 put enum constants there. And dbxread seems to invent a lot of typedefs
36 we never see. Use the new printpsym command to see the partial symbol table
39 FIXME: Change forward declarations of static functions to allow for compilers
42 FIXME: Figure out a better way to tell gdb (all the debug reading routines)
43 the names of the gccX_compiled flags.
45 FIXME: Figure out a better way to tell gdb about the name of the function
46 contain the user's entry point (I.E. main())
48 FIXME: The current DWARF specification has a very strong bias towards
49 machines with 32-bit integers, as it assumes that many attributes of the
50 program (such as an address) will fit in such an integer. There are many
51 references in the spec to things that are 2, 4, or 8 bytes long. Given that
52 we will probably run into problems on machines where some of these assumptions
53 are invalid (64-bit ints for example), we don't bother at this time to try to
54 make this code more flexible and just use shorts, ints, and longs (and their
55 sizes) where it seems appropriate. I.E. we use a short int to hold DWARF
56 tags, and assume that the tag size in the file is the same as sizeof(short).
58 FIXME: Figure out how to get the name of the symbol indicating that a module
59 has been compiled with gcc (gcc_compiledXX) in a more portable way than
60 hardcoding it into the object file readers.
62 FIXME: See other FIXME's and "ifdef 0" scattered throughout the code for
63 other things to work on, if you get bored. :-)
79 #ifdef MAINTENANCE /* Define to 1 to compile in some maintenance stuff */
80 #define SQUAWK(stuff) dwarfwarn stuff
85 #ifndef R_FP /* FIXME */
86 #define R_FP 14 /* Kludge to get frame pointer register number */
89 typedef unsigned int DIEREF; /* Reference to a DIE */
91 #define GCC_COMPILED_FLAG_SYMBOL "gcc_compiled%" /* FIXME */
92 #define GCC2_COMPILED_FLAG_SYMBOL "gcc2_compiled%" /* FIXME */
94 #define STREQ(a,b) (strcmp(a,b)==0)
96 extern CORE_ADDR startup_file_start; /* From blockframe.c */
97 extern CORE_ADDR startup_file_end; /* From blockframe.c */
98 extern CORE_ADDR entry_scope_lowpc; /* From blockframe.c */
99 extern CORE_ADDR entry_scope_highpc; /* From blockframc.c */
100 extern CORE_ADDR main_scope_lowpc; /* From blockframe.c */
101 extern CORE_ADDR main_scope_highpc; /* From blockframc.c */
102 extern int info_verbose; /* From main.c; nonzero => verbose */
105 /* The DWARF debugging information consists of two major pieces,
106 one is a block of DWARF Information Entries (DIE's) and the other
107 is a line number table. The "struct dieinfo" structure contains
108 the information for a single DIE, the one currently being processed.
110 In order to make it easier to randomly access the attribute fields
111 of the current DIE, which are specifically unordered within the DIE
112 each DIE is scanned and an instance of the "struct dieinfo"
113 structure is initialized.
115 Initialization is done in two levels. The first, done by basicdieinfo(),
116 just initializes those fields that are vital to deciding whether or not
117 to use this DIE, how to skip past it, etc. The second, done by the
118 function completedieinfo(), fills in the rest of the information.
120 Attributes which have block forms are not interpreted at the time
121 the DIE is scanned, instead we just save pointers to the start
122 of their value fields.
124 Some fields have a flag <name>_p that is set when the value of the
125 field is valid (I.E. we found a matching attribute in the DIE). Since
126 we may want to test for the presence of some attributes in the DIE,
127 such as AT_is_external, without restricting the values of the field,
128 we need someway to note that we found such an attribute.
135 char * die; /* Pointer to the raw DIE data */
136 long dielength; /* Length of the raw DIE data */
137 DIEREF dieref; /* Offset of this DIE */
138 short dietag; /* Tag for this DIE */
143 unsigned short at_fund_type;
144 BLOCK * at_mod_fund_type;
145 long at_user_def_type;
146 BLOCK * at_mod_u_d_type;
148 BLOCK * at_subscr_data;
152 BLOCK * at_deriv_list;
153 BLOCK * at_element_list;
160 BLOCK * at_discr_value;
163 BLOCK * at_string_length;
173 BLOCK * at_const_data;
174 short at_is_external;
175 unsigned int at_is_external_p:1;
176 unsigned int at_stmt_list_p:1;
179 static int diecount; /* Approximate count of dies for compilation unit */
180 static struct dieinfo *curdie; /* For warnings and such */
182 static char *dbbase; /* Base pointer to dwarf info */
183 static int dbroff; /* Relative offset from start of .debug section */
184 static char *lnbase; /* Base pointer to line section */
185 static int isreg; /* Kludge to identify register variables */
187 static CORE_ADDR baseaddr; /* Add to each symbol value */
189 /* Each partial symbol table entry contains a pointer to private data for the
190 read_symtab() function to use when expanding a partial symbol table entry
191 to a full symbol table entry. For DWARF debugging info, this data is
192 contained in the following structure and macros are provided for easy
193 access to the members given a pointer to a partial symbol table entry.
195 dbfoff Always the absolute file offset to the start of the ".debug"
196 section for the file containing the DIE's being accessed.
198 dbroff Relative offset from the start of the ".debug" access to the
199 first DIE to be accessed. When building the partial symbol
200 table, this value will be zero since we are accessing the
201 entire ".debug" section. When expanding a partial symbol
202 table entry, this value will be the offset to the first
203 DIE for the compilation unit containing the symbol that
204 triggers the expansion.
206 dblength The size of the chunk of DIE's being examined, in bytes.
208 lnfoff The absolute file offset to the line table fragment. Ignored
209 when building partial symbol tables, but used when expanding
210 them, and contains the absolute file offset to the fragment
211 of the ".line" section containing the line numbers for the
212 current compilation unit.
216 int dbfoff; /* Absolute file offset to start of .debug section */
217 int dbroff; /* Relative offset from start of .debug section */
218 int dblength; /* Size of the chunk of DIE's being examined */
219 int lnfoff; /* Absolute file offset to line table fragment */
222 #define DBFOFF(p) (((struct dwfinfo *)((p)->read_symtab_private))->dbfoff)
223 #define DBROFF(p) (((struct dwfinfo *)((p)->read_symtab_private))->dbroff)
224 #define DBLENGTH(p) (((struct dwfinfo *)((p)->read_symtab_private))->dblength)
225 #define LNFOFF(p) (((struct dwfinfo *)((p)->read_symtab_private))->lnfoff)
227 /* Record the symbols defined for each context in a linked list. We don't
228 create a struct block for the context until we know how long to make it.
229 Global symbols for each file are maintained in the global_symbols list. */
231 struct pending_symbol {
232 struct pending_symbol *next; /* Next pending symbol */
233 struct symbol *symbol; /* The actual symbol */
236 static struct pending_symbol *global_symbols; /* global funcs and vars */
237 static struct block *global_symbol_block;
239 /* Line number entries are read into a dynamically expandable vector before
240 being added to the symbol table section. Once we know how many there are
243 static struct linetable *line_vector; /* Vector of line numbers. */
244 static int line_vector_index; /* Index of next entry. */
245 static int line_vector_length; /* Current allocation limit */
247 /* Scope information is kept in a scope tree, one node per scope. Each time
248 a new scope is started, a child node is created under the current node
249 and set to the current scope. Each time a scope is closed, the current
250 scope moves back up the tree to the parent of the current scope.
252 Each scope contains a pointer to the list of symbols defined in the scope,
253 a pointer to the block vector for the scope, a pointer to the symbol
254 that names the scope (if any), and the range of PC values that mark
255 the start and end of the scope. */
258 struct scopenode *parent;
259 struct scopenode *child;
260 struct scopenode *sibling;
261 struct pending_symbol *symbols;
263 struct symbol *namesym;
268 static struct scopenode *scopetree;
269 static struct scopenode *scope;
271 /* DIES which have user defined types or modified user defined types refer to
272 other DIES for the type information. Thus we need to associate the offset
273 of a DIE for a user defined type with a pointer to the type information.
275 Originally this was done using a simple but expensive algorithm, with an
276 array of unsorted structures, each containing an offset/type-pointer pair.
277 This array was scanned linearly each time a lookup was done. The result
278 was that gdb was spending over half it's startup time munging through this
279 array of pointers looking for a structure that had the right offset member.
281 The second attempt used the same array of structures, but the array was
282 sorted using qsort each time a new offset/type was recorded, and a binary
283 search was used to find the type pointer for a given DIE offset. This was
284 even slower, due to the overhead of sorting the array each time a new
285 offset/type pair was entered.
287 The third attempt uses a fixed size array of type pointers, indexed by a
288 value derived from the DIE offset. Since the minimum DIE size is 4 bytes,
289 we can divide any DIE offset by 4 to obtain a unique index into this fixed
290 size array. Since each element is a 4 byte pointer, it takes exactly as
291 much memory to hold this array as to hold the DWARF info for a given
292 compilation unit. But it gets freed as soon as we are done with it. */
294 static struct type **utypes; /* Pointer to array of user type pointers */
295 static int numutypes; /* Max number of user type pointers */
297 /* Forward declarations of static functions so we don't have to worry
298 about ordering within this file. The EXFUN macro may be slightly
299 misleading. Should probably be called DCLFUN instead, or something
300 more intuitive, since it can be used for both static and external
303 static void dwarfwarn (); /* EXFUN breaks with <varargs.h> (FIXME)*/
306 EXFUN (scan_partial_symbols, (char *thisdie AND char *enddie));
309 EXFUN (scan_compilation_units,
310 (char *filename AND CORE_ADDR addr AND char *thisdie AND char *enddie
311 AND unsigned int dbfoff AND unsigned int lnoffset
312 AND struct objfile *objfile));
314 static struct partial_symtab *
315 EXFUN(start_psymtab, (struct objfile *objfile AND CORE_ADDR addr
316 AND char *filename AND CORE_ADDR textlow
317 AND CORE_ADDR texthigh AND int dbfoff
318 AND int curoff AND int culength AND int lnfoff
319 AND struct partial_symbol *global_syms
320 AND struct partial_symbol *static_syms));
322 EXFUN(add_partial_symbol, (struct dieinfo *dip));
325 EXFUN(add_psymbol_to_list,
326 (struct psymbol_allocation_list *listp AND char *name
327 AND enum namespace space AND enum address_class class
328 AND CORE_ADDR value));
331 EXFUN(init_psymbol_list, (int total_symbols));
334 EXFUN(basicdieinfo, (struct dieinfo *dip AND char *diep));
337 EXFUN(completedieinfo, (struct dieinfo *dip));
340 EXFUN(dwarf_psymtab_to_symtab, (struct partial_symtab *pst));
343 EXFUN(psymtab_to_symtab_1, (struct partial_symtab *pst));
345 static struct symtab *
346 EXFUN(read_ofile_symtab, (struct partial_symtab *pst));
350 (char *thisdie AND char *enddie AND struct objfile *objfile));
353 EXFUN(read_structure_scope,
354 (struct dieinfo *dip AND char *thisdie AND char *enddie));
357 EXFUN(decode_array_element_type, (char *scan AND char *end));
360 EXFUN(decode_subscr_data, (char *scan AND char *end));
363 EXFUN(read_array_type, (struct dieinfo *dip));
366 EXFUN(read_subroutine_type,
367 (struct dieinfo *dip AND char *thisdie AND char *enddie));
370 EXFUN(read_enumeration,
371 (struct dieinfo *dip AND char *thisdie AND char *enddie));
375 (struct dieinfo *dip AND char *thisdie AND char *enddie));
378 EXFUN(enum_type, (struct dieinfo *dip));
381 EXFUN(start_symtab, (void));
385 (char *filename AND long language AND struct objfile *objfile));
388 EXFUN(scopecount, (struct scopenode *node));
392 (struct symbol *namesym AND CORE_ADDR lowpc AND CORE_ADDR highpc));
395 EXFUN(freescope, (struct scopenode *node));
397 static struct block *
398 EXFUN(buildblock, (struct pending_symbol *syms));
401 EXFUN(closescope, (void));
404 EXFUN(record_line, (int line AND CORE_ADDR pc));
407 EXFUN(decode_line_numbers, (char *linetable));
410 EXFUN(decode_die_type, (struct dieinfo *dip));
413 EXFUN(decode_mod_fund_type, (char *typedata));
416 EXFUN(decode_mod_u_d_type, (char *typedata));
419 EXFUN(decode_modified_type,
420 (unsigned char *modifiers AND unsigned short modcount AND int mtype));
423 EXFUN(decode_fund_type, (unsigned short fundtype));
426 EXFUN(create_name, (char *name AND struct obstack *obstackp));
429 EXFUN(add_symbol_to_list,
430 (struct symbol *symbol AND struct pending_symbol **listhead));
432 static struct block **
433 EXFUN(gatherblocks, (struct block **dest AND struct scopenode *node));
435 static struct blockvector *
436 EXFUN(make_blockvector, (void));
439 EXFUN(lookup_utype, (DIEREF dieref));
442 EXFUN(alloc_utype, (DIEREF dieref AND struct type *usetype));
444 static struct symbol *
445 EXFUN(new_symbol, (struct dieinfo *dip));
448 EXFUN(locval, (char *loc));
451 EXFUN(record_misc_function, (char *name AND CORE_ADDR address));
454 EXFUN(compare_psymbols,
455 (struct partial_symbol *s1 AND struct partial_symbol *s2));
462 dwarf_build_psymtabs -- build partial symtabs from DWARF debug info
466 void dwarf_build_psymtabs (int desc, char *filename, CORE_ADDR addr,
467 int mainline, unsigned int dbfoff, unsigned int dbsize,
468 unsigned int lnoffset, unsigned int lnsize,
469 struct objfile *objfile)
473 This function is called upon to build partial symtabs from files
474 containing DIE's (Dwarf Information Entries) and DWARF line numbers.
476 It is passed a file descriptor for an open file containing the DIES
477 and line number information, the corresponding filename for that
478 file, a base address for relocating the symbols, a flag indicating
479 whether or not this debugging information is from a "main symbol
480 table" rather than a shared library or dynamically linked file,
481 and file offset/size pairs for the DIE information and line number
491 DEFUN(dwarf_build_psymtabs,
492 (desc, filename, addr, mainline, dbfoff, dbsize, lnoffset, lnsize,
498 unsigned int dbfoff AND
499 unsigned int dbsize AND
500 unsigned int lnoffset AND
501 unsigned int lnsize AND
502 struct objfile *objfile)
504 struct cleanup *back_to;
506 dbbase = xmalloc (dbsize);
508 if ((lseek (desc, dbfoff, 0) != dbfoff) ||
509 (read (desc, dbbase, dbsize) != dbsize))
512 error ("can't read DWARF data from '%s'", filename);
514 back_to = make_cleanup (free, dbbase);
516 /* If we are reinitializing, or if we have never loaded syms yet, init.
517 Since we have no idea how many DIES we are looking at, we just guess
518 some arbitrary value. */
520 if (mainline || global_psymbols.size == 0 || static_psymbols.size == 0)
522 init_psymbol_list (1024);
525 init_misc_bunches ();
526 make_cleanup (discard_misc_bunches, 0);
528 /* Follow the compilation unit sibling chain, building a partial symbol
529 table entry for each one. Save enough information about each compilation
530 unit to locate the full DWARF information later. */
532 scan_compilation_units (filename, addr, dbbase, dbbase + dbsize,
533 dbfoff, lnoffset, objfile);
535 /* Go over the miscellaneous functions and install them in the miscellaneous
538 condense_misc_bunches (!mainline);
539 do_cleanups (back_to);
547 record_misc_function -- add entry to miscellaneous function vector
551 static void record_misc_function (char *name, CORE_ADDR address)
555 Given a pointer to the name of a symbol that should be added to the
556 miscellaneous function vector, and the address associated with that
557 symbol, records this information for later use in building the
558 miscellaneous function vector.
562 FIXME: For now we just use mf_text as the type. This should be
567 DEFUN(record_misc_function, (name, address), char *name AND CORE_ADDR address)
569 prim_record_misc_function (obsavestring (name, strlen (name)), address,
577 dwarfwarn -- issue a DWARF related warning
581 Issue warnings about DWARF related things that aren't serious enough
582 to warrant aborting with an error, but should not be ignored either.
583 This includes things like detectable corruption in DIE's, missing
584 DIE's, unimplemented features, etc.
586 In general, running across tags or attributes that we don't recognize
587 is not considered to be a problem and we should not issue warnings
592 We mostly follow the example of the error() routine, but without
593 returning to command level. It is arguable about whether warnings
594 should be issued at all, and if so, where they should go (stdout or
597 We assume that curdie is valid and contains at least the basic
598 information for the DIE where the problem was noticed.
609 fmt = va_arg (ap, char *);
611 fprintf (stderr, "DWARF warning (ref 0x%x): ", curdie -> dieref);
612 if (curdie -> at_name)
614 fprintf (stderr, "'%s': ", curdie -> at_name);
616 vfprintf (stderr, fmt, ap);
617 fprintf (stderr, "\n");
626 compare_psymbols -- compare two partial symbols by name
630 Given pointer to two partial symbol table entries, compare
631 them by name and return -N, 0, or +N (ala strcmp). Typically
632 used by sorting routines like qsort().
636 This is a copy from dbxread.c. It should be moved to a generic
637 gdb file and made available for all psymtab builders (FIXME).
639 Does direct compare of first two characters before punting
640 and passing to strcmp for longer compares. Note that the
641 original version had a bug whereby two null strings or two
642 identically named one character strings would return the
643 comparison of memory following the null byte.
648 DEFUN(compare_psymbols, (s1, s2),
649 struct partial_symbol *s1 AND
650 struct partial_symbol *s2)
652 register char *st1 = SYMBOL_NAME (s1);
653 register char *st2 = SYMBOL_NAME (s2);
655 if ((st1[0] - st2[0]) || !st1[0])
657 return (st1[0] - st2[0]);
659 else if ((st1[1] - st2[1]) || !st1[1])
661 return (st1[1] - st2[1]);
665 return (strcmp (st1 + 2, st2 + 2));
673 read_lexical_block_scope -- process all dies in a lexical block
677 static void read_lexical_block_scope (struct dieinfo *dip,
678 char *thisdie, char *enddie)
682 Process all the DIES contained within a lexical block scope.
683 Start a new scope, process the dies, and then close the scope.
688 DEFUN(read_lexical_block_scope, (dip, thisdie, enddie, objfile),
689 struct dieinfo *dip AND
692 struct objfile *objfile)
694 openscope (NULL, dip -> at_low_pc, dip -> at_high_pc);
695 process_dies (thisdie + dip -> dielength, enddie, objfile);
703 lookup_utype -- look up a user defined type from die reference
707 static type *lookup_utype (DIEREF dieref)
711 Given a DIE reference, lookup the user defined type associated with
712 that DIE, if it has been registered already. If not registered, then
713 return NULL. Alloc_utype() can be called to register an empty
714 type for this reference, which will be filled in later when the
715 actual referenced DIE is processed.
719 DEFUN(lookup_utype, (dieref), DIEREF dieref)
721 struct type *type = NULL;
724 utypeidx = (dieref - dbroff) / 4;
725 if ((utypeidx < 0) || (utypeidx >= numutypes))
727 dwarfwarn ("reference to DIE (0x%x) outside compilation unit", dieref);
731 type = *(utypes + utypeidx);
741 alloc_utype -- add a user defined type for die reference
745 static type *alloc_utype (DIEREF dieref, struct type *utypep)
749 Given a die reference DIEREF, and a possible pointer to a user
750 defined type UTYPEP, register that this reference has a user
751 defined type and either use the specified type in UTYPEP or
752 make a new empty type that will be filled in later.
754 We should only be called after calling lookup_utype() to verify that
755 there is not currently a type registered for DIEREF.
759 DEFUN(alloc_utype, (dieref, utypep),
766 utypeidx = (dieref - dbroff) / 4;
767 typep = utypes + utypeidx;
768 if ((utypeidx < 0) || (utypeidx >= numutypes))
770 utypep = builtin_type_int;
771 dwarfwarn ("reference to DIE (0x%x) outside compilation unit", dieref);
773 else if (*typep != NULL)
776 SQUAWK (("internal error: dup user type allocation"));
782 utypep = (struct type *)
783 obstack_alloc (symbol_obstack, sizeof (struct type));
784 (void) memset (utypep, 0, sizeof (struct type));
795 decode_die_type -- return a type for a specified die
799 static struct type *decode_die_type (struct dieinfo *dip)
803 Given a pointer to a die information structure DIP, decode the
804 type of the die and return a pointer to the decoded type. All
805 dies without specific types default to type int.
809 DEFUN(decode_die_type, (dip), struct dieinfo *dip)
811 struct type *type = NULL;
813 if (dip -> at_fund_type != 0)
815 type = decode_fund_type (dip -> at_fund_type);
817 else if (dip -> at_mod_fund_type != NULL)
819 type = decode_mod_fund_type (dip -> at_mod_fund_type);
821 else if (dip -> at_user_def_type)
823 if ((type = lookup_utype (dip -> at_user_def_type)) == NULL)
825 type = alloc_utype (dip -> at_user_def_type, NULL);
828 else if (dip -> at_mod_u_d_type)
830 type = decode_mod_u_d_type (dip -> at_mod_u_d_type);
834 type = builtin_type_int;
843 struct_type -- compute and return the type for a struct or union
847 static struct type *struct_type (struct dieinfo *dip, char *thisdie,
852 Given pointer to a die information structure for a die which
853 defines a union or structure, and pointers to the raw die data
854 that define the range of dies which define the members, compute
855 and return the user defined type for the structure or union.
859 DEFUN(struct_type, (dip, thisdie, enddie),
860 struct dieinfo *dip AND
866 struct nextfield *next;
869 struct nextfield *list = NULL;
870 struct nextfield *new;
878 if ((type = lookup_utype (dip -> dieref)) == NULL)
880 type = alloc_utype (dip -> dieref, NULL);
882 switch (dip -> dietag)
884 case TAG_structure_type:
885 TYPE_CODE (type) = TYPE_CODE_STRUCT;
889 TYPE_CODE (type) = TYPE_CODE_UNION;
894 SQUAWK (("missing structure or union tag"));
895 TYPE_CODE (type) = TYPE_CODE_UNDEF;
898 if (dip -> at_name == NULL)
904 tpart2 = dip -> at_name;
906 if (dip -> at_byte_size == 0)
908 tpart3 = " <opaque>";
910 TYPE_LENGTH (type) = dip -> at_byte_size;
913 TYPE_NAME (type) = concat (tpart1, tpart2, tpart3, NULL);
914 thisdie += dip -> dielength;
915 while (thisdie < enddie)
917 basicdieinfo (&mbr, thisdie);
918 completedieinfo (&mbr);
919 if (mbr.dielength <= sizeof (long))
926 /* Get space to record the next field's data. */
927 new = (struct nextfield *) alloca (sizeof (struct nextfield));
931 list -> field.name = savestring (mbr.at_name, strlen (mbr.at_name));
932 list -> field.type = decode_die_type (&mbr);
933 list -> field.bitpos = 8 * locval (mbr.at_location);
934 list -> field.bitsize = 0;
938 SQUAWK (("bad member of '%s'", TYPE_NAME (type)));
941 thisdie += mbr.dielength;
943 /* Now create the vector of fields, and record how big it is. */
944 TYPE_NFIELDS (type) = nfields;
945 TYPE_FIELDS (type) = (struct field *)
946 obstack_alloc (symbol_obstack, sizeof (struct field) * nfields);
947 /* Copy the saved-up fields into the field vector. */
948 for (n = nfields; list; list = list -> next)
950 TYPE_FIELD (type, --n) = list -> field;
959 read_structure_scope -- process all dies within struct or union
963 static void read_structure_scope (struct dieinfo *dip,
964 char *thisdie, char *enddie)
968 Called when we find the DIE that starts a structure or union
969 scope (definition) to process all dies that define the members
970 of the structure or union. DIP is a pointer to the die info
971 struct for the DIE that names the structure or union.
975 Note that we need to call struct_type regardless of whether or not
976 we have a symbol, since we might have a structure or union without
977 a tag name (thus no symbol for the tagname).
981 DEFUN(read_structure_scope, (dip, thisdie, enddie),
982 struct dieinfo *dip AND
989 type = struct_type (dip, thisdie, enddie);
990 if ((sym = new_symbol (dip)) != NULL)
992 SYMBOL_TYPE (sym) = type;
1000 decode_array_element_type -- decode type of the array elements
1004 static struct type *decode_array_element_type (char *scan, char *end)
1008 As the last step in decoding the array subscript information for an
1009 array DIE, we need to decode the type of the array elements. We are
1010 passed a pointer to this last part of the subscript information and
1011 must return the appropriate type. If the type attribute is not
1012 recognized, just warn about the problem and return type int.
1015 static struct type *
1016 DEFUN(decode_array_element_type, (scan, end), char *scan AND char *end)
1021 unsigned short fundtype;
1023 (void) memcpy (&attribute, scan, sizeof (short));
1024 scan += sizeof (short);
1028 (void) memcpy (&fundtype, scan, sizeof (short));
1029 typep = decode_fund_type (fundtype);
1031 case AT_mod_fund_type:
1032 typep = decode_mod_fund_type (scan);
1034 case AT_user_def_type:
1035 (void) memcpy (&dieref, scan, sizeof (DIEREF));
1036 if ((typep = lookup_utype (dieref)) == NULL)
1038 typep = alloc_utype (dieref, NULL);
1041 case AT_mod_u_d_type:
1042 typep = decode_mod_u_d_type (scan);
1045 SQUAWK (("bad array element type attribute 0x%x", attribute));
1046 typep = builtin_type_int;
1056 decode_subscr_data -- decode array subscript and element type data
1060 static struct type *decode_subscr_data (char *scan, char *end)
1064 The array subscripts and the data type of the elements of an
1065 array are described by a list of data items, stored as a block
1066 of contiguous bytes. There is a data item describing each array
1067 dimension, and a final data item describing the element type.
1068 The data items are ordered the same as their appearance in the
1069 source (I.E. leftmost dimension first, next to leftmost second,
1072 We are passed a pointer to the start of the block of bytes
1073 containing the data items, and a pointer to the first byte past
1074 the data. This function decodes the data and returns a type.
1077 FIXME: This code only implements the forms currently used
1078 by the AT&T and GNU C compilers.
1080 The end pointer is supplied for error checking, maybe we should
1084 static struct type *
1085 DEFUN(decode_subscr_data, (scan, end), char *scan AND char *end)
1087 struct type *typep = NULL;
1088 struct type *nexttype;
1098 typep = decode_array_element_type (scan, end);
1101 (void) memcpy (&fundtype, scan, sizeof (short));
1102 scan += sizeof (short);
1103 if (fundtype != FT_integer && fundtype != FT_signed_integer
1104 && fundtype != FT_unsigned_integer)
1106 SQUAWK (("array subscripts must be integral types, not type 0x%x",
1111 (void) memcpy (&lowbound, scan, sizeof (long));
1112 scan += sizeof (long);
1113 (void) memcpy (&highbound, scan, sizeof (long));
1114 scan += sizeof (long);
1115 nexttype = decode_subscr_data (scan, end);
1116 if (nexttype != NULL)
1118 typep = (struct type *)
1119 obstack_alloc (symbol_obstack, sizeof (struct type));
1120 (void) memset (typep, 0, sizeof (struct type));
1121 TYPE_CODE (typep) = TYPE_CODE_ARRAY;
1122 TYPE_LENGTH (typep) = TYPE_LENGTH (nexttype);
1123 TYPE_LENGTH (typep) *= lowbound + highbound + 1;
1124 TYPE_TARGET_TYPE (typep) = nexttype;
1135 SQUAWK (("array subscript format 0x%x not handled yet", format));
1138 SQUAWK (("unknown array subscript format %x", format));
1148 read_array_type -- read TAG_array_type DIE
1152 static void read_array_type (struct dieinfo *dip)
1156 Extract all information from a TAG_array_type DIE and add to
1157 the user defined type vector.
1161 DEFUN(read_array_type, (dip), struct dieinfo *dip)
1168 if (dip -> at_ordering != ORD_row_major)
1170 /* FIXME: Can gdb even handle column major arrays? */
1171 SQUAWK (("array not row major; not handled correctly"));
1173 if ((sub = dip -> at_subscr_data) != NULL)
1175 (void) memcpy (&temp, sub, sizeof (short));
1176 subend = sub + sizeof (short) + temp;
1177 sub += sizeof (short);
1178 type = decode_subscr_data (sub, subend);
1181 type = alloc_utype (dip -> dieref, NULL);
1182 TYPE_CODE (type) = TYPE_CODE_ARRAY;
1183 TYPE_TARGET_TYPE (type) = builtin_type_int;
1184 TYPE_LENGTH (type) = 1 * TYPE_LENGTH (TYPE_TARGET_TYPE (type));
1188 type = alloc_utype (dip -> dieref, type);
1197 read_subroutine_type -- process TAG_subroutine_type dies
1201 static void read_subroutine_type (struct dieinfo *dip, char thisdie,
1206 Handle DIES due to C code like:
1209 int (*funcp)(int a, long l); (Generates TAG_subroutine_type DIE)
1215 The parameter DIES are currently ignored. See if gdb has a way to
1216 include this info in it's type system, and decode them if so. Is
1217 this what the type structure's "arg_types" field is for? (FIXME)
1221 DEFUN(read_subroutine_type, (dip, thisdie, enddie),
1222 struct dieinfo *dip AND
1228 type = decode_die_type (dip);
1229 type = lookup_function_type (type);
1230 type = alloc_utype (dip -> dieref, type);
1237 read_enumeration -- process dies which define an enumeration
1241 static void read_enumeration (struct dieinfo *dip, char *thisdie,
1246 Given a pointer to a die which begins an enumeration, process all
1247 the dies that define the members of the enumeration.
1251 Note that we need to call enum_type regardless of whether or not we
1252 have a symbol, since we might have an enum without a tag name (thus
1253 no symbol for the tagname).
1257 DEFUN(read_enumeration, (dip, thisdie, enddie),
1258 struct dieinfo *dip AND
1265 type = enum_type (dip);
1266 if ((sym = new_symbol (dip)) != NULL)
1268 SYMBOL_TYPE (sym) = type;
1276 enum_type -- decode and return a type for an enumeration
1280 static type *enum_type (struct dieinfo *dip)
1284 Given a pointer to a die information structure for the die which
1285 starts an enumeration, process all the dies that define the members
1286 of the enumeration and return a type pointer for the enumeration.
1289 static struct type *
1290 DEFUN(enum_type, (dip), struct dieinfo *dip)
1294 struct nextfield *next;
1297 struct nextfield *list = NULL;
1298 struct nextfield *new;
1308 if ((type = lookup_utype (dip -> dieref)) == NULL)
1310 type = alloc_utype (dip -> dieref, NULL);
1312 TYPE_CODE (type) = TYPE_CODE_ENUM;
1314 if (dip -> at_name == NULL)
1318 tpart2 = dip -> at_name;
1320 if (dip -> at_byte_size == 0)
1322 tpart3 = " <opaque>";
1326 TYPE_LENGTH (type) = dip -> at_byte_size;
1329 TYPE_NAME (type) = concat (tpart1, tpart2, tpart3, NULL);
1330 if ((scan = dip -> at_element_list) != NULL)
1332 (void) memcpy (&temp, scan, sizeof (temp));
1333 listend = scan + temp + sizeof (temp);
1334 scan += sizeof (temp);
1335 while (scan < listend)
1337 new = (struct nextfield *) alloca (sizeof (struct nextfield));
1340 list -> field.type = NULL;
1341 list -> field.bitsize = 0;
1342 (void) memcpy (&list -> field.bitpos, scan, sizeof (long));
1343 scan += sizeof (long);
1344 list -> field.name = savestring (scan, strlen (scan));
1345 scan += strlen (scan) + 1;
1349 /* Now create the vector of fields, and record how big it is. */
1350 TYPE_NFIELDS (type) = nfields;
1351 TYPE_FIELDS (type) = (struct field *)
1352 obstack_alloc (symbol_obstack, sizeof (struct field) * nfields);
1353 /* Copy the saved-up fields into the field vector. */
1354 for (n = nfields; list; list = list -> next)
1356 TYPE_FIELD (type, --n) = list -> field;
1365 read_func_scope -- process all dies within a function scope
1369 Process all dies within a given function scope. We are passed
1370 a die information structure pointer DIP for the die which
1371 starts the function scope, and pointers into the raw die data
1372 that define the dies within the function scope.
1374 For now, we ignore lexical block scopes within the function.
1375 The problem is that AT&T cc does not define a DWARF lexical
1376 block scope for the function itself, while gcc defines a
1377 lexical block scope for the function. We need to think about
1378 how to handle this difference, or if it is even a problem.
1383 DEFUN(read_func_scope, (dip, thisdie, enddie, objfile),
1384 struct dieinfo *dip AND
1387 struct objfile *objfile)
1391 if (entry_point >= dip -> at_low_pc && entry_point < dip -> at_high_pc)
1393 entry_scope_lowpc = dip -> at_low_pc;
1394 entry_scope_highpc = dip -> at_high_pc;
1396 if (strcmp (dip -> at_name, "main") == 0) /* FIXME: hardwired name */
1398 main_scope_lowpc = dip -> at_low_pc;
1399 main_scope_highpc = dip -> at_high_pc;
1401 sym = new_symbol (dip);
1402 openscope (sym, dip -> at_low_pc, dip -> at_high_pc);
1403 process_dies (thisdie + dip -> dielength, enddie, objfile);
1411 read_file_scope -- process all dies within a file scope
1415 Process all dies within a given file scope. We are passed a
1416 pointer to the die information structure for the die which
1417 starts the file scope, and pointers into the raw die data which
1418 mark the range of dies within the file scope.
1420 When the partial symbol table is built, the file offset for the line
1421 number table for each compilation unit is saved in the partial symbol
1422 table entry for that compilation unit. As the symbols for each
1423 compilation unit are read, the line number table is read into memory
1424 and the variable lnbase is set to point to it. Thus all we have to
1425 do is use lnbase to access the line number table for the current
1430 DEFUN(read_file_scope, (dip, thisdie, enddie, objfile),
1431 struct dieinfo *dip AND
1434 struct objfile *objfile)
1436 struct cleanup *back_to;
1438 if (entry_point >= dip -> at_low_pc && entry_point < dip -> at_high_pc)
1440 startup_file_start = dip -> at_low_pc;
1441 startup_file_end = dip -> at_high_pc;
1443 numutypes = (enddie - thisdie) / 4;
1444 utypes = (struct type **) xmalloc (numutypes * sizeof (struct type *));
1445 back_to = make_cleanup (free, utypes);
1446 (void) memset (utypes, 0, numutypes * sizeof (struct type *));
1448 openscope (NULL, dip -> at_low_pc, dip -> at_high_pc);
1449 decode_line_numbers (lnbase);
1450 process_dies (thisdie + dip -> dielength, enddie, objfile);
1452 end_symtab (dip -> at_name, dip -> at_language, objfile);
1453 do_cleanups (back_to);
1462 start_symtab -- do initialization for starting new symbol table
1466 static void start_symtab (void)
1470 Called whenever we are starting to process dies for a new
1471 compilation unit, to perform initializations. Right now
1472 the only thing we really have to do is initialize storage
1473 space for the line number vector.
1478 DEFUN_VOID (start_symtab)
1482 line_vector_index = 0;
1483 line_vector_length = 1000;
1484 nbytes = sizeof (struct linetable);
1485 nbytes += line_vector_length * sizeof (struct linetable_entry);
1486 line_vector = (struct linetable *) xmalloc (nbytes);
1493 process_dies -- process a range of DWARF Information Entries
1497 static void process_dies (char *thisdie, char *enddie)
1501 Process all DIE's in a specified range. May be (and almost
1502 certainly will be) called recursively.
1506 DEFUN(process_dies, (thisdie, enddie, objfile),
1507 char *thisdie AND char *enddie AND struct objfile *objfile)
1512 while (thisdie < enddie)
1514 basicdieinfo (&di, thisdie);
1515 if (di.dielength < sizeof (long))
1519 else if (di.dietag == TAG_padding)
1521 nextdie = thisdie + di.dielength;
1525 completedieinfo (&di);
1526 if (di.at_sibling != 0)
1528 nextdie = dbbase + di.at_sibling - dbroff;
1532 nextdie = thisdie + di.dielength;
1536 case TAG_compile_unit:
1537 read_file_scope (&di, thisdie, nextdie, objfile);
1539 case TAG_global_subroutine:
1540 case TAG_subroutine:
1541 if (!di.at_is_external_p)
1543 read_func_scope (&di, thisdie, nextdie, objfile);
1546 case TAG_lexical_block:
1547 read_lexical_block_scope (&di, thisdie, nextdie, objfile);
1549 case TAG_structure_type:
1550 case TAG_union_type:
1551 read_structure_scope (&di, thisdie, nextdie);
1553 case TAG_enumeration_type:
1554 read_enumeration (&di, thisdie, nextdie);
1556 case TAG_subroutine_type:
1557 read_subroutine_type (&di, thisdie, nextdie);
1559 case TAG_array_type:
1560 read_array_type (&di);
1563 (void) new_symbol (&di);
1575 end_symtab -- finish processing for a compilation unit
1579 static void end_symtab (char *filename, long language)
1583 Complete the symbol table entry for the current compilation
1584 unit. Make the struct symtab and put it on the list of all
1590 DEFUN(end_symtab, (filename, language, objfile),
1591 char *filename AND long language AND struct objfile *objfile)
1593 struct symtab *symtab;
1594 struct blockvector *blockvector;
1597 /* Ignore a file that has no functions with real debugging info. */
1598 if (global_symbols == NULL && scopetree -> block == NULL)
1602 line_vector_length = -1;
1603 freescope (scopetree);
1604 scope = scopetree = NULL;
1607 /* Create the blockvector that points to all the file's blocks. */
1609 blockvector = make_blockvector ();
1611 /* Now create the symtab object for this source file. */
1613 symtab = allocate_symtab (savestring (filename, strlen (filename)),
1616 symtab -> free_ptr = 0;
1618 /* Fill in its components. */
1619 symtab -> blockvector = blockvector;
1620 symtab -> free_code = free_linetable;
1622 /* Save the line number information. */
1624 line_vector -> nitems = line_vector_index;
1625 nbytes = sizeof (struct linetable);
1626 if (line_vector_index > 1)
1628 nbytes += (line_vector_index - 1) * sizeof (struct linetable_entry);
1630 symtab -> linetable = (struct linetable *) xrealloc (line_vector, nbytes);
1632 /* FIXME: The following may need to be expanded for other languages */
1637 symtab -> language = language_c;
1639 case LANG_C_PLUS_PLUS:
1640 symtab -> language = language_cplus;
1646 /* Link the new symtab into the list of such. */
1647 symtab -> next = symtab_list;
1648 symtab_list = symtab;
1650 /* Recursively free the scope tree */
1651 freescope (scopetree);
1652 scope = scopetree = NULL;
1654 /* Reinitialize for beginning of new file. */
1656 line_vector_length = -1;
1663 scopecount -- count the number of enclosed scopes
1667 static int scopecount (struct scopenode *node)
1671 Given pointer to a node, compute the size of the subtree which is
1672 rooted in this node, which also happens to be the number of scopes
1677 DEFUN(scopecount, (node), struct scopenode *node)
1683 count += scopecount (node -> child);
1684 count += scopecount (node -> sibling);
1694 openscope -- start a new lexical block scope
1698 static void openscope (struct symbol *namesym, CORE_ADDR lowpc,
1703 Start a new scope by allocating a new scopenode, adding it as the
1704 next child of the current scope (if any) or as the root of the
1705 scope tree, and then making the new node the current scope node.
1709 DEFUN(openscope, (namesym, lowpc, highpc),
1710 struct symbol *namesym AND
1714 struct scopenode *new;
1715 struct scopenode *child;
1717 new = (struct scopenode *) xmalloc (sizeof (*new));
1718 (void) memset (new, 0, sizeof (*new));
1719 new -> namesym = namesym;
1720 new -> lowpc = lowpc;
1721 new -> highpc = highpc;
1726 else if ((child = scope -> child) == NULL)
1728 scope -> child = new;
1729 new -> parent = scope;
1733 while (child -> sibling != NULL)
1735 child = child -> sibling;
1737 child -> sibling = new;
1738 new -> parent = scope;
1747 freescope -- free a scope tree rooted at the given node
1751 static void freescope (struct scopenode *node)
1755 Given a pointer to a node in the scope tree, free the subtree
1756 rooted at that node. First free all the children and sibling
1757 nodes, and then the node itself. Used primarily for cleaning
1758 up after ourselves and returning memory to the system.
1762 DEFUN(freescope, (node), struct scopenode *node)
1766 freescope (node -> child);
1767 freescope (node -> sibling);
1776 buildblock -- build a new block from pending symbols list
1780 static struct block *buildblock (struct pending_symbol *syms)
1784 Given a pointer to a list of symbols, build a new block and free
1785 the symbol list structure. Also check each symbol to see if it
1786 is the special symbol that flags that this block was compiled by
1787 gcc, and if so, mark the block appropriately.
1790 static struct block *
1791 DEFUN(buildblock, (syms), struct pending_symbol *syms)
1793 struct pending_symbol *next, *next1;
1795 struct block *newblock;
1798 for (next = syms, i = 0 ; next ; next = next -> next, i++) {;}
1800 /* Allocate a new block */
1802 nbytes = sizeof (struct block);
1805 nbytes += (i - 1) * sizeof (struct symbol *);
1807 newblock = (struct block *) obstack_alloc (symbol_obstack, nbytes);
1808 (void) memset (newblock, 0, nbytes);
1810 /* Copy the symbols into the block. */
1812 BLOCK_NSYMS (newblock) = i;
1813 for (next = syms ; next ; next = next -> next)
1815 BLOCK_SYM (newblock, --i) = next -> symbol;
1816 if (STREQ (GCC_COMPILED_FLAG_SYMBOL, SYMBOL_NAME (next -> symbol)) ||
1817 STREQ (GCC2_COMPILED_FLAG_SYMBOL, SYMBOL_NAME (next -> symbol)))
1819 BLOCK_GCC_COMPILED (newblock) = 1;
1823 /* Now free the links of the list, and empty the list. */
1825 for (next = syms ; next ; next = next1)
1827 next1 = next -> next;
1838 closescope -- close a lexical block scope
1842 static void closescope (void)
1846 Close the current lexical block scope. Closing the current scope
1847 is as simple as moving the current scope pointer up to the parent
1848 of the current scope pointer. But we also take this opportunity
1849 to build the block for the current scope first, since we now have
1850 all of it's symbols.
1854 DEFUN_VOID(closescope)
1856 struct scopenode *child;
1860 error ("DWARF parse error, too many close scopes");
1864 if (scope -> parent == NULL)
1866 global_symbol_block = buildblock (global_symbols);
1867 global_symbols = NULL;
1868 BLOCK_START (global_symbol_block) = scope -> lowpc + baseaddr;
1869 BLOCK_END (global_symbol_block) = scope -> highpc + baseaddr;
1871 scope -> block = buildblock (scope -> symbols);
1872 scope -> symbols = NULL;
1873 BLOCK_START (scope -> block) = scope -> lowpc + baseaddr;
1874 BLOCK_END (scope -> block) = scope -> highpc + baseaddr;
1876 /* Put the local block in as the value of the symbol that names it. */
1878 if (scope -> namesym)
1880 SYMBOL_BLOCK_VALUE (scope -> namesym) = scope -> block;
1881 BLOCK_FUNCTION (scope -> block) = scope -> namesym;
1884 /* Install this scope's local block as the superblock of all child
1887 for (child = scope -> child ; child ; child = child -> sibling)
1889 BLOCK_SUPERBLOCK (child -> block) = scope -> block;
1892 scope = scope -> parent;
1900 record_line -- record a line number entry in the line vector
1904 static void record_line (int line, CORE_ADDR pc)
1908 Given a line number and the corresponding pc value, record
1909 this pair in the line number vector, expanding the vector as
1914 DEFUN(record_line, (line, pc), int line AND CORE_ADDR pc)
1916 struct linetable_entry *e;
1919 /* Make sure line vector is big enough. */
1921 if (line_vector_index + 2 >= line_vector_length)
1923 line_vector_length *= 2;
1924 nbytes = sizeof (struct linetable);
1925 nbytes += (line_vector_length * sizeof (struct linetable_entry));
1926 line_vector = (struct linetable *) xrealloc (line_vector, nbytes);
1928 e = line_vector -> item + line_vector_index++;
1937 decode_line_numbers -- decode a line number table fragment
1941 static void decode_line_numbers (char *tblscan, char *tblend,
1942 long length, long base, long line, long pc)
1946 Translate the DWARF line number information to gdb form.
1948 The ".line" section contains one or more line number tables, one for
1949 each ".line" section from the objects that were linked.
1951 The AT_stmt_list attribute for each TAG_source_file entry in the
1952 ".debug" section contains the offset into the ".line" section for the
1953 start of the table for that file.
1955 The table itself has the following structure:
1957 <table length><base address><source statement entry>
1958 4 bytes 4 bytes 10 bytes
1960 The table length is the total size of the table, including the 4 bytes
1961 for the length information.
1963 The base address is the address of the first instruction generated
1964 for the source file.
1966 Each source statement entry has the following structure:
1968 <line number><statement position><address delta>
1969 4 bytes 2 bytes 4 bytes
1971 The line number is relative to the start of the file, starting with
1974 The statement position either -1 (0xFFFF) or the number of characters
1975 from the beginning of the line to the beginning of the statement.
1977 The address delta is the difference between the base address and
1978 the address of the first instruction for the statement.
1980 Note that we must copy the bytes from the packed table to our local
1981 variables before attempting to use them, to avoid alignment problems
1982 on some machines, particularly RISC processors.
1986 Does gdb expect the line numbers to be sorted? They are now by
1987 chance/luck, but are not required to be. (FIXME)
1989 The line with number 0 is unused, gdb apparently can discover the
1990 span of the last line some other way. How? (FIXME)
1994 DEFUN(decode_line_numbers, (linetable), char *linetable)
2003 if (linetable != NULL)
2005 tblscan = tblend = linetable;
2006 (void) memcpy (&length, tblscan, sizeof (long));
2007 tblscan += sizeof (long);
2009 (void) memcpy (&base, tblscan, sizeof (long));
2011 tblscan += sizeof (long);
2012 while (tblscan < tblend)
2014 (void) memcpy (&line, tblscan, sizeof (long));
2015 tblscan += sizeof (long) + sizeof (short);
2016 (void) memcpy (&pc, tblscan, sizeof (long));
2017 tblscan += sizeof (long);
2021 record_line (line, pc);
2031 add_symbol_to_list -- add a symbol to head of current symbol list
2035 static void add_symbol_to_list (struct symbol *symbol, struct
2036 pending_symbol **listhead)
2040 Given a pointer to a symbol and a pointer to a pointer to a
2041 list of symbols, add this symbol as the current head of the
2042 list. Typically used for example to add a symbol to the
2043 symbol list for the current scope.
2048 DEFUN(add_symbol_to_list, (symbol, listhead),
2049 struct symbol *symbol AND struct pending_symbol **listhead)
2051 struct pending_symbol *link;
2055 link = (struct pending_symbol *) xmalloc (sizeof (*link));
2056 link -> next = *listhead;
2057 link -> symbol = symbol;
2066 gatherblocks -- walk a scope tree and build block vectors
2070 static struct block **gatherblocks (struct block **dest,
2071 struct scopenode *node)
2075 Recursively walk a scope tree rooted in the given node, adding blocks
2076 to the array pointed to by DEST, in preorder. I.E., first we add the
2077 block for the current scope, then all the blocks for child scopes,
2078 and finally all the blocks for sibling scopes.
2081 static struct block **
2082 DEFUN(gatherblocks, (dest, node),
2083 struct block **dest AND struct scopenode *node)
2087 *dest++ = node -> block;
2088 dest = gatherblocks (dest, node -> child);
2089 dest = gatherblocks (dest, node -> sibling);
2098 make_blockvector -- make a block vector from current scope tree
2102 static struct blockvector *make_blockvector (void)
2106 Make a blockvector from all the blocks in the current scope tree.
2107 The first block is always the global symbol block, followed by the
2108 block for the root of the scope tree which is the local symbol block,
2109 followed by all the remaining blocks in the scope tree, which are all
2114 Note that since the root node of the scope tree is created at the time
2115 each file scope is entered, there are always at least two blocks,
2116 neither of which may have any symbols, but always contribute a block
2117 to the block vector. So the test for number of blocks greater than 1
2118 below is unnecessary given bug free code.
2120 The resulting block structure varies slightly from that produced
2121 by dbxread.c, in that block 0 and block 1 are sibling blocks while
2122 with dbxread.c, block 1 is a child of block 0. This does not
2123 seem to cause any problems, but probably should be fixed. (FIXME)
2126 static struct blockvector *
2127 DEFUN_VOID(make_blockvector)
2129 struct blockvector *blockvector = NULL;
2133 /* Recursively walk down the tree, counting the number of blocks.
2134 Then add one to account for the global's symbol block */
2136 i = scopecount (scopetree) + 1;
2137 nbytes = sizeof (struct blockvector);
2140 nbytes += (i - 1) * sizeof (struct block *);
2142 blockvector = (struct blockvector *)
2143 obstack_alloc (symbol_obstack, nbytes);
2145 /* Copy the blocks into the blockvector. */
2147 BLOCKVECTOR_NBLOCKS (blockvector) = i;
2148 BLOCKVECTOR_BLOCK (blockvector, 0) = global_symbol_block;
2149 gatherblocks (&BLOCKVECTOR_BLOCK (blockvector, 1), scopetree);
2151 return (blockvector);
2158 locval -- compute the value of a location attribute
2162 static int locval (char *loc)
2166 Given pointer to a string of bytes that define a location, compute
2167 the location and return the value.
2169 When computing values involving the current value of the frame pointer,
2170 the value zero is used, which results in a value relative to the frame
2171 pointer, rather than the absolute value. This is what GDB wants
2174 When the result is a register number, the global isreg flag is set,
2175 otherwise it is cleared. This is a kludge until we figure out a better
2176 way to handle the problem. Gdb's design does not mesh well with the
2177 DWARF notion of a location computing interpreter, which is a shame
2178 because the flexibility goes unused.
2182 Note that stack[0] is unused except as a default error return.
2183 Note that stack overflow is not yet handled.
2187 DEFUN(locval, (loc), char *loc)
2189 unsigned short nbytes;
2195 (void) memcpy (&nbytes, loc, sizeof (short));
2196 end = loc + sizeof (short) + nbytes;
2200 for (loc += sizeof (short); loc < end; loc += sizeof (long))
2208 /* push register (number) */
2209 (void) memcpy (&stack[++stacki], loc, sizeof (long));
2213 /* push value of register (number) */
2214 /* Actually, we compute the value as if register has 0 */
2215 (void) memcpy (®no, loc, sizeof (long));
2218 stack[++stacki] = 0;
2222 stack[++stacki] = 0;
2223 SQUAWK (("BASEREG %d not handled!", regno));
2227 /* push address (relocated address) */
2228 (void) memcpy (&stack[++stacki], loc, sizeof (long));
2231 /* push constant (number) */
2232 (void) memcpy (&stack[++stacki], loc, sizeof (long));
2235 /* pop, deref and push 2 bytes (as a long) */
2236 SQUAWK (("OP_DEREF2 address %#x not handled", stack[stacki]));
2238 case OP_DEREF4: /* pop, deref and push 4 bytes (as a long) */
2239 SQUAWK (("OP_DEREF4 address %#x not handled", stack[stacki]));
2241 case OP_ADD: /* pop top 2 items, add, push result */
2242 stack[stacki - 1] += stack[stacki];
2247 return (stack[stacki]);
2254 read_ofile_symtab -- build a full symtab entry from chunk of DIE's
2258 static struct symtab *read_ofile_symtab (struct partial_symtab *pst)
2262 OFFSET is a relocation offset which gets added to each symbol (FIXME).
2265 static struct symtab *
2266 DEFUN(read_ofile_symtab, (pst),
2267 struct partial_symtab *pst)
2269 struct cleanup *back_to;
2272 bfd *abfd = pst->objfile->obfd;
2274 /* Allocate a buffer for the entire chunk of DIE's for this compilation
2275 unit, seek to the location in the file, and read in all the DIE's. */
2278 dbbase = xmalloc (DBLENGTH(pst));
2279 dbroff = DBROFF(pst);
2280 foffset = DBFOFF(pst) + dbroff;
2281 if (bfd_seek (abfd, foffset, 0) ||
2282 (bfd_read (dbbase, DBLENGTH(pst), 1, abfd) != DBLENGTH(pst)))
2285 error ("can't read DWARF data");
2287 back_to = make_cleanup (free, dbbase);
2289 /* If there is a line number table associated with this compilation unit
2290 then read the first long word from the line number table fragment, which
2291 contains the size of the fragment in bytes (including the long word
2292 itself). Allocate a buffer for the fragment and read it in for future
2298 if (bfd_seek (abfd, LNFOFF (pst), 0) ||
2299 (bfd_read (&lnsize, sizeof(long), 1, abfd) != sizeof(long)))
2301 error ("can't read DWARF line number table size");
2303 lnbase = xmalloc (lnsize);
2304 if (bfd_seek (abfd, LNFOFF (pst), 0) ||
2305 (bfd_read (lnbase, lnsize, 1, abfd) != lnsize))
2308 error ("can't read DWARF line numbers");
2310 make_cleanup (free, lnbase);
2313 process_dies (dbbase, dbbase + DBLENGTH(pst), pst->objfile);
2314 do_cleanups (back_to);
2315 return (symtab_list);
2322 psymtab_to_symtab_1 -- do grunt work for building a full symtab entry
2326 static void psymtab_to_symtab_1 (struct partial_symtab *pst)
2330 Called once for each partial symbol table entry that needs to be
2331 expanded into a full symbol table entry.
2336 DEFUN(psymtab_to_symtab_1,
2338 struct partial_symtab *pst)
2348 fprintf (stderr, "Psymtab for %s already read in. Shouldn't happen.\n",
2353 /* Read in all partial symtabs on which this one is dependent */
2354 for (i = 0; i < pst -> number_of_dependencies; i++)
2355 if (!pst -> dependencies[i] -> readin)
2357 /* Inform about additional files that need to be read in. */
2360 fputs_filtered (" ", stdout);
2362 fputs_filtered ("and ", stdout);
2364 printf_filtered ("%s...", pst -> dependencies[i] -> filename);
2365 wrap_here (""); /* Flush output */
2368 psymtab_to_symtab_1 (pst -> dependencies[i]);
2371 if (DBLENGTH(pst)) /* Otherwise it's a dummy */
2373 /* Init stuff necessary for reading in symbols */
2374 pst -> symtab = read_ofile_symtab (pst);
2377 printf_filtered ("%d DIE's, sorting...", diecount);
2380 sort_symtab_syms (pst -> symtab);
2389 dwarf_psymtab_to_symtab -- build a full symtab entry from partial one
2393 static void dwarf_psymtab_to_symtab (struct partial_symtab *pst)
2397 This is the DWARF support entry point for building a full symbol
2398 table entry from a partial symbol table entry. We are passed a
2399 pointer to the partial symbol table entry that needs to be expanded.
2404 DEFUN(dwarf_psymtab_to_symtab, (pst), struct partial_symtab *pst)
2415 fprintf (stderr, "Psymtab for %s already read in. Shouldn't happen.\n",
2420 if (DBLENGTH(pst) || pst -> number_of_dependencies)
2422 /* Print the message now, before starting serious work, to avoid
2423 disconcerting pauses. */
2426 printf_filtered ("Reading in symbols for %s...", pst -> filename);
2430 psymtab_to_symtab_1 (pst);
2432 #if 0 /* FIXME: Check to see what dbxread is doing here and see if
2433 we need to do an equivalent or is this something peculiar to
2434 stabs/a.out format. */
2435 /* Match with global symbols. This only needs to be done once,
2436 after all of the symtabs and dependencies have been read in. */
2437 scan_file_globals ();
2440 /* Finish up the debug error message. */
2443 printf_filtered ("done.\n");
2452 init_psymbol_list -- initialize storage for partial symbols
2456 static void init_psymbol_list (int total_symbols)
2460 Initializes storage for all of the partial symbols that will be
2461 created by dwarf_build_psymtabs and subsidiaries.
2465 DEFUN(init_psymbol_list, (total_symbols), int total_symbols)
2467 /* Free any previously allocated psymbol lists. */
2469 if (global_psymbols.list)
2471 free (global_psymbols.list);
2473 if (static_psymbols.list)
2475 free (static_psymbols.list);
2478 /* Current best guess is that there are approximately a twentieth
2479 of the total symbols (in a debugging file) are global or static
2482 global_psymbols.size = total_symbols / 10;
2483 static_psymbols.size = total_symbols / 10;
2484 global_psymbols.next = global_psymbols.list = (struct partial_symbol *)
2485 xmalloc (global_psymbols.size * sizeof (struct partial_symbol));
2486 static_psymbols.next = static_psymbols.list = (struct partial_symbol *)
2487 xmalloc (static_psymbols.size * sizeof (struct partial_symbol));
2494 start_psymtab -- allocate and partially fill a partial symtab entry
2498 Allocate and partially fill a partial symtab. It will be completely
2499 filled at the end of the symbol list.
2501 SYMFILE_NAME is the name of the symbol-file we are reading from, and
2502 ADDR is the address relative to which its symbols are (incremental)
2503 or 0 (normal). FILENAME is the name of the compilation unit that
2504 these symbols were defined in, and they appear starting a address
2505 TEXTLOW. DBROFF is the absolute file offset in SYMFILE_NAME where
2506 the full symbols can be read for compilation unit FILENAME.
2507 GLOBAL_SYMS and STATIC_SYMS are pointers to the current end of the
2512 static struct partial_symtab *
2513 DEFUN(start_psymtab,
2514 (objfile, addr, filename, textlow, texthigh, dbfoff, curoff,
2515 culength, lnfoff, global_syms, static_syms),
2516 struct objfile *objfile AND
2519 CORE_ADDR textlow AND
2520 CORE_ADDR texthigh AND
2525 struct partial_symbol *global_syms AND
2526 struct partial_symbol *static_syms)
2528 struct partial_symtab *result;
2530 result = (struct partial_symtab *)
2531 obstack_alloc (psymbol_obstack, sizeof (struct partial_symtab));
2532 (void) memset (result, 0, sizeof (struct partial_symtab));
2533 result -> addr = addr;
2534 result -> objfile = objfile;
2535 result -> filename = create_name (filename, psymbol_obstack);
2536 result -> textlow = textlow;
2537 result -> texthigh = texthigh;
2538 result -> read_symtab_private = (char *) obstack_alloc (psymbol_obstack,
2539 sizeof (struct dwfinfo));
2540 DBFOFF (result) = dbfoff;
2541 DBROFF (result) = curoff;
2542 DBLENGTH (result) = culength;
2543 LNFOFF (result) = lnfoff;
2544 result -> readin = 0;
2545 result -> symtab = NULL;
2546 result -> read_symtab = dwarf_psymtab_to_symtab;
2547 result -> globals_offset = global_syms - global_psymbols.list;
2548 result -> statics_offset = static_syms - static_psymbols.list;
2550 result->n_global_syms = 0;
2551 result->n_static_syms = 0;
2560 add_psymbol_to_list -- add a partial symbol to given list
2564 Add a partial symbol to one of the partial symbol vectors (pointed to
2565 by listp). The vector is grown as necessary.
2570 DEFUN(add_psymbol_to_list,
2571 (listp, name, space, class, value),
2572 struct psymbol_allocation_list *listp AND
2574 enum namespace space AND
2575 enum address_class class AND
2578 struct partial_symbol *psym;
2581 if (listp -> next >= listp -> list + listp -> size)
2583 newsize = listp -> size * 2;
2584 listp -> list = (struct partial_symbol *)
2585 xrealloc (listp -> list, (newsize * sizeof (struct partial_symbol)));
2586 /* Next assumes we only went one over. Should be good if program works
2588 listp -> next = listp -> list + listp -> size;
2589 listp -> size = newsize;
2591 psym = listp -> next++;
2592 SYMBOL_NAME (psym) = create_name (name, psymbol_obstack);
2593 SYMBOL_NAMESPACE (psym) = space;
2594 SYMBOL_CLASS (psym) = class;
2595 SYMBOL_VALUE (psym) = value;
2602 add_partial_symbol -- add symbol to partial symbol table
2606 Given a DIE, if it is one of the types that we want to
2607 add to a partial symbol table, finish filling in the die info
2608 and then add a partial symbol table entry for it.
2613 DEFUN(add_partial_symbol, (dip), struct dieinfo *dip)
2615 switch (dip -> dietag)
2617 case TAG_global_subroutine:
2618 record_misc_function (dip -> at_name, dip -> at_low_pc);
2619 add_psymbol_to_list (&global_psymbols, dip -> at_name, VAR_NAMESPACE,
2620 LOC_BLOCK, dip -> at_low_pc);
2622 case TAG_global_variable:
2623 add_psymbol_to_list (&global_psymbols, dip -> at_name, VAR_NAMESPACE,
2626 case TAG_subroutine:
2627 add_psymbol_to_list (&static_psymbols, dip -> at_name, VAR_NAMESPACE,
2628 LOC_BLOCK, dip -> at_low_pc);
2630 case TAG_local_variable:
2631 add_psymbol_to_list (&static_psymbols, dip -> at_name, VAR_NAMESPACE,
2635 add_psymbol_to_list (&static_psymbols, dip -> at_name, VAR_NAMESPACE,
2638 case TAG_structure_type:
2639 case TAG_union_type:
2640 case TAG_enumeration_type:
2641 add_psymbol_to_list (&static_psymbols, dip -> at_name, STRUCT_NAMESPACE,
2651 scan_partial_symbols -- scan DIE's within a single compilation unit
2655 Process the DIE's within a single compilation unit, looking for
2656 interesting DIE's that contribute to the partial symbol table entry
2657 for this compilation unit. Since we cannot follow any sibling
2658 chains without reading the complete DIE info for every DIE,
2659 it is probably faster to just sequentially check each one to
2660 see if it is one of the types we are interested in, and if
2661 so, then extracting all the attributes info and generating a
2662 partial symbol table entry.
2667 DEFUN(scan_partial_symbols, (thisdie, enddie), char *thisdie AND char *enddie)
2672 while (thisdie < enddie)
2674 basicdieinfo (&di, thisdie);
2675 if (di.dielength < sizeof (long))
2681 nextdie = thisdie + di.dielength;
2684 case TAG_global_subroutine:
2685 case TAG_global_variable:
2686 case TAG_subroutine:
2687 case TAG_local_variable:
2689 case TAG_structure_type:
2690 case TAG_union_type:
2691 case TAG_enumeration_type:
2692 completedieinfo (&di);
2693 /* Don't attempt to add anonymous structures, unions, or
2694 enumerations since they have no name. Also check that
2695 this is the place where the actual definition occurs,
2696 rather than just a reference to an external. */
2697 if (di.at_name != NULL && !di.at_is_external_p)
2699 add_partial_symbol (&di);
2712 scan_compilation_units -- build a psymtab entry for each compilation
2716 This is the top level dwarf parsing routine for building partial
2719 It scans from the beginning of the DWARF table looking for the first
2720 TAG_compile_unit DIE, and then follows the sibling chain to locate
2721 each additional TAG_compile_unit DIE.
2723 For each TAG_compile_unit DIE it creates a partial symtab structure,
2724 calls a subordinate routine to collect all the compilation unit's
2725 global DIE's, file scope DIEs, typedef DIEs, etc, and then links the
2726 new partial symtab structure into the partial symbol table. It also
2727 records the appropriate information in the partial symbol table entry
2728 to allow the chunk of DIE's and line number table for this compilation
2729 unit to be located and re-read later, to generate a complete symbol
2730 table entry for the compilation unit.
2732 Thus it effectively partitions up a chunk of DIE's for multiple
2733 compilation units into smaller DIE chunks and line number tables,
2734 and associates them with a partial symbol table entry.
2738 If any compilation unit has no line number table associated with
2739 it for some reason (a missing at_stmt_list attribute, rather than
2740 just one with a value of zero, which is valid) then we ensure that
2741 the recorded file offset is zero so that the routine which later
2742 reads line number table fragments knows that there is no fragment
2752 DEFUN(scan_compilation_units,
2753 (filename, addr, thisdie, enddie, dbfoff, lnoffset, objfile),
2758 unsigned int dbfoff AND
2759 unsigned int lnoffset AND
2760 struct objfile *objfile)
2764 struct partial_symtab *pst;
2769 while (thisdie < enddie)
2771 basicdieinfo (&di, thisdie);
2772 if (di.dielength < sizeof (long))
2776 else if (di.dietag != TAG_compile_unit)
2778 nextdie = thisdie + di.dielength;
2782 completedieinfo (&di);
2783 if (di.at_sibling != 0)
2785 nextdie = dbbase + di.at_sibling - dbroff;
2789 nextdie = thisdie + di.dielength;
2791 curoff = thisdie - dbbase;
2792 culength = nextdie - thisdie;
2793 curlnoffset = di.at_stmt_list_p ? lnoffset + di.at_stmt_list : 0;
2794 pst = start_psymtab (objfile, addr, di.at_name,
2795 di.at_low_pc, di.at_high_pc,
2796 dbfoff, curoff, culength, curlnoffset,
2797 global_psymbols.next,
2798 static_psymbols.next);
2799 scan_partial_symbols (thisdie + di.dielength, nextdie);
2800 pst -> n_global_syms = global_psymbols.next -
2801 (global_psymbols.list + pst -> globals_offset);
2802 pst -> n_static_syms = static_psymbols.next -
2803 (static_psymbols.list + pst -> statics_offset);
2804 /* Sort the global list; don't sort the static list */
2805 qsort (global_psymbols.list + pst -> globals_offset,
2806 pst -> n_global_syms, sizeof (struct partial_symbol),
2808 /* If there is already a psymtab or symtab for a file of this name,
2809 remove it. (If there is a symtab, more drastic things also
2810 happen.) This happens in VxWorks. */
2811 free_named_symtabs (pst -> filename);
2812 /* Place the partial symtab on the partial symtab list */
2813 pst -> next = partial_symtab_list;
2814 partial_symtab_list = pst;
2824 new_symbol -- make a symbol table entry for a new symbol
2828 static struct symbol *new_symbol (struct dieinfo *dip)
2832 Given a pointer to a DWARF information entry, figure out if we need
2833 to make a symbol table entry for it, and if so, create a new entry
2834 and return a pointer to it.
2837 static struct symbol *
2838 DEFUN(new_symbol, (dip), struct dieinfo *dip)
2840 struct symbol *sym = NULL;
2842 if (dip -> at_name != NULL)
2844 sym = (struct symbol *) obstack_alloc (symbol_obstack,
2845 sizeof (struct symbol));
2846 (void) memset (sym, 0, sizeof (struct symbol));
2847 SYMBOL_NAME (sym) = create_name (dip -> at_name, symbol_obstack);
2848 /* default assumptions */
2849 SYMBOL_NAMESPACE (sym) = VAR_NAMESPACE;
2850 SYMBOL_CLASS (sym) = LOC_STATIC;
2851 SYMBOL_TYPE (sym) = decode_die_type (dip);
2852 switch (dip -> dietag)
2855 SYMBOL_VALUE (sym) = dip -> at_low_pc + baseaddr;
2856 SYMBOL_CLASS (sym) = LOC_LABEL;
2858 case TAG_global_subroutine:
2859 case TAG_subroutine:
2860 SYMBOL_VALUE (sym) = dip -> at_low_pc + baseaddr;
2861 SYMBOL_TYPE (sym) = lookup_function_type (SYMBOL_TYPE (sym));
2862 SYMBOL_CLASS (sym) = LOC_BLOCK;
2863 if (dip -> dietag == TAG_global_subroutine)
2865 add_symbol_to_list (sym, &global_symbols);
2869 add_symbol_to_list (sym, &scope -> symbols);
2872 case TAG_global_variable:
2873 case TAG_local_variable:
2874 if (dip -> at_location != NULL)
2876 SYMBOL_VALUE (sym) = locval (dip -> at_location);
2878 if (dip -> dietag == TAG_global_variable)
2880 add_symbol_to_list (sym, &global_symbols);
2881 SYMBOL_CLASS (sym) = LOC_STATIC;
2882 SYMBOL_VALUE (sym) += baseaddr;
2886 add_symbol_to_list (sym, &scope -> symbols);
2887 if (scope -> parent != NULL)
2891 SYMBOL_CLASS (sym) = LOC_REGISTER;
2895 SYMBOL_CLASS (sym) = LOC_LOCAL;
2900 SYMBOL_CLASS (sym) = LOC_STATIC;
2901 SYMBOL_VALUE (sym) += baseaddr;
2905 case TAG_formal_parameter:
2906 if (dip -> at_location != NULL)
2908 SYMBOL_VALUE (sym) = locval (dip -> at_location);
2910 add_symbol_to_list (sym, &scope -> symbols);
2913 SYMBOL_CLASS (sym) = LOC_REGPARM;
2917 SYMBOL_CLASS (sym) = LOC_ARG;
2920 case TAG_unspecified_parameters:
2921 /* From varargs functions; gdb doesn't seem to have any interest in
2922 this information, so just ignore it for now. (FIXME?) */
2924 case TAG_structure_type:
2925 case TAG_union_type:
2926 case TAG_enumeration_type:
2927 SYMBOL_CLASS (sym) = LOC_TYPEDEF;
2928 SYMBOL_NAMESPACE (sym) = STRUCT_NAMESPACE;
2929 add_symbol_to_list (sym, &scope -> symbols);
2932 SYMBOL_CLASS (sym) = LOC_TYPEDEF;
2933 SYMBOL_NAMESPACE (sym) = VAR_NAMESPACE;
2934 add_symbol_to_list (sym, &scope -> symbols);
2937 /* Not a tag we recognize. Hopefully we aren't processing trash
2938 data, but since we must specifically ignore things we don't
2939 recognize, there is nothing else we should do at this point. */
2950 decode_mod_fund_type -- decode a modified fundamental type
2954 static struct type *decode_mod_fund_type (char *typedata)
2958 Decode a block of data containing a modified fundamental
2959 type specification. TYPEDATA is a pointer to the block,
2960 which consists of a two byte length, containing the size
2961 of the rest of the block. At the end of the block is a
2962 two byte value that gives the fundamental type. Everything
2963 in between are type modifiers.
2965 We simply compute the number of modifiers and call the general
2966 function decode_modified_type to do the actual work.
2969 static struct type *
2970 DEFUN(decode_mod_fund_type, (typedata), char *typedata)
2972 struct type *typep = NULL;
2973 unsigned short modcount;
2974 unsigned char *modifiers;
2976 /* Get the total size of the block, exclusive of the size itself */
2977 (void) memcpy (&modcount, typedata, sizeof (short));
2978 /* Deduct the size of the fundamental type bytes at the end of the block. */
2979 modcount -= sizeof (short);
2980 /* Skip over the two size bytes at the beginning of the block. */
2981 modifiers = (unsigned char *) typedata + sizeof (short);
2982 /* Now do the actual decoding */
2983 typep = decode_modified_type (modifiers, modcount, AT_mod_fund_type);
2991 decode_mod_u_d_type -- decode a modified user defined type
2995 static struct type *decode_mod_u_d_type (char *typedata)
2999 Decode a block of data containing a modified user defined
3000 type specification. TYPEDATA is a pointer to the block,
3001 which consists of a two byte length, containing the size
3002 of the rest of the block. At the end of the block is a
3003 four byte value that gives a reference to a user defined type.
3004 Everything in between are type modifiers.
3006 We simply compute the number of modifiers and call the general
3007 function decode_modified_type to do the actual work.
3010 static struct type *
3011 DEFUN(decode_mod_u_d_type, (typedata), char *typedata)
3013 struct type *typep = NULL;
3014 unsigned short modcount;
3015 unsigned char *modifiers;
3017 /* Get the total size of the block, exclusive of the size itself */
3018 (void) memcpy (&modcount, typedata, sizeof (short));
3019 /* Deduct the size of the reference type bytes at the end of the block. */
3020 modcount -= sizeof (long);
3021 /* Skip over the two size bytes at the beginning of the block. */
3022 modifiers = (unsigned char *) typedata + sizeof (short);
3023 /* Now do the actual decoding */
3024 typep = decode_modified_type (modifiers, modcount, AT_mod_u_d_type);
3032 decode_modified_type -- decode modified user or fundamental type
3036 static struct type *decode_modified_type (unsigned char *modifiers,
3037 unsigned short modcount, int mtype)
3041 Decode a modified type, either a modified fundamental type or
3042 a modified user defined type. MODIFIERS is a pointer to the
3043 block of bytes that define MODCOUNT modifiers. Immediately
3044 following the last modifier is a short containing the fundamental
3045 type or a long containing the reference to the user defined
3046 type. Which one is determined by MTYPE, which is either
3047 AT_mod_fund_type or AT_mod_u_d_type to indicate what modified
3048 type we are generating.
3050 We call ourself recursively to generate each modified type,`
3051 until MODCOUNT reaches zero, at which point we have consumed
3052 all the modifiers and generate either the fundamental type or
3053 user defined type. When the recursion unwinds, each modifier
3054 is applied in turn to generate the full modified type.
3058 If we find a modifier that we don't recognize, and it is not one
3059 of those reserved for application specific use, then we issue a
3060 warning and simply ignore the modifier.
3064 We currently ignore MOD_const and MOD_volatile. (FIXME)
3068 static struct type *
3069 DEFUN(decode_modified_type,
3070 (modifiers, modcount, mtype),
3071 unsigned char *modifiers AND unsigned short modcount AND int mtype)
3073 struct type *typep = NULL;
3074 unsigned short fundtype;
3076 unsigned char modifier;
3082 case AT_mod_fund_type:
3083 (void) memcpy (&fundtype, modifiers, sizeof (short));
3084 typep = decode_fund_type (fundtype);
3086 case AT_mod_u_d_type:
3087 (void) memcpy (&dieref, modifiers, sizeof (DIEREF));
3088 if ((typep = lookup_utype (dieref)) == NULL)
3090 typep = alloc_utype (dieref, NULL);
3094 SQUAWK (("botched modified type decoding (mtype 0x%x)", mtype));
3095 typep = builtin_type_int;
3101 modifier = *modifiers++;
3102 typep = decode_modified_type (modifiers, --modcount, mtype);
3105 case MOD_pointer_to:
3106 typep = lookup_pointer_type (typep);
3108 case MOD_reference_to:
3109 typep = lookup_reference_type (typep);
3112 SQUAWK (("type modifier 'const' ignored")); /* FIXME */
3115 SQUAWK (("type modifier 'volatile' ignored")); /* FIXME */
3118 if (!(MOD_lo_user <= modifier && modifier <= MOD_hi_user))
3120 SQUAWK (("unknown type modifier %u", modifier));
3132 decode_fund_type -- translate basic DWARF type to gdb base type
3136 Given an integer that is one of the fundamental DWARF types,
3137 translate it to one of the basic internal gdb types and return
3138 a pointer to the appropriate gdb type (a "struct type *").
3142 If we encounter a fundamental type that we are unprepared to
3143 deal with, and it is not in the range of those types defined
3144 as application specific types, then we issue a warning and
3145 treat the type as builtin_type_int.
3148 static struct type *
3149 DEFUN(decode_fund_type, (fundtype), unsigned short fundtype)
3151 struct type *typep = NULL;
3157 typep = builtin_type_void;
3160 case FT_pointer: /* (void *) */
3161 typep = lookup_pointer_type (builtin_type_void);
3165 case FT_signed_char:
3166 typep = builtin_type_char;
3170 case FT_signed_short:
3171 typep = builtin_type_short;
3175 case FT_signed_integer:
3176 case FT_boolean: /* Was FT_set in AT&T version */
3177 typep = builtin_type_int;
3181 case FT_signed_long:
3182 typep = builtin_type_long;
3186 typep = builtin_type_float;
3189 case FT_dbl_prec_float:
3190 typep = builtin_type_double;
3193 case FT_unsigned_char:
3194 typep = builtin_type_unsigned_char;
3197 case FT_unsigned_short:
3198 typep = builtin_type_unsigned_short;
3201 case FT_unsigned_integer:
3202 typep = builtin_type_unsigned_int;
3205 case FT_unsigned_long:
3206 typep = builtin_type_unsigned_long;
3209 case FT_ext_prec_float:
3210 typep = builtin_type_long_double;
3214 typep = builtin_type_complex;
3217 case FT_dbl_prec_complex:
3218 typep = builtin_type_double_complex;
3222 case FT_signed_long_long:
3223 typep = builtin_type_long_long;
3226 case FT_unsigned_long_long:
3227 typep = builtin_type_unsigned_long_long;
3232 if ((typep == NULL) && !(FT_lo_user <= fundtype && fundtype <= FT_hi_user))
3234 SQUAWK (("unexpected fundamental type 0x%x", fundtype));
3235 typep = builtin_type_void;
3245 create_name -- allocate a fresh copy of a string on an obstack
3249 Given a pointer to a string and a pointer to an obstack, allocates
3250 a fresh copy of the string on the specified obstack.
3255 DEFUN(create_name, (name, obstackp), char *name AND struct obstack *obstackp)
3260 length = strlen (name) + 1;
3261 newname = (char *) obstack_alloc (obstackp, length);
3262 (void) strcpy (newname, name);
3270 basicdieinfo -- extract the minimal die info from raw die data
3274 void basicdieinfo (char *diep, struct dieinfo *dip)
3278 Given a pointer to raw DIE data, and a pointer to an instance of a
3279 die info structure, this function extracts the basic information
3280 from the DIE data required to continue processing this DIE, along
3281 with some bookkeeping information about the DIE.
3283 The information we absolutely must have includes the DIE tag,
3284 and the DIE length. If we need the sibling reference, then we
3285 will have to call completedieinfo() to process all the remaining
3288 Note that since there is no guarantee that the data is properly
3289 aligned in memory for the type of access required (indirection
3290 through anything other than a char pointer), we use memcpy to
3291 shuffle data items larger than a char. Possibly inefficient, but
3294 We also take care of some other basic things at this point, such
3295 as ensuring that the instance of the die info structure starts
3296 out completely zero'd and that curdie is initialized for use
3297 in error reporting if we have a problem with the current die.
3301 All DIE's must have at least a valid length, thus the minimum
3302 DIE size is sizeof (long). In order to have a valid tag, the
3303 DIE size must be at least sizeof (short) larger, otherwise they
3304 are forced to be TAG_padding DIES.
3306 Padding DIES must be at least sizeof(long) in length, implying that
3307 if a padding DIE is used for alignment and the amount needed is less
3308 than sizeof(long) then the padding DIE has to be big enough to align
3309 to the next alignment boundry.
3313 DEFUN(basicdieinfo, (dip, diep), struct dieinfo *dip AND char *diep)
3316 (void) memset (dip, 0, sizeof (struct dieinfo));
3318 dip -> dieref = dbroff + (diep - dbbase);
3319 (void) memcpy (&dip -> dielength, diep, sizeof (long));
3320 if (dip -> dielength < sizeof (long))
3322 dwarfwarn ("malformed DIE, bad length (%d bytes)", dip -> dielength);
3324 else if (dip -> dielength < (sizeof (long) + sizeof (short)))
3326 dip -> dietag = TAG_padding;
3330 (void) memcpy (&dip -> dietag, diep + sizeof (long), sizeof (short));
3338 completedieinfo -- finish reading the information for a given DIE
3342 void completedieinfo (struct dieinfo *dip)
3346 Given a pointer to an already partially initialized die info structure,
3347 scan the raw DIE data and finish filling in the die info structure
3348 from the various attributes found.
3350 Note that since there is no guarantee that the data is properly
3351 aligned in memory for the type of access required (indirection
3352 through anything other than a char pointer), we use memcpy to
3353 shuffle data items larger than a char. Possibly inefficient, but
3358 Each time we are called, we increment the diecount variable, which
3359 keeps an approximate count of the number of dies processed for
3360 each compilation unit. This information is presented to the user
3361 if the info_verbose flag is set.
3366 DEFUN(completedieinfo, (dip), struct dieinfo *dip)
3368 char *diep; /* Current pointer into raw DIE data */
3369 char *end; /* Terminate DIE scan here */
3370 unsigned short attr; /* Current attribute being scanned */
3371 unsigned short form; /* Form of the attribute */
3372 short block2sz; /* Size of a block2 attribute field */
3373 long block4sz; /* Size of a block4 attribute field */
3377 end = diep + dip -> dielength;
3378 diep += sizeof (long) + sizeof (short);
3381 (void) memcpy (&attr, diep, sizeof (short));
3382 diep += sizeof (short);
3386 (void) memcpy (&dip -> at_fund_type, diep, sizeof (short));
3389 (void) memcpy (&dip -> at_ordering, diep, sizeof (short));
3392 (void) memcpy (&dip -> at_bit_offset, diep, sizeof (short));
3395 (void) memcpy (&dip -> at_visibility, diep, sizeof (short));
3398 (void) memcpy (&dip -> at_sibling, diep, sizeof (long));
3401 (void) memcpy (&dip -> at_stmt_list, diep, sizeof (long));
3402 dip -> at_stmt_list_p = 1;
3405 (void) memcpy (&dip -> at_low_pc, diep, sizeof (long));
3408 (void) memcpy (&dip -> at_high_pc, diep, sizeof (long));
3411 (void) memcpy (&dip -> at_language, diep, sizeof (long));
3413 case AT_user_def_type:
3414 (void) memcpy (&dip -> at_user_def_type, diep, sizeof (long));
3417 (void) memcpy (&dip -> at_byte_size, diep, sizeof (long));
3420 (void) memcpy (&dip -> at_bit_size, diep, sizeof (long));
3423 (void) memcpy (&dip -> at_member, diep, sizeof (long));
3426 (void) memcpy (&dip -> at_discr, diep, sizeof (long));
3429 (void) memcpy (&dip -> at_import, diep, sizeof (long));
3432 dip -> at_location = diep;
3434 case AT_mod_fund_type:
3435 dip -> at_mod_fund_type = diep;
3437 case AT_subscr_data:
3438 dip -> at_subscr_data = diep;
3440 case AT_mod_u_d_type:
3441 dip -> at_mod_u_d_type = diep;
3444 dip -> at_deriv_list = diep;
3446 case AT_element_list:
3447 dip -> at_element_list = diep;
3449 case AT_discr_value:
3450 dip -> at_discr_value = diep;
3452 case AT_string_length:
3453 dip -> at_string_length = diep;
3456 dip -> at_name = diep;
3459 dip -> at_comp_dir = diep;
3462 dip -> at_producer = diep;
3465 (void) memcpy (&dip -> at_loclist, diep, sizeof (long));
3468 (void) memcpy (&dip -> at_frame_base, diep, sizeof (long));
3471 (void) memcpy (&dip -> at_incomplete, diep, sizeof (short));
3473 case AT_start_scope:
3474 (void) memcpy (&dip -> at_start_scope, diep, sizeof (long));
3476 case AT_stride_size:
3477 (void) memcpy (&dip -> at_stride_size, diep, sizeof (long));
3480 (void) memcpy (&dip -> at_src_info, diep, sizeof (long));
3483 (void) memcpy (&dip -> at_prototyped, diep, sizeof (short));
3486 dip -> at_const_data = diep;
3488 case AT_is_external:
3489 (void) memcpy (&dip -> at_is_external, diep, sizeof (short));
3490 dip -> at_is_external_p = 1;
3493 /* Found an attribute that we are unprepared to handle. However
3494 it is specifically one of the design goals of DWARF that
3495 consumers should ignore unknown attributes. As long as the
3496 form is one that we recognize (so we know how to skip it),
3497 we can just ignore the unknown attribute. */
3504 diep += sizeof (short);
3507 diep += sizeof (long);
3510 diep += 8 * sizeof (char); /* sizeof (long long) ? */
3514 diep += sizeof (long);
3517 (void) memcpy (&block2sz, diep, sizeof (short));
3518 block2sz += sizeof (short);
3522 (void) memcpy (&block4sz, diep, sizeof (long));
3523 block4sz += sizeof (long);
3527 diep += strlen (diep) + 1;
3530 SQUAWK (("unknown attribute form (0x%x), skipped rest", form));