1 /* Read a symbol table in MIPS' format (Third-Eye).
2 Copyright 1986, 1987, 1989, 1990, 1991, 1992 Free Software Foundation, Inc.
4 work by Per Bothner and John Gilmore at Cygnus Support.
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. */
22 /* This module provides three functions: mipscoff_symfile_init,
23 which initializes to read a symbol file; mipscoff_new_init, which
24 discards existing cached information when all symbols are being
25 discarded; and mipscoff_symfile_read, which reads a symbol table
28 mipscoff_symfile_read only does the minimum work necessary for letting the
29 user "name" things symbolically; it does not read the entire symtab.
30 Instead, it reads the external and static symbols and puts them in partial
31 symbol tables. When more extensive information is requested of a
32 file, the corresponding partial symbol table is mutated into a full
33 fledged symbol table by going back and reading the symbols
34 for real. mipscoff_psymtab_to_symtab() is called indirectly through
35 a pointer in the psymtab to do this.
37 ECOFF symbol tables are mostly written in the byte order of the
38 target machine. However, one section of the table (the auxiliary
39 symbol information) is written in the host byte order. There is a
40 bit in the other symbol info which describes which host byte order
41 was used. ECOFF thereby takes the trophy from Intel `b.out' for
42 the most brain-dead adaptation of a file format to byte order.
44 This module can read all four of the known byte-order combinations,
45 on any type of host. However, it does make (and check) the assumption
46 that the external form of a symbol table structure (on disk)
47 occupies the same number of bytes as the internal form (in a struct).
48 Fixing this is possible but requires larger structural changes. */
50 #define TM_FILE_OVERRIDE
62 #include <sys/types.h>
67 #include <sys/param.h>
71 #include "coff/mips.h" /* COFF-like aspects of ecoff files */
72 #include "coff/ecoff-ext.h" /* External forms of ecoff sym structures */
74 #include "libbfd.h" /* FIXME Secret internal BFD stuff (bfd_read) */
75 #include "libaout.h" /* FIXME Secret internal BFD stuff for a.out */
76 #include "aout/aout64.h"
77 #include "aout/stab_gnu.h" /* STABS information */
80 struct external_filehdr f;
81 struct external_aouthdr a;
84 /* These must match the corresponding definition in gcc/config/xm-mips.h.
85 At some point, these should probably go into a shared include file,
86 but currently gcc and gdb do not share any directories. */
88 #define CODE_MASK 0x8F300
89 #define MIPS_IS_STAB(sym) (((sym)->index & 0xFFF00) == CODE_MASK)
90 #define MIPS_MARK_STAB(code) ((code)+CODE_MASK)
91 #define MIPS_UNMARK_STAB(code) ((code)-CODE_MASK)
92 #define STABS_SYMBOL "@stabs"
94 /* Each partial symbol table entry contains a pointer to private data for the
95 read_symtab() function to use when expanding a partial symbol table entry
96 to a full symbol table entry.
98 For mipsread this structure contains the index of the FDR that this psymtab
99 represents and a pointer to the symbol table header HDRR from the symbol
100 file that the psymtab was created from. */
102 #define PST_PRIVATE(p) ((struct symloc *)(p)->read_symtab_private)
103 #define FDR_IDX(p) (PST_PRIVATE(p)->fdr_idx)
104 #define CUR_HDR(p) (PST_PRIVATE(p)->cur_hdr)
109 EXTR **extern_tab; /* Pointer to external symbols for this file. */
110 int extern_count; /* Size of extern_tab. */
113 /* Things we import explicitly from other modules */
115 extern int info_verbose;
117 /* Various complaints about symbol reading that don't abort the process */
119 struct complaint bad_file_number_complaint =
120 {"bad file number %d", 0, 0};
122 struct complaint index_complaint =
123 {"bad aux index at symbol %s", 0, 0};
125 struct complaint aux_index_complaint =
126 {"bad proc end in aux found from symbol %s", 0, 0};
128 struct complaint unknown_ext_complaint =
129 {"unknown external symbol %s", 0, 0};
131 struct complaint unknown_sym_complaint =
132 {"unknown local symbol %s", 0, 0};
134 struct complaint unknown_st_complaint =
135 {"with type %d", 0, 0};
137 struct complaint block_overflow_complaint =
138 {"block containing %s overfilled", 0, 0};
140 struct complaint basic_type_complaint =
141 {"cannot map MIPS basic type 0x%x", 0, 0};
143 struct complaint unknown_type_qual_complaint =
144 {"unknown type qualifier 0x%x", 0, 0};
146 struct complaint array_bitsize_complaint =
147 {"size of array target type not known, assuming %d bits", 0, 0};
149 struct complaint bad_tag_guess_complaint =
150 {"guessed tag type of %s incorrectly", 0, 0};
152 struct complaint block_member_complaint =
153 {"declaration block contains unhandled symbol type %d", 0, 0};
155 struct complaint stEnd_complaint =
156 {"stEnd with storage class %d not handled", 0, 0};
158 struct complaint unknown_mips_symtype_complaint =
159 {"unknown symbol type 0x%x", 0, 0};
161 struct complaint stab_unknown_complaint =
162 {"unknown stabs symbol %s", 0, 0};
164 struct complaint pdr_for_nonsymbol_complaint =
165 {"PDR for %s, but no symbol", 0, 0};
167 struct complaint pdr_static_symbol_complaint =
168 {"can't handle PDR for static proc at 0x%x", 0, 0};
170 /* Macros and extra defs */
172 /* Already-parsed symbols are marked specially */
174 #define stParsed stType
176 /* Puns: hard to find whether -g was used and how */
178 #define MIN_GLEVEL GLEVEL_0
179 #define compare_glevel(a,b) \
180 (((a) == GLEVEL_3) ? ((b) < GLEVEL_3) : \
181 ((b) == GLEVEL_3) ? -1 : (int)((b) - (a)))
183 /* When looking at .o files, avoid tripping over bad addresses */
185 #define SAFE_TEXT_ADDR 0x400000
186 #define SAFE_DATA_ADDR 0x10000000
188 #define UNSAFE_DATA_ADDR(p) ((unsigned)p < SAFE_DATA_ADDR || (unsigned)p > 2*SAFE_DATA_ADDR)
190 /* Things that really are local to this module */
192 /* MIPS symtab header for the current file */
194 static HDRR *cur_hdr;
196 /* Pointer to current file decriptor record, and its index */
201 /* Index of current symbol */
205 /* Note how much "debuggable" this image is. We would like
206 to see at least one FDR with full symbols */
211 /* When examining .o files, report on undefined symbols */
213 static int n_undef_symbols, n_undef_labels, n_undef_vars, n_undef_procs;
215 /* Pseudo symbol to use when putting stabs into the symbol table. */
217 static char stabs_symbol[] = STABS_SYMBOL;
219 /* Extra builtin types */
221 struct type *builtin_type_complex;
222 struct type *builtin_type_double_complex;
223 struct type *builtin_type_fixed_dec;
224 struct type *builtin_type_float_dec;
225 struct type *builtin_type_string;
227 /* Forward declarations */
230 fixup_symtab PARAMS ((HDRR *, char *, int, bfd *));
233 read_mips_symtab PARAMS ((struct objfile *));
236 read_the_mips_symtab PARAMS ((bfd *, CORE_ADDR *));
239 upgrade_type PARAMS ((struct type **, int, union aux_ext *, int));
242 parse_partial_symbols PARAMS ((int, struct objfile *));
245 cross_ref PARAMS ((union aux_ext *, struct type **, enum type_code, char **,
249 fixup_sigtramp PARAMS ((void));
251 static struct symbol *
252 new_symbol PARAMS ((char *));
255 new_type PARAMS ((char *));
257 static struct block *
258 new_block PARAMS ((int));
260 static struct symtab *
261 new_symtab PARAMS ((char *, int, int, struct objfile *));
263 static struct linetable *
264 new_linetable PARAMS ((int));
266 static struct blockvector *
267 new_bvect PARAMS ((int));
270 parse_type PARAMS ((union aux_ext *, int *, int));
272 static struct symbol *
273 mylookup_symbol PARAMS ((char *, struct block *, enum namespace,
274 enum address_class));
276 static struct block *
277 shrink_block PARAMS ((struct block *, struct symtab *));
280 xzalloc PARAMS ((unsigned int));
283 sort_blocks PARAMS ((struct symtab *));
286 compare_blocks PARAMS ((const void *, const void *));
288 static struct partial_symtab *
289 new_psymtab PARAMS ((char *, struct objfile *));
292 static struct partial_symtab *
293 parse_fdr PARAMS ((int, int, struct objfile *));
297 psymtab_to_symtab_1 PARAMS ((struct partial_symtab *, char *));
300 add_block PARAMS ((struct block *, struct symtab *));
303 add_symbol PARAMS ((struct symbol *, struct block *));
306 add_line PARAMS ((struct linetable *, int, CORE_ADDR, int));
308 static struct linetable *
309 shrink_linetable PARAMS ((struct linetable *));
312 mips_next_symbol_text PARAMS ((void));
314 /* Things we export to other modules */
316 /* Address bounds for the signal trampoline in inferior, if any */
317 /* FIXME: Nothing really seems to use this. Why is it here? */
319 CORE_ADDR sigtramp_address, sigtramp_end;
322 mipscoff_new_init (ignore)
323 struct objfile *ignore;
328 mipscoff_symfile_init (objfile)
329 struct objfile *objfile;
331 if (objfile -> sym_private != NULL)
333 mfree (objfile -> md, objfile -> sym_private);
335 objfile -> sym_private = NULL;
339 mipscoff_symfile_read (objfile, addr, mainline)
340 struct objfile *objfile;
344 init_minimal_symbol_collection ();
345 make_cleanup (discard_minimal_symbols, 0);
347 /* Now that the executable file is positioned at symbol table,
348 process it and define symbols accordingly. */
350 read_mips_symtab(objfile);
352 /* Install any minimal symbols that have been collected as the current
353 minimal symbols for this objfile. */
355 install_minimal_symbols (objfile);
358 /* Perform any local cleanups required when we are done with a particular
359 objfile. I.E, we are in the process of discarding all symbol information
360 for an objfile, freeing up all memory held for it, and unlinking the
361 objfile struct from the global list of known objfiles. */
364 mipscoff_symfile_finish (objfile)
365 struct objfile *objfile;
367 if (objfile -> sym_private != NULL)
369 mfree (objfile -> md, objfile -> sym_private);
372 /* If we have a file symbol header lying around, blow it away. */
381 /* Allocate zeroed memory */
387 PTR p = xmalloc (size);
393 /* Exported procedure: Builds a symtab from the PST partial one.
394 Restores the environment in effect when PST was created, delegates
395 most of the work to an ancillary procedure, and sorts
396 and reorders the symtab list at the end */
399 mipscoff_psymtab_to_symtab(pst)
400 struct partial_symtab *pst;
407 printf_filtered("Reading in symbols for %s...", pst->filename);
410 /* Restore the header and list of pending typedefs */
411 cur_hdr = CUR_HDR(pst);
413 next_symbol_text_func = mips_next_symbol_text;
415 psymtab_to_symtab_1(pst, pst->filename);
417 /* Match with global symbols. This only needs to be done once,
418 after all of the symtabs and dependencies have been read in. */
419 scan_file_globals (pst->objfile);
422 printf_filtered("done.\n");
425 /* Exported procedure: Is PC in the signal trampoline code */
428 in_sigtramp(pc, ignore)
430 char *ignore; /* function name */
432 if (sigtramp_address == 0)
434 return (pc >= sigtramp_address && pc < sigtramp_end);
437 /* File-level interface functions */
439 /* Read the symtab information from file ABFD into memory. Also,
440 return address just past end of our text segment in *END_OF_TEXT_SEGP. */
443 read_the_mips_symtab(abfd, end_of_text_segp)
445 CORE_ADDR *end_of_text_segp;
447 int stsize, st_hdrsize;
449 struct hdr_ext hdr_ext;
451 /* Header for executable/object file we read symbols from */
452 struct coff_exec filhdr;
455 /* We need some info from the initial headers */
456 val = bfd_seek(abfd, 0L, L_SET);
457 val = bfd_read((PTR)&filhdr, sizeof filhdr, 1, abfd);
459 if (end_of_text_segp)
461 bfd_h_get_32 (abfd, filhdr.a.text_start) +
462 bfd_h_get_32 (abfd, filhdr.a.tsize);
464 /* Find and read the symbol table header */
465 st_hdrsize = bfd_h_get_32 (abfd, filhdr.f.f_nsyms);
466 st_filptr = bfd_h_get_32 (abfd, filhdr.f.f_symptr);
470 bfd_seek (abfd, st_filptr, L_SET);
471 if (st_hdrsize != sizeof (hdr_ext)) { /* Profanity check */
472 error ("Wrong header size: %d, not %d", st_hdrsize,
475 if (bfd_read((PTR)&hdr_ext, st_hdrsize, 1, abfd) != st_hdrsize)
477 ecoff_swap_hdr_in (abfd, &hdr_ext, &st_hdr);
479 /* Find out how large the symbol table is */
480 stsize = (st_hdr.cbExtOffset - (st_filptr + st_hdrsize))
481 + st_hdr.iextMax * cbEXTR;
483 /* Allocate space for the symbol table. Read it in. */
484 cur_hdr = (HDRR *) xmalloc(stsize + st_hdrsize);
486 memcpy((PTR)cur_hdr, (PTR)&hdr_ext, st_hdrsize);
487 if (bfd_read((char *)cur_hdr + st_hdrsize, stsize, 1, abfd) != stsize)
490 /* Fixup file_pointers in it */
491 fixup_symtab(cur_hdr, (char *) cur_hdr + st_hdrsize,
492 st_filptr + st_hdrsize, abfd);
496 error("Short read on %s", bfd_get_filename (abfd));
500 /* Turn all file-relative pointers in the symtab described by HDR
501 into memory pointers, given that the symtab itself is located
502 at DATA in memory and F_PTR in the file.
504 Byte-swap all the data structures, in place, while we are at it --
505 except AUX entries, which we leave in their original byte order.
506 They will be swapped as they are used instead. (FIXME: we ought to
507 do all the data structures that way.) */
510 fixup_symtab (hdr, data, f_ptr, abfd)
521 struct rfd_ext *rbase;
523 /* This function depends on the external and internal forms
524 of the MIPS symbol table taking identical space. Check this
525 assumption at compile-time. */
526 #if 0 /* FIXME: Unused */
527 static check_hdr1[1 + sizeof (struct hdr_ext) - sizeof (HDRR)] = {0};
528 static check_hdr2[1 + sizeof (HDRR) - sizeof (struct hdr_ext)] = {0};
529 static check_fdr1[1 + sizeof (struct fdr_ext) - sizeof (FDR)] = {0};
530 static check_fdr2[1 + sizeof (FDR) - sizeof (struct fdr_ext)] = {0};
531 static check_pdr1[1 + sizeof (struct pdr_ext) - sizeof (PDR)] = {0};
532 static check_pdr2[1 + sizeof (PDR) - sizeof (struct pdr_ext)] = {0};
533 static check_sym1[1 + sizeof (struct sym_ext) - sizeof (SYMR)] = {0};
534 static check_sym2[1 + sizeof (SYMR) - sizeof (struct sym_ext)] = {0};
535 static check_ext1[1 + sizeof (struct ext_ext) - sizeof (EXTR)] = {0};
536 static check_ext2[1 + sizeof (EXTR) - sizeof (struct ext_ext)] = {0};
537 static check_rfd1[1 + sizeof (struct rfd_ext) - sizeof (RFDT)] = {0};
538 static check_rfd2[1 + sizeof (RFDT) - sizeof (struct rfd_ext)] = {0};
541 /* Swap in the header record. */
542 ecoff_swap_hdr_in (abfd, hdr, hdr);
545 * These fields are useless (and empty) by now:
546 * hdr->cbDnOffset, hdr->cbOptOffset
547 * We use them for other internal purposes.
550 hdr->cbOptOffset = 0;
553 if (hdr->off) hdr->off = (unsigned int)data + (hdr->off - f_ptr);
567 /* Fix all the RFD's. */
568 rbase = (struct rfd_ext *)(hdr->cbRfdOffset);
569 for (i = 0; i < hdr->crfd; i++) {
570 ecoff_swap_rfd_in (abfd, rbase+i, (pRFDT) rbase+i);
573 /* Fix all string pointers inside the symtab, and
574 the FDR records. Also fix other miscellany. */
576 for (f_idx = 0; f_idx < hdr->ifdMax; f_idx++) {
577 register unsigned code_offset;
579 /* Header itself, and strings */
580 fh = (FDR *) (hdr->cbFdOffset) + f_idx;
582 /* Swap in the FDR */
583 ecoff_swap_fdr_in (abfd, fh, fh);
585 fh->issBase += hdr->cbSsOffset;
587 fh->rss = (long)fh->rss + fh->issBase;
590 fh->isymBase = (int)((SYMR*)(hdr->cbSymOffset)+fh->isymBase);
592 /* FIXME! Probably don't want to do this here! */
593 for (s_idx = 0; s_idx < fh->csym; s_idx++) {
594 sh = (SYMR*)fh->isymBase + s_idx;
595 ecoff_swap_sym_in (abfd, sh, sh);
597 sh->iss = (long) sh->iss + fh->issBase;
603 /* cannot fix fh->ipdFirst because it is a short */
604 #define IPDFIRST(h,fh) \
605 ((long)h->cbPdOffset + fh->ipdFirst * sizeof(PDR))
607 /* Optional symbols (actually used for partial_symtabs) */
613 fh->iauxBase = hdr->cbAuxOffset + fh->iauxBase * sizeof(union aux_ext);
614 /* Relative file descriptor table */
615 fh->rfdBase = hdr->cbRfdOffset + fh->rfdBase * sizeof(RFDT);
619 fh->cbLineOffset += hdr->cbLineOffset;
621 /* Procedure symbols. (XXX This should be done later) */
622 code_offset = fh->adr;
623 for (s_idx = 0; s_idx < fh->cpd; s_idx++) {
624 unsigned name, only_ext;
626 pr = (PDR*)(IPDFIRST(hdr,fh)) + s_idx;
627 ecoff_swap_pdr_in (abfd, pr, pr);
629 /* Simple rule to find files linked "-x" */
630 only_ext = fh->rss == -1;
632 if (pr->isym == -1) {
633 /* static function */
637 name = hdr->cbExtOffset + pr->isym * sizeof(EXTR);
638 sh = &((EXTR*)name)->asym;
642 sh = (SYMR*)fh->isymBase + pr->isym;
643 /* Included code ? */
644 if (s_idx == 0 && pr->adr != 0)
645 code_offset -= pr->adr;
648 /* Turn index into a pointer */
651 /* Fix line numbers */
652 pr->cbLineOffset += fh->cbLineOffset;
654 /* Relocate address */
656 pr->adr += code_offset;
660 /* External symbols: swap in, and fix string */
661 for (s_idx = 0; s_idx < hdr->iextMax; s_idx++) {
662 esh = (EXTR*)(hdr->cbExtOffset) + s_idx;
663 ecoff_swap_ext_in (abfd, esh, esh);
664 esh->asym.iss = esh->asym.iss + hdr->cbSsExtOffset;
669 /* Find a file descriptor given its index RF relative to a file CF */
677 f = (FDR *) (cur_hdr->cbFdOffset) + cf;
678 /* Object files do not have the RFD table, all refs are absolute */
680 return (FDR *) (cur_hdr->cbFdOffset) + rf;
681 cf = *((pRFDT) f->rfdBase + rf);
682 return (FDR *) (cur_hdr->cbFdOffset) + cf;
685 /* Return a safer print NAME for a file descriptor */
691 if (name == (char *) -1)
692 return "<stripped file>";
693 if (UNSAFE_DATA_ADDR(name))
699 /* Read in and parse the symtab of the file DESC. INCREMENTAL says
700 whether we are adding to the general symtab or not.
701 FIXME: INCREMENTAL is currently always zero, though it should not be. */
704 read_mips_symtab (objfile)
705 struct objfile *objfile;
707 CORE_ADDR end_of_text_seg;
709 read_the_mips_symtab(objfile->obfd, &end_of_text_seg);
711 parse_partial_symbols(end_of_text_seg, objfile);
715 * Check to make sure file was compiled with -g.
716 * If not, warn the user of this limitation.
718 if (compare_glevel(max_glevel, GLEVEL_2) < 0) {
719 if (max_gdbinfo == 0)
721 "\n%s not compiled with -g, debugging support is limited.\n",
724 "You should compile with -g2 or -g3 for best debugging support.\n");
730 /* Local utilities */
732 /* Map of FDR indexes to partial symtabs */
735 struct partial_symtab *pst; /* the psymtab proper */
736 int n_globals; /* exported globals (external symbols) */
737 int globals_offset; /* cumulative */
741 /* Utility stack, used to nest procedures and blocks properly.
742 It is a doubly linked list, to avoid too many alloc/free.
743 Since we might need it quite a few times it is NOT deallocated
746 static struct parse_stack {
747 struct parse_stack *next, *prev;
748 struct symtab *cur_st; /* Current symtab. */
749 struct block *cur_block; /* Block in it. */
750 int blocktype; /* What are we parsing. */
751 int maxsyms; /* Max symbols in this block. */
752 struct type *cur_type; /* Type we parse fields for. */
753 int cur_field; /* Field number in cur_type. */
754 int procadr; /* Start addres of this procedure */
755 int numargs; /* Its argument count */
756 } *top_stack; /* Top stack ptr */
759 /* Enter a new lexical context */
764 struct parse_stack *new;
766 /* Reuse frames if possible */
767 if (top_stack && top_stack->prev)
768 new = top_stack->prev;
770 new = (struct parse_stack *) xzalloc(sizeof(struct parse_stack));
771 /* Initialize new frame with previous content */
773 register struct parse_stack *prev = new->prev;
776 top_stack->prev = new;
778 new->next = top_stack;
783 /* Exit a lexical context */
791 top_stack = top_stack->next;
795 /* Cross-references might be to things we haven't looked at
796 yet, e.g. type references. To avoid too many type
797 duplications we keep a quick fixup table, an array
798 of lists of references indexed by file descriptor */
800 static struct mips_pending {
801 struct mips_pending *next; /* link */
802 SYMR *s; /* the symbol */
803 struct type *t; /* its partial type descriptor */
807 /* Check whether we already saw symbol SH in file FH as undefined */
809 static struct mips_pending *
810 is_pending_symbol(fh, sh)
814 int f_idx = fh - (FDR *) cur_hdr->cbFdOffset;
815 register struct mips_pending *p;
817 /* Linear search is ok, list is typically no more than 10 deep */
818 for (p = pending_list[f_idx]; p; p = p->next)
824 /* Add a new undef symbol SH of type T */
827 add_pending(fh, sh, t)
832 int f_idx = fh - (FDR *) cur_hdr->cbFdOffset;
833 struct mips_pending *p = is_pending_symbol(fh, sh);
835 /* Make sure we do not make duplicates */
837 p = (struct mips_pending *) xmalloc(sizeof(*p));
840 p->next = pending_list[f_idx];
841 pending_list[f_idx] = p;
843 sh->reserved = 1; /* for quick check */
846 /* Throw away undef entries when done with file index F_IDX */
847 /* FIXME -- storage leak. This is never called!!! --gnu */
855 register struct mips_pending *p, *q;
857 for (p = pending_list[f_idx]; p; p = q) {
861 pending_list[f_idx] = 0;
867 prepend_tag_kind(tag_name, type_code)
869 enum type_code type_code;
877 case TYPE_CODE_STRUCT:
880 case TYPE_CODE_UNION:
887 result = (char*)obstack_alloc (¤t_objfile->symbol_obstack,
888 strlen(prefix) + strlen(tag_name) + 1);
889 sprintf(result, "%s%s", prefix, tag_name);
894 /* Parsing Routines proper. */
896 /* Parse a single symbol. Mostly just make up a GDB symbol for it.
897 For blocks, procedures and types we open a new lexical context.
898 This is basically just a big switch on the symbol's type.
899 Argument AX is the base pointer of aux symbols for this file (fh->iauxBase).
900 BIGEND says whether aux symbols are big-endian or little-endian.
901 Return count of SYMR's handled (normally one). */
904 parse_symbol(sh, ax, bigend)
915 /* When a symbol is cross-referenced from other files/symbols
916 we mark it explicitly */
917 int pend = (sh->reserved == 1);
918 enum address_class class;
926 case stGlobal: /* external symbol, goes into global block */
928 b = BLOCKVECTOR_BLOCK(BLOCKVECTOR(top_stack->cur_st),
930 s = new_symbol((char *)sh->iss);
931 SYMBOL_VALUE_ADDRESS(s) = (CORE_ADDR)sh->value;
934 case stStatic: /* static data, goes into current block. */
936 b = top_stack->cur_block;
937 s = new_symbol((char *)sh->iss);
938 SYMBOL_VALUE_ADDRESS(s) = (CORE_ADDR)sh->value;
941 case stLocal: /* local variable, goes into current block */
942 if (sh->sc == scRegister) {
943 class = LOC_REGISTER;
945 sh->value += FP0_REGNUM-32;
948 b = top_stack->cur_block;
949 s = new_symbol((char *)sh->iss);
950 SYMBOL_VALUE(s) = sh->value;
952 data: /* Common code for symbols describing data */
953 SYMBOL_NAMESPACE(s) = VAR_NAMESPACE;
954 SYMBOL_CLASS(s) = class;
957 /* Type could be missing in a number of cases */
958 if (sh->sc == scUndefined || sh->sc == scNil ||
959 sh->index == 0xfffff)
960 SYMBOL_TYPE(s) = builtin_type_int; /* undefined? */
962 SYMBOL_TYPE(s) = parse_type(ax + sh->index, 0, bigend);
963 /* Value of a data symbol is its memory address */
966 case stParam: /* arg to procedure, goes into current block */
968 top_stack->numargs++;
970 name = (char*)sh->iss;
971 /* Special GNU C++ name. */
972 if (name[0] == CPLUS_MARKER && name[1] == 't' && name[2] == 0)
973 name = "this"; /* FIXME, not alloc'd in obstack */
974 s = new_symbol(name);
976 SYMBOL_NAMESPACE(s) = VAR_NAMESPACE;
977 if (sh->sc == scRegister) {
978 SYMBOL_CLASS(s) = LOC_REGPARM;
980 sh->value += FP0_REGNUM-32;
982 SYMBOL_CLASS(s) = LOC_ARG;
983 SYMBOL_VALUE(s) = sh->value;
984 SYMBOL_TYPE(s) = parse_type(ax + sh->index, 0, bigend);
985 add_symbol(s, top_stack->cur_block);
987 /* FIXME: This has not been tested. See dbxread.c */
988 /* Add the type of this parameter to the function/procedure
989 type of this block. */
990 add_param_to_type(&top_stack->cur_block->function->type,s);
994 case stLabel: /* label, goes into current block */
995 s = new_symbol((char *)sh->iss);
996 SYMBOL_NAMESPACE(s) = VAR_NAMESPACE; /* so that it can be used */
997 SYMBOL_CLASS(s) = LOC_LABEL; /* but not misused */
998 SYMBOL_VALUE_ADDRESS(s) = (CORE_ADDR)sh->value;
999 SYMBOL_TYPE(s) = builtin_type_int;
1000 add_symbol(s, top_stack->cur_block);
1003 case stProc: /* Procedure, usually goes into global block */
1004 case stStaticProc: /* Static procedure, goes into current block */
1005 s = new_symbol((char *)sh->iss);
1006 SYMBOL_NAMESPACE(s) = VAR_NAMESPACE;
1007 SYMBOL_CLASS(s) = LOC_BLOCK;
1008 /* Type of the return value */
1009 if (sh->sc == scUndefined || sh->sc == scNil)
1010 t = builtin_type_int;
1012 t = parse_type(ax + sh->index + 1, 0, bigend);
1013 b = top_stack->cur_block;
1014 if (sh->st == stProc) {
1015 struct blockvector *bv = BLOCKVECTOR(top_stack->cur_st);
1016 /* The next test should normally be true,
1017 but provides a hook for nested functions
1018 (which we don't want to make global). */
1019 if (b == BLOCKVECTOR_BLOCK(bv, STATIC_BLOCK))
1020 b = BLOCKVECTOR_BLOCK(bv, GLOBAL_BLOCK);
1024 /* Make a type for the procedure itself */
1026 /* FIXME: This has not been tested yet! See dbxread.c */
1027 /* Generate a template for the type of this function. The
1028 types of the arguments will be added as we read the symbol
1030 bcopy(SYMBOL_TYPE(s),lookup_function_type(t),sizeof(struct type));
1032 SYMBOL_TYPE(s) = lookup_function_type (t);
1035 /* Create and enter a new lexical context */
1036 b = new_block(top_stack->maxsyms);
1037 SYMBOL_BLOCK_VALUE(s) = b;
1038 BLOCK_FUNCTION(b) = s;
1039 BLOCK_START(b) = BLOCK_END(b) = sh->value;
1040 BLOCK_SUPERBLOCK(b) = top_stack->cur_block;
1041 add_block(b, top_stack->cur_st);
1043 /* Not if we only have partial info */
1044 if (sh->sc == scUndefined || sh->sc == scNil)
1048 top_stack->cur_block = b;
1049 top_stack->blocktype = sh->st;
1050 top_stack->cur_type = SYMBOL_TYPE(s);
1051 top_stack->cur_field = -1;
1052 top_stack->procadr = sh->value;
1053 top_stack->numargs = 0;
1055 sh->value = (long) SYMBOL_TYPE(s);
1058 /* Beginning of code for structure, union, and enum definitions.
1059 They all share a common set of local variables, defined here. */
1061 enum type_code type_code;
1067 case stStruct: /* Start a block defining a struct type */
1068 type_code = TYPE_CODE_STRUCT;
1069 goto structured_common;
1071 case stUnion: /* Start a block defining a union type */
1072 type_code = TYPE_CODE_UNION;
1073 goto structured_common;
1075 case stEnum: /* Start a block defining an enum type */
1076 type_code = TYPE_CODE_ENUM;
1077 goto structured_common;
1079 case stBlock: /* Either a lexical block, or some type */
1080 if (sh->sc != scInfo)
1081 goto case_stBlock_code; /* Lexical block */
1083 type_code = TYPE_CODE_UNDEF; /* We have a type. */
1085 /* Common code for handling struct, union, enum, and/or as-yet-
1086 unknown-type blocks of info about structured data. `type_code'
1087 has been set to the proper TYPE_CODE, if we know it. */
1090 top_stack->blocktype = stBlock;
1092 s = new_symbol((char *)sh->iss);
1093 SYMBOL_NAMESPACE(s) = STRUCT_NAMESPACE;
1094 SYMBOL_CLASS(s) = LOC_TYPEDEF;
1095 SYMBOL_VALUE(s) = 0;
1096 add_symbol(s, top_stack->cur_block);
1098 /* First count the number of fields and the highest value. */
1101 for (tsym = sh+1; tsym->st != stEnd; tsym++)
1103 if (tsym->st == stMember) {
1104 if (nfields == 0 && type_code == TYPE_CODE_UNDEF)
1105 /* If the type of the member is Nil (or Void),
1106 assume the tag is an enumeration. */
1107 if (tsym->index == indexNil)
1108 type_code = TYPE_CODE_ENUM;
1110 ecoff_swap_tir_in (bigend,
1111 &ax[tsym->index].a_ti,
1113 if (tir.bt == btNil || tir.bt == btVoid)
1114 type_code = TYPE_CODE_ENUM;
1117 if (tsym->value > max_value)
1118 max_value = tsym->value;
1120 else if (tsym->st == stBlock
1121 || tsym->st == stUnion
1122 || tsym->st == stEnum
1123 || tsym->st == stStruct
1124 || tsym->st == stParsed) {
1125 if (tsym->sc == scVariant) ; /*UNIMPLEMENTED*/
1126 if (tsym->index != 0)
1127 tsym = ((SYMR*)cur_fdr->isymBase)
1130 else complain (&block_member_complaint, (char *)tsym->st);
1133 /* In an stBlock, there is no way to distinguish structs,
1134 unions, and enums at this point. This is a bug in the
1135 original design (that has been fixed with the
1136 recent addition of the stStruct, stUnion, and stEnum
1137 symbol types.) The way you can tell is if/when you
1138 see a variable or field of that type. In that case
1139 the variable's type (in the AUX table) says if the
1140 type is struct, union, or enum,
1141 and points back to the stBlock here.
1142 So you can patch the tag kind up later - but only
1143 if there actually is a variable or field of that type.
1145 So until we know for sure, we will guess at this point.
1147 If the first member has index==indexNil or a void type,
1148 assume we have an enumeration.
1149 Otherwise, if there is more than one member, and all
1150 the members have offset 0, assume we have a union.
1151 Otherwise, assume we have a struct.
1153 The heuristic could guess wrong in the case of
1154 of an enumeration with no members or a union
1155 with one (or zero) members, or when all except the
1156 last field of a struct have width zero.
1157 These are uncommon and/or illegal situations, and
1158 in any case guessing wrong probably doesn't matter much.
1160 But if we later do find out we were wrong,
1161 we fixup the tag kind. Members of an enumeration
1162 must be handled differently from struct/union fields,
1163 and that is harder to patch up, but luckily we
1164 shouldn't need to. (If there are any enumeration
1165 members, we can tell for sure it's an enum here.) */
1167 if (type_code == TYPE_CODE_UNDEF)
1168 if (nfields > 1 && max_value == 0)
1169 type_code = TYPE_CODE_UNION;
1171 type_code = TYPE_CODE_STRUCT;
1173 /* If this type was expected, use its partial definition */
1175 t = is_pending_symbol(cur_fdr, sh)->t;
1177 t = new_type(prepend_tag_kind((char *)sh->iss,
1180 TYPE_CODE(t) = type_code;
1181 TYPE_LENGTH(t) = sh->value;
1182 TYPE_NFIELDS(t) = nfields;
1183 TYPE_FIELDS(t) = f = (struct field*)
1184 obstack_alloc (¤t_objfile -> type_obstack,
1185 nfields * sizeof (struct field));
1187 if (type_code == TYPE_CODE_ENUM) {
1188 /* This is a non-empty enum. */
1189 for (tsym = sh + 1; tsym->st == stMember; tsym++) {
1190 struct symbol *enum_sym;
1191 f->bitpos = tsym->value;
1193 f->name = (char*)tsym->iss;
1196 enum_sym = (struct symbol *)
1197 obstack_alloc (¤t_objfile->symbol_obstack,
1198 sizeof (struct symbol));
1199 memset ((PTR)enum_sym, 0, sizeof (struct symbol));
1200 SYMBOL_NAME (enum_sym) = f->name;
1201 SYMBOL_CLASS (enum_sym) = LOC_CONST;
1202 SYMBOL_TYPE (enum_sym) = t;
1203 SYMBOL_NAMESPACE (enum_sym) = VAR_NAMESPACE;
1204 SYMBOL_VALUE (enum_sym) = tsym->value;
1205 add_symbol(enum_sym, top_stack->cur_block);
1207 /* Skip the stMembers that we've handled. */
1213 /* make this the current type */
1214 top_stack->cur_type = t;
1215 top_stack->cur_field = 0;
1216 /* Mark that symbol has a type, and say which one */
1217 sh->value = (long) t;
1220 /* End of local variables shared by struct, union, enum, and
1221 block (as yet unknown struct/union/enum) processing. */
1225 /* beginnning of (code) block. Value of symbol
1226 is the displacement from procedure start */
1228 top_stack->blocktype = stBlock;
1229 b = new_block(top_stack->maxsyms);
1230 BLOCK_START(b) = sh->value + top_stack->procadr;
1231 BLOCK_SUPERBLOCK(b) = top_stack->cur_block;
1232 top_stack->cur_block = b;
1233 add_block(b, top_stack->cur_st);
1236 case stEnd: /* end (of anything) */
1237 if (sh->sc == scInfo) {
1238 /* Finished with type */
1239 top_stack->cur_type = 0;
1240 } else if (sh->sc == scText &&
1241 (top_stack->blocktype == stProc ||
1242 top_stack->blocktype == stStaticProc)) {
1243 /* Finished with procedure */
1244 struct blockvector *bv = BLOCKVECTOR(top_stack->cur_st);
1245 struct mips_extra_func_info *e;
1249 BLOCK_END(top_stack->cur_block) += sh->value; /* size */
1251 /* Make up special symbol to contain procedure specific
1253 s = new_symbol(".gdbinfo.");
1254 SYMBOL_NAMESPACE(s) = LABEL_NAMESPACE;
1255 SYMBOL_CLASS(s) = LOC_CONST;
1256 SYMBOL_TYPE(s) = builtin_type_void;
1257 e = (struct mips_extra_func_info *)
1258 obstack_alloc (¤t_objfile->symbol_obstack,
1259 sizeof (struct mips_extra_func_info));
1260 SYMBOL_VALUE(s) = (int)e;
1261 e->numargs = top_stack->numargs;
1262 add_symbol(s, top_stack->cur_block);
1264 /* Reallocate symbols, saving memory */
1265 b = shrink_block(top_stack->cur_block, top_stack->cur_st);
1267 /* f77 emits proc-level with address bounds==[0,0],
1268 So look for such child blocks, and patch them. */
1269 for (i = 0; i < BLOCKVECTOR_NBLOCKS(bv); i++) {
1270 struct block *b_bad = BLOCKVECTOR_BLOCK(bv,i);
1271 if (BLOCK_SUPERBLOCK(b_bad) == b
1272 && BLOCK_START(b_bad) == top_stack->procadr
1273 && BLOCK_END(b_bad) == top_stack->procadr) {
1274 BLOCK_START(b_bad) = BLOCK_START(b);
1275 BLOCK_END(b_bad) = BLOCK_END(b);
1278 } else if (sh->sc == scText && top_stack->blocktype == stBlock) {
1279 /* End of (code) block. The value of the symbol
1280 is the displacement from the procedure`s start
1281 address of the end of this block. */
1282 BLOCK_END(top_stack->cur_block) = sh->value + top_stack->procadr;
1283 shrink_block(top_stack->cur_block, top_stack->cur_st);
1284 } else complain (&stEnd_complaint, (char *)sh->sc);
1286 pop_parse_stack(); /* restore previous lexical context */
1289 case stMember: /* member of struct or union */
1290 f = &TYPE_FIELDS(top_stack->cur_type)[top_stack->cur_field++];
1291 f->name = (char*)sh->iss;
1292 f->bitpos = sh->value;
1294 f->type = parse_type(ax + sh->index, &f->bitsize, bigend);
1297 case stTypedef: /* type definition */
1298 s = new_symbol((char *)sh->iss);
1299 SYMBOL_NAMESPACE(s) = VAR_NAMESPACE;
1300 SYMBOL_CLASS(s) = LOC_TYPEDEF;
1301 SYMBOL_BLOCK_VALUE(s) = top_stack->cur_block;
1302 add_symbol(s, top_stack->cur_block);
1303 SYMBOL_TYPE(s) = parse_type(ax + sh->index, 0, bigend);
1304 sh->value = (long) SYMBOL_TYPE(s);
1307 case stFile: /* file name */
1309 top_stack->blocktype = sh->st;
1312 /* I`ve never seen these for C */
1314 break; /* register relocation */
1316 break; /* forwarding address */
1318 break; /* constant */
1320 complain(&unknown_mips_symtype_complaint, (char *)sh->st);
1327 /* Parse the type information provided in the raw AX entries for
1328 the symbol SH. Return the bitfield size in BS, in case.
1329 We must byte-swap the AX entries before we use them; BIGEND says whether
1330 they are big-endian or little-endian (from fh->fBigendian). */
1332 static struct type *
1333 parse_type(ax, bs, bigend)
1338 /* Null entries in this map are treated specially */
1339 static struct type **map_bt[] =
1341 &builtin_type_void, /* btNil */
1343 &builtin_type_char, /* btChar */
1344 &builtin_type_unsigned_char, /* btUChar */
1345 &builtin_type_short, /* btShort */
1346 &builtin_type_unsigned_short, /* btUShort */
1347 &builtin_type_int, /* btInt */
1348 &builtin_type_unsigned_int, /* btUInt */
1349 &builtin_type_long, /* btLong */
1350 &builtin_type_unsigned_long, /* btULong */
1351 &builtin_type_float, /* btFloat */
1352 &builtin_type_double, /* btDouble */
1359 &builtin_type_complex, /* btComplex */
1360 &builtin_type_double_complex, /* btDComplex */
1362 &builtin_type_fixed_dec, /* btFixedDec */
1363 &builtin_type_float_dec, /* btFloatDec */
1364 &builtin_type_string, /* btString */
1367 &builtin_type_void, /* btVoid */
1368 &builtin_type_long_long, /* btLongLong */
1369 &builtin_type_unsigned_long_long,/* btULongLong */
1373 struct type *tp = 0;
1376 enum type_code type_code;
1378 /* Use aux as a type information record, map its basic type. */
1380 ecoff_swap_tir_in (bigend, &tax->a_ti, t);
1381 if (t->bt > (sizeof (map_bt)/sizeof (*map_bt))) {
1382 complain (&basic_type_complaint, (char *)t->bt);
1383 return builtin_type_int;
1385 if (map_bt[t->bt]) {
1386 tp = *map_bt[t->bt];
1390 /* Cannot use builtin types -- build our own */
1393 tp = lookup_pointer_type (builtin_type_void);
1397 type_code = TYPE_CODE_STRUCT;
1401 type_code = TYPE_CODE_UNION;
1405 type_code = TYPE_CODE_ENUM;
1409 type_code = TYPE_CODE_RANGE;
1413 type_code = TYPE_CODE_SET;
1418 complain (&basic_type_complaint, (char *)t->bt);
1419 return builtin_type_int;
1423 /* Skip over any further type qualifiers (FIXME). */
1425 /* This is the way it would work if the compiler worked */
1429 ecoff_swap_tir_in (bigend, ax, t1);
1430 } while (t1->continued);
1433 /* Move on to next aux */
1437 *bs = AUX_GET_WIDTH (bigend, ax);
1441 /* All these types really point to some (common) MIPS type
1442 definition, and only the type-qualifiers fully identify
1443 them. We'll make the same effort at sharing. */
1444 if (t->bt == btIndirect ||
1445 t->bt == btStruct ||
1448 t->bt == btTypedef ||
1451 char name[256], *pn;
1453 /* Try to cross reference this type */
1454 ax += cross_ref(ax, &tp, type_code, &pn, bigend);
1455 /* reading .o file ? */
1456 if (UNSAFE_DATA_ADDR(tp))
1457 tp = init_type(type_code, 0, 0, (char *) NULL,
1458 (struct objfile *) NULL);
1459 /* SOMEONE OUGHT TO FIX DBXREAD TO DROP "STRUCT" */
1460 sprintf(name, fmt, pn);
1462 /* Usually, TYPE_CODE(tp) is already type_code. The main
1463 exception is if we guessed wrong re struct/union/enum. */
1464 if (TYPE_CODE(tp) != type_code) {
1465 complain (&bad_tag_guess_complaint, name);
1466 TYPE_CODE(tp) = type_code;
1468 if (TYPE_NAME(tp) == NULL || strcmp(TYPE_NAME(tp), name) != 0)
1469 TYPE_NAME(tp) = obsavestring(name, strlen(name),
1470 ¤t_objfile -> type_obstack);
1473 /* Deal with range types */
1474 if (t->bt == btRange) {
1475 TYPE_NFIELDS (tp) = 2;
1477 (struct field *) obstack_alloc (¤t_objfile -> type_obstack,
1478 2 * sizeof (struct field));
1479 TYPE_FIELD_NAME (tp, 0) = obsavestring ("Low", strlen ("Low"),
1480 ¤t_objfile -> type_obstack);
1481 TYPE_FIELD_BITPOS (tp, 0) = AUX_GET_DNLOW (bigend, ax);
1483 TYPE_FIELD_NAME (tp, 1) = obsavestring ("High", strlen ("High"),
1484 ¤t_objfile -> type_obstack);
1485 TYPE_FIELD_BITPOS (tp, 1) = AUX_GET_DNHIGH (bigend, ax);
1489 /* Parse all the type qualifiers now. If there are more
1490 than 6 the game will continue in the next aux */
1492 #define PARSE_TQ(tq) \
1493 if (t->tq != tqNil) ax += upgrade_type(&tp, t->tq, ax, bigend);
1495 again: PARSE_TQ(tq0);
1505 ecoff_swap_tir_in (bigend, &tax->a_ti, t);
1511 /* Make up a complex type from a basic one. Type is passed by
1512 reference in TPP and side-effected as necessary. The type
1513 qualifier TQ says how to handle the aux symbols at AX for
1514 the symbol SX we are currently analyzing. BIGEND says whether
1515 aux symbols are big-endian or little-endian.
1516 Returns the number of aux symbols we parsed. */
1519 upgrade_type(tpp, tq, ax, bigend)
1528 /* Used in array processing */
1537 t = lookup_pointer_type (*tpp);
1542 t = lookup_function_type (*tpp);
1548 t = init_type(TYPE_CODE_ARRAY, 0, 0, (char *) NULL,
1549 (struct objfile *) NULL);
1550 TYPE_TARGET_TYPE(t) = *tpp;
1552 /* Determine and record the domain type (type of index) */
1553 ecoff_swap_rndx_in (bigend, ax, &rndx);
1558 rf = AUX_GET_ISYM (bigend, ax);
1561 fh = get_rfd(cur_fd, rf);
1563 /* Fields are kept in an array */
1564 /* FIXME - Memory leak! */
1565 if (TYPE_NFIELDS(t))
1566 TYPE_FIELDS(t) = (struct field*)
1567 xrealloc((PTR) TYPE_FIELDS(t),
1568 (TYPE_NFIELDS(t)+1) * sizeof(struct field));
1570 TYPE_FIELDS(t) = (struct field*)
1571 xzalloc(sizeof(struct field));
1572 f = &(TYPE_FIELD(t,TYPE_NFIELDS(t)));
1574 memset((PTR)f, 0, sizeof(struct field));
1576 /* XXX */ f->type = parse_type(id + (union aux_ext *)fh->iauxBase,
1577 &f->bitsize, bigend);
1580 lower = AUX_GET_DNLOW (bigend, ax);
1582 upper = AUX_GET_DNHIGH (bigend, ax);
1584 rf = AUX_GET_WIDTH (bigend, ax); /* bit size of array element */
1586 /* Check whether supplied array element bit size matches
1587 the known size of the element type. If this complaint
1588 ends up not happening, we can remove this code. It's
1589 here because we aren't sure we understand this *&%&$
1591 id = TYPE_LENGTH(TYPE_TARGET_TYPE(t)) << 3; /* bitsize */
1593 /* Most likely an undefined type */
1595 TYPE_LENGTH(TYPE_TARGET_TYPE(t)) = id >> 3;
1598 complain (&array_bitsize_complaint, (char *)rf);
1600 TYPE_LENGTH(t) = (upper < 0) ? 0 :
1601 (upper - lower + 1) * (rf >> 3);
1606 /* Volatile -- currently ignored */
1610 /* Const -- currently ignored */
1614 complain (&unknown_type_qual_complaint, (char *)tq);
1620 /* Parse a procedure descriptor record PR. Note that the procedure
1621 is parsed _after_ the local symbols, now we just insert the extra
1622 information we need into a special ".gdbinfo." symbol that has already
1623 been placed in the procedure's main block. Note also that images that
1624 have been partially stripped (ld -x) have been deprived
1625 of local symbols, and we have to cope with them here.
1626 The procedure's code ends at BOUND */
1629 parse_procedure (pr, bound, have_stabs)
1634 struct symbol *s, *i;
1635 SYMR *sh = (SYMR*)pr->isym;
1637 struct mips_extra_func_info *e;
1640 /* Static procedure at address pr->adr. Sigh. */
1641 if (sh == (SYMR*)-1) {
1642 complain (&pdr_static_symbol_complaint, (char *)pr->adr);
1645 sh_name = (char*)sh->iss;
1647 s = lookup_symbol(sh_name, NULL, VAR_NAMESPACE, 0, NULL);
1649 s = mylookup_symbol(sh_name, top_stack->cur_block,
1650 VAR_NAMESPACE, LOC_BLOCK);
1653 b = SYMBOL_BLOCK_VALUE(s);
1655 complain (&pdr_for_nonsymbol_complaint, sh_name);
1659 /* FIXME -- delete. We can't do symbol allocation now; it's all done. */
1660 s = new_symbol(sh_name);
1661 SYMBOL_NAMESPACE(s) = VAR_NAMESPACE;
1662 SYMBOL_CLASS(s) = LOC_BLOCK;
1663 /* Donno its type, hope int is ok */
1664 SYMBOL_TYPE(s) = lookup_function_type (builtin_type_int);
1665 add_symbol(s, top_stack->cur_block);
1666 /* Wont have symbols for this one */
1668 SYMBOL_BLOCK_VALUE(s) = b;
1669 BLOCK_FUNCTION(b) = s;
1670 BLOCK_START(b) = pr->adr;
1671 BLOCK_END(b) = bound;
1672 BLOCK_SUPERBLOCK(b) = top_stack->cur_block;
1673 add_block(b, top_stack->cur_st);
1677 i = mylookup_symbol(".gdbinfo.", b, LABEL_NAMESPACE, LOC_CONST);
1681 e = (struct mips_extra_func_info *)SYMBOL_VALUE(i);
1683 e->pdr.isym = (long)s;
1687 /* Parse the external symbol ES. Just call parse_symbol() after
1688 making sure we know where the aux are for it. For procedures,
1689 parsing of the PDRs has already provided all the needed
1690 information, we only parse them if SKIP_PROCEDURES is false,
1691 and only if this causes no symbol duplication.
1692 BIGEND says whether aux entries are big-endian or little-endian.
1694 This routine clobbers top_stack->cur_block and ->cur_st. */
1697 parse_external(es, skip_procedures, bigend)
1699 int skip_procedures;
1704 if (es->ifd != ifdNil) {
1706 cur_fdr = (FDR*)(cur_hdr->cbFdOffset) + cur_fd;
1707 ax = (union aux_ext *)cur_fdr->iauxBase;
1709 cur_fdr = (FDR*)(cur_hdr->cbFdOffset);
1713 /* Reading .o files */
1714 if (es->asym.sc == scUndefined || es->asym.sc == scNil) {
1716 switch (es->asym.st) {
1718 case stProc: what = "procedure"; n_undef_procs++; break;
1719 case stGlobal: what = "variable"; n_undef_vars++; break;
1720 case stLabel: what = "label"; n_undef_labels++; break;
1721 default : what = "symbol"; break;
1724 /* FIXME: Turn this into a complaint? */
1726 printf_filtered("Warning: %s `%s' is undefined (in %s)\n",
1727 what, es->asym.iss, fdr_name((char *)cur_fdr->rss));
1731 switch (es->asym.st) {
1733 /* If we have full symbols we do not need more */
1734 if (skip_procedures)
1736 if (mylookup_symbol ((char *)es->asym.iss, top_stack->cur_block,
1737 VAR_NAMESPACE, LOC_BLOCK))
1743 * Note that the case of a symbol with indexNil
1744 * must be handled anyways by parse_symbol().
1746 parse_symbol(&es->asym, ax, bigend);
1753 /* Parse the line number info for file descriptor FH into
1754 GDB's linetable LT. MIPS' encoding requires a little bit
1755 of magic to get things out. Note also that MIPS' line
1756 numbers can go back and forth, apparently we can live
1757 with that and do not need to reorder our linetables */
1762 struct linetable *lt;
1764 unsigned char *base = (unsigned char*)fh->cbLineOffset;
1766 int delta, count, lineno = 0;
1772 /* Scan by procedure descriptors */
1774 for (pr = (PDR*)IPDFIRST(cur_hdr,fh); j < fh->cpd; j++, pr++) {
1777 /* No code for this one */
1778 if (pr->iline == ilineNil ||
1779 pr->lnLow == -1 || pr->lnHigh == -1)
1782 * Aurgh! To know where to stop expanding we
1785 for (l = 1; l < (fh->cpd - j); l++)
1786 if (pr[l].iline != -1)
1788 if (l == (fh->cpd - j))
1793 * When procedures are moved around the linenumbers
1794 * are attributed to the next procedure up
1796 if (pr->iline >= halt) continue;
1798 base = (unsigned char*)pr->cbLineOffset;
1799 l = pr->adr >> 2; /* in words */
1800 halt += (pr->adr >> 2) - pr->iline;
1801 for (lineno = pr->lnLow; l < halt;) {
1802 count = *base & 0x0f;
1803 delta = *base++ >> 4;
1807 delta = (base[0] << 8) | base[1];
1808 if (delta >= 0x8000)
1812 lineno += delta;/* first delta is 0 */
1813 k = add_line(lt, lineno, l, k);
1819 /* Master parsing procedure for first-pass reading of file symbols
1820 into a partial_symtab.
1822 Parses the symtab described by the global symbolic header CUR_HDR.
1823 END_OF_TEXT_SEG gives the address just after the text segment for
1824 the symtab we are reading. */
1827 parse_partial_symbols (end_of_text_seg, objfile)
1828 int end_of_text_seg;
1829 struct objfile *objfile;
1832 HDRR *hdr = cur_hdr;
1833 /* Running pointers */
1837 struct partial_symtab *pst;
1839 int past_first_source_file = 0;
1841 /* List of current psymtab's include files */
1842 char **psymtab_include_list;
1843 int includes_allocated;
1846 struct pst_map * fdr_to_pst;
1847 /* Index within current psymtab dependency list */
1848 struct partial_symtab **dependency_list;
1849 int dependencies_used, dependencies_allocated;
1850 struct cleanup *old_chain;
1852 extern_tab = (EXTR**)obstack_alloc (&objfile->psymbol_obstack,
1853 sizeof(EXTR *) * hdr->iextMax);
1855 includes_allocated = 30;
1857 psymtab_include_list = (char **) alloca (includes_allocated *
1859 next_symbol_text_func = mips_next_symbol_text;
1861 dependencies_allocated = 30;
1862 dependencies_used = 0;
1864 (struct partial_symtab **) alloca (dependencies_allocated *
1865 sizeof (struct partial_symtab *));
1867 last_source_file = 0;
1872 * Only parse the Local and External symbols, and the Relative FDR.
1873 * Fixup enough of the loader symtab to be able to use it.
1874 * Allocate space only for the file's portions we need to
1879 max_glevel = MIN_GLEVEL;
1881 /* Allocate the map FDR -> PST.
1882 Minor hack: -O3 images might claim some global data belongs
1883 to FDR -1. We`ll go along with that */
1884 fdr_to_pst = (struct pst_map *)xzalloc((hdr->ifdMax+1) * sizeof *fdr_to_pst);
1885 old_chain = make_cleanup (free, fdr_to_pst);
1888 struct partial_symtab * pst = new_psymtab("", objfile);
1889 fdr_to_pst[-1].pst = pst;
1893 /* Pass 1 over external syms: Presize and partition the list */
1894 for (s_idx = 0; s_idx < hdr->iextMax; s_idx++) {
1895 esh = (EXTR *) (hdr->cbExtOffset) + s_idx;
1896 fdr_to_pst[esh->ifd].n_globals++;
1899 /* Pass 1.5 over files: partition out global symbol space */
1901 for (f_idx = -1; f_idx < hdr->ifdMax; f_idx++) {
1902 fdr_to_pst[f_idx].globals_offset = s_idx;
1903 s_idx += fdr_to_pst[f_idx].n_globals;
1904 fdr_to_pst[f_idx].n_globals = 0;
1907 /* Pass 2 over external syms: fill in external symbols */
1908 for (s_idx = 0; s_idx < hdr->iextMax; s_idx++) {
1909 enum minimal_symbol_type ms_type = mst_text;
1910 esh = (EXTR *) (hdr->cbExtOffset) + s_idx;
1912 extern_tab[fdr_to_pst[esh->ifd].globals_offset
1913 + fdr_to_pst[esh->ifd].n_globals++] = esh;
1915 if (esh->asym.sc == scUndefined || esh->asym.sc == scNil)
1918 switch (esh->asym.st) {
1927 ms_type = mst_unknown;
1928 complain (&unknown_ext_complaint, (char *)esh->asym.iss);
1930 prim_record_minimal_symbol ((char *)esh->asym.iss,
1935 /* Pass 3 over files, over local syms: fill in static symbols */
1936 for (f_idx = 0; f_idx < hdr->ifdMax; f_idx++) {
1937 struct partial_symtab *save_pst;
1939 cur_fdr = fh = f_idx + (FDR *)(cur_hdr->cbFdOffset);
1941 if (fh->csym == 0) {
1942 fdr_to_pst[f_idx].pst = NULL;
1945 pst = start_psymtab_common (objfile, 0, (char*)fh->rss,
1946 fh->cpd ? fh->adr : 0,
1947 objfile->global_psymbols.next,
1948 objfile->static_psymbols.next);
1949 pst->read_symtab_private = (char *)
1950 obstack_alloc (&objfile->psymbol_obstack, sizeof (struct symloc));
1953 /* Make everything point to everything. */
1954 FDR_IDX(pst) = f_idx;
1955 fdr_to_pst[f_idx].pst = pst;
1956 fh->ioptBase = (int)pst;
1958 CUR_HDR(pst) = cur_hdr;
1960 /* The way to turn this into a symtab is to call... */
1961 pst->read_symtab = mipscoff_psymtab_to_symtab;
1963 pst->texthigh = pst->textlow;
1965 #if 0 /* This is done in start_psymtab_common */
1966 pst->globals_offset = global_psymbols.next - global_psymbols.list;
1967 pst->statics_offset = static_psymbols.next - static_psymbols.list;
1969 pst->n_global_syms = 0;
1970 pst->n_static_syms = 0;
1973 /* The second symbol must be @stab.
1974 This symbol is emitted by mips-tfile to signal
1975 that the current object file uses encapsulated stabs
1976 instead of mips ecoff for local symbols.
1977 (It is the second symbol because the first symbol is
1978 the stFile used to signal the start of a file). */
1980 && strcmp((char *)(((SYMR *)fh->isymBase)[1].iss),
1981 stabs_symbol) == 0) {
1982 for (cur_sdx = 2; cur_sdx < fh->csym; cur_sdx++) {
1985 sh = cur_sdx + (SYMR *) fh->isymBase;
1986 type_code = MIPS_UNMARK_STAB(sh->index);
1987 if (!MIPS_IS_STAB(sh)) {
1988 if (sh->st == stProc || sh->st == stStaticProc) {
1989 long procaddr = sh->value;
1990 sh = AUX_GET_ISYM (fh->fBigendian,
1991 sh->index + (union aux_ext *)(fh->iauxBase))
1992 + (SYMR *) fh->isymBase - 1;
1993 if (sh->st == stEnd) {
1994 long high = procaddr + sh->value;
1995 if (high > pst->texthigh)
1996 pst->texthigh = high;
2001 #define SET_NAMESTRING() namestring = (char*)sh->iss
2002 #define CUR_SYMBOL_TYPE type_code
2003 #define CUR_SYMBOL_VALUE sh->value
2004 #define START_PSYMTAB(ofile,addr,fname,low,symoff,global_syms,static_syms)\
2006 #define END_PSYMTAB(pst,ilist,ninc,c_off,c_text,dep_list,n_deps) (void)0
2007 #define addr 0 /* FIXME, should be offset of addresses */
2008 #define HANDLE_RBRAC(val) \
2009 if ((val) > save_pst->texthigh) save_pst->texthigh = (val);
2010 #include "partial-stab.h"
2015 for (cur_sdx = 0; cur_sdx < fh->csym; ) {
2017 enum address_class class;
2018 sh = cur_sdx + (SYMR *) fh->isymBase;
2020 if (MIPS_IS_STAB(sh)) {
2025 if (sh->sc == scUndefined || sh->sc == scNil ||
2026 sh->index == 0xfffff) {
2027 /* FIXME, premature? */
2032 name = (char *)(sh->iss);
2039 case stProc: /* Asm labels apparently */
2040 case stStaticProc: /* Function */
2041 ADD_PSYMBOL_TO_LIST(name, strlen(name),
2042 VAR_NAMESPACE, LOC_BLOCK,
2043 objfile->static_psymbols, sh->value);
2044 /* Skip over procedure to next one. */
2045 if (sh->index >= hdr->iauxMax)
2047 /* Should not happen, but does when cross-compiling
2048 with the MIPS compiler. FIXME -- pull later. */
2049 complain (&index_complaint, name);
2050 new_sdx = cur_sdx+1; /* Don't skip at all */
2053 new_sdx = AUX_GET_ISYM (fh->fBigendian,
2054 sh->index + (union aux_ext *)fh->iauxBase);
2055 procaddr = sh->value;
2057 if (new_sdx <= cur_sdx)
2059 /* This should not happen either... FIXME. */
2060 complain (&aux_index_complaint, name);
2061 new_sdx = cur_sdx + 1; /* Don't skip backward */
2065 sh = cur_sdx + (SYMR *) fh->isymBase - 1;
2066 if (sh->st != stEnd)
2068 high = procaddr + sh->value;
2069 if (high > pst->texthigh)
2070 pst->texthigh = high;
2073 case stStatic: /* Variable */
2077 case stTypedef: /* Typedef */
2078 class = LOC_TYPEDEF;
2081 case stConstant: /* Constant decl */
2088 case stBlock: /* { }, str, un, enum*/
2089 if (sh->sc == scInfo) {
2090 ADD_PSYMBOL_TO_LIST(name, strlen(name),
2091 STRUCT_NAMESPACE, LOC_TYPEDEF,
2092 objfile->static_psymbols, sh->value);
2094 /* Skip over the block */
2095 cur_sdx = sh->index;
2098 case stFile: /* File headers */
2099 case stLabel: /* Labels */
2100 case stEnd: /* Ends of files */
2104 /* Both complaints are valid: one gives symbol name,
2105 the other the offending symbol type. */
2106 complain (&unknown_sym_complaint, (char *)sh->iss);
2107 complain (&unknown_st_complaint, (char *)sh->st);
2111 /* Use this gdb symbol */
2112 ADD_PSYMBOL_TO_LIST(name, strlen(name),
2113 VAR_NAMESPACE, class,
2114 objfile->static_psymbols, sh->value);
2116 cur_sdx++; /* Go to next file symbol */
2119 /* Now do enter the external symbols. */
2120 ext_ptr = &extern_tab[fdr_to_pst[f_idx].globals_offset];
2121 cur_sdx = fdr_to_pst[f_idx].n_globals;
2122 PST_PRIVATE(save_pst)->extern_count = cur_sdx;
2123 PST_PRIVATE(save_pst)->extern_tab = ext_ptr;
2124 for (; --cur_sdx >= 0; ext_ptr++) {
2125 register struct partial_symbol *psym;
2126 enum address_class class;
2128 if ((*ext_ptr)->ifd != f_idx)
2130 sh = &(*ext_ptr)->asym;
2139 complain (&unknown_ext_complaint, (char *)sh->iss);
2140 /* Fall through, pretend it's global. */
2145 if (objfile->global_psymbols.next >=
2146 objfile->global_psymbols.list + objfile->global_psymbols.size)
2147 extend_psymbol_list (&objfile->global_psymbols, objfile);
2148 psym = objfile->global_psymbols.next++;
2149 SYMBOL_NAME (psym) = (char*)sh->iss;
2150 SYMBOL_NAMESPACE (psym) = VAR_NAMESPACE;
2151 SYMBOL_CLASS (psym) = class;
2152 SYMBOL_VALUE_ADDRESS (psym) = (CORE_ADDR)sh->value;
2156 end_psymtab (save_pst, psymtab_include_list, includes_used,
2157 -1, save_pst->texthigh,
2158 dependency_list, dependencies_used);
2159 if (objfile -> ei.entry_point >= save_pst->textlow &&
2160 objfile -> ei.entry_point < save_pst->texthigh)
2162 objfile -> ei.entry_file_lowpc = save_pst->textlow;
2163 objfile -> ei.entry_file_highpc = save_pst->texthigh;
2167 /* Mark the last code address, and remember it for later */
2168 hdr->cbDnOffset = end_of_text_seg;
2170 /* Now scan the FDRs for dependencies */
2171 for (f_idx = 0; f_idx < hdr->ifdMax; f_idx++) {
2173 fh = f_idx + (FDR *)(cur_hdr->cbFdOffset);
2174 pst = fdr_to_pst[f_idx].pst;
2176 /* This should catch stabs-in-ecoff. */
2180 if (fh->cpd == 0) { /* If there are no functions defined here ... */
2181 /* ...then presumably a .h file: drop reverse depends .h->.c */
2182 for (; s_id0 < fh->crfd; s_id0++) {
2183 RFDT *rh = (RFDT *) (fh->rfdBase) + s_id0;
2185 s_id0++; /* Skip self-dependency */
2190 pst->number_of_dependencies = fh->crfd - s_id0;
2191 pst->dependencies = (struct partial_symtab **)
2192 obstack_alloc (&objfile->psymbol_obstack,
2193 pst->number_of_dependencies *
2194 sizeof (struct partial_symtab *));
2195 for (s_idx = s_id0; s_idx < fh->crfd; s_idx++) {
2196 RFDT *rh = (RFDT *) (fh->rfdBase) + s_idx;
2197 if (*rh < 0 || *rh >= hdr->ifdMax)
2198 complain(&bad_file_number_complaint, (char *)*rh);
2200 pst->dependencies[s_idx-s_id0] = fdr_to_pst[*rh].pst;
2203 do_cleanups (old_chain);
2208 /* Do the initial analisys of the F_IDX-th file descriptor.
2209 Allocates a partial symtab for it, and builds the list
2210 of dependent files by recursion. LEV says at which level
2211 of recursion we are called (to pretty up debug traces) */
2213 static struct partial_symtab *
2214 parse_fdr(f_idx, lev, objfile)
2217 struct objfile *objfile;
2220 register struct partial_symtab *pst;
2223 fh = (FDR *) (cur_hdr->cbFdOffset) + f_idx;
2225 /* Use this to indicate into which symtab this file was parsed */
2227 return (struct partial_symtab *) fh->ioptBase;
2229 /* Debuggability level */
2230 if (compare_glevel(max_glevel, fh->glevel) < 0)
2231 max_glevel = fh->glevel;
2233 /* Make a new partial_symtab */
2234 pst = new_psymtab(fh->rss, objfile);
2239 pst->textlow = fh->adr;
2240 pst->texthigh = fh->cpd; /* To be fixed later */
2243 /* Make everything point to everything. */
2244 FDR_IDX(pst) = f_idx;
2245 fdr_to_pst[f_idx].pst = pst;
2246 fh->ioptBase = (int)pst;
2248 /* Analyze its dependencies */
2253 if (fh->cpd == 0) { /* If there are no functions defined here ... */
2254 /* ...then presumably a .h file: drop reverse depends .h->.c */
2255 for (; s_id0 < fh->crfd; s_id0++) {
2256 RFDT *rh = (RFDT *) (fh->rfdBase) + s_id0;
2258 s_id0++; /* Skip self-dependency */
2263 pst->number_of_dependencies = fh->crfd - s_id0;
2264 pst->dependencies = (struct partial_symtab **)
2265 obstack_alloc (&objfile->psymbol_obstack,
2266 pst->number_of_dependencies *
2267 sizeof (struct partial_symtab *));
2268 for (s_idx = s_id0; s_idx < fh->crfd; s_idx++) {
2269 RFDT *rh = (RFDT *) (fh->rfdBase) + s_idx;
2271 pst->dependencies[s_idx-s_id0] = parse_fdr(*rh, lev+1, objfile);
2279 mips_next_symbol_text ()
2282 return (char*)((SYMR *)cur_fdr->isymBase)[cur_sdx].iss;
2285 /* Ancillary function to psymtab_to_symtab(). Does all the work
2286 for turning the partial symtab PST into a symtab, recurring
2287 first on all dependent psymtabs. The argument FILENAME is
2288 only passed so we can see in debug stack traces what file
2291 This function has a split personality, based on whether the
2292 symbol table contains ordinary ecoff symbols, or stabs-in-ecoff.
2293 The flow of control and even the memory allocation differs. FIXME. */
2296 psymtab_to_symtab_1(pst, filename)
2297 struct partial_symtab *pst;
2303 struct linetable *lines;
2310 /* Read in all partial symbtabs on which this one is dependent.
2311 NOTE that we do have circular dependencies, sigh. We solved
2312 that by setting pst->readin before this point. */
2314 for (i = 0; i < pst->number_of_dependencies; i++)
2315 if (!pst->dependencies[i]->readin) {
2316 /* Inform about additional files to be read in. */
2319 fputs_filtered (" ", stdout);
2321 fputs_filtered ("and ", stdout);
2323 printf_filtered ("%s...",
2324 pst->dependencies[i]->filename);
2325 wrap_here (""); /* Flush output */
2328 /* We only pass the filename for debug purposes */
2329 psymtab_to_symtab_1(pst->dependencies[i],
2330 pst->dependencies[i]->filename);
2333 /* Now read the symbols for this symtab */
2335 current_objfile = pst->objfile;
2336 cur_fd = FDR_IDX(pst);
2337 fh = (cur_fd == -1) ? 0 : (FDR *) (cur_hdr->cbFdOffset) + FDR_IDX(pst);
2340 /* BOUND is the highest core address of this file's procedures */
2341 bound = (cur_fd == cur_hdr->ifdMax - 1) ?
2342 cur_hdr->cbDnOffset :
2345 /* See comment in parse_partial_symbols about the @stabs sentinel. */
2346 if (fh && fh->csym >= 2
2347 && strcmp((char *)(((SYMR *)fh->isymBase)[1].iss), stabs_symbol)
2351 * This symbol table contains stabs-in-ecoff entries.
2356 /* Parse local symbols first */
2358 if (fh->csym <= 2) /* FIXME, this blows psymtab->symtab ptr */
2360 current_objfile = NULL;
2363 for (cur_sdx = 2; cur_sdx < fh->csym; cur_sdx++) {
2364 register SYMR *sh = cur_sdx + (SYMR *) fh->isymBase;
2365 char *name = (char*)sh->iss;
2366 CORE_ADDR valu = sh->value;
2367 if (MIPS_IS_STAB(sh)) {
2368 int type_code = MIPS_UNMARK_STAB(sh->index);
2369 process_one_symbol (type_code, 0, valu, name, /*FIXME*/ 0,
2371 if (type_code == N_FUN) {
2372 /* Make up special symbol to contain
2373 procedure specific info */
2374 struct mips_extra_func_info *e =
2375 (struct mips_extra_func_info *)
2376 obstack_alloc(¤t_objfile->symbol_obstack,
2377 sizeof(struct mips_extra_func_info));
2378 struct symbol *s = new_symbol(".gdbinfo.");
2379 SYMBOL_NAMESPACE(s) = LABEL_NAMESPACE;
2380 SYMBOL_CLASS(s) = LOC_CONST;
2381 SYMBOL_TYPE(s) = builtin_type_void;
2382 SYMBOL_VALUE(s) = (int)e;
2383 add_symbol_to_list (s, &local_symbols);
2386 else if (sh->st == stLabel && sh->index != indexNil) {
2387 /* Handle encoded stab line number. */
2388 record_line (current_subfile, sh->index, valu);
2390 else complain (&stab_unknown_complaint, (char *)sh->iss);
2392 st = end_symtab (pst->texthigh, 0, 0, pst->objfile);
2394 /* Sort the symbol table now, we are done adding symbols to it.
2395 We must do this before parse_procedure calls lookup_symbol. */
2396 sort_symtab_syms(st);
2398 /* This may not be necessary for stabs symtabs. FIXME. */
2401 /* Fill in procedure info next. We need to look-ahead to
2402 find out where each procedure's code ends. */
2404 for (i = 0; i <= fh->cpd-1; i++) {
2405 pr = (PDR *) (IPDFIRST(cur_hdr, fh)) + i;
2406 parse_procedure (pr, i < fh->cpd-1 ? pr[1].adr : bound, 1);
2411 * This symbol table contains ordinary ecoff entries.
2418 /* How many symbols will we need */
2419 /* FIXME, this does not count enum values. */
2420 f_max = pst->n_global_syms + pst->n_static_syms;
2423 st = new_symtab ("unknown", f_max, 0, pst->objfile);
2425 f_max += fh->csym + fh->cpd;
2426 maxlines = 2 * fh->cline;
2427 st = new_symtab (pst->filename, 2 * f_max, maxlines, pst->objfile);
2430 lines = LINETABLE(st);
2431 pending_list = (struct mips_pending **) cur_hdr->cbOptOffset;
2432 if (pending_list == 0) {
2433 pending_list = (struct mips_pending **)
2434 xzalloc(cur_hdr->ifdMax * sizeof(struct mips_pending *));
2435 cur_hdr->cbOptOffset = (int)pending_list;
2438 /* Get a new lexical context */
2441 top_stack->cur_st = st;
2442 top_stack->cur_block = BLOCKVECTOR_BLOCK(BLOCKVECTOR(st),
2444 BLOCK_START(top_stack->cur_block) = fh ? fh->adr : 0;
2445 BLOCK_END(top_stack->cur_block) = 0;
2446 top_stack->blocktype = stFile;
2447 top_stack->maxsyms = 2*f_max;
2448 top_stack->cur_type = 0;
2449 top_stack->procadr = 0;
2450 top_stack->numargs = 0;
2456 /* Parse local symbols first */
2458 for (cur_sdx = 0; cur_sdx < fh->csym; ) {
2459 sh = (SYMR *) (fh->isymBase) + cur_sdx;
2460 cur_sdx += parse_symbol(sh, (union aux_ent *)fh->iauxBase,
2464 /* Linenumbers. At the end, check if we can save memory */
2466 parse_lines(fh, lines);
2467 if (lines->nitems < fh->cline)
2468 lines = shrink_linetable(lines);
2470 /* Fill in procedure info next. We need to look-ahead to
2471 find out where each procedure's code ends. */
2473 for (i = 0; i <= fh->cpd-1; i++) {
2474 pr = (PDR *) (IPDFIRST(cur_hdr, fh)) + i;
2475 parse_procedure(pr, i < fh->cpd-1 ? pr[1].adr : bound, 0);
2479 LINETABLE(st) = lines;
2481 /* .. and our share of externals.
2482 XXX use the global list to speed up things here. how?
2483 FIXME, Maybe quit once we have found the right number of ext's? */
2484 top_stack->cur_st = st;
2485 top_stack->cur_block = BLOCKVECTOR_BLOCK(BLOCKVECTOR(top_stack->cur_st),
2487 top_stack->blocktype = stFile;
2488 top_stack->maxsyms =
2489 cur_hdr->isymMax + cur_hdr->ipdMax + cur_hdr->iextMax;
2491 ext_ptr = PST_PRIVATE(pst)->extern_tab;
2492 for (i = PST_PRIVATE(pst)->extern_count; --i >= 0; ext_ptr++)
2493 parse_external(*ext_ptr, 1, fh->fBigendian);
2495 /* If there are undefined, tell the user */
2496 if (n_undef_symbols) {
2497 printf_filtered("File %s contains %d unresolved references:",
2498 st->filename, n_undef_symbols);
2499 printf_filtered("\n\t%4d variables\n\t%4d procedures\n\t%4d labels\n",
2500 n_undef_vars, n_undef_procs, n_undef_labels);
2501 n_undef_symbols = n_undef_labels = n_undef_vars = n_undef_procs = 0;
2506 /* Sort the symbol table now, we are done adding symbols to it.*/
2507 sort_symtab_syms(st);
2512 /* Now link the psymtab and the symtab. */
2515 current_objfile = NULL;
2518 /* Ancillary parsing procedures. */
2520 /* Lookup the type at relative index RN. Return it in TPP
2521 if found and in any event come up with its name PNAME.
2522 BIGEND says whether aux symbols are big-endian or not (from fh->fBigendian).
2523 Return value says how many aux symbols we ate. */
2526 cross_ref(ax, tpp, type_code, pname, bigend)
2529 enum type_code type_code; /* Use to alloc new type if none is found. */
2537 ecoff_swap_rndx_in (bigend, ax, rn);
2539 /* Escape index means 'the next one' */
2540 if (rn->rfd == 0xfff) {
2542 rf = AUX_GET_ISYM (bigend, ax + 1);
2549 *pname = "<undefined>";
2552 * Find the relative file descriptor and the symbol in it
2554 FDR *fh = get_rfd(cur_fd, rf);
2559 * If we have processed this symbol then we left a forwarding
2560 * pointer to the corresponding GDB symbol. If not, we`ll put
2561 * it in a list of pending symbols, to be processed later when
2562 * the file f will be. In any event, we collect the name for
2563 * the type here. Which is why we made a first pass at
2566 sh = (SYMR *) (fh->isymBase) + rn->index;
2568 /* Careful, we might be looking at .o files */
2569 *pname = (UNSAFE_DATA_ADDR(sh->iss)) ? "<undefined>" :
2572 /* Have we parsed it ? */
2573 if ((!UNSAFE_DATA_ADDR(sh->value)) && (sh->st == stParsed)) {
2574 t = (struct type *) sh->value;
2577 /* Avoid duplicates */
2578 struct mips_pending *p = is_pending_symbol(fh, sh);
2582 *tpp = init_type(type_code, 0, 0, (char *) NULL,
2583 (struct objfile *) NULL);
2584 add_pending(fh, sh, *tpp);
2589 /* We used one auxent normally, two if we got a "next one" rf. */
2594 /* Quick&dirty lookup procedure, to avoid the MI ones that require
2595 keeping the symtab sorted */
2597 static struct symbol *
2598 mylookup_symbol (name, block, namespace, class)
2600 register struct block *block;
2601 enum namespace namespace;
2602 enum address_class class;
2604 register int bot, top, inc;
2605 register struct symbol *sym;
2608 top = BLOCK_NSYMS(block);
2611 sym = BLOCK_SYM(block, bot);
2612 if (SYMBOL_NAME(sym)[0] == inc
2613 && SYMBOL_NAMESPACE(sym) == namespace
2614 && SYMBOL_CLASS(sym) == class
2615 && !strcmp(SYMBOL_NAME(sym), name))
2619 block = BLOCK_SUPERBLOCK (block);
2621 return mylookup_symbol (name, block, namespace, class);
2626 /* Add a new symbol S to a block B.
2627 Infrequently, we will need to reallocate the block to make it bigger.
2628 We only detect this case when adding to top_stack->cur_block, since
2629 that's the only time we know how big the block is. FIXME. */
2636 int nsyms = BLOCK_NSYMS(b)++;
2637 struct block *origb;
2638 struct parse_stack *stackp;
2640 if (b == top_stack->cur_block &&
2641 nsyms >= top_stack->maxsyms) {
2642 complain (&block_overflow_complaint, s->name);
2643 /* In this case shrink_block is actually grow_block, since
2644 BLOCK_NSYMS(b) is larger than its current size. */
2646 b = shrink_block (top_stack->cur_block, top_stack->cur_st);
2648 /* Now run through the stack replacing pointers to the
2649 original block. shrink_block has already done this
2650 for the blockvector and BLOCK_FUNCTION. */
2651 for (stackp = top_stack; stackp; stackp = stackp->next) {
2652 if (stackp->cur_block == origb) {
2653 stackp->cur_block = b;
2654 stackp->maxsyms = BLOCK_NSYMS (b);
2658 BLOCK_SYM(b,nsyms) = s;
2661 /* Add a new block B to a symtab S */
2668 struct blockvector *bv = BLOCKVECTOR(s);
2670 bv = (struct blockvector *)xrealloc((PTR) bv,
2671 sizeof(struct blockvector) +
2672 BLOCKVECTOR_NBLOCKS(bv)
2673 * sizeof(bv->block));
2674 if (bv != BLOCKVECTOR(s))
2675 BLOCKVECTOR(s) = bv;
2677 BLOCKVECTOR_BLOCK(bv, BLOCKVECTOR_NBLOCKS(bv)++) = b;
2680 /* Add a new linenumber entry (LINENO,ADR) to a linevector LT.
2681 MIPS' linenumber encoding might need more than one byte
2682 to describe it, LAST is used to detect these continuation lines */
2685 add_line(lt, lineno, adr, last)
2686 struct linetable *lt;
2692 last = -2; /* make sure we record first line */
2694 if (last == lineno) /* skip continuation lines */
2697 lt->item[lt->nitems].line = lineno;
2698 lt->item[lt->nitems++].pc = adr << 2;
2702 /* Sorting and reordering procedures */
2704 /* Blocks with a smaller low bound should come first */
2707 compare_blocks(arg1, arg2)
2708 const void *arg1, *arg2;
2710 register int addr_diff;
2711 struct block **b1 = (struct block **) arg1;
2712 struct block **b2 = (struct block **) arg2;
2714 addr_diff = (BLOCK_START((*b1))) - (BLOCK_START((*b2)));
2716 return (BLOCK_END((*b1))) - (BLOCK_END((*b2)));
2720 /* Sort the blocks of a symtab S.
2721 Reorder the blocks in the blockvector by code-address,
2722 as required by some MI search routines */
2728 struct blockvector *bv = BLOCKVECTOR(s);
2730 if (BLOCKVECTOR_NBLOCKS(bv) <= 2) {
2732 if (BLOCK_END(BLOCKVECTOR_BLOCK(bv,GLOBAL_BLOCK)) == 0)
2733 BLOCK_START(BLOCKVECTOR_BLOCK(bv,GLOBAL_BLOCK)) = 0;
2734 if (BLOCK_END(BLOCKVECTOR_BLOCK(bv,STATIC_BLOCK)) == 0)
2735 BLOCK_START(BLOCKVECTOR_BLOCK(bv,STATIC_BLOCK)) = 0;
2739 * This is very unfortunate: normally all functions are compiled in
2740 * the order they are found, but if the file is compiled -O3 things
2741 * are very different. It would be nice to find a reliable test
2742 * to detect -O3 images in advance.
2744 if (BLOCKVECTOR_NBLOCKS(bv) > 3)
2745 qsort(&BLOCKVECTOR_BLOCK(bv,FIRST_LOCAL_BLOCK),
2746 BLOCKVECTOR_NBLOCKS(bv) - FIRST_LOCAL_BLOCK,
2747 sizeof(struct block *),
2751 register CORE_ADDR high = 0;
2752 register int i, j = BLOCKVECTOR_NBLOCKS(bv);
2754 for (i = FIRST_LOCAL_BLOCK; i < j; i++)
2755 if (high < BLOCK_END(BLOCKVECTOR_BLOCK(bv,i)))
2756 high = BLOCK_END(BLOCKVECTOR_BLOCK(bv,i));
2757 BLOCK_END(BLOCKVECTOR_BLOCK(bv,GLOBAL_BLOCK)) = high;
2760 BLOCK_START(BLOCKVECTOR_BLOCK(bv,GLOBAL_BLOCK)) =
2761 BLOCK_START(BLOCKVECTOR_BLOCK(bv,FIRST_LOCAL_BLOCK));
2763 BLOCK_START(BLOCKVECTOR_BLOCK(bv,STATIC_BLOCK)) =
2764 BLOCK_START(BLOCKVECTOR_BLOCK(bv,GLOBAL_BLOCK));
2765 BLOCK_END (BLOCKVECTOR_BLOCK(bv,STATIC_BLOCK)) =
2766 BLOCK_END (BLOCKVECTOR_BLOCK(bv,GLOBAL_BLOCK));
2770 /* Constructor/restructor/destructor procedures */
2772 /* Allocate a new symtab for NAME. Needs an estimate of how many symbols
2773 MAXSYMS and linenumbers MAXLINES we'll put in it */
2775 static struct symtab *
2776 new_symtab(name, maxsyms, maxlines, objfile)
2780 struct objfile *objfile;
2782 struct symtab *s = allocate_symtab (name, objfile);
2784 LINETABLE(s) = new_linetable(maxlines);
2786 /* All symtabs must have at least two blocks */
2787 BLOCKVECTOR(s) = new_bvect(2);
2788 BLOCKVECTOR_BLOCK(BLOCKVECTOR(s), GLOBAL_BLOCK) = new_block(maxsyms);
2789 BLOCKVECTOR_BLOCK(BLOCKVECTOR(s), STATIC_BLOCK) = new_block(maxsyms);
2790 BLOCK_SUPERBLOCK( BLOCKVECTOR_BLOCK(BLOCKVECTOR(s),STATIC_BLOCK)) =
2791 BLOCKVECTOR_BLOCK(BLOCKVECTOR(s), GLOBAL_BLOCK);
2793 s->free_code = free_linetable;
2798 /* Allocate a new partial_symtab NAME */
2800 static struct partial_symtab *
2801 new_psymtab(name, objfile)
2803 struct objfile *objfile;
2805 struct partial_symtab *psymtab;
2807 /* FIXME -- why (char *) -1 rather than NULL? */
2808 psymtab = allocate_psymtab (name == (char *) -1 ? "<no name>" : name,
2811 /* Keep a backpointer to the file's symbols */
2813 psymtab -> read_symtab_private = (char *)
2814 obstack_alloc (&objfile->psymbol_obstack, sizeof (struct symloc));
2815 CUR_HDR(psymtab) = cur_hdr;
2817 /* The way to turn this into a symtab is to call... */
2818 psymtab->read_symtab = mipscoff_psymtab_to_symtab;
2823 /* Allocate a linetable array of the given SIZE. Since the struct
2824 already includes one item, we subtract one when calculating the
2825 proper size to allocate. */
2827 static struct linetable *
2831 struct linetable *l;
2833 size = (size-1) * sizeof(l->item) + sizeof(struct linetable);
2834 l = (struct linetable *)xmalloc(size);
2839 /* Oops, too big. Shrink it. This was important with the 2.4 linetables,
2840 I am not so sure about the 3.4 ones.
2842 Since the struct linetable already includes one item, we subtract one when
2843 calculating the proper size to allocate. */
2845 static struct linetable *
2846 shrink_linetable(lt)
2847 struct linetable * lt;
2850 return (struct linetable *) xrealloc ((PTR)lt,
2851 sizeof(struct linetable)
2852 + (lt->nitems - 1) * sizeof(lt->item));
2855 /* Allocate and zero a new blockvector of NBLOCKS blocks. */
2857 static struct blockvector *
2861 struct blockvector *bv;
2864 size = sizeof(struct blockvector) + nblocks * sizeof(struct block*);
2865 bv = (struct blockvector *) xzalloc(size);
2867 BLOCKVECTOR_NBLOCKS(bv) = nblocks;
2872 /* Allocate and zero a new block of MAXSYMS symbols */
2874 static struct block *
2878 int size = sizeof(struct block) + (maxsyms-1) * sizeof(struct symbol *);
2880 return (struct block *)xzalloc (size);
2883 /* Ooops, too big. Shrink block B in symtab S to its minimal size.
2884 Shrink_block can also be used by add_symbol to grow a block. */
2886 static struct block *
2892 struct blockvector *bv = BLOCKVECTOR(s);
2895 /* Just reallocate it and fix references to the old one */
2897 new = (struct block *) xrealloc ((PTR)b, sizeof(struct block) +
2898 (BLOCK_NSYMS(b)-1) * sizeof(struct symbol *));
2900 /* Should chase pointers to old one. Fortunately, that`s just
2901 the block`s function and inferior blocks */
2902 if (BLOCK_FUNCTION(new) && SYMBOL_BLOCK_VALUE(BLOCK_FUNCTION(new)) == b)
2903 SYMBOL_BLOCK_VALUE(BLOCK_FUNCTION(new)) = new;
2904 for (i = 0; i < BLOCKVECTOR_NBLOCKS(bv); i++)
2905 if (BLOCKVECTOR_BLOCK(bv,i) == b)
2906 BLOCKVECTOR_BLOCK(bv,i) = new;
2907 else if (BLOCK_SUPERBLOCK(BLOCKVECTOR_BLOCK(bv,i)) == b)
2908 BLOCK_SUPERBLOCK(BLOCKVECTOR_BLOCK(bv,i)) = new;
2912 /* Create a new symbol with printname NAME */
2914 static struct symbol *
2918 struct symbol *s = (struct symbol *)
2919 obstack_alloc (¤t_objfile->symbol_obstack, sizeof (struct symbol));
2921 memset ((PTR)s, 0, sizeof (*s));
2922 SYMBOL_NAME(s) = name;
2926 /* Create a new type with printname NAME */
2928 static struct type *
2934 t = alloc_type (current_objfile);
2935 TYPE_NAME(t) = name;
2936 TYPE_CPLUS_SPECIFIC(t) = (struct cplus_struct_type *)
2937 &cplus_struct_default;
2942 /* Things used for calling functions in the inferior.
2943 These functions are exported to our companion
2944 mips-tdep.c file and are here because they play
2945 with the symbol-table explicitly. */
2947 /* Sigtramp: make sure we have all the necessary information
2948 about the signal trampoline code. Since the official code
2949 from MIPS does not do so, we make up that information ourselves.
2950 If they fix the library (unlikely) this code will neutralize itself. */
2957 struct block *b, *b0;
2959 sigtramp_address = -1;
2961 /* We know it is sold as sigvec */
2962 s = lookup_symbol("sigvec", 0, VAR_NAMESPACE, 0, NULL);
2964 /* Most programs do not play with signals */
2966 s = lookup_symbol("_sigtramp", 0, VAR_NAMESPACE, 0, NULL);
2969 b0 = SYMBOL_BLOCK_VALUE(s);
2971 /* A label of sigvec, to be more precise */
2972 s = lookup_symbol("sigtramp", b0, VAR_NAMESPACE, 0, NULL);
2975 /* But maybe this program uses its own version of sigvec */
2979 /* Did we or MIPSco fix the library ? */
2980 if (SYMBOL_CLASS(s) == LOC_BLOCK)
2982 sigtramp_address = BLOCK_START(SYMBOL_BLOCK_VALUE(s));
2983 sigtramp_end = BLOCK_END(SYMBOL_BLOCK_VALUE(s));
2987 sigtramp_address = SYMBOL_VALUE(s);
2988 sigtramp_end = sigtramp_address + 0x88; /* black magic */
2990 /* But what symtab does it live in ? */
2991 st = find_pc_symtab(SYMBOL_VALUE(s));
2994 * Ok, there goes the fix: turn it into a procedure, with all the
2995 * needed info. Note we make it a nested procedure of sigvec,
2996 * which is the way the (assembly) code is actually written.
2998 SYMBOL_NAMESPACE(s) = VAR_NAMESPACE;
2999 SYMBOL_CLASS(s) = LOC_BLOCK;
3000 SYMBOL_TYPE(s) = init_type(TYPE_CODE_FUNC, 4, 0, (char *) NULL,
3001 (struct objfile *) NULL);
3002 TYPE_TARGET_TYPE(SYMBOL_TYPE(s)) = builtin_type_void;
3004 /* Need a block to allocate .gdbinfo. in */
3006 SYMBOL_BLOCK_VALUE(s) = b;
3007 BLOCK_START(b) = sigtramp_address;
3008 BLOCK_END(b) = sigtramp_end;
3009 BLOCK_FUNCTION(b) = s;
3010 BLOCK_SUPERBLOCK(b) = BLOCK_SUPERBLOCK(b0);
3014 /* Make a .gdbinfo. for it */
3016 struct mips_extra_func_info *e =
3017 (struct mips_extra_func_info *)
3018 xzalloc(sizeof(struct mips_extra_func_info));
3020 e->numargs = 0; /* the kernel thinks otherwise */
3021 /* align_longword(sigcontext + SIGFRAME) */
3022 e->pdr.frameoffset = 0x150;
3023 e->pdr.framereg = SP_REGNUM;
3025 e->pdr.regmask = -2;
3026 e->pdr.regoffset = -(41 * sizeof(int));
3027 e->pdr.fregmask = -1;
3028 e->pdr.fregoffset = -(37 * sizeof(int));
3029 e->pdr.isym = (long)s;
3031 current_objfile = st->objfile; /* Keep new_symbol happy */
3032 s = new_symbol(".gdbinfo.");
3033 SYMBOL_VALUE(s) = (int) e;
3034 SYMBOL_NAMESPACE(s) = LABEL_NAMESPACE;
3035 SYMBOL_CLASS(s) = LOC_CONST;
3036 SYMBOL_TYPE(s) = builtin_type_void;
3037 current_objfile = NULL;
3040 BLOCK_SYM(b,BLOCK_NSYMS(b)++) = s;
3043 /* Initialization */
3045 static struct sym_fns ecoff_sym_fns =
3047 "ecoff", /* sym_name: name or name prefix of BFD target type */
3048 5, /* sym_namelen: number of significant sym_name chars */
3049 mipscoff_new_init, /* sym_new_init: init anything gbl to entire symtab */
3050 mipscoff_symfile_init,/* sym_init: read initial info, setup for sym_read() */
3051 mipscoff_symfile_read,/* sym_read: read a symbol file into symtab */
3052 mipscoff_symfile_finish,/* sym_finish: finished with file, cleanup */
3053 NULL /* next: pointer to next struct sym_fns */
3058 _initialize_mipsread ()
3060 add_symtab_fns (&ecoff_sym_fns);
3062 /* Missing basic types */
3064 builtin_type_string =
3065 init_type(TYPE_CODE_PASCAL_ARRAY,
3066 TARGET_CHAR_BIT / TARGET_CHAR_BIT,
3068 (struct objfile *) NULL);
3069 builtin_type_complex =
3070 init_type(TYPE_CODE_FLT,
3071 TARGET_COMPLEX_BIT / TARGET_CHAR_BIT,
3073 (struct objfile *) NULL);
3074 builtin_type_double_complex =
3075 init_type(TYPE_CODE_FLT,
3076 TARGET_DOUBLE_COMPLEX_BIT / TARGET_CHAR_BIT,
3077 0, "double complex",
3078 (struct objfile *) NULL);
3079 builtin_type_fixed_dec =
3080 init_type(TYPE_CODE_INT,
3081 TARGET_INT_BIT / TARGET_CHAR_BIT,
3083 (struct objfile *) NULL);
3084 builtin_type_float_dec =
3085 init_type(TYPE_CODE_FLT,
3086 TARGET_DOUBLE_BIT / TARGET_CHAR_BIT,
3087 0, "floating decimal",
3088 (struct objfile *) NULL);